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/2016/dev_r7012_ROBUST5_CNRS/NEMOGCM/NEMO/TOP_SRC/PISCES – NEMO

source: branches/2016/dev_r7012_ROBUST5_CNRS/NEMOGCM/NEMO/TOP_SRC/PISCES/trcini_pisces.F90 @ 7041

Last change on this file since 7041 was 7041, checked in by cetlod, 8 years ago

ROBUST5_CNRS : implementation of part I of new TOP interface - 1st step -, see ticket #1782

  • Property svn:keywords set to Id
File size: 13.7 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#if defined key_pisces 
14   !!----------------------------------------------------------------------
15   !!   'key_pisces'                                       PISCES bio-model
16   !!----------------------------------------------------------------------
17   !! trc_ini_pisces   : PISCES biochemical model initialisation
18   !!----------------------------------------------------------------------
19   USE par_trc         ! TOP parameters
20   USE oce_trc         !  shared variables between ocean and passive tracers
21   USE trc             !  passive tracers common variables
22   USE sms_pisces      !  PISCES Source Minus Sink variables
23
24   IMPLICIT NONE
25   PRIVATE
26
27   PUBLIC   trc_ini_pisces   ! called by trcini.F90 module
28
29   !!----------------------------------------------------------------------
30   !! NEMO/TOP 3.3 , NEMO Consortium (2010)
31   !! $Id$
32   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
33   !!----------------------------------------------------------------------
34CONTAINS
35
36   SUBROUTINE trc_ini_pisces
37      !!----------------------------------------------------------------------
38      !!                   ***  ROUTINE trc_ini_pisces ***
39      !!
40      !! ** Purpose :   Initialisation of the PISCES biochemical model
41      !!----------------------------------------------------------------------
42
43      IF( ln_p4z ) THEN  ;   CALL p4z_ini   !  PISCES
44      ELSE               ;   CALL p2z_ini   !  LOBSTER
45      ENDIF
46
47   END SUBROUTINE trc_ini_pisces
48
49   SUBROUTINE p4z_ini
50      !!----------------------------------------------------------------------
51      !!                   ***  ROUTINE p4z_ini ***
52      !!
53      !! ** Purpose :   Initialisation of the PISCES biochemical model
54      !!----------------------------------------------------------------------
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      !
72      REAL(wp), SAVE :: sco2   =  2.312e-3_wp
73      REAL(wp), SAVE :: alka0  =  2.426e-3_wp
74      REAL(wp), SAVE :: oxyg0  =  177.6e-6_wp 
75      REAL(wp), SAVE :: po4    =  2.165e-6_wp 
76      REAL(wp), SAVE :: bioma0 =  1.000e-8_wp 
77      REAL(wp), SAVE :: silic1 =  91.51e-6_wp 
78      REAL(wp), SAVE :: no3    =  30.9e-6_wp * 7.625_wp
79      !
80      INTEGER  ::  ji, jj, jk, jn, ierr
81      REAL(wp) ::  zcaralk, zbicarb, zco3
82      REAL(wp) ::  ztmas, ztmas1
83      CHARACTER(len = 20)  ::  cltra
84
85      !!----------------------------------------------------------------------
86
87      IF(lwp) WRITE(numout,*)
88      IF(lwp) WRITE(numout,*) ' p4z_ini :   PISCES biochemical model initialisation'
89      IF(lwp) WRITE(numout,*) ' ~~~~~~~~~~~~~~'
90
91                                                 ! Allocate PISCES arrays
92      ierr =         sms_pisces_alloc()         
93      ierr = ierr +  p4z_che_alloc()
94      ierr = ierr +  p4z_sink_alloc()
95      ierr = ierr +  p4z_opt_alloc()
96      ierr = ierr +  p4z_prod_alloc()
97      ierr = ierr +  p4z_rem_alloc()
98      ierr = ierr +  p4z_flx_alloc()
99      ierr = ierr +  p4z_sed_alloc()
100      !
101      IF( lk_mpp    )   CALL mpp_sum( ierr )
102      IF( ierr /= 0 )   CALL ctl_stop( 'STOP', 'pisces_alloc: unable to allocate PISCES arrays' )
103      !
104      ryyss    = nyear_len(1) * rday    ! number of seconds per year
105      r1_ryyss = 1. / ryyss
106      !
107
108      ! assign an index in trc arrays for each prognostic variables
109      DO jn = 1, jptra
110        cltra = ctrcnm(jn) 
111        IF( cltra == 'DIC'      )   jpdic = jn      !: dissolved inoganic carbon concentration
112        IF( cltra == 'Alkalini' )   jptal = jn      !: total alkalinity
113        IF( cltra == 'O2'       )   jpoxy = jn      !: oxygen carbon concentration
114        IF( cltra == 'CaCO3'    )   jpcal = jn      !: calcite  concentration
115        IF( cltra == 'PO4'      )   jppo4 = jn      !: phosphate concentration
116        IF( cltra == 'POC'      )   jppoc = jn      !: small particulate organic phosphate concentration
117        IF( cltra == 'Si'       )   jpsil = jn      !: silicate concentration
118        IF( cltra == 'PHY'      )   jpphy = jn      !: phytoplancton concentration
119        IF( cltra == 'ZOO'      )   jpzoo = jn      !: zooplancton concentration
120        IF( cltra == 'DOC'      )   jpdoc = jn      !: dissolved organic carbon concentration
121        IF( cltra == 'PHY2'     )   jpdia = jn      !: Diatoms Concentration
122        IF( cltra == 'ZOO2'     )   jpmes = jn      !: Mesozooplankton Concentration
123        IF( cltra == 'DSi'      )   jpdsi = jn      !: Diatoms Silicate Concentration
124        IF( cltra == 'Fer'      )   jpfer = jn      !: Iron Concentration
125        IF( cltra == 'BFe'      )   jpbfe = jn      !: Big iron particles Concentration
126        IF( cltra == 'GOC'      )   jpgoc = jn      !: Big particulate organic phosphate concentration
127        IF( cltra == 'SFe'      )   jpsfe = jn      !: Small iron particles Concentration
128        IF( cltra == 'DFe'      )   jpdfe = jn      !: Diatoms iron Concentration
129        IF( cltra == 'GSi'      )   jpgsi = jn      !: (big) Silicate Concentration
130        IF( cltra == 'NFe'      )   jpnfe = jn      !: Nano iron Concentration
131        IF( cltra == 'NCHL'     )   jpnch = jn      !: Nano Chlorophyll Concentration
132        IF( cltra == 'DCHL'     )   jpdch = jn      !: Diatoms Chlorophyll Concentration
133        IF( cltra == 'NO3'      )   jpno3 = jn      !: Nitrates Concentration
134        IF( cltra == 'NH4'      )   jpnh4 = jn      !: Ammonium Concentration
135      ENDDO
136
137      jp_pisces = 24
138      jp_pcs0 = MIN( jpdic, jptal, jpoxy, jpcal, jppo4, jppoc, jpsil, &
139         &           jpphy, jpzoo, jpdoc, jpdia, jpmes, jpdsi, jpfer, &
140         &           jpbfe, jpgoc, jpsfe, jpdfe, jpgsi, jpnfe, jpnch, &
141         &           jpdch, jpno3, jpnh4 )
142
143      jp_pcs1     =  jp_pcs0 + jp_pisces - 1
144
145
146      IF( lwp ) THEN
147        WRITE(numout,*) ''
148        WRITE(numout,*) ' First index of PISCES model in the passive tracer array   jp_pcs0 = ', jp_pcs0
149        WRITE(numout,*) ' Last  index of PISCES model in the passive tracer array   jp_pcs1 = ', jp_pcs1
150        WRITE(numout,*) 
151      ENDIF
152     
153
154      CALL p4z_sms_init       !  Maint routine
155      !                                            ! Time-step
156
157      ! Set biological ratios
158      ! ---------------------
159      rno3    =  16._wp / 122._wp
160      po4r    =   1._wp / 122._wp
161      o2nit   =  32._wp / 122._wp
162      o2ut    = 133._wp / 122._wp
163      rdenit  =  ( ( o2ut + o2nit ) * 0.80 - rno3 - rno3 * 0.60 ) / rno3
164      rdenita =   3._wp /  5._wp
165
166
167      ! Initialization of tracer concentration in case of  no restart
168      !--------------------------------------------------------------
169      IF( .NOT.ln_rsttr ) THEN 
170         trn(:,:,:,jpdic) = sco2
171         trn(:,:,:,jpdoc) = bioma0
172         trn(:,:,:,jptal) = alka0
173         trn(:,:,:,jpoxy) = oxyg0
174         trn(:,:,:,jpcal) = bioma0
175         trn(:,:,:,jppo4) = po4 / po4r
176         trn(:,:,:,jppoc) = bioma0
177         trn(:,:,:,jpgoc) = bioma0
178         trn(:,:,:,jpbfe) = bioma0 * 5.e-6
179         trn(:,:,:,jpsil) = silic1
180         trn(:,:,:,jpdsi) = bioma0 * 0.15
181         trn(:,:,:,jpgsi) = bioma0 * 5.e-6
182         trn(:,:,:,jpphy) = bioma0
183         trn(:,:,:,jpdia) = bioma0
184         trn(:,:,:,jpzoo) = bioma0
185         trn(:,:,:,jpmes) = bioma0
186         trn(:,:,:,jpfer) = 0.6E-9
187         trn(:,:,:,jpsfe) = bioma0 * 5.e-6
188         trn(:,:,:,jpdfe) = bioma0 * 5.e-6
189         trn(:,:,:,jpnfe) = bioma0 * 5.e-6
190         trn(:,:,:,jpnch) = bioma0 * 12. / 55.
191         trn(:,:,:,jpdch) = bioma0 * 12. / 55.
192         trn(:,:,:,jpno3) = no3
193         trn(:,:,:,jpnh4) = bioma0
194
195         ! initialize the half saturation constant for silicate
196         ! ----------------------------------------------------
197         xksi(:,:)    = 2.e-6
198         xksimax(:,:) = xksi(:,:)
199      END IF
200
201
202      CALL p4z_sink_init      !  vertical flux of particulate organic matter
203      CALL p4z_opt_init       !  Optic: PAR in the water column
204      CALL p4z_lim_init       !  co-limitations by the various nutrients
205      CALL p4z_prod_init      !  phytoplankton growth rate over the global ocean.
206      CALL p4z_sbc_init       !  boundary conditions
207      CALL p4z_fechem_init    !  Iron chemistry
208      CALL p4z_rem_init       !  remineralisation
209      CALL p4z_mort_init      !  phytoplankton mortality
210      CALL p4z_micro_init     !  microzooplankton
211      CALL p4z_meso_init      !  mesozooplankton
212      CALL p4z_lys_init       !  calcite saturation
213      CALL p4z_flx_init       !  gas exchange
214
215      ndayflxtr = 0
216
217      IF(lwp) WRITE(numout,*) 
218      IF(lwp) WRITE(numout,*) 'Initialization of PISCES tracers done'
219      IF(lwp) WRITE(numout,*) 
220      !
221   END SUBROUTINE p4z_ini
222
223   SUBROUTINE p2z_ini
224      !!----------------------------------------------------------------------
225      !!                   ***  ROUTINE p2z_ini ***
226      !!
227      !! ** Purpose :   Initialisation of the LOBSTER biochemical model
228      !!----------------------------------------------------------------------
229      !
230      USE p2zopt
231      USE p2zexp
232      USE p2zbio
233      USE p2zsed
234      !
235      INTEGER  ::  ji, jj, jk, jn, ierr
236      CHARACTER(len = 10)  ::  cltra
237      !!----------------------------------------------------------------------
238
239      IF(lwp) WRITE(numout,*)
240      IF(lwp) WRITE(numout,*) ' p2z_ini :   LOBSTER biochemical model initialisation'
241      IF(lwp) WRITE(numout,*) ' ~~~~~~~~~~~~~~'
242
243      ierr =        sms_pisces_alloc()         
244      ierr = ierr + p2z_exp_alloc()
245      !
246      IF( lk_mpp    )   CALL mpp_sum( ierr )
247      IF( ierr /= 0 )   CALL ctl_stop( 'STOP', 'p2z_ini: unable to allocate LOBSTER arrays' )
248
249      DO jn = 1, jptra
250        cltra = ctrcnm(jn) 
251        IF( cltra == 'DET' )   jpdet = jn       !: detritus                    [mmoleN/m3]
252        IF( cltra == 'ZOO' )   jpzoo = jn       !: zooplancton concentration   [mmoleN/m3]
253        IF( cltra == 'PHY' )   jpphy = jn       !: phytoplancton concentration [mmoleN/m3]
254        IF( cltra == 'NO3' )   jpno3 = jn       !: nitrate concentration       [mmoleN/m3]
255        IF( cltra == 'NH4' )   jpnh4 = jn       !: ammonium concentration      [mmoleN/m3]
256        IF( cltra == 'DOM' )   jpdom = jn       !: dissolved organic matter    [mmoleN/m3]
257      ENDDO
258
259
260      jp_pcs0 = MIN( jpdet, jpzoo, jpphy, jpno3, jpnh4, jpdom )
261      jp_pcs1 =  jp_pcs0 + jp_pisces - 1
262
263
264      IF( lwp ) THEN
265        WRITE(numout,*) ''
266        WRITE(numout,*) ' First index of LOBSTER model in the passive tracer array   jp_pcs0 = ', jp_pcs0
267        WRITE(numout,*) ' Last  index of LOBSTER model in the passive tracer array   jp_pcs1 = ', jp_pcs1
268        WRITE(numout,*) 
269      ENDIF
270
271
272      jpkb = 10        !  last level where depth less than 200 m
273      DO jk = jpkm1, 1, -1
274         IF( gdept_1d(jk) > 200. ) jpkb = jk 
275      END DO
276      IF (lwp) WRITE(numout,*)
277      IF (lwp) WRITE(numout,*) ' first vertical layers where biology is active (200m depth ) ', jpkb
278      IF (lwp) WRITE(numout,*)
279      jpkbm1 = jpkb - 1
280      !
281
282
283      ! LOBSTER initialisation for GYRE : init NO3=f(density) by asklod AS Kremeur 2005-07
284      ! ----------------------
285      IF( .NOT. ln_rsttr ) THEN             ! in case of  no restart
286         trn(:,:,:,jpdet) = 0.1 * tmask(:,:,:)
287         trn(:,:,:,jpzoo) = 0.1 * tmask(:,:,:)
288         trn(:,:,:,jpnh4) = 0.1 * tmask(:,:,:)
289         trn(:,:,:,jpphy) = 0.1 * tmask(:,:,:)
290         trn(:,:,:,jpdom) = 1.0 * tmask(:,:,:)
291         WHERE( rhd(:,:,:) <= 24.5e-3 )  ;  trn(:,:,:,jpno3) = 2._wp * tmask(:,:,:)
292         ELSE WHERE                      ;  trn(:,:,:,jpno3) = ( 15.55 * ( rhd(:,:,:) * 1000. ) - 380.11 ) * tmask(:,:,:)
293         END WHERE                       
294      ENDIF
295      !                       !  Namelist read
296      CALL p2z_opt_init       !  Optics parameters
297      CALL p2z_sed_init       !  sedimentation
298      CALL p2z_bio_init       !  biology
299      CALL p2z_exp_init       !  export
300      !
301      IF(lwp) WRITE(numout,*) 
302      IF(lwp) WRITE(numout,*) 'Initialization of LOBSTER tracers done'
303      IF(lwp) WRITE(numout,*) 
304      !
305   END SUBROUTINE p2z_ini
306#else
307   !!----------------------------------------------------------------------
308   !!   Dummy module                            No PISCES biochemical model
309   !!----------------------------------------------------------------------
310CONTAINS
311   SUBROUTINE trc_ini_pisces             ! Empty routine
312   END SUBROUTINE trc_ini_pisces
313#endif
314
315   !!======================================================================
316END MODULE trcini_pisces
Note: See TracBrowser for help on using the repository browser.