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 @ 10068

Last change on this file since 10068 was 10068, checked in by nicolasmartin, 6 years ago

First part of modifications to have a common default header : fix typos and SVN keywords properties

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