1 | MODULE trcini_pisces |
---|
2 | !!====================================================================== |
---|
3 | !! *** MODULE trcini_pisces *** |
---|
4 | !! TOP : initialisation of the PISCES biochemical model |
---|
5 | !!====================================================================== |
---|
6 | !! History : - ! 1988-07 (E. Maier-Reiner) Original code |
---|
7 | !! - ! 1999-10 (O. Aumont, C. Le Quere) |
---|
8 | !! - ! 2002 (O. Aumont) PISCES |
---|
9 | !! 1.0 ! 2005-03 (O. Aumont, A. El Moussaoui) F90 |
---|
10 | !! 2.0 ! 2007-12 (C. Ethe, G. Madec) from trcini.pisces.h90 |
---|
11 | !! 3.5 ! 2012-05 (C. Ethe) Merge PISCES-LOBSTER |
---|
12 | !!---------------------------------------------------------------------- |
---|
13 | !! trc_ini_pisces : PISCES biochemical model initialisation |
---|
14 | !!---------------------------------------------------------------------- |
---|
15 | USE par_trc ! TOP parameters |
---|
16 | USE oce_trc ! shared variables between ocean and passive tracers |
---|
17 | USE trc ! passive tracers common variables |
---|
18 | USE trcnam_pisces ! PISCES namelist |
---|
19 | USE sms_pisces ! PISCES Source Minus Sink variables |
---|
20 | USE sedini ! SEDIMENTS initialization routine |
---|
21 | |
---|
22 | IMPLICIT NONE |
---|
23 | PRIVATE |
---|
24 | |
---|
25 | PUBLIC trc_ini_pisces ! called by trcini.F90 module |
---|
26 | |
---|
27 | !!---------------------------------------------------------------------- |
---|
28 | !! NEMO/TOP 4.0 , NEMO Consortium (2018) |
---|
29 | !! $Id$ |
---|
30 | !! Software governed by the CeCILL license (see ./LICENSE) |
---|
31 | !!---------------------------------------------------------------------- |
---|
32 | CONTAINS |
---|
33 | |
---|
34 | SUBROUTINE trc_ini_pisces |
---|
35 | !!---------------------------------------------------------------------- |
---|
36 | !! *** ROUTINE trc_ini_pisces *** |
---|
37 | !! |
---|
38 | !! ** Purpose : Initialisation of the PISCES biochemical model |
---|
39 | !!---------------------------------------------------------------------- |
---|
40 | ! |
---|
41 | CALL trc_nam_pisces |
---|
42 | ! |
---|
43 | IF( ln_p4z .OR. ln_p5z ) THEN ; CALL p4z_ini ! PISCES |
---|
44 | ELSE ; CALL p2z_ini ! LOBSTER |
---|
45 | ENDIF |
---|
46 | |
---|
47 | END SUBROUTINE trc_ini_pisces |
---|
48 | |
---|
49 | |
---|
50 | SUBROUTINE p4z_ini |
---|
51 | !!---------------------------------------------------------------------- |
---|
52 | !! *** ROUTINE p4z_ini *** |
---|
53 | !! |
---|
54 | !! ** Purpose : Initialisation of the PISCES biochemical model |
---|
55 | !!---------------------------------------------------------------------- |
---|
56 | USE p4zsms ! Main P4Z routine |
---|
57 | USE p4zche ! Chemical model |
---|
58 | USE p4zsink ! vertical flux of particulate matter due to sinking |
---|
59 | USE p4zopt ! optical model |
---|
60 | USE p4zsbc ! Boundary conditions |
---|
61 | USE p4zfechem ! Iron chemistry |
---|
62 | USE p4zrem ! Remineralisation of organic matter |
---|
63 | USE p4zflx ! Gas exchange |
---|
64 | USE p4zlim ! Co-limitations of differents nutrients |
---|
65 | USE p4zprod ! Growth rate of the 2 phyto groups |
---|
66 | USE p4zmicro ! Sources and sinks of microzooplankton |
---|
67 | USE p4zmeso ! Sources and sinks of mesozooplankton |
---|
68 | USE p4zmort ! Mortality terms for phytoplankton |
---|
69 | USE p4zlys ! Calcite saturation |
---|
70 | USE p4zsed ! Sedimentation & burial |
---|
71 | USE p4zpoc ! Remineralization of organic particles |
---|
72 | USE p4zligand ! Remineralization of organic ligands |
---|
73 | USE p5zlim ! Co-limitations of differents nutrients |
---|
74 | USE p5zprod ! Growth rate of the 2 phyto groups |
---|
75 | USE p5zmicro ! Sources and sinks of microzooplankton |
---|
76 | USE p5zmeso ! Sources and sinks of mesozooplankton |
---|
77 | USE p5zmort ! Mortality terms for phytoplankton |
---|
78 | ! |
---|
79 | REAL(wp), SAVE :: sco2 = 2.312e-3_wp |
---|
80 | REAL(wp), SAVE :: alka0 = 2.426e-3_wp |
---|
81 | REAL(wp), SAVE :: oxyg0 = 177.6e-6_wp |
---|
82 | REAL(wp), SAVE :: po4 = 2.165e-6_wp |
---|
83 | REAL(wp), SAVE :: bioma0 = 1.000e-8_wp |
---|
84 | REAL(wp), SAVE :: silic1 = 91.51e-6_wp |
---|
85 | REAL(wp), SAVE :: no3 = 30.9e-6_wp * 7.625_wp |
---|
86 | ! |
---|
87 | INTEGER :: ji, jj, jk, jn, ierr |
---|
88 | REAL(wp) :: zcaralk, zbicarb, zco3 |
---|
89 | REAL(wp) :: ztmas, ztmas1 |
---|
90 | CHARACTER(len = 20) :: cltra |
---|
91 | !!---------------------------------------------------------------------- |
---|
92 | ! |
---|
93 | IF(lwp) THEN |
---|
94 | WRITE(numout,*) |
---|
95 | IF( ln_p4z ) THEN |
---|
96 | WRITE(numout,*) 'p4z_ini : PISCES biochemical model initialisation' |
---|
97 | WRITE(numout,*) '~~~~~~~' |
---|
98 | ELSE |
---|
99 | WRITE(numout,*) 'p5z_ini : PISCES biochemical model initialisation' |
---|
100 | WRITE(numout,*) '~~~~~~~ With variable stoichiometry' |
---|
101 | ENDIF |
---|
102 | ENDIF |
---|
103 | ! |
---|
104 | ! Allocate PISCES arrays |
---|
105 | ierr = sms_pisces_alloc() |
---|
106 | ierr = ierr + p4z_che_alloc() |
---|
107 | ierr = ierr + p4z_sink_alloc() |
---|
108 | ierr = ierr + p4z_opt_alloc() |
---|
109 | ierr = ierr + p4z_flx_alloc() |
---|
110 | ierr = ierr + p4z_sed_alloc() |
---|
111 | ierr = ierr + p4z_lim_alloc() |
---|
112 | IF( ln_p4z ) THEN |
---|
113 | ierr = ierr + p4z_prod_alloc() |
---|
114 | ELSE |
---|
115 | ierr = ierr + p5z_lim_alloc() |
---|
116 | ierr = ierr + p5z_prod_alloc() |
---|
117 | ENDIF |
---|
118 | ierr = ierr + p4z_rem_alloc() |
---|
119 | ! |
---|
120 | CALL mpp_sum( 'trcini_pisces', ierr ) |
---|
121 | IF( ierr /= 0 ) CALL ctl_stop( 'STOP', 'pisces_alloc: unable to allocate PISCES arrays' ) |
---|
122 | ! |
---|
123 | ryyss = nyear_len(1) * rday ! number of seconds per year |
---|
124 | r1_ryyss = 1. / ryyss |
---|
125 | ! |
---|
126 | |
---|
127 | ! assign an index in trc arrays for each prognostic variables |
---|
128 | DO jn = 1, jptra |
---|
129 | cltra = ctrcnm(jn) |
---|
130 | IF( cltra == 'DIC' ) jpdic = jn !: dissolved inoganic carbon concentration |
---|
131 | IF( cltra == 'Alkalini' ) jptal = jn !: total alkalinity |
---|
132 | IF( cltra == 'O2' ) jpoxy = jn !: oxygen carbon concentration |
---|
133 | IF( cltra == 'CaCO3' ) jpcal = jn !: calcite concentration |
---|
134 | IF( cltra == 'PO4' ) jppo4 = jn !: phosphate concentration |
---|
135 | IF( cltra == 'POC' ) jppoc = jn !: small particulate organic phosphate concentration |
---|
136 | IF( cltra == 'Si' ) jpsil = jn !: silicate concentration |
---|
137 | IF( cltra == 'PHY' ) jpphy = jn !: phytoplancton concentration |
---|
138 | IF( cltra == 'ZOO' ) jpzoo = jn !: zooplancton concentration |
---|
139 | IF( cltra == 'DOC' ) jpdoc = jn !: dissolved organic carbon concentration |
---|
140 | IF( cltra == 'PHY2' ) jpdia = jn !: Diatoms Concentration |
---|
141 | IF( cltra == 'ZOO2' ) jpmes = jn !: Mesozooplankton Concentration |
---|
142 | IF( cltra == 'DSi' ) jpdsi = jn !: Diatoms Silicate Concentration |
---|
143 | IF( cltra == 'Fer' ) jpfer = jn !: Iron Concentration |
---|
144 | IF( cltra == 'BFe' ) jpbfe = jn !: Big iron particles Concentration |
---|
145 | IF( cltra == 'GOC' ) jpgoc = jn !: Big particulate organic phosphate concentration |
---|
146 | IF( cltra == 'SFe' ) jpsfe = jn !: Small iron particles Concentration |
---|
147 | IF( cltra == 'DFe' ) jpdfe = jn !: Diatoms iron Concentration |
---|
148 | IF( cltra == 'GSi' ) jpgsi = jn !: (big) Silicate Concentration |
---|
149 | IF( cltra == 'NFe' ) jpnfe = jn !: Nano iron Concentration |
---|
150 | IF( cltra == 'NCHL' ) jpnch = jn !: Nano Chlorophyll Concentration |
---|
151 | IF( cltra == 'DCHL' ) jpdch = jn !: Diatoms Chlorophyll Concentration |
---|
152 | IF( cltra == 'NO3' ) jpno3 = jn !: Nitrates Concentration |
---|
153 | IF( cltra == 'NH4' ) jpnh4 = jn !: Ammonium Concentration |
---|
154 | IF( cltra == 'DON' ) jpdon = jn !: Dissolved organic N Concentration |
---|
155 | IF( cltra == 'DOP' ) jpdop = jn !: Dissolved organic P Concentration |
---|
156 | IF( cltra == 'PON' ) jppon = jn !: Small Nitrogen particle Concentration |
---|
157 | IF( cltra == 'POP' ) jppop = jn !: Small Phosphorus particle Concentration |
---|
158 | IF( cltra == 'GON' ) jpgon = jn !: Big Nitrogen particles Concentration |
---|
159 | IF( cltra == 'GOP' ) jpgop = jn !: Big Phosphorus Concentration |
---|
160 | IF( cltra == 'PHYN' ) jpnph = jn !: Nanophytoplankton N biomass |
---|
161 | IF( cltra == 'PHYP' ) jppph = jn !: Nanophytoplankton P biomass |
---|
162 | IF( cltra == 'DIAN' ) jpndi = jn !: Diatoms N biomass |
---|
163 | IF( cltra == 'DIAP' ) jppdi = jn !: Diatoms P biomass |
---|
164 | IF( cltra == 'PIC' ) jppic = jn !: Picophytoplankton C biomass |
---|
165 | IF( cltra == 'PICN' ) jpnpi = jn !: Picophytoplankton N biomass |
---|
166 | IF( cltra == 'PICP' ) jpppi = jn !: Picophytoplankton P biomass |
---|
167 | IF( cltra == 'PCHL' ) jppch = jn !: Diatoms Chlorophyll Concentration |
---|
168 | IF( cltra == 'PFe' ) jppfe = jn !: Picophytoplankton Fe biomass |
---|
169 | IF( cltra == 'LGW' ) jplgw = jn !: Weak ligands |
---|
170 | END DO |
---|
171 | |
---|
172 | CALL p4z_sms_init ! Maint routine |
---|
173 | ! |
---|
174 | |
---|
175 | ! Set biological ratios |
---|
176 | ! --------------------- |
---|
177 | rno3 = 16._wp / 122._wp |
---|
178 | po4r = 1._wp / 122._wp |
---|
179 | o2nit = 32._wp / 122._wp |
---|
180 | o2ut = 133._wp / 122._wp |
---|
181 | rdenit = ( ( o2ut + o2nit ) * 0.80 - rno3 - rno3 * 0.60 ) / rno3 |
---|
182 | rdenita = 3._wp / 5._wp |
---|
183 | IF( ln_p5z ) THEN |
---|
184 | no3rat3 = no3rat3 / rno3 |
---|
185 | po4rat3 = po4rat3 / po4r |
---|
186 | ENDIF |
---|
187 | |
---|
188 | ! Initialization of tracer concentration in case of no restart |
---|
189 | !-------------------------------------------------------------- |
---|
190 | IF( .NOT.ln_rsttr ) THEN |
---|
191 | trn(:,:,:,jpdic) = sco2 |
---|
192 | trn(:,:,:,jpdoc) = bioma0 |
---|
193 | trn(:,:,:,jptal) = alka0 |
---|
194 | trn(:,:,:,jpoxy) = oxyg0 |
---|
195 | trn(:,:,:,jpcal) = bioma0 |
---|
196 | trn(:,:,:,jppo4) = po4 / po4r |
---|
197 | trn(:,:,:,jppoc) = bioma0 |
---|
198 | trn(:,:,:,jpgoc) = bioma0 |
---|
199 | trn(:,:,:,jpbfe) = bioma0 * 5.e-6 |
---|
200 | trn(:,:,:,jpsil) = silic1 |
---|
201 | trn(:,:,:,jpdsi) = bioma0 * 0.15 |
---|
202 | trn(:,:,:,jpgsi) = bioma0 * 5.e-6 |
---|
203 | trn(:,:,:,jpphy) = bioma0 |
---|
204 | trn(:,:,:,jpdia) = bioma0 |
---|
205 | trn(:,:,:,jpzoo) = bioma0 |
---|
206 | trn(:,:,:,jpmes) = bioma0 |
---|
207 | trn(:,:,:,jpfer) = 0.6E-9 |
---|
208 | trn(:,:,:,jpsfe) = bioma0 * 5.e-6 |
---|
209 | trn(:,:,:,jpdfe) = bioma0 * 5.e-6 |
---|
210 | trn(:,:,:,jpnfe) = bioma0 * 5.e-6 |
---|
211 | trn(:,:,:,jpnch) = bioma0 * 12. / 55. |
---|
212 | trn(:,:,:,jpdch) = bioma0 * 12. / 55. |
---|
213 | trn(:,:,:,jpno3) = no3 |
---|
214 | trn(:,:,:,jpnh4) = bioma0 |
---|
215 | IF( ln_ligand) THEN |
---|
216 | trn(:,:,:,jplgw) = 0.6E-9 |
---|
217 | ENDIF |
---|
218 | IF( ln_p5z ) THEN |
---|
219 | trn(:,:,:,jpdon) = bioma0 |
---|
220 | trn(:,:,:,jpdop) = bioma0 |
---|
221 | trn(:,:,:,jppon) = bioma0 |
---|
222 | trn(:,:,:,jppop) = bioma0 |
---|
223 | trn(:,:,:,jpgon) = bioma0 |
---|
224 | trn(:,:,:,jpgop) = bioma0 |
---|
225 | trn(:,:,:,jpnph) = bioma0 |
---|
226 | trn(:,:,:,jppph) = bioma0 |
---|
227 | trn(:,:,:,jppic) = bioma0 |
---|
228 | trn(:,:,:,jpnpi) = bioma0 |
---|
229 | trn(:,:,:,jpppi) = bioma0 |
---|
230 | trn(:,:,:,jpndi) = bioma0 |
---|
231 | trn(:,:,:,jppdi) = bioma0 |
---|
232 | trn(:,:,:,jppfe) = bioma0 * 5.e-6 |
---|
233 | trn(:,:,:,jppch) = bioma0 * 12. / 55. |
---|
234 | ENDIF |
---|
235 | ! initialize the half saturation constant for silicate |
---|
236 | ! ---------------------------------------------------- |
---|
237 | xksi(:,:) = 2.e-6 |
---|
238 | xksimax(:,:) = xksi(:,:) |
---|
239 | IF( ln_p5z ) THEN |
---|
240 | sized(:,:,:) = 1.0 |
---|
241 | sizen(:,:,:) = 1.0 |
---|
242 | sized(:,:,:) = 1.0 |
---|
243 | ENDIF |
---|
244 | END IF |
---|
245 | |
---|
246 | |
---|
247 | CALL p4z_sink_init ! vertical flux of particulate organic matter |
---|
248 | CALL p4z_opt_init ! Optic: PAR in the water column |
---|
249 | IF( ln_p4z ) THEN |
---|
250 | CALL p4z_lim_init ! co-limitations by the various nutrients |
---|
251 | CALL p4z_prod_init ! phytoplankton growth rate over the global ocean. |
---|
252 | ELSE |
---|
253 | CALL p5z_lim_init ! co-limitations by the various nutrients |
---|
254 | CALL p5z_prod_init ! phytoplankton growth rate over the global ocean. |
---|
255 | ENDIF |
---|
256 | CALL p4z_sbc_init ! boundary conditions |
---|
257 | CALL p4z_fechem_init ! Iron chemistry |
---|
258 | CALL p4z_rem_init ! remineralisation |
---|
259 | CALL p4z_poc_init ! remineralisation of organic particles |
---|
260 | IF( ln_ligand ) & |
---|
261 | & CALL p4z_ligand_init ! remineralisation of organic ligands |
---|
262 | |
---|
263 | IF( ln_p4z ) THEN |
---|
264 | CALL p4z_mort_init ! phytoplankton mortality |
---|
265 | CALL p4z_micro_init ! microzooplankton |
---|
266 | CALL p4z_meso_init ! mesozooplankton |
---|
267 | ELSE |
---|
268 | CALL p5z_mort_init ! phytoplankton mortality |
---|
269 | CALL p5z_micro_init ! microzooplankton |
---|
270 | CALL p5z_meso_init ! mesozooplankton |
---|
271 | ENDIF |
---|
272 | CALL p4z_lys_init ! calcite saturation |
---|
273 | IF( .NOT.l_co2cpl ) & |
---|
274 | & CALL p4z_flx_init ! gas exchange |
---|
275 | |
---|
276 | ! Initialization of the sediment model |
---|
277 | IF( ln_sediment) CALL sed_init |
---|
278 | |
---|
279 | IF(lwp) WRITE(numout,*) |
---|
280 | IF(lwp) WRITE(numout,*) ' ==>>> Initialization of PISCES tracers done' |
---|
281 | IF(lwp) WRITE(numout,*) |
---|
282 | ! |
---|
283 | END SUBROUTINE p4z_ini |
---|
284 | |
---|
285 | |
---|
286 | SUBROUTINE p2z_ini |
---|
287 | !!---------------------------------------------------------------------- |
---|
288 | !! *** ROUTINE p2z_ini *** |
---|
289 | !! |
---|
290 | !! ** Purpose : Initialisation of the LOBSTER biochemical model |
---|
291 | !!---------------------------------------------------------------------- |
---|
292 | ! |
---|
293 | USE p2zopt |
---|
294 | USE p2zexp |
---|
295 | USE p2zbio |
---|
296 | USE p2zsed |
---|
297 | ! |
---|
298 | INTEGER :: ji, jj, jk, jn, ierr |
---|
299 | CHARACTER(len = 10) :: cltra |
---|
300 | !!---------------------------------------------------------------------- |
---|
301 | |
---|
302 | IF(lwp) WRITE(numout,*) |
---|
303 | IF(lwp) WRITE(numout,*) ' p2z_ini : LOBSTER biochemical model initialisation' |
---|
304 | IF(lwp) WRITE(numout,*) ' ~~~~~~~' |
---|
305 | |
---|
306 | ierr = sms_pisces_alloc() |
---|
307 | ierr = ierr + p2z_exp_alloc() |
---|
308 | ! |
---|
309 | CALL mpp_sum( 'trcini_pisces', ierr ) |
---|
310 | IF( ierr /= 0 ) CALL ctl_stop( 'STOP', 'p2z_ini: unable to allocate LOBSTER arrays' ) |
---|
311 | |
---|
312 | DO jn = 1, jptra |
---|
313 | cltra = ctrcnm(jn) |
---|
314 | IF( cltra == 'DET' ) jpdet = jn !: detritus [mmoleN/m3] |
---|
315 | IF( cltra == 'ZOO' ) jpzoo = jn !: zooplancton concentration [mmoleN/m3] |
---|
316 | IF( cltra == 'PHY' ) jpphy = jn !: phytoplancton concentration [mmoleN/m3] |
---|
317 | IF( cltra == 'NO3' ) jpno3 = jn !: nitrate concentration [mmoleN/m3] |
---|
318 | IF( cltra == 'NH4' ) jpnh4 = jn !: ammonium concentration [mmoleN/m3] |
---|
319 | IF( cltra == 'DOM' ) jpdom = jn !: dissolved organic matter [mmoleN/m3] |
---|
320 | ENDDO |
---|
321 | |
---|
322 | jpkb = 10 ! last level where depth less than 200 m |
---|
323 | DO jk = jpkm1, 1, -1 |
---|
324 | IF( gdept_1d(jk) > 200. ) jpkb = jk |
---|
325 | END DO |
---|
326 | IF (lwp) WRITE(numout,*) |
---|
327 | IF (lwp) WRITE(numout,*) ' first vertical layers where biology is active (200m depth ) ', jpkb |
---|
328 | IF (lwp) WRITE(numout,*) |
---|
329 | jpkbm1 = jpkb - 1 |
---|
330 | ! |
---|
331 | |
---|
332 | |
---|
333 | ! LOBSTER initialisation for GYRE : init NO3=f(density) by asklod AS Kremeur 2005-07 |
---|
334 | ! ---------------------- |
---|
335 | IF( .NOT. ln_rsttr ) THEN ! in case of no restart |
---|
336 | trn(:,:,:,jpdet) = 0.1 * tmask(:,:,:) |
---|
337 | trn(:,:,:,jpzoo) = 0.1 * tmask(:,:,:) |
---|
338 | trn(:,:,:,jpnh4) = 0.1 * tmask(:,:,:) |
---|
339 | trn(:,:,:,jpphy) = 0.1 * tmask(:,:,:) |
---|
340 | trn(:,:,:,jpdom) = 1.0 * tmask(:,:,:) |
---|
341 | WHERE( rhd(:,:,:) <= 24.5e-3 ) ; trn(:,:,:,jpno3) = 2._wp * tmask(:,:,:) |
---|
342 | ELSE WHERE ; trn(:,:,:,jpno3) = ( 15.55 * ( rhd(:,:,:) * 1000. ) - 380.11 ) * tmask(:,:,:) |
---|
343 | END WHERE |
---|
344 | ENDIF |
---|
345 | ! ! Namelist read |
---|
346 | CALL p2z_opt_init ! Optics parameters |
---|
347 | CALL p2z_sed_init ! sedimentation |
---|
348 | CALL p2z_bio_init ! biology |
---|
349 | CALL p2z_exp_init ! export |
---|
350 | ! |
---|
351 | IF(lwp) WRITE(numout,*) |
---|
352 | IF(lwp) WRITE(numout,*) ' ==>>> Initialization of LOBSTER tracers done' |
---|
353 | IF(lwp) WRITE(numout,*) |
---|
354 | ! |
---|
355 | END SUBROUTINE p2z_ini |
---|
356 | |
---|
357 | !!====================================================================== |
---|
358 | END MODULE trcini_pisces |
---|