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

Last change on this file since 5726 was 5726, checked in by jpalmier, 9 years ago

JPALM -- 10-09-2015 -- add MEDUSA in the branch ; adapted TOP_SRC to MEDUSA ; remove some svn keywords in the branch

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