New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
trcini_pisces.F90 in branches/CNRS/dev_r4826_PISCES_QUOTA/NEMOGCM/NEMO/TOP_SRC/PISCES – NEMO

source: branches/CNRS/dev_r4826_PISCES_QUOTA/NEMOGCM/NEMO/TOP_SRC/PISCES/trcini_pisces.F90 @ 5289

Last change on this file since 5289 was 5289, checked in by aumont, 9 years ago

various bug fixes and updates of PISCES quota

  • Property svn:keywords set to Id
File size: 16.2 KB
Line 
1MODULE 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   !!             3.6  !  2015-05  (O. Aumont) PISCES quota
13   !!----------------------------------------------------------------------
14#if defined key_pisces || defined key_pisces_reduced || defined key_pisces_quota
15   !!----------------------------------------------------------------------
16   !!   'key_pisces*'                                       PISCES bio-model
17   !!----------------------------------------------------------------------
18   !! trc_ini_pisces   : PISCES biochemical model initialisation
19   !!----------------------------------------------------------------------
20   USE par_trc         ! TOP parameters
21   USE oce_trc         !  shared variables between ocean and passive tracers
22   USE trc             !  passive tracers common variables
23   USE sms_pisces      !  PISCES Source Minus Sink variables
24
25   IMPLICIT NONE
26   PRIVATE
27
28   PUBLIC   trc_ini_pisces   ! called by trcini.F90 module
29
30
31#  include "top_substitute.h90"
32   !!----------------------------------------------------------------------
33   !! NEMO/TOP 3.3 , NEMO Consortium (2010)
34   !! $Id$
35   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
36   !!----------------------------------------------------------------------
37CONTAINS
38
39   SUBROUTINE trc_ini_pisces
40      !!----------------------------------------------------------------------
41      !!                   ***  ROUTINE trc_ini_pisces ***
42      !!
43      !! ** Purpose :   Initialisation of the PISCES biochemical model
44      !!----------------------------------------------------------------------
45
46      SELECT CASE ( nn_p4z )
47      !
48        CASE(1)          ;   CALL p2z_ini   !  LOBSTER
49        CASE(2)          ;   CALL p4z_ini   !  PISCES
50        CASE(3)          ;   CALL p5z_ini   !  PISCES QUOTA
51
52      END SELECT
53
54   END SUBROUTINE trc_ini_pisces
55
56   SUBROUTINE p5z_ini
57      !!----------------------------------------------------------------------
58      !!                   ***  ROUTINE p5z_ini ***
59      !!
60      !! ** Purpose :   Initialisation of the PISCES biochemical model
61      !!                with variable stoichiometry
62      !!----------------------------------------------------------------------
63#if defined key_pisces_quota 
64      !
65      USE p5zsms          ! Main P4Z routine
66      USE p4zche          !  Chemical model
67      USE p5zsink         !  vertical flux of particulate matter due to sinking
68      USE p4zopt          !  optical model
69      USE p4zsbc          !  Boundary conditions
70      USE p4zfechem       !  Iron chemistry
71      USE p5zrem          !  Remineralisation of organic matter
72      USE p4zflx          !  Gas exchange
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      USE p4zlys          !  Calcite saturation
79      !
80      REAL(wp), SAVE :: sco2   =  2.312e-3_wp
81      REAL(wp), SAVE :: alka0  =  2.423e-3_wp
82      REAL(wp), SAVE :: oxyg0  =  177.6e-6_wp 
83      REAL(wp), SAVE :: po4    =  2.174e-6_wp 
84      REAL(wp), SAVE :: bioma0 =  1.000e-8_wp 
85      REAL(wp), SAVE :: silic1 =  91.65e-6_wp 
86      REAL(wp), SAVE :: no3    =  31.04e-6_wp * 7.625_wp
87      !
88      INTEGER  ::  ji, jj, jk, ierr
89      REAL(wp) ::  zcaralk, zbicarb, zco3
90      REAL(wp) ::  ztmas, ztmas1
91      !!----------------------------------------------------------------------
92
93      IF(lwp) WRITE(numout,*)
94      IF(lwp) WRITE(numout,*) ' p5z_ini :   PISCES biochemical model initialisation'
95      IF(lwp) WRITE(numout,*) '             With variable stoichiometry'
96      IF(lwp) WRITE(numout,*) ' ~~~~~~~~~~~~~~'
97
98                                                 ! Allocate PISCES arrays
99      ierr =         sms_pisces_alloc()         
100      ierr = ierr +  p4z_che_alloc()
101      ierr = ierr +  p5z_sink_alloc()
102      ierr = ierr +  p4z_opt_alloc()
103      ierr = ierr +  p5z_prod_alloc()
104      ierr = ierr +  p5z_rem_alloc()
105      ierr = ierr +  p4z_flx_alloc()
106      !
107      IF( lk_mpp    )   CALL mpp_sum( ierr )
108      IF( ierr /= 0 )   CALL ctl_stop( 'STOP', 'pisces_alloc: unable to allocate PISCES arrays' )
109      !
110      CALL p5z_sms_init       !  Maint routine
111      !                                            ! Time-step
112      rfact   = rdttrc(1)                          ! ---------
113      rfactr  = 1. / rfact
114      rfact2  = rfact / FLOAT( nrdttrc )
115      rfact2r = 1. / rfact2
116
117      IF(lwp) WRITE(numout,*) '    Passive Tracer  time step    rfact  = ', rfact, ' rdt = ', rdttra(1)
118      IF(lwp) write(numout,*) '    PISCES  Biology time step    rfact2 = ', rfact2
119
120      ! Set biological ratios
121      ! ---------------------
122      rno3    =  16._wp / 122._wp
123      po4r    =   1._wp / 122._wp
124      o2nit   =  32._wp / 122._wp
125      rdenit  = 105._wp /  16._wp
126      rdenita =   3._wp /  5._wp
127      o2ut    = 133._wp / 122._wp
128      no3rat3 = no3rat3 / rno3
129      po4rat3 = po4rat3 / po4r
130
131      ! Initialization of tracer concentration in case of  no restart
132      !--------------------------------------------------------------
133      IF( .NOT. ln_rsttr ) THEN 
134         
135         trn(:,:,:,jpdic) = sco2
136         trn(:,:,:,jpdoc) = bioma0
137         trn(:,:,:,jpdon) = bioma0
138         trn(:,:,:,jpdop) = bioma0
139         trn(:,:,:,jptal) = alka0
140         trn(:,:,:,jpoxy) = oxyg0
141         trn(:,:,:,jpcal) = bioma0
142         trn(:,:,:,jppo4) = po4 / po4r
143         trn(:,:,:,jppoc) = bioma0
144         trn(:,:,:,jppon) = bioma0
145         trn(:,:,:,jppop) = bioma0
146#  if ! defined key_kriest
147         trn(:,:,:,jpgoc) = bioma0
148         trn(:,:,:,jpgon) = bioma0
149         trn(:,:,:,jpgop) = bioma0
150         trn(:,:,:,jpbfe) = bioma0 * 5.e-6
151#  else
152         trn(:,:,:,jpnum) = bioma0 / ( 6. * xkr_massp )
153#  endif
154         trn(:,:,:,jpsil) = silic1
155         trn(:,:,:,jpdsi) = bioma0 * 0.15
156         trn(:,:,:,jpgsi) = bioma0 * 5.e-6
157         trn(:,:,:,jpphy) = bioma0
158         trn(:,:,:,jpnph) = bioma0
159         trn(:,:,:,jppph) = bioma0
160         trn(:,:,:,jppic) = bioma0
161         trn(:,:,:,jpnpi) = bioma0
162         trn(:,:,:,jpppi) = bioma0
163         trn(:,:,:,jpdia) = bioma0
164         trn(:,:,:,jpndi) = bioma0
165         trn(:,:,:,jppdi) = bioma0
166         trn(:,:,:,jpzoo) = bioma0
167         trn(:,:,:,jpmes) = bioma0
168         trn(:,:,:,jpfer) = 0.6E-9
169         trn(:,:,:,jpsfe) = bioma0 * 5.e-6
170         trn(:,:,:,jppfe) = bioma0 * 5.e-6
171         trn(:,:,:,jpdfe) = bioma0 * 5.e-6
172         trn(:,:,:,jpnfe) = bioma0 * 5.e-6
173         trn(:,:,:,jpnch) = bioma0 * 12. / 55.
174         trn(:,:,:,jppch) = bioma0 * 12. / 55.
175         trn(:,:,:,jpdch) = bioma0 * 12. / 55.
176         trn(:,:,:,jpno3) = no3
177         trn(:,:,:,jpnh4) = bioma0
178
179         ! initialize the half saturation constant for silicate
180         ! ----------------------------------------------------
181         xksi(:,:)    = 2.e-6
182         xksimax(:,:) = xksi(:,:)
183      END IF
184
185      ! Time step duration for biology
186      xstep = rfact2 / rday
187
188      CALL p5z_sink_init      !  vertical flux of particulate organic matter
189      CALL p4z_opt_init       !  Optic: PAR in the water column
190      CALL p5z_lim_init       !  co-limitations by the various nutrients
191      CALL p5z_prod_init      !  phytoplankton growth rate over the global ocean.
192      CALL p4z_sbc_init       !  boundary conditions
193      CALL p4z_fechem_init    !  Iron chemistry
194      CALL p5z_rem_init       !  remineralisation
195      CALL p5z_mort_init      !  phytoplankton mortality
196      CALL p5z_micro_init     !  microzooplankton
197      CALL p5z_meso_init      !  mesozooplankton
198      CALL p4z_lys_init       !  calcite saturation
199      CALL p4z_flx_init       !  gas exchange
200
201      ndayflxtr = 0
202
203      IF(lwp) WRITE(numout,*) 
204      IF(lwp) WRITE(numout,*) 'Initialization of PISCES tracers done'
205      IF(lwp) WRITE(numout,*) 
206#endif
207      !
208   END SUBROUTINE p5z_ini
209
210   SUBROUTINE p4z_ini
211      !!----------------------------------------------------------------------
212      !!                   ***  ROUTINE p4z_ini ***
213      !!
214      !! ** Purpose :   Initialisation of the PISCES biochemical model
215      !!----------------------------------------------------------------------
216#if defined key_pisces 
217      !
218      USE p4zsms          ! Main P4Z routine
219      USE p4zche          !  Chemical model
220      USE p4zsink         !  vertical flux of particulate matter due to sinking
221      USE p4zopt          !  optical model
222      USE p4zsbc          !  Boundary conditions
223      USE p4zfechem       !  Iron chemistry
224      USE p4zrem          !  Remineralisation of organic matter
225      USE p4zflx          !  Gas exchange
226      USE p4zlim          !  Co-limitations of differents nutrients
227      USE p4zprod         !  Growth rate of the 2 phyto groups
228      USE p4zmicro        !  Sources and sinks of microzooplankton
229      USE p4zmeso         !  Sources and sinks of mesozooplankton
230      USE p4zmort         !  Mortality terms for phytoplankton
231      USE p4zlys          !  Calcite saturation
232      !
233      REAL(wp), SAVE :: sco2   =  2.312e-3_wp
234      REAL(wp), SAVE :: alka0  =  2.423e-3_wp
235      REAL(wp), SAVE :: oxyg0  =  177.6e-6_wp
236      REAL(wp), SAVE :: po4    =  2.174e-6_wp
237      REAL(wp), SAVE :: bioma0 =  1.000e-8_wp
238      REAL(wp), SAVE :: silic1 =  91.65e-6_wp
239      REAL(wp), SAVE :: no3    =  31.04e-6_wp * 7.625_wp
240      !
241      INTEGER  ::  ji, jj, jk, ierr
242      REAL(wp) ::  zcaralk, zbicarb, zco3
243      REAL(wp) ::  ztmas, ztmas1
244      !!----------------------------------------------------------------------
245
246      IF(lwp) WRITE(numout,*)
247      IF(lwp) WRITE(numout,*) ' p4z_ini :   PISCES biochemical model initialisation'
248      IF(lwp) WRITE(numout,*) ' ~~~~~~~~~~~~~~'
249
250                                                 ! Allocate PISCES arrays
251      ierr =         sms_pisces_alloc()
252      ierr = ierr +  p4z_che_alloc()
253      ierr = ierr +  p4z_sink_alloc()
254      ierr = ierr +  p4z_opt_alloc()
255      ierr = ierr +  p4z_prod_alloc()
256      ierr = ierr +  p4z_rem_alloc()
257      ierr = ierr +  p4z_flx_alloc()
258      !
259      IF( lk_mpp    )   CALL mpp_sum( ierr )
260      IF( ierr /= 0 )   CALL ctl_stop( 'STOP', 'pisces_alloc: unable to allocate PISCES arrays' )
261      !
262
263      CALL p4z_sms_init       !  Maint routine
264      !                                            ! Time-step
265      rfact   = rdttrc(1)                          ! ---------
266      rfactr  = 1. / rfact
267      rfact2  = rfact / FLOAT( nrdttrc )
268      rfact2r = 1. / rfact2
269
270      IF(lwp) WRITE(numout,*) '    Passive Tracer  time step    rfact  = ', rfact, ' rdt = ', rdttra(1)
271      IF(lwp) write(numout,*) '    PISCES  Biology time step    rfact2 = ', rfact2
272
273
274
275      ! Set biological ratios
276      ! ---------------------
277      rno3    =  16._wp / 122._wp
278      po4r    =   1._wp / 122._wp
279      o2nit   =  32._wp / 122._wp
280      rdenit  = 105._wp /  16._wp
281      rdenita =   3._wp /  5._wp
282      o2ut    = 133._wp / 122._wp
283
284      ! Initialization of tracer concentration in case of  no restart
285      !--------------------------------------------------------------
286      IF( .NOT. ln_rsttr ) THEN
287
288         trn(:,:,:,jpdic) = sco2
289         trn(:,:,:,jpdoc) = bioma0
290         trn(:,:,:,jptal) = alka0
291         trn(:,:,:,jpoxy) = oxyg0
292         trn(:,:,:,jpcal) = bioma0
293         trn(:,:,:,jppo4) = po4 / po4r
294         trn(:,:,:,jppoc) = bioma0
295#  if ! defined key_kriest
296         trn(:,:,:,jpgoc) = bioma0
297         trn(:,:,:,jpbfe) = bioma0 * 5.e-6
298#  else
299         trn(:,:,:,jpnum) = bioma0 / ( 6. * xkr_massp )
300#  endif
301         trn(:,:,:,jpsil) = silic1
302         trn(:,:,:,jpdsi) = bioma0 * 0.15
303         trn(:,:,:,jpgsi) = bioma0 * 5.e-6
304         trn(:,:,:,jpphy) = bioma0
305         trn(:,:,:,jpdia) = bioma0
306         trn(:,:,:,jpzoo) = bioma0
307         trn(:,:,:,jpmes) = bioma0
308         trn(:,:,:,jpfer) = 0.6E-9
309         trn(:,:,:,jpsfe) = bioma0 * 5.e-6
310         trn(:,:,:,jpdfe) = bioma0 * 5.e-6
311         trn(:,:,:,jpnfe) = bioma0 * 5.e-6
312         trn(:,:,:,jpnch) = bioma0 * 12. / 55.
313         trn(:,:,:,jpdch) = bioma0 * 12. / 55.
314         trn(:,:,:,jpno3) = no3
315         trn(:,:,:,jpnh4) = bioma0
316
317         ! initialize the half saturation constant for silicate
318         ! ----------------------------------------------------
319         xksi(:,:)    = 2.e-6
320         xksimax(:,:) = xksi(:,:)
321      END IF
322
323      ! Time step duration for biology
324      xstep = rfact2 / rday
325
326      CALL p4z_sink_init      !  vertical flux of particulate organic matter
327      CALL p4z_opt_init       !  Optic: PAR in the water column
328      CALL p4z_lim_init       !  co-limitations by the various nutrients
329      CALL p4z_prod_init      !  phytoplankton growth rate over the global ocean.
330      CALL p4z_sbc_init       !  boundary conditions
331      CALL p4z_fechem_init    !  Iron chemistry
332      CALL p4z_rem_init       !  remineralisation
333      CALL p4z_mort_init      !  phytoplankton mortality
334      CALL p4z_micro_init     !  microzooplankton
335      CALL p4z_meso_init      !  mesozooplankton
336      CALL p4z_lys_init       !  calcite saturation
337      CALL p4z_flx_init       !  gas exchange
338
339      ndayflxtr = 0
340
341      IF(lwp) WRITE(numout,*)
342      IF(lwp) WRITE(numout,*) 'Initialization of PISCES tracers done'
343      IF(lwp) WRITE(numout,*)
344#endif
345      !
346   END SUBROUTINE p4z_ini
347
348   SUBROUTINE p2z_ini
349      !!----------------------------------------------------------------------
350      !!                   ***  ROUTINE p2z_ini ***
351      !!
352      !! ** Purpose :   Initialisation of the LOBSTER biochemical model
353      !!----------------------------------------------------------------------
354#if defined key_pisces_reduced 
355      !
356      USE p2zopt
357      USE p2zexp
358      USE p2zbio
359      USE p2zsed
360      !
361      INTEGER  ::  ji, jj, jk, ierr
362      !!----------------------------------------------------------------------
363
364      IF(lwp) WRITE(numout,*)
365      IF(lwp) WRITE(numout,*) ' p2z_ini :   LOBSTER biochemical model initialisation'
366      IF(lwp) WRITE(numout,*) ' ~~~~~~~~~~~~~~'
367
368      ierr =        sms_pisces_alloc()         
369      ierr = ierr + p2z_exp_alloc()
370      !
371      IF( lk_mpp    )   CALL mpp_sum( ierr )
372      IF( ierr /= 0 )   CALL ctl_stop( 'STOP', 'p2z_ini: unable to allocate LOBSTER arrays' )
373
374      ! LOBSTER initialisation for GYRE : init NO3=f(density) by asklod AS Kremeur 2005-07
375      ! ----------------------
376      IF( .NOT. ln_rsttr ) THEN             ! in case of  no restart
377         trn(:,:,:,jpdet) = 0.1 * tmask(:,:,:)
378         trn(:,:,:,jpzoo) = 0.1 * tmask(:,:,:)
379         trn(:,:,:,jpnh4) = 0.1 * tmask(:,:,:)
380         trn(:,:,:,jpphy) = 0.1 * tmask(:,:,:)
381         trn(:,:,:,jpdom) = 1.0 * tmask(:,:,:)
382         WHERE( rhd(:,:,:) <= 24.5e-3 )  ;  trn(:,:,:,jpno3 ) = 2._wp * tmask(:,:,:)
383         ELSE WHERE                      ;  trn(:,:,:,jpno3) = ( 15.55 * ( rhd(:,:,:) * 1000. ) - 380.11 ) * tmask(:,:,:)
384         END WHERE                       
385      ENDIF
386      !                       !  Namelist read
387      CALL p2z_opt_init       !  Optics parameters
388      CALL p2z_sed_init       !  sedimentation
389      CALL p2z_bio_init       !  biology
390      CALL p2z_exp_init       !  export
391      !
392      IF(lwp) WRITE(numout,*) 
393      IF(lwp) WRITE(numout,*) 'Initialization of LOBSTER tracers done'
394      IF(lwp) WRITE(numout,*) 
395#endif
396      !
397   END SUBROUTINE p2z_ini
398#else
399   !!----------------------------------------------------------------------
400   !!   Dummy module                            No PISCES biochemical model
401   !!----------------------------------------------------------------------
402CONTAINS
403   SUBROUTINE trc_ini_pisces             ! Empty routine
404   END SUBROUTINE trc_ini_pisces
405#endif
406
407   !!======================================================================
408END MODULE trcini_pisces
Note: See TracBrowser for help on using the repository browser.