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.
trcrst.F90 in branches/NERC/dev_r5518_NOC_MEDUSA_Stable/NEMOGCM/NEMO/TOP_SRC – NEMO

source: branches/NERC/dev_r5518_NOC_MEDUSA_Stable/NEMOGCM/NEMO/TOP_SRC/trcrst.F90 @ 6173

Last change on this file since 6173 was 6173, checked in by jpalmier, 8 years ago

JPALM --28-12-2015-- cleaning

File size: 22.0 KB
Line 
1MODULE trcrst
2   !!======================================================================
3   !!                         ***  MODULE trcrst  ***
4   !! TOP :   Manage the passive tracer restart
5   !!======================================================================
6   !! History :    -   !  1991-03  ()  original code
7   !!             1.0  !  2005-03 (O. Aumont, A. El Moussaoui) F90
8   !!              -   !  2005-10 (C. Ethe) print control
9   !!             2.0  !  2005-10 (C. Ethe, G. Madec) revised architecture
10   !!----------------------------------------------------------------------
11#if defined key_top
12   !!----------------------------------------------------------------------
13   !!   'key_top'                                                TOP models
14   !!----------------------------------------------------------------------
15   !!----------------------------------------------------------------------
16   !!   trc_rst :   Restart for passive tracer
17   !!----------------------------------------------------------------------
18   !!----------------------------------------------------------------------
19   !!   'key_top'                                                TOP models
20   !!----------------------------------------------------------------------
21   !!   trc_rst_opn    : open  restart file
22   !!   trc_rst_read   : read  restart file
23   !!   trc_rst_wri    : write restart file
24   !!----------------------------------------------------------------------
25   USE oce_trc
26   USE trc
27   USE trcnam_trp
28   USE iom
29   USE ioipsl, ONLY : ju2ymds    ! for calendar
30   USE daymod
31   !! AXY (05/11/13): need these for MEDUSA to input/output benthic reservoirs
32   USE sms_medusa
33   USE trcsms_medusa
34   !!
35   IMPLICIT NONE
36   PRIVATE
37
38   PUBLIC   trc_rst_opn       ! called by ???
39   PUBLIC   trc_rst_read      ! called by ???
40   PUBLIC   trc_rst_wri       ! called by ???
41   PUBLIC   trc_rst_cal
42
43   !! * Substitutions
44#  include "top_substitute.h90"
45   
46CONTAINS
47   
48   SUBROUTINE trc_rst_opn( kt )
49      !!----------------------------------------------------------------------
50      !!                    ***  trc_rst_opn  ***
51      !!
52      !! ** purpose  :   output of sea-trc variable in a netcdf file
53      !!----------------------------------------------------------------------
54      INTEGER, INTENT(in) ::   kt       ! number of iteration
55      INTEGER             ::   iyear, imonth, iday
56      REAL (wp)           ::   zsec
57      !
58      CHARACTER(LEN=20)   ::   clkt     ! ocean time-step define as a character
59      CHARACTER(LEN=50)   ::   clname   ! trc output restart file name
60      CHARACTER(LEN=256)  ::   clpath   ! full path to ocean output restart file
61      !!----------------------------------------------------------------------
62      !
63      IF( lk_offline ) THEN
64         IF( kt == nittrc000 ) THEN
65            lrst_trc = .FALSE.
66            IF( ln_rst_list ) THEN
67               nrst_lst = 1
68               nitrst = nstocklist( nrst_lst )
69            ELSE
70               nitrst = nitend
71            ENDIF
72         ENDIF
73
74         IF( .NOT. ln_rst_list .AND. MOD( kt - 1, nstock ) == 0 ) THEN
75            ! we use kt - 1 and not kt - nittrc000 to keep the same periodicity from the beginning of the experiment
76            nitrst = kt + nstock - 1                  ! define the next value of nitrst for restart writing
77            IF( nitrst > nitend )   nitrst = nitend   ! make sure we write a restart at the end of the run
78         ENDIF
79      ELSE
80         IF( kt == nittrc000 ) lrst_trc = .FALSE.
81      ENDIF
82
83      ! to get better performances with NetCDF format:
84      ! we open and define the tracer restart file one tracer time step before writing the data (-> at nitrst - 2*nn_dttrc + 1)
85      ! except if we write tracer restart files every tracer time step or if a tracer restart file was writen at nitend - 2*nn_dttrc + 1
86      IF( kt == nitrst - 2*nn_dttrc .OR. nstock == nn_dttrc .OR. ( kt == nitend - nn_dttrc .AND. .NOT. lrst_trc ) ) THEN
87         IF ( ln_rstdate ) THEN
88            !! JPALM -- 22-12-2015 -- modif to get the good date on restart trc
89            !file name
90            !!                     -- the condition to open the rst file is not
91            !the same than for the dynamic rst.
92            !!                     -- here it - for an obscure reason - is open
93            !2 time-step before the restart writing process
94            !!                     instead of 1.
95            !!                     -- i am not sure if someone forgot +1 in the
96            !if loop condition as
97            !!                     it is writen in all comments nitrst -
98            !2*nn_dttrc + 1 and the condition is nitrst - 2*nn_dttrc
99            !!                     -- nevertheless we didn't wanted to broke
100            !something already working
101            !!                     and just adapted the part we added.
102            !!                     -- So instead of calling ju2ymds( fjulday +
103            !(rdttra(1)) ....
104            !!                     we call ju2ymds( fjulday + (2*rdttra(1))
105            !.....
106            !!--------------------------------------------------------------------     
107            CALL ju2ymds( fjulday + (2*rdttra(1)) / rday, iyear, imonth, iday,
108zsec )
109            WRITE(clkt, '(i4.4,2i2.2)') iyear, imonth, iday
110         ELSE
111            ! beware of the format used to write kt (default is i8.8, that should be large enough)
112            IF( nitrst > 1.0e9 ) THEN   ;   WRITE(clkt,*       ) nitrst
113            ELSE                        ;   WRITE(clkt,'(i8.8)') nitrst
114            ENDIF
115         ENDIF
116         ! create the file
117         IF(lwp) WRITE(numout,*)
118         clname = TRIM(cexper)//"_"//TRIM(ADJUSTL(clkt))//"_"//TRIM(cn_trcrst_out)
119         clpath = TRIM(cn_trcrst_outdir)
120         IF( clpath(LEN_TRIM(clpath):) /= '/' ) clpath = TRIM(clpath) // '/'
121         IF(lwp) WRITE(numout,*) &
122             '             open trc restart.output NetCDF file: ',TRIM(clpath)//clname
123         CALL iom_open( TRIM(clpath)//TRIM(clname), numrtw, ldwrt = .TRUE., kiolib = jprstlib )
124         lrst_trc = .TRUE.
125      ENDIF
126      !
127   END SUBROUTINE trc_rst_opn
128
129   SUBROUTINE trc_rst_read
130      !!----------------------------------------------------------------------
131      !!                    ***  trc_rst_opn  ***
132      !!
133      !! ** purpose  :   read passive tracer fields in restart files
134      !!----------------------------------------------------------------------
135      INTEGER  ::  jn     
136      !! AXY (05/11/13): temporary variables
137      REAL(wp) ::    fq0,fq1,fq2
138
139      !!----------------------------------------------------------------------
140      !
141      IF(lwp) WRITE(numout,*)
142      IF(lwp) WRITE(numout,*) 'trc_rst_read : read data in the TOP restart file'
143      IF(lwp) WRITE(numout,*) '~~~~~~~~~~~~'
144
145      ! READ prognostic variables and computes diagnostic variable
146      DO jn = 1, jptra
147         CALL iom_get( numrtr, jpdom_autoglo, 'TRN'//ctrcnm(jn), trn(:,:,:,jn) )
148      END DO
149
150      DO jn = 1, jptra
151         CALL iom_get( numrtr, jpdom_autoglo, 'TRB'//ctrcnm(jn), trb(:,:,:,jn) )
152      END DO
153
154      !! AXY (09/06/14): the ARCHER version of MEDUSA-2 does not include an equivalent
155      !!                 call to MEDUSA-2 at this point; this suggests that the FCM
156      !!                 version of NEMO date significantly earlier than the current
157      !!                 version
158
159#if defined key_medusa
160      !! AXY (13/01/12): check if the restart contains sediment fields;
161      !!                 this is only relevant for simulations that include
162      !!                 biogeochemistry and are restarted from earlier runs
163      !!                 in which there was no sediment component
164      !!
165      IF( iom_varid( numrtr, 'B_SED_N', ldstop = .FALSE. ) > 0 ) THEN
166         !! YES; in which case read them
167         !!
168         IF(lwp) WRITE(numout,*) ' MEDUSA sediment fields present - reading in ...'
169         CALL iom_get( numrtr, jpdom_autoglo, 'B_SED_N',  zb_sed_n(:,:)  )
170         CALL iom_get( numrtr, jpdom_autoglo, 'N_SED_N',  zn_sed_n(:,:)  )
171         CALL iom_get( numrtr, jpdom_autoglo, 'B_SED_FE', zb_sed_fe(:,:) )
172         CALL iom_get( numrtr, jpdom_autoglo, 'N_SED_FE', zn_sed_fe(:,:) )
173         CALL iom_get( numrtr, jpdom_autoglo, 'B_SED_SI', zb_sed_si(:,:) )
174         CALL iom_get( numrtr, jpdom_autoglo, 'N_SED_SI', zn_sed_si(:,:) )
175         CALL iom_get( numrtr, jpdom_autoglo, 'B_SED_C',  zb_sed_c(:,:)  )
176         CALL iom_get( numrtr, jpdom_autoglo, 'N_SED_C',  zn_sed_c(:,:)  )
177         CALL iom_get( numrtr, jpdom_autoglo, 'B_SED_CA', zb_sed_ca(:,:) )
178         CALL iom_get( numrtr, jpdom_autoglo, 'N_SED_CA', zn_sed_ca(:,:) )
179      ELSE
180         !! NO; in which case set them to zero
181         !!
182         IF(lwp) WRITE(numout,*) ' MEDUSA sediment fields absent - setting to zero ...'
183         zb_sed_n(:,:)  = 0.0   !! organic N
184         zn_sed_n(:,:)  = 0.0
185         zb_sed_fe(:,:) = 0.0   !! organic Fe
186         zn_sed_fe(:,:) = 0.0
187         zb_sed_si(:,:) = 0.0   !! inorganic Si
188         zn_sed_si(:,:) = 0.0
189         zb_sed_c(:,:)  = 0.0   !! organic C
190         zn_sed_c(:,:)  = 0.0
191         zb_sed_ca(:,:) = 0.0   !! inorganic C
192         zn_sed_ca(:,:) = 0.0
193      ENDIF
194      !!
195      !! calculate stats on these fields
196      IF(lwp) WRITE(numout,*) ' MEDUSA sediment field stats (min, max, sum) ...'
197      fq0 = MINVAL(zn_sed_n(:,:))
198      fq1 = MAXVAL(zn_sed_n(:,:))
199      fq2 = SUM(zn_sed_n(:,:))
200      if (lwp) write (numout,'(a,3f15.5)') 'Sediment  N ', &
201         &        fq0, fq1, fq2
202      fq0 = MINVAL(zn_sed_fe(:,:))
203      fq1 = MAXVAL(zn_sed_fe(:,:))
204      fq2 = SUM(zn_sed_fe(:,:))
205      if (lwp) write (numout,'(a,3f15.5)') 'Sediment Fe ', &
206         &        fq0, fq1, fq2
207      fq0 = MINVAL(zn_sed_si(:,:))
208      fq1 = MAXVAL(zn_sed_si(:,:))
209      fq2 = SUM(zn_sed_si(:,:))
210      if (lwp) write (numout,'(a,3f15.5)') 'Sediment Si ', &
211         &        fq0, fq1, fq2
212      fq0 = MINVAL(zn_sed_c(:,:))
213      fq1 = MAXVAL(zn_sed_c(:,:))
214      fq2 = SUM(zn_sed_c(:,:))
215      if (lwp) write (numout,'(a,3f15.5)') 'Sediment  C ', &
216         &        fq0, fq1, fq2
217      fq0 = MINVAL(zn_sed_ca(:,:))
218      fq1 = MAXVAL(zn_sed_ca(:,:))
219      fq2 = SUM(zn_sed_ca(:,:))
220      if (lwp) write (numout,'(a,3f15.5)') 'Sediment Ca ', &
221         &        fq0, fq1, fq2
222#endif
223 
224      !
225   END SUBROUTINE trc_rst_read
226
227   SUBROUTINE trc_rst_wri( kt )
228      !!----------------------------------------------------------------------
229      !!                    ***  trc_rst_wri  ***
230      !!
231      !! ** purpose  :   write passive tracer fields in restart files
232      !!----------------------------------------------------------------------
233      INTEGER, INTENT( in ) ::   kt    ! ocean time-step index
234      !!
235      INTEGER  :: jn
236      REAL(wp) :: zarak0
237      !! AXY (05/11/13): temporary variables
238      REAL(wp) ::    fq0,fq1,fq2
239      !!----------------------------------------------------------------------
240      !
241      CALL iom_rstput( kt, nitrst, numrtw, 'rdttrc1', rdttrc(1) )   ! surface passive tracer time step
242      ! prognostic variables
243      ! --------------------
244      DO jn = 1, jptra
245         CALL iom_rstput( kt, nitrst, numrtw, 'TRN'//ctrcnm(jn), trn(:,:,:,jn) )
246      END DO
247
248      DO jn = 1, jptra
249         CALL iom_rstput( kt, nitrst, numrtw, 'TRB'//ctrcnm(jn), trb(:,:,:,jn) )
250      END DO
251
252      !! AXY (09/06/14): the ARCHER version of MEDUSA-2 does not include an equivalent
253      !!                 call to MEDUSA-2 at this point; this suggests that the FCM
254      !!                 version of NEMO date significantly earlier than the current
255      !!                 version
256
257#if defined key_medusa
258      !! AXY (13/01/12): write out "before" and "now" state of seafloor
259      !!                 sediment pools into restart; this happens
260      !!                 whether or not the pools are to be used by
261      !!                 MEDUSA (which is controlled by a switch in the
262      !!                 namelist_top file)
263      !!
264      IF(lwp) WRITE(numout,*) ' MEDUSA sediment fields - writing out ...'
265      CALL iom_rstput( kt, nitrst, numrtw, 'B_SED_N',  zb_sed_n(:,:)  )
266      CALL iom_rstput( kt, nitrst, numrtw, 'N_SED_N',  zn_sed_n(:,:)  )
267      CALL iom_rstput( kt, nitrst, numrtw, 'B_SED_FE', zb_sed_fe(:,:) )
268      CALL iom_rstput( kt, nitrst, numrtw, 'N_SED_FE', zn_sed_fe(:,:) )
269      CALL iom_rstput( kt, nitrst, numrtw, 'B_SED_SI', zb_sed_si(:,:) )
270      CALL iom_rstput( kt, nitrst, numrtw, 'N_SED_SI', zn_sed_si(:,:) )
271      CALL iom_rstput( kt, nitrst, numrtw, 'B_SED_C',  zb_sed_c(:,:)  )
272      CALL iom_rstput( kt, nitrst, numrtw, 'N_SED_C',  zn_sed_c(:,:)  )
273      CALL iom_rstput( kt, nitrst, numrtw, 'B_SED_CA', zb_sed_ca(:,:) )
274      CALL iom_rstput( kt, nitrst, numrtw, 'N_SED_CA', zn_sed_ca(:,:) )
275      !!
276      !! calculate stats on these fields
277      IF(lwp) WRITE(numout,*) ' MEDUSA sediment field stats (min, max, sum) ...'
278      fq0 = MINVAL(zn_sed_n(:,:))
279      fq1 = MAXVAL(zn_sed_n(:,:))
280      fq2 = SUM(zn_sed_n(:,:))
281      if (lwp) write (numout,'(a,3f15.5)') 'Sediment  N ', &
282         &        fq0, fq1, fq2
283      fq0 = MINVAL(zn_sed_fe(:,:))
284      fq1 = MAXVAL(zn_sed_fe(:,:))
285      fq2 = SUM(zn_sed_fe(:,:))
286      if (lwp) write (numout,'(a,3f15.5)') 'Sediment Fe ', &
287         &        fq0, fq1, fq2
288      fq0 = MINVAL(zn_sed_si(:,:))
289      fq1 = MAXVAL(zn_sed_si(:,:))
290      fq2 = SUM(zn_sed_si(:,:))
291      if (lwp) write (numout,'(a,3f15.5)') 'Sediment Si ', &
292         &        fq0, fq1, fq2
293      fq0 = MINVAL(zn_sed_c(:,:))
294      fq1 = MAXVAL(zn_sed_c(:,:))
295      fq2 = SUM(zn_sed_c(:,:))
296      if (lwp) write (numout,'(a,3f15.5)') 'Sediment  C ', &
297         &        fq0, fq1, fq2
298      fq0 = MINVAL(zn_sed_ca(:,:))
299      fq1 = MAXVAL(zn_sed_ca(:,:))
300      fq2 = SUM(zn_sed_ca(:,:))
301      if (lwp) write (numout,'(a,3f15.5)') 'Sediment Ca ', &
302         &        fq0, fq1, fq2
303#endif
304
305      !
306      IF( kt == nitrst ) THEN
307          CALL trc_rst_stat            ! statistics
308          CALL iom_close( numrtw )     ! close the restart file (only at last time step)
309#if ! defined key_trdmxl_trc
310          lrst_trc = .FALSE.
311#endif
312          IF( lk_offline .AND. ln_rst_list ) THEN
313             nrst_lst = nrst_lst + 1
314             nitrst = nstocklist( nrst_lst )
315          ENDIF
316      ENDIF
317      !
318   END SUBROUTINE trc_rst_wri 
319
320
321   SUBROUTINE trc_rst_cal( kt, cdrw )
322      !!---------------------------------------------------------------------
323      !!                   ***  ROUTINE trc_rst_cal  ***
324      !!
325      !!  ** Purpose : Read or write calendar in restart file:
326      !!
327      !!  WRITE(READ) mode:
328      !!       kt        : number of time step since the begining of the experiment at the
329      !!                   end of the current(previous) run
330      !!       adatrj(0) : number of elapsed days since the begining of the experiment at the
331      !!                   end of the current(previous) run (REAL -> keep fractions of day)
332      !!       ndastp    : date at the end of the current(previous) run (coded as yyyymmdd integer)
333      !!
334      !!   According to namelist parameter nrstdt,
335      !!       nn_rsttr = 0  no control on the date (nittrc000 is  arbitrary).
336      !!       nn_rsttr = 1  we verify that nittrc000 is equal to the last
337      !!                   time step of previous run + 1.
338      !!       In both those options, the  exact duration of the experiment
339      !!       since the beginning (cumulated duration of all previous restart runs)
340      !!       is not stored in the restart and is assumed to be (nittrc000-1)*rdt.
341      !!       This is valid is the time step has remained constant.
342      !!
343      !!       nn_rsttr = 2  the duration of the experiment in days (adatrj)
344      !!                    has been stored in the restart file.
345      !!----------------------------------------------------------------------
346      INTEGER         , INTENT(in) ::   kt         ! ocean time-step
347      CHARACTER(len=*), INTENT(in) ::   cdrw       ! "READ"/"WRITE" flag
348      !
349      INTEGER  ::  jlibalt = jprstlib
350      LOGICAL  ::  llok
351      REAL(wp) ::  zkt, zrdttrc1
352      REAL(wp) ::  zndastp
353
354      ! Time domain : restart
355      ! ---------------------
356
357      IF( TRIM(cdrw) == 'READ' ) THEN
358
359         IF(lwp) WRITE(numout,*)
360         IF(lwp) WRITE(numout,*) 'trc_rst_cal : read the TOP restart file for calendar'
361         IF(lwp) WRITE(numout,*) '~~~~~~~~~~~~'
362
363         IF ( jprstlib == jprstdimg ) THEN
364           ! eventually read netcdf file (monobloc)  for restarting on different number of processors
365           ! if {cn_trcrst_in}.nc exists, then set jlibalt to jpnf90
366           INQUIRE( FILE = TRIM(cn_trcrst_indir)//'/'//TRIM(cn_trcrst_in)//'.nc', EXIST = llok )
367           IF ( llok ) THEN ; jlibalt = jpnf90  ; ELSE ; jlibalt = jprstlib ; ENDIF
368         ENDIF
369
370         IF( ln_rsttr ) THEN
371            CALL iom_open( TRIM(cn_trcrst_indir)//'/'//cn_trcrst_in, numrtr, kiolib = jlibalt )
372            CALL iom_get ( numrtr, 'kt', zkt )   ! last time-step of previous run
373
374            IF(lwp) THEN
375               WRITE(numout,*) ' *** Info read in restart : '
376               WRITE(numout,*) '   previous time-step                               : ', NINT( zkt )
377               WRITE(numout,*) ' *** restart option'
378               SELECT CASE ( nn_rsttr )
379               CASE ( 0 )   ;   WRITE(numout,*) ' nn_rsttr = 0 : no control of nittrc000'
380               CASE ( 1 )   ;   WRITE(numout,*) ' nn_rsttr = 1 : no control the date at nittrc000 (use ndate0 read in the namelist)'
381               CASE ( 2 )   ;   WRITE(numout,*) ' nn_rsttr = 2 : calendar parameters read in restart'
382               END SELECT
383               WRITE(numout,*)
384            ENDIF
385            ! Control of date
386            IF( nittrc000  - NINT( zkt ) /= nn_dttrc .AND.  nn_rsttr /= 0 )                                  &
387               &   CALL ctl_stop( ' ===>>>> : problem with nittrc000 for the restart',                 &
388               &                  ' verify the restart file or rerun with nn_rsttr = 0 (namelist)' )
389         ENDIF
390         !
391         IF( lk_offline ) THEN   
392            !                                          ! set the date in offline mode
393            IF( ln_rsttr .AND. nn_rsttr == 2 ) THEN
394               CALL iom_get( numrtr, 'ndastp', zndastp ) 
395               ndastp = NINT( zndastp )
396               CALL iom_get( numrtr, 'adatrj', adatrj  )
397             ELSE
398               ndastp = ndate0 - 1     ! ndate0 read in the namelist in dom_nam
399               adatrj = ( REAL( nittrc000-1, wp ) * rdttra(1) ) / rday
400               ! note this is wrong if time step has changed during run
401            ENDIF
402            !
403            IF(lwp) THEN
404              WRITE(numout,*) ' *** Info used values : '
405              WRITE(numout,*) '   date ndastp                                      : ', ndastp
406              WRITE(numout,*) '   number of elapsed days since the begining of run : ', adatrj
407              WRITE(numout,*)
408            ENDIF
409            !
410            IF( ln_rsttr )  THEN   ;    neuler = 1
411            ELSE                   ;    neuler = 0
412            ENDIF
413            !
414            CALL day_init          ! compute calendar
415            !
416         ENDIF
417         !
418      ELSEIF( TRIM(cdrw) == 'WRITE' ) THEN
419         !
420         IF(  kt == nitrst ) THEN
421            IF(lwp) WRITE(numout,*)
422            IF(lwp) WRITE(numout,*) 'trc_wri : write the TOP restart file (NetCDF) at it= ', kt, ' date= ', ndastp
423            IF(lwp) WRITE(numout,*) '~~~~~~~'
424         ENDIF
425         CALL iom_rstput( kt, nitrst, numrtw, 'kt'     , REAL( kt    , wp) )   ! time-step
426         CALL iom_rstput( kt, nitrst, numrtw, 'ndastp' , REAL( ndastp, wp) )   ! date
427         CALL iom_rstput( kt, nitrst, numrtw, 'adatrj' , adatrj            )   ! number of elapsed days since
428         !                                                                     ! the begining of the run [s]
429      ENDIF
430
431   END SUBROUTINE trc_rst_cal
432
433
434   SUBROUTINE trc_rst_stat
435      !!----------------------------------------------------------------------
436      !!                    ***  trc_rst_stat  ***
437      !!
438      !! ** purpose  :   Compute tracers statistics
439      !!----------------------------------------------------------------------
440      INTEGER  :: jk, jn
441      REAL(wp) :: ztraf, zmin, zmax, zmean, zdrift
442      REAL(wp), DIMENSION(jpi,jpj,jpk) :: zvol
443      !!----------------------------------------------------------------------
444
445      IF( lwp ) THEN
446         WRITE(numout,*) 
447         WRITE(numout,*) '           ----TRACER STAT----             '
448         WRITE(numout,*) 
449      ENDIF
450      !
451      DO jk = 1, jpk
452         zvol(:,:,jk) = e1e2t(:,:) * fse3t_a(:,:,jk) * tmask(:,:,jk)
453      END DO
454      !
455      DO jn = 1, jptra
456         ztraf = glob_sum( trn(:,:,:,jn) * zvol(:,:,:) )
457         zmin  = MINVAL( trn(:,:,:,jn), mask= ((tmask*SPREAD(tmask_i,DIM=3,NCOPIES=jpk).NE.0.)) )
458         zmax  = MAXVAL( trn(:,:,:,jn), mask= ((tmask*SPREAD(tmask_i,DIM=3,NCOPIES=jpk).NE.0.)) )
459         IF( lk_mpp ) THEN
460            CALL mpp_min( zmin )      ! min over the global domain
461            CALL mpp_max( zmax )      ! max over the global domain
462         END IF
463         zmean  = ztraf / areatot
464         zdrift = ( ( ztraf - trai(jn) ) / ( trai(jn) + 1.e-12 )  ) * 100._wp
465         IF(lwp) WRITE(numout,9000) jn, TRIM( ctrcnm(jn) ), zmean, zmin, zmax, zdrift
466      END DO
467      WRITE(numout,*) 
4689000  FORMAT(' tracer nb :',i2,'    name :',a10,'    mean :',e18.10,'    min :',e18.10, &
469      &      '    max :',e18.10,'    drift :',e18.10, ' %')
470      !
471   END SUBROUTINE trc_rst_stat
472
473#else
474   !!----------------------------------------------------------------------
475   !!  Dummy module :                                     No passive tracer
476   !!----------------------------------------------------------------------
477CONTAINS
478   SUBROUTINE trc_rst_read                      ! Empty routines
479   END SUBROUTINE trc_rst_read
480   SUBROUTINE trc_rst_wri( kt )
481      INTEGER, INTENT ( in ) :: kt
482      WRITE(*,*) 'trc_rst_wri: You should not have seen this print! error?', kt
483   END SUBROUTINE trc_rst_wri   
484#endif
485
486   !!----------------------------------------------------------------------
487   !! NEMO/TOP 3.3 , NEMO Consortium (2010)
488   !! $Id$
489   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
490   !!======================================================================
491END MODULE trcrst
Note: See TracBrowser for help on using the repository browser.