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

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

JPALM --09-12-2015 -- debugg

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