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 NEMO/trunk/src/TOP/PISCES – NEMO

source: NEMO/trunk/src/TOP/PISCES/trcini_pisces.F90 @ 13891

Last change on this file since 13891 was 12377, checked in by acc, 4 years ago

The big one. Merging all 2019 developments from the option 1 branch back onto the trunk.

This changeset reproduces 2019/dev_r11943_MERGE_2019 on the trunk using a 2-URL merge
onto a working copy of the trunk. I.e.:

svn merge --ignore-ancestry \

svn+ssh://acc@forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/NEMO/trunk \
svn+ssh://acc@forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/NEMO/branches/2019/dev_r11943_MERGE_2019 ./

The --ignore-ancestry flag avoids problems that may otherwise arise from the fact that
the merge history been trunk and branch may have been applied in a different order but
care has been taken before this step to ensure that all applicable fixes and updates
are present in the merge branch.

The trunk state just before this step has been branched to releases/release-4.0-HEAD
and that branch has been immediately tagged as releases/release-4.0.2. Any fixes
or additions in response to tickets on 4.0, 4.0.1 or 4.0.2 should be done on
releases/release-4.0-HEAD. From now on future 'point' releases (e.g. 4.0.2) will
remain unchanged with periodic releases as needs demand. Note release-4.0-HEAD is a
transitional naming convention. Future full releases, say 4.2, will have a release-4.2
branch which fulfills this role and the first point release (e.g. 4.2.0) will be made
immediately following the release branch creation.

2020 developments can be started from any trunk revision later than this one.

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