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 @ 6174

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

JPALM --28-12-2015-- cleaning2 - MEDUSA

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, zsec )
108            WRITE(clkt, '(i4.4,2i2.2)') iyear, imonth, iday
109         ELSE
110            ! beware of the format used to write kt (default is i8.8, that should be large enough)
111            IF( nitrst > 1.0e9 ) THEN   ;   WRITE(clkt,*       ) nitrst
112            ELSE                        ;   WRITE(clkt,'(i8.8)') nitrst
113            ENDIF
114         ENDIF
115         ! create the file
116         IF(lwp) WRITE(numout,*)
117         clname = TRIM(cexper)//"_"//TRIM(ADJUSTL(clkt))//"_"//TRIM(cn_trcrst_out)
118         clpath = TRIM(cn_trcrst_outdir)
119         IF( clpath(LEN_TRIM(clpath):) /= '/' ) clpath = TRIM(clpath) // '/'
120         IF(lwp) WRITE(numout,*) &
121             '             open trc restart.output NetCDF file: ',TRIM(clpath)//clname
122         CALL iom_open( TRIM(clpath)//TRIM(clname), numrtw, ldwrt = .TRUE., kiolib = jprstlib )
123         lrst_trc = .TRUE.
124      ENDIF
125      !
126   END SUBROUTINE trc_rst_opn
127
128   SUBROUTINE trc_rst_read
129      !!----------------------------------------------------------------------
130      !!                    ***  trc_rst_opn  ***
131      !!
132      !! ** purpose  :   read passive tracer fields in restart files
133      !!----------------------------------------------------------------------
134      INTEGER  ::  jn     
135      !! AXY (05/11/13): temporary variables
136      REAL(wp) ::    fq0,fq1,fq2
137
138      !!----------------------------------------------------------------------
139      !
140      IF(lwp) WRITE(numout,*)
141      IF(lwp) WRITE(numout,*) 'trc_rst_read : read data in the TOP restart file'
142      IF(lwp) WRITE(numout,*) '~~~~~~~~~~~~'
143
144      ! READ prognostic variables and computes diagnostic variable
145      DO jn = 1, jptra
146         CALL iom_get( numrtr, jpdom_autoglo, 'TRN'//ctrcnm(jn), trn(:,:,:,jn) )
147      END DO
148
149      DO jn = 1, jptra
150         CALL iom_get( numrtr, jpdom_autoglo, 'TRB'//ctrcnm(jn), trb(:,:,:,jn) )
151      END DO
152
153      !! AXY (09/06/14): the ARCHER version of MEDUSA-2 does not include an equivalent
154      !!                 call to MEDUSA-2 at this point; this suggests that the FCM
155      !!                 version of NEMO date significantly earlier than the current
156      !!                 version
157
158#if defined key_medusa
159      !! AXY (13/01/12): check if the restart contains sediment fields;
160      !!                 this is only relevant for simulations that include
161      !!                 biogeochemistry and are restarted from earlier runs
162      !!                 in which there was no sediment component
163      !!
164      IF( iom_varid( numrtr, 'B_SED_N', ldstop = .FALSE. ) > 0 ) THEN
165         !! YES; in which case read them
166         !!
167         IF(lwp) WRITE(numout,*) ' MEDUSA sediment fields present - reading in ...'
168         CALL iom_get( numrtr, jpdom_autoglo, 'B_SED_N',  zb_sed_n(:,:)  )
169         CALL iom_get( numrtr, jpdom_autoglo, 'N_SED_N',  zn_sed_n(:,:)  )
170         CALL iom_get( numrtr, jpdom_autoglo, 'B_SED_FE', zb_sed_fe(:,:) )
171         CALL iom_get( numrtr, jpdom_autoglo, 'N_SED_FE', zn_sed_fe(:,:) )
172         CALL iom_get( numrtr, jpdom_autoglo, 'B_SED_SI', zb_sed_si(:,:) )
173         CALL iom_get( numrtr, jpdom_autoglo, 'N_SED_SI', zn_sed_si(:,:) )
174         CALL iom_get( numrtr, jpdom_autoglo, 'B_SED_C',  zb_sed_c(:,:)  )
175         CALL iom_get( numrtr, jpdom_autoglo, 'N_SED_C',  zn_sed_c(:,:)  )
176         CALL iom_get( numrtr, jpdom_autoglo, 'B_SED_CA', zb_sed_ca(:,:) )
177         CALL iom_get( numrtr, jpdom_autoglo, 'N_SED_CA', zn_sed_ca(:,:) )
178      ELSE
179         !! NO; in which case set them to zero
180         !!
181         IF(lwp) WRITE(numout,*) ' MEDUSA sediment fields absent - setting to zero ...'
182         zb_sed_n(:,:)  = 0.0   !! organic N
183         zn_sed_n(:,:)  = 0.0
184         zb_sed_fe(:,:) = 0.0   !! organic Fe
185         zn_sed_fe(:,:) = 0.0
186         zb_sed_si(:,:) = 0.0   !! inorganic Si
187         zn_sed_si(:,:) = 0.0
188         zb_sed_c(:,:)  = 0.0   !! organic C
189         zn_sed_c(:,:)  = 0.0
190         zb_sed_ca(:,:) = 0.0   !! inorganic C
191         zn_sed_ca(:,:) = 0.0
192      ENDIF
193      !!
194      !! calculate stats on these fields
195      IF(lwp) WRITE(numout,*) ' MEDUSA sediment field stats (min, max, sum) ...'
196      fq0 = MINVAL(zn_sed_n(:,:))
197      fq1 = MAXVAL(zn_sed_n(:,:))
198      fq2 = SUM(zn_sed_n(:,:))
199      if (lwp) write (numout,'(a,3f15.5)') 'Sediment  N ', &
200         &        fq0, fq1, fq2
201      fq0 = MINVAL(zn_sed_fe(:,:))
202      fq1 = MAXVAL(zn_sed_fe(:,:))
203      fq2 = SUM(zn_sed_fe(:,:))
204      if (lwp) write (numout,'(a,3f15.5)') 'Sediment Fe ', &
205         &        fq0, fq1, fq2
206      fq0 = MINVAL(zn_sed_si(:,:))
207      fq1 = MAXVAL(zn_sed_si(:,:))
208      fq2 = SUM(zn_sed_si(:,:))
209      if (lwp) write (numout,'(a,3f15.5)') 'Sediment Si ', &
210         &        fq0, fq1, fq2
211      fq0 = MINVAL(zn_sed_c(:,:))
212      fq1 = MAXVAL(zn_sed_c(:,:))
213      fq2 = SUM(zn_sed_c(:,:))
214      if (lwp) write (numout,'(a,3f15.5)') 'Sediment  C ', &
215         &        fq0, fq1, fq2
216      fq0 = MINVAL(zn_sed_ca(:,:))
217      fq1 = MAXVAL(zn_sed_ca(:,:))
218      fq2 = SUM(zn_sed_ca(:,:))
219      if (lwp) write (numout,'(a,3f15.5)') 'Sediment Ca ', &
220         &        fq0, fq1, fq2
221#endif
222 
223      !
224   END SUBROUTINE trc_rst_read
225
226   SUBROUTINE trc_rst_wri( kt )
227      !!----------------------------------------------------------------------
228      !!                    ***  trc_rst_wri  ***
229      !!
230      !! ** purpose  :   write passive tracer fields in restart files
231      !!----------------------------------------------------------------------
232      INTEGER, INTENT( in ) ::   kt    ! ocean time-step index
233      !!
234      INTEGER  :: jn
235      REAL(wp) :: zarak0
236      !! AXY (05/11/13): temporary variables
237      REAL(wp) ::    fq0,fq1,fq2
238      !!----------------------------------------------------------------------
239      !
240      CALL iom_rstput( kt, nitrst, numrtw, 'rdttrc1', rdttrc(1) )   ! surface passive tracer time step
241      ! prognostic variables
242      ! --------------------
243      DO jn = 1, jptra
244         CALL iom_rstput( kt, nitrst, numrtw, 'TRN'//ctrcnm(jn), trn(:,:,:,jn) )
245      END DO
246
247      DO jn = 1, jptra
248         CALL iom_rstput( kt, nitrst, numrtw, 'TRB'//ctrcnm(jn), trb(:,:,:,jn) )
249      END DO
250
251      !! AXY (09/06/14): the ARCHER version of MEDUSA-2 does not include an equivalent
252      !!                 call to MEDUSA-2 at this point; this suggests that the FCM
253      !!                 version of NEMO date significantly earlier than the current
254      !!                 version
255
256#if defined key_medusa
257      !! AXY (13/01/12): write out "before" and "now" state of seafloor
258      !!                 sediment pools into restart; this happens
259      !!                 whether or not the pools are to be used by
260      !!                 MEDUSA (which is controlled by a switch in the
261      !!                 namelist_top file)
262      !!
263      IF(lwp) WRITE(numout,*) ' MEDUSA sediment fields - writing out ...'
264      CALL iom_rstput( kt, nitrst, numrtw, 'B_SED_N',  zb_sed_n(:,:)  )
265      CALL iom_rstput( kt, nitrst, numrtw, 'N_SED_N',  zn_sed_n(:,:)  )
266      CALL iom_rstput( kt, nitrst, numrtw, 'B_SED_FE', zb_sed_fe(:,:) )
267      CALL iom_rstput( kt, nitrst, numrtw, 'N_SED_FE', zn_sed_fe(:,:) )
268      CALL iom_rstput( kt, nitrst, numrtw, 'B_SED_SI', zb_sed_si(:,:) )
269      CALL iom_rstput( kt, nitrst, numrtw, 'N_SED_SI', zn_sed_si(:,:) )
270      CALL iom_rstput( kt, nitrst, numrtw, 'B_SED_C',  zb_sed_c(:,:)  )
271      CALL iom_rstput( kt, nitrst, numrtw, 'N_SED_C',  zn_sed_c(:,:)  )
272      CALL iom_rstput( kt, nitrst, numrtw, 'B_SED_CA', zb_sed_ca(:,:) )
273      CALL iom_rstput( kt, nitrst, numrtw, 'N_SED_CA', zn_sed_ca(:,:) )
274      !!
275      !! calculate stats on these fields
276      IF(lwp) WRITE(numout,*) ' MEDUSA sediment field stats (min, max, sum) ...'
277      fq0 = MINVAL(zn_sed_n(:,:))
278      fq1 = MAXVAL(zn_sed_n(:,:))
279      fq2 = SUM(zn_sed_n(:,:))
280      if (lwp) write (numout,'(a,3f15.5)') 'Sediment  N ', &
281         &        fq0, fq1, fq2
282      fq0 = MINVAL(zn_sed_fe(:,:))
283      fq1 = MAXVAL(zn_sed_fe(:,:))
284      fq2 = SUM(zn_sed_fe(:,:))
285      if (lwp) write (numout,'(a,3f15.5)') 'Sediment Fe ', &
286         &        fq0, fq1, fq2
287      fq0 = MINVAL(zn_sed_si(:,:))
288      fq1 = MAXVAL(zn_sed_si(:,:))
289      fq2 = SUM(zn_sed_si(:,:))
290      if (lwp) write (numout,'(a,3f15.5)') 'Sediment Si ', &
291         &        fq0, fq1, fq2
292      fq0 = MINVAL(zn_sed_c(:,:))
293      fq1 = MAXVAL(zn_sed_c(:,:))
294      fq2 = SUM(zn_sed_c(:,:))
295      if (lwp) write (numout,'(a,3f15.5)') 'Sediment  C ', &
296         &        fq0, fq1, fq2
297      fq0 = MINVAL(zn_sed_ca(:,:))
298      fq1 = MAXVAL(zn_sed_ca(:,:))
299      fq2 = SUM(zn_sed_ca(:,:))
300      if (lwp) write (numout,'(a,3f15.5)') 'Sediment Ca ', &
301         &        fq0, fq1, fq2
302#endif
303
304      !
305      IF( kt == nitrst ) THEN
306          CALL trc_rst_stat            ! statistics
307          CALL iom_close( numrtw )     ! close the restart file (only at last time step)
308#if ! defined key_trdmxl_trc
309          lrst_trc = .FALSE.
310#endif
311          IF( lk_offline .AND. ln_rst_list ) THEN
312             nrst_lst = nrst_lst + 1
313             nitrst = nstocklist( nrst_lst )
314          ENDIF
315      ENDIF
316      !
317   END SUBROUTINE trc_rst_wri 
318
319
320   SUBROUTINE trc_rst_cal( kt, cdrw )
321      !!---------------------------------------------------------------------
322      !!                   ***  ROUTINE trc_rst_cal  ***
323      !!
324      !!  ** Purpose : Read or write calendar in restart file:
325      !!
326      !!  WRITE(READ) mode:
327      !!       kt        : number of time step since the begining of the experiment at the
328      !!                   end of the current(previous) run
329      !!       adatrj(0) : number of elapsed days since the begining of the experiment at the
330      !!                   end of the current(previous) run (REAL -> keep fractions of day)
331      !!       ndastp    : date at the end of the current(previous) run (coded as yyyymmdd integer)
332      !!
333      !!   According to namelist parameter nrstdt,
334      !!       nn_rsttr = 0  no control on the date (nittrc000 is  arbitrary).
335      !!       nn_rsttr = 1  we verify that nittrc000 is equal to the last
336      !!                   time step of previous run + 1.
337      !!       In both those options, the  exact duration of the experiment
338      !!       since the beginning (cumulated duration of all previous restart runs)
339      !!       is not stored in the restart and is assumed to be (nittrc000-1)*rdt.
340      !!       This is valid is the time step has remained constant.
341      !!
342      !!       nn_rsttr = 2  the duration of the experiment in days (adatrj)
343      !!                    has been stored in the restart file.
344      !!----------------------------------------------------------------------
345      INTEGER         , INTENT(in) ::   kt         ! ocean time-step
346      CHARACTER(len=*), INTENT(in) ::   cdrw       ! "READ"/"WRITE" flag
347      !
348      INTEGER  ::  jlibalt = jprstlib
349      LOGICAL  ::  llok
350      REAL(wp) ::  zkt, zrdttrc1
351      REAL(wp) ::  zndastp
352
353      ! Time domain : restart
354      ! ---------------------
355
356      IF( TRIM(cdrw) == 'READ' ) THEN
357
358         IF(lwp) WRITE(numout,*)
359         IF(lwp) WRITE(numout,*) 'trc_rst_cal : read the TOP restart file for calendar'
360         IF(lwp) WRITE(numout,*) '~~~~~~~~~~~~'
361
362         IF ( jprstlib == jprstdimg ) THEN
363           ! eventually read netcdf file (monobloc)  for restarting on different number of processors
364           ! if {cn_trcrst_in}.nc exists, then set jlibalt to jpnf90
365           INQUIRE( FILE = TRIM(cn_trcrst_indir)//'/'//TRIM(cn_trcrst_in)//'.nc', EXIST = llok )
366           IF ( llok ) THEN ; jlibalt = jpnf90  ; ELSE ; jlibalt = jprstlib ; ENDIF
367         ENDIF
368
369         IF( ln_rsttr ) THEN
370            CALL iom_open( TRIM(cn_trcrst_indir)//'/'//cn_trcrst_in, numrtr, kiolib = jlibalt )
371            CALL iom_get ( numrtr, 'kt', zkt )   ! last time-step of previous run
372
373            IF(lwp) THEN
374               WRITE(numout,*) ' *** Info read in restart : '
375               WRITE(numout,*) '   previous time-step                               : ', NINT( zkt )
376               WRITE(numout,*) ' *** restart option'
377               SELECT CASE ( nn_rsttr )
378               CASE ( 0 )   ;   WRITE(numout,*) ' nn_rsttr = 0 : no control of nittrc000'
379               CASE ( 1 )   ;   WRITE(numout,*) ' nn_rsttr = 1 : no control the date at nittrc000 (use ndate0 read in the namelist)'
380               CASE ( 2 )   ;   WRITE(numout,*) ' nn_rsttr = 2 : calendar parameters read in restart'
381               END SELECT
382               WRITE(numout,*)
383            ENDIF
384            ! Control of date
385            IF( nittrc000  - NINT( zkt ) /= nn_dttrc .AND.  nn_rsttr /= 0 )                                  &
386               &   CALL ctl_stop( ' ===>>>> : problem with nittrc000 for the restart',                 &
387               &                  ' verify the restart file or rerun with nn_rsttr = 0 (namelist)' )
388         ENDIF
389         !
390         IF( lk_offline ) THEN   
391            !                                          ! set the date in offline mode
392            IF( ln_rsttr .AND. nn_rsttr == 2 ) THEN
393               CALL iom_get( numrtr, 'ndastp', zndastp ) 
394               ndastp = NINT( zndastp )
395               CALL iom_get( numrtr, 'adatrj', adatrj  )
396             ELSE
397               ndastp = ndate0 - 1     ! ndate0 read in the namelist in dom_nam
398               adatrj = ( REAL( nittrc000-1, wp ) * rdttra(1) ) / rday
399               ! note this is wrong if time step has changed during run
400            ENDIF
401            !
402            IF(lwp) THEN
403              WRITE(numout,*) ' *** Info used values : '
404              WRITE(numout,*) '   date ndastp                                      : ', ndastp
405              WRITE(numout,*) '   number of elapsed days since the begining of run : ', adatrj
406              WRITE(numout,*)
407            ENDIF
408            !
409            IF( ln_rsttr )  THEN   ;    neuler = 1
410            ELSE                   ;    neuler = 0
411            ENDIF
412            !
413            CALL day_init          ! compute calendar
414            !
415         ENDIF
416         !
417      ELSEIF( TRIM(cdrw) == 'WRITE' ) THEN
418         !
419         IF(  kt == nitrst ) THEN
420            IF(lwp) WRITE(numout,*)
421            IF(lwp) WRITE(numout,*) 'trc_wri : write the TOP restart file (NetCDF) at it= ', kt, ' date= ', ndastp
422            IF(lwp) WRITE(numout,*) '~~~~~~~'
423         ENDIF
424         CALL iom_rstput( kt, nitrst, numrtw, 'kt'     , REAL( kt    , wp) )   ! time-step
425         CALL iom_rstput( kt, nitrst, numrtw, 'ndastp' , REAL( ndastp, wp) )   ! date
426         CALL iom_rstput( kt, nitrst, numrtw, 'adatrj' , adatrj            )   ! number of elapsed days since
427         !                                                                     ! the begining of the run [s]
428      ENDIF
429
430   END SUBROUTINE trc_rst_cal
431
432
433   SUBROUTINE trc_rst_stat
434      !!----------------------------------------------------------------------
435      !!                    ***  trc_rst_stat  ***
436      !!
437      !! ** purpose  :   Compute tracers statistics
438      !!----------------------------------------------------------------------
439      INTEGER  :: jk, jn
440      REAL(wp) :: ztraf, zmin, zmax, zmean, zdrift
441      REAL(wp), DIMENSION(jpi,jpj,jpk) :: zvol
442      !!----------------------------------------------------------------------
443
444      IF( lwp ) THEN
445         WRITE(numout,*) 
446         WRITE(numout,*) '           ----TRACER STAT----             '
447         WRITE(numout,*) 
448      ENDIF
449      !
450      DO jk = 1, jpk
451         zvol(:,:,jk) = e1e2t(:,:) * fse3t_a(:,:,jk) * tmask(:,:,jk)
452      END DO
453      !
454      DO jn = 1, jptra
455         ztraf = glob_sum( trn(:,:,:,jn) * zvol(:,:,:) )
456         zmin  = MINVAL( trn(:,:,:,jn), mask= ((tmask*SPREAD(tmask_i,DIM=3,NCOPIES=jpk).NE.0.)) )
457         zmax  = MAXVAL( trn(:,:,:,jn), mask= ((tmask*SPREAD(tmask_i,DIM=3,NCOPIES=jpk).NE.0.)) )
458         IF( lk_mpp ) THEN
459            CALL mpp_min( zmin )      ! min over the global domain
460            CALL mpp_max( zmax )      ! max over the global domain
461         END IF
462         zmean  = ztraf / areatot
463         zdrift = ( ( ztraf - trai(jn) ) / ( trai(jn) + 1.e-12 )  ) * 100._wp
464         IF(lwp) WRITE(numout,9000) jn, TRIM( ctrcnm(jn) ), zmean, zmin, zmax, zdrift
465      END DO
466      WRITE(numout,*) 
4679000  FORMAT(' tracer nb :',i2,'    name :',a10,'    mean :',e18.10,'    min :',e18.10, &
468      &      '    max :',e18.10,'    drift :',e18.10, ' %')
469      !
470   END SUBROUTINE trc_rst_stat
471
472#else
473   !!----------------------------------------------------------------------
474   !!  Dummy module :                                     No passive tracer
475   !!----------------------------------------------------------------------
476CONTAINS
477   SUBROUTINE trc_rst_read                      ! Empty routines
478   END SUBROUTINE trc_rst_read
479   SUBROUTINE trc_rst_wri( kt )
480      INTEGER, INTENT ( in ) :: kt
481      WRITE(*,*) 'trc_rst_wri: You should not have seen this print! error?', kt
482   END SUBROUTINE trc_rst_wri   
483#endif
484
485   !!----------------------------------------------------------------------
486   !! NEMO/TOP 3.3 , NEMO Consortium (2010)
487   !! $Id$
488   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
489   !!======================================================================
490END MODULE trcrst
Note: See TracBrowser for help on using the repository browser.