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/2015/dev_r5803_NOC_WAD/NEMOGCM/NEMO/TOP_SRC/PISCES – NEMO

source: branches/2015/dev_r5803_NOC_WAD/NEMOGCM/NEMO/TOP_SRC/PISCES/trcini_pisces.F90 @ 5870

Last change on this file since 5870 was 5870, checked in by acc, 8 years ago

Branch 2015/dev_r5803_NOC_WAD. Merge in trunk changes from 5803 to 5869 in preparation for merge. Also tidied and reorganised some wetting and drying code. Renamed wadlmt.F90 to wetdry.F90. Wetting drying code changes restricted to domzgr.F90, domvvl.F90 nemogcm.F90 sshwzv.F90, dynspg_ts.F90, wetdry.F90 and dynhpg.F90. Code passes full SETTE tests with ln_wd=.false.. Still awaiting test case for checking with ln_wd=.false.

  • Property svn:keywords set to Id
File size: 9.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#if defined key_pisces || defined key_pisces_reduced
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( lk_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#if defined key_pisces 
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
61      USE p4zsbc          !  Boundary conditions
62      USE p4zfechem       !  Iron chemistry
63      USE p4zrem          !  Remineralisation of organic matter
64      USE p4zflx          !  Gas exchange
65      USE p4zlim          !  Co-limitations of differents nutrients
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
71      USE p4zsed          !  Sedimentation & burial
72      !
73      REAL(wp), SAVE :: sco2   =  2.312e-3_wp
74      REAL(wp), SAVE :: alka0  =  2.426e-3_wp
75      REAL(wp), SAVE :: oxyg0  =  177.6e-6_wp 
76      REAL(wp), SAVE :: po4    =  2.165e-6_wp 
77      REAL(wp), SAVE :: bioma0 =  1.000e-8_wp 
78      REAL(wp), SAVE :: silic1 =  91.51e-6_wp 
79      REAL(wp), SAVE :: no3    =  30.9e-6_wp * 7.625_wp
80      !
81      INTEGER  ::  ji, jj, jk, ierr
82      REAL(wp) ::  zcaralk, zbicarb, zco3
83      REAL(wp) ::  ztmas, ztmas1
84      !!----------------------------------------------------------------------
85
86      IF(lwp) WRITE(numout,*)
87      IF(lwp) WRITE(numout,*) ' p4z_ini :   PISCES biochemical model initialisation'
88      IF(lwp) WRITE(numout,*) ' ~~~~~~~~~~~~~~'
89
90                                                 ! Allocate PISCES arrays
91      ierr =         sms_pisces_alloc()         
92      ierr = ierr +  p4z_che_alloc()
93      ierr = ierr +  p4z_sink_alloc()
94      ierr = ierr +  p4z_opt_alloc()
95      ierr = ierr +  p4z_prod_alloc()
96      ierr = ierr +  p4z_rem_alloc()
97      ierr = ierr +  p4z_flx_alloc()
98      ierr = ierr +  p4z_sed_alloc()
99      !
100      IF( lk_mpp    )   CALL mpp_sum( ierr )
101      IF( ierr /= 0 )   CALL ctl_stop( 'STOP', 'pisces_alloc: unable to allocate PISCES arrays' )
102      !
103      ryyss    = nyear_len(1) * rday    ! number of seconds per year
104      r1_ryyss = 1. / ryyss
105      !
106
107      CALL p4z_sms_init       !  Maint routine
108      !                                            ! Time-step
109
110      ! Set biological ratios
111      ! ---------------------
112      rno3    =  16._wp / 122._wp
113      po4r    =   1._wp / 122._wp
114      o2nit   =  32._wp / 122._wp
115      rdenit  = 105._wp /  16._wp
116      rdenita =   3._wp /  5._wp
117      o2ut    = 133._wp / 122._wp
118
119      ! Initialization of tracer concentration in case of  no restart
120      !--------------------------------------------------------------
121      IF( .NOT. ln_rsttr ) THEN 
122         
123         trn(:,:,:,jpdic) = sco2
124         trn(:,:,:,jpdoc) = bioma0
125         trn(:,:,:,jptal) = alka0
126         trn(:,:,:,jpoxy) = oxyg0
127         trn(:,:,:,jpcal) = bioma0
128         trn(:,:,:,jppo4) = po4 / po4r
129         trn(:,:,:,jppoc) = bioma0
130#  if ! defined key_kriest
131         trn(:,:,:,jpgoc) = bioma0
132         trn(:,:,:,jpbfe) = bioma0 * 5.e-6
133#  else
134         trn(:,:,:,jpnum) = bioma0 / ( 6. * xkr_massp )
135#  endif
136         trn(:,:,:,jpsil) = silic1
137         trn(:,:,:,jpdsi) = bioma0 * 0.15
138         trn(:,:,:,jpgsi) = bioma0 * 5.e-6
139         trn(:,:,:,jpphy) = bioma0
140         trn(:,:,:,jpdia) = bioma0
141         trn(:,:,:,jpzoo) = bioma0
142         trn(:,:,:,jpmes) = bioma0
143         trn(:,:,:,jpfer) = 0.6E-9
144         trn(:,:,:,jpsfe) = bioma0 * 5.e-6
145         trn(:,:,:,jpdfe) = bioma0 * 5.e-6
146         trn(:,:,:,jpnfe) = bioma0 * 5.e-6
147         trn(:,:,:,jpnch) = bioma0 * 12. / 55.
148         trn(:,:,:,jpdch) = bioma0 * 12. / 55.
149         trn(:,:,:,jpno3) = no3
150         trn(:,:,:,jpnh4) = bioma0
151
152         ! initialize the half saturation constant for silicate
153         ! ----------------------------------------------------
154         xksi(:,:)    = 2.e-6
155         xksimax(:,:) = xksi(:,:)
156      END IF
157
158
159      CALL p4z_sink_init      !  vertical flux of particulate organic matter
160      CALL p4z_opt_init       !  Optic: PAR in the water column
161      CALL p4z_lim_init       !  co-limitations by the various nutrients
162      CALL p4z_prod_init      !  phytoplankton growth rate over the global ocean.
163      CALL p4z_sbc_init       !  boundary conditions
164      CALL p4z_fechem_init    !  Iron chemistry
165      CALL p4z_rem_init       !  remineralisation
166      CALL p4z_mort_init      !  phytoplankton mortality
167      CALL p4z_micro_init     !  microzooplankton
168      CALL p4z_meso_init      !  mesozooplankton
169      CALL p4z_lys_init       !  calcite saturation
170      CALL p4z_flx_init       !  gas exchange
171
172      ndayflxtr = 0
173
174      IF(lwp) WRITE(numout,*) 
175      IF(lwp) WRITE(numout,*) 'Initialization of PISCES tracers done'
176      IF(lwp) WRITE(numout,*) 
177#endif
178      !
179   END SUBROUTINE p4z_ini
180
181   SUBROUTINE p2z_ini
182      !!----------------------------------------------------------------------
183      !!                   ***  ROUTINE p2z_ini ***
184      !!
185      !! ** Purpose :   Initialisation of the LOBSTER biochemical model
186      !!----------------------------------------------------------------------
187#if defined key_pisces_reduced 
188      !
189      USE p2zopt
190      USE p2zexp
191      USE p2zbio
192      USE p2zsed
193      !
194      INTEGER  ::  ji, jj, jk, ierr
195      !!----------------------------------------------------------------------
196
197      IF(lwp) WRITE(numout,*)
198      IF(lwp) WRITE(numout,*) ' p2z_ini :   LOBSTER biochemical model initialisation'
199      IF(lwp) WRITE(numout,*) ' ~~~~~~~~~~~~~~'
200
201      ierr =        sms_pisces_alloc()         
202      ierr = ierr + p2z_exp_alloc()
203      !
204      IF( lk_mpp    )   CALL mpp_sum( ierr )
205      IF( ierr /= 0 )   CALL ctl_stop( 'STOP', 'p2z_ini: unable to allocate LOBSTER arrays' )
206
207      ! LOBSTER initialisation for GYRE : init NO3=f(density) by asklod AS Kremeur 2005-07
208      ! ----------------------
209      IF( .NOT. ln_rsttr ) THEN             ! in case of  no restart
210         trn(:,:,:,jpdet) = 0.1 * tmask(:,:,:)
211         trn(:,:,:,jpzoo) = 0.1 * tmask(:,:,:)
212         trn(:,:,:,jpnh4) = 0.1 * tmask(:,:,:)
213         trn(:,:,:,jpphy) = 0.1 * tmask(:,:,:)
214         trn(:,:,:,jpdom) = 1.0 * tmask(:,:,:)
215         WHERE( rhd(:,:,:) <= 24.5e-3 )  ;  trn(:,:,:,jpno3 ) = 2._wp * tmask(:,:,:)
216         ELSE WHERE                      ;  trn(:,:,:,jpno3) = ( 15.55 * ( rhd(:,:,:) * 1000. ) - 380.11 ) * tmask(:,:,:)
217         END WHERE                       
218      ENDIF
219      !                       !  Namelist read
220      CALL p2z_opt_init       !  Optics parameters
221      CALL p2z_sed_init       !  sedimentation
222      CALL p2z_bio_init       !  biology
223      CALL p2z_exp_init       !  export
224      !
225      IF(lwp) WRITE(numout,*) 
226      IF(lwp) WRITE(numout,*) 'Initialization of LOBSTER tracers done'
227      IF(lwp) WRITE(numout,*) 
228#endif
229      !
230   END SUBROUTINE p2z_ini
231#else
232   !!----------------------------------------------------------------------
233   !!   Dummy module                            No PISCES biochemical model
234   !!----------------------------------------------------------------------
235CONTAINS
236   SUBROUTINE trc_ini_pisces             ! Empty routine
237   END SUBROUTINE trc_ini_pisces
238#endif
239
240   !!======================================================================
241END MODULE trcini_pisces
Note: See TracBrowser for help on using the repository browser.