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.
trcsms_pisces.F90 in branches/2011/dev_NEMO_MERGE_2011/NEMOGCM/NEMO/TOP_SRC/PISCES – NEMO

source: branches/2011/dev_NEMO_MERGE_2011/NEMOGCM/NEMO/TOP_SRC/PISCES/trcsms_pisces.F90 @ 3175

Last change on this file since 3175 was 3175, checked in by cetlod, 12 years ago

Add missing average of rhop when substepping in TOP+some minor corrections

  • Property svn:keywords set to Id
File size: 12.7 KB
Line 
1MODULE trcsms_pisces
2   !!======================================================================
3   !!                         ***  MODULE trcsms_pisces  ***
4   !! TOP :   PISCES Source Minus Sink manager
5   !!======================================================================
6   !! History :   1.0  !  2004-03 (O. Aumont) Original code
7   !!             2.0  !  2007-12  (C. Ethe, G. Madec)  F90
8   !!----------------------------------------------------------------------
9#if defined key_pisces
10   !!----------------------------------------------------------------------
11   !!   'key_pisces'                                       PISCES bio-model
12   !!----------------------------------------------------------------------
13   !!   trcsms_pisces        :  Time loop of passive tracers sms
14   !!----------------------------------------------------------------------
15   USE oce_trc         !  shared variables between ocean and passive tracers
16   USE trc             !  passive tracers common variables
17   USE sms_pisces      !  PISCES Source Minus Sink variables
18   USE p4zbio          !  Biological model
19   USE p4zche          !  Chemical model
20   USE p4zsink         !  vertical flux of particulate matter due to sinking
21   USE p4zopt          !  optical model
22   USE p4zlim          !  Co-limitations of differents nutrients
23   USE p4zprod         !  Growth rate of the 2 phyto groups
24   USE p4zmort         !  Mortality terms for phytoplankton
25   USE p4zmicro        !  Sources and sinks of microzooplankton
26   USE p4zmeso         !  Sources and sinks of mesozooplankton
27   USE p4zrem          !  Remineralisation of organic matter
28   USE p4zlys          !  Calcite saturation
29   USE p4zflx          !  Gas exchange
30   USE p4zsed          !  Sedimentation
31   USE p4zint          !  time interpolation
32   USE trdmod_oce      !  Ocean trends variables
33   USE trdmod_trc      !  TOP trends variables
34   USE sedmodel        !  Sediment model
35   USE prtctl_trc      !  print control for debugging
36
37   IMPLICIT NONE
38   PRIVATE
39
40   PUBLIC   trc_sms_pisces    ! called in trcsms.F90
41
42   LOGICAL ::  ln_check_mass = .false.       !: Flag to check mass conservation
43
44   INTEGER ::  numno3  !: logical unit for NO3 budget
45   INTEGER ::  numalk  !: logical unit for talk budget
46   INTEGER ::  numsil  !: logical unit for Si budget
47
48   !!----------------------------------------------------------------------
49   !! NEMO/TOP 3.3 , NEMO Consortium (2010)
50   !! $Id$
51   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
52   !!----------------------------------------------------------------------
53
54CONTAINS
55
56   SUBROUTINE trc_sms_pisces( kt )
57      !!---------------------------------------------------------------------
58      !!                     ***  ROUTINE trc_sms_pisces  ***
59      !!
60      !! ** Purpose :   Managment of the call to Biological sources and sinks
61      !!              routines of PISCES bio-model
62      !!
63      !! ** Method  : - at each new day ...
64      !!              - several calls of bio and sed ???
65      !!              - ...
66      !!---------------------------------------------------------------------
67      !
68      INTEGER, INTENT( in ) ::   kt      ! ocean time-step index     
69      !!
70      INTEGER ::   jnt, jn
71      CHARACTER (len=25) :: charout
72      !!---------------------------------------------------------------------
73      !
74      IF( nn_timing == 1 )  CALL timing_start('trc_sms_pisces')
75      !
76      IF( kt == nittrc000 )                                        CALL trc_sms_pisces_init       ! Initialization (first time-step only)
77      IF( ln_pisdmp .AND. MOD( kt - nn_dttrc, nn_pisdmp ) == 0 )   CALL trc_sms_pisces_dmp( kt )  ! Relaxation of some tracers
78                                                                   CALL trc_sms_pisces_mass_conserv( kt )
79
80      IF( ndayflxtr /= nday_year ) THEN      ! New days
81         !
82         ndayflxtr = nday_year
83
84         IF(lwp) write(numout,*)
85         IF(lwp) write(numout,*) ' New chemical constants and various rates for biogeochemistry at new day : ', nday_year
86         IF(lwp) write(numout,*) '~~~~~~'
87
88         CALL p4z_che              ! computation of chemical constants
89         CALL p4z_int              ! computation of various rates for biogeochemistry
90         !
91      ENDIF
92
93      DO jnt = 1, nrdttrc          ! Potential time splitting if requested
94         !
95         CALL p4z_bio (kt, jnt)    ! Compute soft tissue production (POC)
96         CALL p4z_sed (kt, jnt)    ! compute soft tissue remineralisation
97         !
98         trb(:,:,:,:) = trn(:,:,:,:)
99         !
100      END DO
101
102      CALL p4z_lys( kt )             ! Compute CaCO3 saturation
103      CALL p4z_flx( kt )             ! Compute surface fluxes
104
105      DO jn = jp_pcs0, jp_pcs1
106        CALL lbc_lnk( trn(:,:,:,jn), 'T', 1. )
107        CALL lbc_lnk( trb(:,:,:,jn), 'T', 1. )
108        CALL lbc_lnk( tra(:,:,:,jn), 'T', 1. )
109      END DO
110
111      IF( l_trdtrc ) THEN
112          DO jn = jp_pcs0, jp_pcs1
113            CALL trd_mod_trc( tra(:,:,:,jn), jn, jptra_trd_sms, kt )   ! save trends
114          END DO
115      END IF
116
117      IF( lk_sed ) THEN 
118         !
119         CALL sed_model( kt )     !  Main program of Sediment model
120         !
121         DO jn = jp_pcs0, jp_pcs1
122           CALL lbc_lnk( trn(:,:,:,jn), 'T', 1. )
123         END DO
124         !
125      ENDIF
126      !
127      IF( nn_timing == 1 )  CALL timing_stop('trc_sms_pisces')
128      !
129   END SUBROUTINE trc_sms_pisces
130
131   SUBROUTINE trc_sms_pisces_dmp( kt )
132      !!----------------------------------------------------------------------
133      !!                    ***  trc_sms_pisces_dmp  ***
134      !!
135      !! ** purpose  : Relaxation of some tracers
136      !!----------------------------------------------------------------------
137      !
138      INTEGER, INTENT( in )  ::     kt ! time step
139      !
140      REAL(wp) ::  alkmean = 2426.     ! mean value of alkalinity ( Glodap ; for Goyet 2391. )
141      REAL(wp) ::  po4mean = 2.165     ! mean value of phosphates
142      REAL(wp) ::  no3mean = 30.90     ! mean value of nitrate
143      REAL(wp) ::  silmean = 91.51     ! mean value of silicate
144      !
145      REAL(wp) :: zarea, zalksum, zpo4sum, zno3sum, zsilsum
146      !!---------------------------------------------------------------------
147
148
149      IF(lwp)  WRITE(numout,*)
150      IF(lwp)  WRITE(numout,*) ' trc_sms_pisces_dmp : Relaxation of nutrients at time-step kt = ', kt
151      IF(lwp)  WRITE(numout,*)
152
153      IF( cp_cfg == "orca" .AND. .NOT. lk_c1d ) THEN      ! ORCA condiguration (not 1D) !
154         !                                                    ! --------------------------- !
155         ! set total alkalinity, phosphate, nitrate & silicate
156         zarea          = 1._wp / glob_sum( cvol(:,:,:) ) * 1e6             
157
158         zalksum = glob_sum( trn(:,:,:,jptal) * cvol(:,:,:)  ) * zarea
159         zpo4sum = glob_sum( trn(:,:,:,jppo4) * cvol(:,:,:)  ) * zarea / 122.
160         zno3sum = glob_sum( trn(:,:,:,jpno3) * cvol(:,:,:)  ) * zarea / 7.6
161         zsilsum = glob_sum( trn(:,:,:,jpsil) * cvol(:,:,:)  ) * zarea
162 
163         IF(lwp) WRITE(numout,*) '       TALK mean : ', zalksum
164         trn(:,:,:,jptal) = trn(:,:,:,jptal) * alkmean / zalksum
165
166         IF(lwp) WRITE(numout,*) '       PO4  mean : ', zpo4sum
167         trn(:,:,:,jppo4) = trn(:,:,:,jppo4) * po4mean / zpo4sum
168
169         IF(lwp) WRITE(numout,*) '       NO3  mean : ', zno3sum
170         trn(:,:,:,jpno3) = trn(:,:,:,jpno3) * no3mean / zno3sum
171
172         IF(lwp) WRITE(numout,*) '       SiO3 mean : ', zsilsum
173         trn(:,:,:,jpsil) = MIN( 400.e-6,trn(:,:,:,jpsil) * silmean / zsilsum )
174         !
175      ENDIF
176
177   END SUBROUTINE trc_sms_pisces_dmp
178
179   SUBROUTINE trc_sms_pisces_init
180      !!----------------------------------------------------------------------
181      !!                  ***  ROUTINE trc_sms_pisces_init  ***
182      !!
183      !! ** Purpose :   Initialization of PH variable
184      !!
185      !!----------------------------------------------------------------------
186      INTEGER  ::  ji, jj, jk
187      REAL(wp) ::  zcaralk, zbicarb, zco3
188      REAL(wp) ::  ztmas, ztmas1
189
190      IF( .NOT. ln_rsttr ) THEN
191         ! Initialization of chemical variables of the carbon cycle
192         ! --------------------------------------------------------
193         DO jk = 1, jpk
194            DO jj = 1, jpj
195               DO ji = 1, jpi
196                  ztmas   = tmask(ji,jj,jk)
197                  ztmas1  = 1. - tmask(ji,jj,jk)
198                  zcaralk = trn(ji,jj,jk,jptal) - borat(ji,jj,jk) / (  1. + 1.E-8 / ( rtrn + akb3(ji,jj,jk) )  )
199                  zco3    = ( zcaralk - trn(ji,jj,jk,jpdic) ) * ztmas + 0.5e-3 * ztmas1
200                  zbicarb = ( 2. * trn(ji,jj,jk,jpdic) - zcaralk )
201                  hi(ji,jj,jk) = ( ak23(ji,jj,jk) * zbicarb / zco3 ) * ztmas + 1.e-9 * ztmas1
202               END DO
203            END DO
204         END DO
205         !
206      END IF
207
208      ! Time step duration for biology
209      xstep = rfact2 / rday
210
211      CALL p4z_sink_init      !  vertical flux of particulate organic matter
212      CALL p4z_opt_init       !  Optic: PAR in the water column
213      CALL p4z_lim_init       !  co-limitations by the various nutrients
214      CALL p4z_prod_init      !  phytoplankton growth rate over the global ocean.
215      CALL p4z_rem_init       !  remineralisation
216      CALL p4z_mort_init      !  phytoplankton mortality
217      CALL p4z_micro_init     !  microzooplankton
218      CALL p4z_meso_init      !  mesozooplankton
219      CALL p4z_sed_init       !  sedimentation
220      CALL p4z_lys_init       !  calcite saturation
221      CALL p4z_flx_init       !  gas exchange
222
223      ndayflxtr = 0
224
225   END SUBROUTINE trc_sms_pisces_init
226
227   SUBROUTINE trc_sms_pisces_mass_conserv ( kt )
228      !!----------------------------------------------------------------------
229      !!                  ***  ROUTINE trc_sms_pisces_mass_conserv  ***
230      !!
231      !! ** Purpose :  Mass conservation check
232      !!
233      !!---------------------------------------------------------------------
234      !
235      INTEGER, INTENT( in ) ::   kt      ! ocean time-step index     
236      !!
237      REAL(wp) :: zalkbudget, zno3budget, zsilbudget
238      !
239      NAMELIST/nampismass/ ln_check_mass
240      !!---------------------------------------------------------------------
241
242      IF( kt == nittrc000 ) THEN
243         REWIND( numnatp )       
244         READ  ( numnatp, nampismass )
245         IF(lwp) THEN                         ! control print
246            WRITE(numout,*) ' '
247            WRITE(numout,*) ' Namelist parameter for mass conservation checking'
248            WRITE(numout,*) ' ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~'
249            WRITE(numout,*) '    Flag to check mass conservation of NO3/Si/TALK ln_check_mass = ', ln_check_mass
250         ENDIF
251
252         IF( ln_check_mass .AND. lwp) THEN      !   Open budget file of NO3, ALK, Si
253            CALL ctl_opn( numno3, 'no3.budget' , 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, 6, .FALSE., narea )
254            CALL ctl_opn( numsil, 'sil.budget' , 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, 6, .FALSE., narea )
255            CALL ctl_opn( numalk, 'talk.budget', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, 6, .FALSE., narea )
256         ENDIF
257      ENDIF
258
259      IF( ln_check_mass ) THEN      !   Compute the budget of NO3, ALK, Si
260         zno3budget = glob_sum( (   trn(:,:,:,jpno3) + trn(:,:,:,jpnh4)  &
261            &                     + trn(:,:,:,jpphy) + trn(:,:,:,jpdia)  &
262            &                     + trn(:,:,:,jpzoo) + trn(:,:,:,jpmes)  &
263            &                     + trn(:,:,:,jppoc) + trn(:,:,:,jpgoc)  &
264            &                     + trn(:,:,:,jpdoc)                     ) * cvol(:,:,:)  ) 
265         !
266         zsilbudget = glob_sum( (   trn(:,:,:,jpsil) + trn(:,:,:,jpdsi)  &
267            &                     + trn(:,:,:,jpbsi)                     ) * cvol(:,:,:)  )
268         !
269         zalkbudget = glob_sum( (   trn(:,:,:,jpno3) * rno3              &
270            &                     + trn(:,:,:,jptal)                     &
271            &                     + trn(:,:,:,jpcal) * 2.                ) * cvol(:,:,:)  )
272
273         IF( lwp ) THEN
274            WRITE(numno3,9500) kt,  zno3budget / areatot
275            WRITE(numsil,9500) kt,  zsilbudget / areatot
276            WRITE(numalk,9500) kt,  zalkbudget / areatot
277         ENDIF
278       ENDIF
279 9500  FORMAT(i6,e18.10)     
280       !
281   END SUBROUTINE trc_sms_pisces_mass_conserv
282
283#else
284   !!======================================================================
285   !!  Dummy module :                                   No PISCES bio-model
286   !!======================================================================
287CONTAINS
288   SUBROUTINE trc_sms_pisces( kt )                   ! Empty routine
289      INTEGER, INTENT( in ) ::   kt
290      WRITE(*,*) 'trc_sms_pisces: You should not have seen this print! error?', kt
291   END SUBROUTINE trc_sms_pisces
292#endif 
293
294   !!======================================================================
295END MODULE trcsms_pisces 
Note: See TracBrowser for help on using the repository browser.