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

source: trunk/NEMOGCM/NEMO/TOP_SRC/PISCES/trcsms_pisces.F90 @ 3320

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

trunk:bugfix on trends diagnostics in the mixed-layer, see ticket#928 and ticket #930

  • Property svn:keywords set to Id
File size: 10.8 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 p4zlys          !  Calcite saturation
21   USE p4zflx          !  Gas exchange
22   USE p4zsed          !  Sedimentation
23   USE p4zint          !  time interpolation
24   USE trdmod_oce      !  Ocean trends variables
25   USE trdmod_trc      !  TOP trends variables
26   USE sedmodel        !  Sediment model
27   USE prtctl_trc      !  print control for debugging
28
29   IMPLICIT NONE
30   PRIVATE
31
32   PUBLIC   trc_sms_pisces    ! called in trcsms.F90
33
34   LOGICAL ::  ln_check_mass = .false.       !: Flag to check mass conservation
35
36   INTEGER ::  numno3  !: logical unit for NO3 budget
37   INTEGER ::  numalk  !: logical unit for talk budget
38   INTEGER ::  numsil  !: logical unit for Si budget
39
40   !!----------------------------------------------------------------------
41   !! NEMO/TOP 3.3 , NEMO Consortium (2010)
42   !! $Id$
43   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
44   !!----------------------------------------------------------------------
45
46CONTAINS
47
48   SUBROUTINE trc_sms_pisces( kt )
49      !!---------------------------------------------------------------------
50      !!                     ***  ROUTINE trc_sms_pisces  ***
51      !!
52      !! ** Purpose :   Managment of the call to Biological sources and sinks
53      !!              routines of PISCES bio-model
54      !!
55      !! ** Method  : - at each new day ...
56      !!              - several calls of bio and sed ???
57      !!              - ...
58      !!---------------------------------------------------------------------
59      !
60      INTEGER, INTENT( in ) ::   kt      ! ocean time-step index     
61      !!
62      INTEGER ::   jnt, jn, jl
63      CHARACTER (len=25) :: charout
64      REAL(wp), POINTER, DIMENSION(:,:,:,:)  :: ztrdpis
65      !!---------------------------------------------------------------------
66      !
67      IF( nn_timing == 1 )  CALL timing_start('trc_sms_pisces')
68      !
69      IF( ln_pisdmp .AND. MOD( kt - nn_dttrc, nn_pisdmp ) == 0 )   CALL trc_sms_pisces_dmp( kt )  ! Relaxation of some tracers
70                                                                   CALL trc_sms_pisces_mass_conserv( kt ) ! Mass conservation checking
71      IF( l_trdtrc )  THEN
72         CALL wrk_alloc( jpi, jpj, jpk, jp_pisces, ztrdpis ) 
73         DO jn = 1, jp_pisces
74            jl = jn + jp_pcs0 - 1
75            ztrdpis(:,:,:,jn) = trn(:,:,:,jl)
76         ENDDO
77      ENDIF
78
79      IF( ndayflxtr /= nday_year ) THEN      ! New days
80         !
81         ndayflxtr = nday_year
82
83         IF(lwp) write(numout,*)
84         IF(lwp) write(numout,*) ' New chemical constants and various rates for biogeochemistry at new day : ', nday_year
85         IF(lwp) write(numout,*) '~~~~~~'
86
87         CALL p4z_che              ! computation of chemical constants
88         CALL p4z_int              ! computation of various rates for biogeochemistry
89         !
90      ENDIF
91
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         DO jn = jp_pcs0, jp_pcs1
99            trb(:,:,:,jn) = trn(:,:,:,jn)
100         ENDDO
101         !
102      END DO
103
104      IF( l_trdtrc )  THEN
105         DO jn = 1, jp_pisces
106            jl = jn + jp_pcs0 - 1
107            ztrdpis(:,:,:,jn) = ( ztrdpis(:,:,:,jn) - trn(:,:,:,jl) ) * rfact2r
108         ENDDO
109      ENDIF
110
111      CALL p4z_lys( kt )             ! Compute CaCO3 saturation
112      CALL p4z_flx( kt )             ! Compute surface fluxes
113
114      DO jn = jp_pcs0, jp_pcs1
115        CALL lbc_lnk( trn(:,:,:,jn), 'T', 1. )
116        CALL lbc_lnk( trb(:,:,:,jn), 'T', 1. )
117        CALL lbc_lnk( tra(:,:,:,jn), 'T', 1. )
118      END DO
119
120      IF( l_trdtrc ) THEN
121         DO jn = 1, jp_pisces
122            jl = jn + jp_pcs0 - 1
123             ztrdpis(:,:,:,jn) = ztrdpis(:,:,:,jn) + tra(:,:,:,jl)
124             CALL trd_mod_trc( ztrdpis(:,:,:,jn), jn, jptra_trd_sms, kt )   ! save trends
125          END DO
126          CALL wrk_dealloc( jpi, jpj, jpk, jp_pisces, ztrdpis ) 
127      END IF
128
129      IF( lk_sed ) THEN 
130         !
131         CALL sed_model( kt )     !  Main program of Sediment model
132         !
133         DO jn = jp_pcs0, jp_pcs1
134           CALL lbc_lnk( trn(:,:,:,jn), 'T', 1. )
135         END DO
136         !
137      ENDIF
138      !
139      IF( nn_timing == 1 )  CALL timing_stop('trc_sms_pisces')
140      !
141   END SUBROUTINE trc_sms_pisces
142
143   SUBROUTINE trc_sms_pisces_dmp( kt )
144      !!----------------------------------------------------------------------
145      !!                    ***  trc_sms_pisces_dmp  ***
146      !!
147      !! ** purpose  : Relaxation of some tracers
148      !!----------------------------------------------------------------------
149      !
150      INTEGER, INTENT( in )  ::     kt ! time step
151      !
152      REAL(wp) ::  alkmean = 2426.     ! mean value of alkalinity ( Glodap ; for Goyet 2391. )
153      REAL(wp) ::  po4mean = 2.165     ! mean value of phosphates
154      REAL(wp) ::  no3mean = 30.90     ! mean value of nitrate
155      REAL(wp) ::  silmean = 91.51     ! mean value of silicate
156      !
157      REAL(wp) :: zarea, zalksum, zpo4sum, zno3sum, zsilsum
158      !!---------------------------------------------------------------------
159
160
161      IF(lwp)  WRITE(numout,*)
162      IF(lwp)  WRITE(numout,*) ' trc_sms_pisces_dmp : Relaxation of nutrients at time-step kt = ', kt
163      IF(lwp)  WRITE(numout,*)
164
165      IF( cp_cfg == "orca" .AND. .NOT. lk_c1d ) THEN      ! ORCA condiguration (not 1D) !
166         !                                                    ! --------------------------- !
167         ! set total alkalinity, phosphate, nitrate & silicate
168         zarea          = 1._wp / glob_sum( cvol(:,:,:) ) * 1e6             
169
170         zalksum = glob_sum( trn(:,:,:,jptal) * cvol(:,:,:)  ) * zarea
171         zpo4sum = glob_sum( trn(:,:,:,jppo4) * cvol(:,:,:)  ) * zarea / 122.
172         zno3sum = glob_sum( trn(:,:,:,jpno3) * cvol(:,:,:)  ) * zarea / 7.6
173         zsilsum = glob_sum( trn(:,:,:,jpsil) * cvol(:,:,:)  ) * zarea
174 
175         IF(lwp) WRITE(numout,*) '       TALK mean : ', zalksum
176         trn(:,:,:,jptal) = trn(:,:,:,jptal) * alkmean / zalksum
177
178         IF(lwp) WRITE(numout,*) '       PO4  mean : ', zpo4sum
179         trn(:,:,:,jppo4) = trn(:,:,:,jppo4) * po4mean / zpo4sum
180
181         IF(lwp) WRITE(numout,*) '       NO3  mean : ', zno3sum
182         trn(:,:,:,jpno3) = trn(:,:,:,jpno3) * no3mean / zno3sum
183
184         IF(lwp) WRITE(numout,*) '       SiO3 mean : ', zsilsum
185         trn(:,:,:,jpsil) = MIN( 400.e-6,trn(:,:,:,jpsil) * silmean / zsilsum )
186         !
187      ENDIF
188
189   END SUBROUTINE trc_sms_pisces_dmp
190
191   SUBROUTINE trc_sms_pisces_mass_conserv ( kt )
192      !!----------------------------------------------------------------------
193      !!                  ***  ROUTINE trc_sms_pisces_mass_conserv  ***
194      !!
195      !! ** Purpose :  Mass conservation check
196      !!
197      !!---------------------------------------------------------------------
198      !
199      INTEGER, INTENT( in ) ::   kt      ! ocean time-step index     
200      !!
201      REAL(wp) :: zalkbudget, zno3budget, zsilbudget
202      !
203      NAMELIST/nampismass/ ln_check_mass
204      !!---------------------------------------------------------------------
205
206      IF( kt == nittrc000 ) THEN
207         REWIND( numnatp )       
208         READ  ( numnatp, nampismass )
209         IF(lwp) THEN                         ! control print
210            WRITE(numout,*) ' '
211            WRITE(numout,*) ' Namelist parameter for mass conservation checking'
212            WRITE(numout,*) ' ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~'
213            WRITE(numout,*) '    Flag to check mass conservation of NO3/Si/TALK ln_check_mass = ', ln_check_mass
214         ENDIF
215
216         IF( ln_check_mass .AND. lwp) THEN      !   Open budget file of NO3, ALK, Si
217            CALL ctl_opn( numno3, 'no3.budget' , 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, 6, .FALSE., narea )
218            CALL ctl_opn( numsil, 'sil.budget' , 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, 6, .FALSE., narea )
219            CALL ctl_opn( numalk, 'talk.budget', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, 6, .FALSE., narea )
220         ENDIF
221      ENDIF
222
223      IF( ln_check_mass ) THEN      !   Compute the budget of NO3, ALK, Si
224         zno3budget = glob_sum( (   trn(:,:,:,jpno3) + trn(:,:,:,jpnh4)  &
225            &                     + trn(:,:,:,jpphy) + trn(:,:,:,jpdia)  &
226            &                     + trn(:,:,:,jpzoo) + trn(:,:,:,jpmes)  &
227            &                     + trn(:,:,:,jppoc) + trn(:,:,:,jpgoc)  &
228            &                     + trn(:,:,:,jpdoc)                     ) * cvol(:,:,:)  ) 
229         !
230         zsilbudget = glob_sum( (   trn(:,:,:,jpsil) + trn(:,:,:,jpgsi)  &
231            &                     + trn(:,:,:,jpdsi)                     ) * cvol(:,:,:)  )
232         !
233         zalkbudget = glob_sum( (   trn(:,:,:,jpno3) * rno3              &
234            &                     + trn(:,:,:,jptal)                     &
235            &                     + trn(:,:,:,jpcal) * 2.                ) * cvol(:,:,:)  )
236
237         IF( lwp ) THEN
238            WRITE(numno3,9500) kt,  zno3budget / areatot
239            WRITE(numsil,9500) kt,  zsilbudget / areatot
240            WRITE(numalk,9500) kt,  zalkbudget / areatot
241         ENDIF
242       ENDIF
243 9500  FORMAT(i10,e18.10)     
244       !
245   END SUBROUTINE trc_sms_pisces_mass_conserv
246
247#else
248   !!======================================================================
249   !!  Dummy module :                                   No PISCES bio-model
250   !!======================================================================
251CONTAINS
252   SUBROUTINE trc_sms_pisces( kt )                   ! Empty routine
253      INTEGER, INTENT( in ) ::   kt
254      WRITE(*,*) 'trc_sms_pisces: You should not have seen this print! error?', kt
255   END SUBROUTINE trc_sms_pisces
256#endif 
257
258   !!======================================================================
259END MODULE trcsms_pisces 
Note: See TracBrowser for help on using the repository browser.