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.
trcdia.F90 in branches/2015/dev_r5003_MERCATOR6_CRS/NEMOGCM/NEMO/TOP_SRC – NEMO

source: branches/2015/dev_r5003_MERCATOR6_CRS/NEMOGCM/NEMO/TOP_SRC/trcdia.F90 @ 8894

Last change on this file since 8894 was 8894, checked in by cbricaud, 6 years ago

crs improvments

  • Property svn:keywords set to Id
File size: 19.2 KB
RevLine 
[268]1MODULE trcdia
[945]2   !!======================================================================
[268]3   !!                       *** MODULE trcdia ***
[945]4   !! TOP :   Output of passive tracers
5   !!======================================================================
[2528]6   !! History :   OPA  !  1995-01 (M. Levy)  Original code
[1011]7   !!              -   !  1998-01 (C. Levy) NETCDF format using ioipsl interface
8   !!              -   !  1999-01 (M.A. Foujols) adapted for passive tracer
9   !!              -   !  1999-09 (M.A. Foujols) split into three parts
[2528]10   !!   NEMO      1.0  !  2005-03 (O. Aumont, A. El Moussaoui) F90
[1011]11   !!                  !  2008-05 (C. Ethe re-organization)
[274]12   !!----------------------------------------------------------------------
[3294]13#if defined key_top 
[335]14   !!----------------------------------------------------------------------
[945]15   !!   'key_top'                                                TOP models
16   !!----------------------------------------------------------------------
[1011]17   !! trc_dia     : main routine of output passive tracer
18   !! trcdit_wr   : outputs of concentration fields
19   !! trcdii_wr   : outputs of additional 2D/3D diagnostics
20   !! trcdib_wr   : outputs of biological fields
[945]21   !!----------------------------------------------------------------------
[8894]22   USE trc_oce, ONLY : lk_offline,nn_dttrc ! offline flag
[1011]23   USE trc
[1836]24   USE par_trc
[1011]25   USE dianam    ! build name of file (routine)
[3294]26   USE ioipsl    ! I/O manager
27   USE iom       ! I/O manager
28   USE lib_mpp   ! MPP library
[268]29
30   IMPLICIT NONE
31   PRIVATE
32
[2715]33   PUBLIC   trc_dia        ! called by XXX module
[268]34
[1011]35   INTEGER  ::   nit5      !: id for tracer output file
36   INTEGER  ::   ndepit5   !: id for depth mesh
37   INTEGER  ::   nhorit5   !: id for horizontal mesh
38   INTEGER  ::   ndimt50   !: number of ocean points in index array
39   INTEGER  ::   ndimt51   !: number of ocean points in index array
[1836]40   REAL(wp) ::   zjulian   !: ????   not DOCTOR !
[2715]41   INTEGER , ALLOCATABLE, SAVE, DIMENSION (:) ::   ndext50   !: integer arrays for ocean 3D index
42   INTEGER , ALLOCATABLE, SAVE, DIMENSION (:) ::   ndext51   !: integer arrays for ocean surface index
[3294]43
[1011]44   INTEGER  ::   nitd      !: id for additional array output file
45   INTEGER  ::   ndepitd   !: id for depth mesh
46   INTEGER  ::   nhoritd   !: id for horizontal mesh
[3294]47
[1077]48   INTEGER  ::   nitb        !:         id.         for additional array output file
[1011]49   INTEGER  ::   ndepitb   !:  id for depth mesh
50   INTEGER  ::   nhoritb   !:  id for horizontal mesh
51
52   !! * Substitutions
53#  include "top_substitute.h90"
[945]54   !!----------------------------------------------------------------------
[2528]55   !! NEMO/TOP 3.3 , NEMO Consortium (2010)
[1152]56   !! $Id$
[2715]57   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
[945]58   !!----------------------------------------------------------------------
[268]59CONTAINS
60
[1457]61   SUBROUTINE trc_dia( kt ) 
[945]62      !!---------------------------------------------------------------------
63      !!                     ***  ROUTINE trc_dia  ***
[335]64      !!
[945]65      !! ** Purpose :   output passive tracers fields
66      !!---------------------------------------------------------------------
[3294]67      INTEGER, INTENT(in) ::   kt    ! ocean time-step
[2715]68      !
[3294]69      INTEGER             ::  ierr   ! local integer
[945]70      !!---------------------------------------------------------------------
[2528]71      !
[3294]72      IF( kt == nittrc000 )  THEN
73         ALLOCATE( ndext50(jpij*jpk), ndext51(jpij), STAT=ierr )
74         IF( ierr > 0 ) THEN
75            CALL ctl_stop( 'STOP', 'trc_diat: unable to allocate arrays' )  ;   RETURN
76         ENDIF
77      ENDIF
[945]78      !
[3294]79      IF( .NOT.lk_iomput ) THEN
80                          CALL trcdit_wr( kt )      ! outputs for tracer concentration
81         IF( ln_diatrc )  CALL trcdii_wr( kt )      ! outputs for additional arrays
82         IF( ln_diabio )  CALL trcdib_wr( kt )      ! outputs for biological trends
83      ENDIF
84      !
[335]85   END SUBROUTINE trc_dia
[268]86
[2528]87
[3294]88   SUBROUTINE trcdit_wr( kt )
[1011]89      !!----------------------------------------------------------------------
90      !!                     ***  ROUTINE trcdit_wr  ***
91      !!
92      !! ** Purpose :   Standard output of passive tracer : concentration fields
93      !!
[3294]94      !! ** Method  :   At the beginning of the first time step (nittrc000), define all
[1011]95      !!             the NETCDF files and fields for concentration of passive tracer
96      !!
97      !!        At each time step call histdef to compute the mean if necessary
98      !!        Each nwritetrc time step, output the instantaneous or mean fields
99      !!
100      !!----------------------------------------------------------------------
[2715]101      INTEGER, INTENT(in) ::   kt       ! ocean time-step
102      !
[1011]103      INTEGER ::   jn
104      LOGICAL ::   ll_print = .FALSE.
105      CHARACTER (len=40) :: clhstnam, clop
[1656]106      INTEGER ::   inum = 11             ! temporary logical unit
[1011]107      CHARACTER (len=20) :: cltra, cltrau
108      CHARACTER (len=80) :: cltral
109      REAL(wp) :: zsto, zout, zdt
[2528]110      INTEGER  :: iimi, iima, ijmi, ijma, ipk, it, itmod, iiter
[1011]111      !!----------------------------------------------------------------------
112
113      ! Initialisation
114      ! --------------
115
116      ! local variable for debugging
117      ll_print = .FALSE.                  ! change it to true for more control print
118      ll_print = ll_print .AND. lwp
119
120      ! Define frequency of output and means
121      zdt = rdt
[1312]122      IF( ln_mskland )   THEN   ;   clop = "only(x)"   ! put 1.e+20 on land (very expensive!!)
123      ELSE                      ;   clop = "x"         ! no use of the mask value (require less cpu time)
124      ENDIF
[1011]125# if defined key_diainstant
[2528]126      zsto = nn_writetrc * rdt
[1312]127      clop = "inst("//TRIM(clop)//")"
[1011]128# else
129      zsto = zdt
[1312]130      clop = "ave("//TRIM(clop)//")"
[1011]131# endif
[2528]132      zout = nn_writetrc * zdt
[1011]133
134      ! Define indices of the horizontal output zoom and vertical limit storage
135      iimi = 1      ;      iima = jpi
136      ijmi = 1      ;      ijma = jpj
137      ipk = jpk
138
139      ! define time axis
[3294]140      itmod = kt - nittrc000 + 1
[1353]141      it    = kt
[3294]142      iiter = ( nittrc000 - 1 ) / nn_dttrc
[1011]143
144      ! Define NETCDF files and fields at beginning of first time step
145      ! --------------------------------------------------------------
146
[3294]147      IF(ll_print)WRITE(numout,*)'trcdit_wr kt=',kt
[1011]148     
[3294]149      IF( kt == nittrc000 ) THEN
[1011]150
[3294]151         IF(lwp) THEN                   ! control print
152            WRITE(numout,*)
153            WRITE(numout,*) '    frequency of outputs for passive tracers nn_writetrc = ', nn_writetrc
154            DO jn = 1, jptra
155               IF( ln_trc_wri(jn) )  WRITE(numout,*) ' ouput tracer nb : ', jn, '    short name : ', ctrcnm(jn) 
156            END DO
157            WRITE(numout,*) ' '
158         ENDIF
159
[1011]160         ! Compute julian date from starting date of the run
[1836]161         CALL ymds2ju( nyear, nmonth, nday, rdt, zjulian )
162         zjulian = zjulian - adatrj   !   set calendar origin to the beginning of the experiment
[1011]163         IF(lwp)WRITE(numout,*)' ' 
[3294]164         IF(lwp)WRITE(numout,*)' Date 0 used :', nittrc000                         &
[1011]165            &                 ,' YEAR ', nyear, ' MONTH ', nmonth, ' DAY ', nday   &
[1836]166            &                 ,'Julian day : ', zjulian 
[1353]167 
[1011]168         IF(lwp) WRITE(numout,*) ' indexes of zoom = ', iimi, iima, ijmi, ijma,  &
169            &                    ' limit storage in depth = ', ipk
170
[2528]171         IF( lk_offline .AND. lwp ) THEN
172            CALL dia_nam( clhstnam, nn_writetrc,' ' )
[2421]173            CALL ctl_opn( inum, 'date.file', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', 1, numout, lwp, narea )
[1656]174            WRITE(inum,*) clhstnam
175            CLOSE(inum)
176         ENDIF
[1011]177
[1353]178         ! Define the NETCDF files for passive tracer concentration
[2528]179         CALL dia_nam( clhstnam, nn_writetrc, 'ptrc_T' )
[1011]180         IF(lwp)WRITE(numout,*)" Name of NETCDF file ", clhstnam
[1353]181
182         ! Horizontal grid : glamt and gphit
[1011]183         CALL histbeg( clhstnam, jpi, glamt, jpj, gphit,     &
184            &          iimi, iima-iimi+1, ijmi, ijma-ijmi+1,         & 
[2528]185            &          iiter, zjulian, zdt, nhorit5, nit5 , domain_id=nidom, snc4chunks=snc4set)
[1011]186
[1353]187         ! Vertical grid for tracer : gdept
[4292]188         CALL histvert( nit5, 'deptht', 'Vertical T levels', 'm', ipk, gdept_1d, ndepit5)
[1011]189
[1353]190         ! Index of ocean points in 3D and 2D (surface)
191         CALL wheneq( jpi*jpj*ipk, tmask, 1, 1., ndext50, ndimt50 )
192         CALL wheneq( jpi*jpj    , tmask, 1, 1., ndext51, ndimt51 )
[1011]193
[1353]194         ! Declare all the output fields as NETCDF variables
[1011]195         DO jn = 1, jptra
[3294]196            IF( ln_trc_wri(jn) ) THEN
[2715]197               cltra  = TRIM( ctrcnm(jn) )   ! short title for tracer
[3294]198               cltral = TRIM( ctrcln(jn) )   ! long title for tracer
[2715]199               cltrau = TRIM( ctrcun(jn) )   ! UNIT for tracer
[1011]200               CALL histdef( nit5, cltra, cltral, cltrau, jpi, jpj, nhorit5,  &
[1353]201                  &          ipk, 1, ipk,  ndepit5, 32, clop, zsto, zout ) 
[1011]202            ENDIF
203         END DO
204
205         ! end netcdf files header
[2528]206         CALL histend( nit5, snc4set )
[1011]207         IF(lwp) WRITE(numout,*)
208         IF(lwp) WRITE(numout,*) 'End of NetCDF Initialization in trcdit_wr'
209         IF( ll_print )   CALL FLUSH(numout )
210
211      ENDIF
212
213      ! Start writing the tracer concentrations
214      ! ---------------------------------------
215
[2528]216      IF( lwp .AND. MOD( itmod, nn_writetrc ) == 0 ) THEN
[1011]217         WRITE(numout,*) 'trcdit_wr : write NetCDF passive tracer concentrations at ', kt, 'time-step'
218         WRITE(numout,*) '~~~~~~~~~ '
219      ENDIF
220
221      DO jn = 1, jptra
[2715]222         cltra  = TRIM( ctrcnm(jn) )   ! short title for tracer
[3294]223         IF( ln_trc_wri(jn) ) CALL histwrite( nit5, cltra, it, trn(:,:,:,jn), ndimt50, ndext50 )
[1011]224      END DO
225
226      ! close the file
227      ! --------------
[3294]228      IF( kt == nitend )   CALL histclo( nit5 )
[1011]229      !
230   END SUBROUTINE trcdit_wr
231
[3294]232   SUBROUTINE trcdii_wr( kt )
[1011]233      !!----------------------------------------------------------------------
234      !!                     ***  ROUTINE trcdii_wr  ***
235      !!
236      !! ** Purpose :   output of passive tracer : additional 2D and 3D arrays
237      !!
[3294]238      !! ** Method  :   At the beginning of the first time step (nittrc000), define all
[1011]239      !!             the NETCDF files and fields for concentration of passive tracer
240      !!
241      !!        At each time step call histdef to compute the mean if necessary
[2567]242      !!        Each nn_writedia time step, output the instantaneous or mean fields
[1011]243      !!
244      !!----------------------------------------------------------------------
[2715]245      INTEGER, INTENT(in) ::   kt       ! ocean time-step
[1011]246      !!
247      LOGICAL ::   ll_print = .FALSE.
248      CHARACTER (len=40) ::   clhstnam, clop
249      CHARACTER (len=20) ::   cltra, cltrau
250      CHARACTER (len=80) ::   cltral
[1450]251      INTEGER  ::   jl
[2528]252      INTEGER  ::   iimi, iima, ijmi, ijma, ipk, it, itmod, iiter
[1011]253      REAL(wp) ::   zsto, zout, zdt
254      !!----------------------------------------------------------------------
255
256      ! Initialisation
257      ! --------------
[1450]258     
[1011]259      ! local variable for debugging
260      ll_print = .FALSE.
261      ll_print = ll_print .AND. lwp
262      !
263      ! Define frequency of output and means
264      zdt = rdt
[1316]265      IF( ln_mskland )   THEN   ;   clop = "only(x)"   ! put 1.e+20 on land (very expensive!!)
266      ELSE                      ;   clop = "x"         ! no use of the mask value (require less cpu time)
267      ENDIF
[1011]268#  if defined key_diainstant
[2528]269      zsto = nn_writedia * zdt
[1316]270      clop = "inst("//TRIM(clop)//")"
[1011]271#  else
[1353]272      zsto = zdt
[1316]273      clop = "ave("//TRIM(clop)//")"
[1011]274#  endif
[2528]275      zout = nn_writedia * zdt
[1011]276
277      ! Define indices of the horizontal output zoom and vertical limit storage
278      iimi = 1      ;      iima = jpi
279      ijmi = 1      ;      ijma = jpj
280      ipk = jpk
281
282      ! define time axis
[3294]283      itmod = kt - nittrc000 + 1
[1353]284      it    = kt
[3294]285      iiter = ( nittrc000 - 1 ) / nn_dttrc
[1011]286
287      ! 1. Define NETCDF files and fields at beginning of first time step
288      ! -----------------------------------------------------------------
289
[3294]290      IF( ll_print ) WRITE(numout,*) 'trcdii_wr kt=', kt
[1011]291
[3294]292      IF( kt == nittrc000 ) THEN
[1011]293
294         ! Define the NETCDF files for additional arrays : 2D or 3D
295
296         ! Define the T grid file for tracer auxiliary files
297
[2528]298         CALL dia_nam( clhstnam, nn_writedia, 'diad_T' )
[1011]299         IF(lwp) WRITE(numout,*) " Name of NETCDF file ", clhstnam
300
301         ! Define a netcdf FILE for 2d and 3d arrays
302
303         CALL histbeg( clhstnam, jpi, glamt, jpj, gphit,             &
304            &          iimi, iima-iimi+1, ijmi, ijma-ijmi+1,         &
[2528]305            &          iiter, zjulian, zdt, nhoritd, nitd , domain_id=nidom, snc4chunks=snc4set )
[1011]306
307         ! Vertical grid for 2d and 3d arrays
308
[4292]309         CALL histvert( nitd, 'deptht', 'Vertical T levels','m', ipk, gdept_1d, ndepitd)
[1011]310
311         ! Declare all the output fields as NETCDF variables
312
313         ! more 3D horizontal arrays
[1450]314         DO jl = 1, jpdia3d
[2715]315            cltra  = TRIM( ctrc3d(jl) )   ! short title for 3D diagnostic
316            cltral = TRIM( ctrc3l(jl) )  ! long title for 3D diagnostic
317            cltrau = TRIM( ctrc3u(jl) )  ! UNIT for 3D diagnostic
[1011]318            CALL histdef( nitd, cltra, cltral, cltrau, jpi, jpj, nhoritd,   &
319               &          ipk, 1, ipk,  ndepitd, 32, clop, zsto, zout )
320         END DO
321
322         ! more 2D horizontal arrays
[1450]323         DO jl = 1, jpdia2d
[2715]324            cltra  = TRIM( ctrc2d(jl) )   ! short title for 2D diagnostic
325            cltral = TRIM( ctrc2l(jl) )  ! long title for 2D diagnostic
326            cltrau = TRIM( ctrc2u(jl) )  ! UNIT for 2D diagnostic
[1011]327            CALL histdef( nitd, cltra, cltral, cltrau, jpi, jpj, nhoritd,  &
328               &          1, 1, 1,  -99, 32, clop, zsto, zout )
329         END DO
330
331         ! TODO: more 2D vertical sections arrays : I or J indice fixed
332
333         ! CLOSE netcdf Files
[2528]334         CALL histend( nitd, snc4set )
[1011]335
336         IF(lwp) WRITE(numout,*)
337         IF(lwp) WRITE(numout,*) 'End of NetCDF Initialization in trcdii_wr'
338         IF( ll_print )   CALL FLUSH(numout )
339         !
340      ENDIF
341
342      ! 2. Start writing data
343      ! ---------------------
344
[2528]345      IF( lwp .AND. MOD( itmod, nn_writedia ) == 0 ) THEN
[1011]346         WRITE(numout,*) 'trcdii_wr : write NetCDF additional arrays at ', kt, 'time-step'
347         WRITE(numout,*) '~~~~~~ '
348      ENDIF
349
350      ! more 3D horizontal arrays
[1450]351      DO jl = 1, jpdia3d
[2715]352         cltra  = TRIM( ctrc3d(jl) )   ! short title for 3D diagnostic
[1450]353         CALL histwrite( nitd, cltra, it, trc3d(:,:,:,jl), ndimt50 ,ndext50)
[1011]354      END DO
355
356      ! more 2D horizontal arrays
[1450]357      DO jl = 1, jpdia2d
[2715]358         cltra  = TRIM( ctrc2d(jl) )   ! short title for 2D diagnostic
[1450]359         CALL histwrite(nitd, cltra, it, trc2d(:,:,jl), ndimt51  ,ndext51)
[1011]360      END DO
361
362      ! Closing all files
363      ! -----------------
[3294]364      IF( kt == nitend )   CALL histclo(nitd)
[1011]365      !
[1450]366
[1011]367   END SUBROUTINE trcdii_wr
368
[3294]369   SUBROUTINE trcdib_wr( kt )
[1011]370      !!----------------------------------------------------------------------
371      !!                     ***  ROUTINE trcdib_wr  ***
372      !!
373      !! ** Purpose :   output of passive tracer : biological fields
374      !!
[3294]375      !! ** Method  :   At the beginning of the first time step (nittrc000), define all
[1011]376      !!             the NETCDF files and fields for concentration of passive tracer
377      !!
378      !!        At each time step call histdef to compute the mean if necessary
[2567]379      !!        Each nn_writebio time step, output the instantaneous or mean fields
[1011]380      !!
381      !!----------------------------------------------------------------------
382      INTEGER, INTENT( in ) ::   kt          ! ocean time-step
383      !!
384      LOGICAL ::   ll_print = .FALSE.
385      CHARACTER (len=40) ::   clhstnam, clop
386      CHARACTER (len=20) ::   cltra, cltrau
387      CHARACTER (len=80) ::   cltral
[1450]388      INTEGER  ::   ji, jj, jk, jl
[2528]389      INTEGER  ::   iimi, iima, ijmi, ijma, ipk, it, itmod, iiter
[1011]390      REAL(wp) ::   zsto, zout, zdt
391      !!----------------------------------------------------------------------
392
393      ! Initialisation
394      ! --------------
[1450]395     
[1011]396      ! local variable for debugging
397      ll_print = .FALSE.
398      ll_print = ll_print .AND. lwp
399
400      ! Define frequency of output and means
401      zdt = rdt
[1316]402      IF( ln_mskland )   THEN   ;   clop = "only(x)"   ! put 1.e+20 on land (very expensive!!)
403      ELSE                      ;   clop = "x"         ! no use of the mask value (require less cpu time)
404      ENDIF
[1011]405#        if defined key_diainstant
[2528]406      zsto = nn_writebio * zdt
[1316]407      clop = "inst("//TRIM(clop)//")"
[1011]408#        else
[1353]409      zsto = zdt
[1316]410      clop = "ave("//TRIM(clop)//")"
[1011]411#        endif
[2528]412      zout = nn_writebio * zdt
[1011]413
[1353]414      ! Define indices of the horizontal output zoom and vertical limit storage
[1011]415      iimi = 1      ;      iima = jpi
416      ijmi = 1      ;      ijma = jpj
417      ipk = jpk
418
419      ! define time axis
[3294]420      itmod = kt - nittrc000 + 1
[1353]421      it    = kt
[3294]422      iiter = ( nittrc000 - 1 ) / nn_dttrc
[1011]423
424      ! Define NETCDF files and fields at beginning of first time step
425      ! --------------------------------------------------------------
426
[3294]427      IF(ll_print) WRITE(numout,*)'trcdib_wr kt=',kt
[1011]428
[3294]429      IF( kt == nittrc000 ) THEN
[1011]430
431         ! Define the NETCDF files for biological trends
432
[2528]433         CALL dia_nam(clhstnam,nn_writebio,'biolog')
[1011]434         IF(lwp)WRITE(numout,*) " Name of NETCDF file for biological trends ", clhstnam
435         ! Horizontal grid : glamt and gphit
[1353]436         CALL histbeg( clhstnam, jpi, glamt, jpj, gphit,      &
[1011]437            &    iimi, iima-iimi+1, ijmi, ijma-ijmi+1,          &
[2528]438            &    iiter, zjulian, zdt, nhoritb, nitb , domain_id=nidom, snc4chunks=snc4set )
[1011]439         ! Vertical grid for biological trends
[4292]440         CALL histvert(nitb, 'deptht', 'Vertical T levels', 'm', ipk, gdept_1d, ndepitb)
[1011]441
442         ! Declare all the output fields as NETCDF variables
443         ! biological trends
[1450]444         DO jl = 1, jpdiabio
[2715]445            cltra  = TRIM( ctrbio(jl) )   ! short title for biological diagnostic
446            cltral = TRIM( ctrbil(jl) )  ! long title for biological diagnostic
447            cltrau = TRIM( ctrbiu(jl) )  ! UNIT for biological diagnostic
[1353]448            CALL histdef( nitb, cltra, cltral, cltrau, jpi, jpj, nhoritb,  &
[1011]449               &         ipk, 1, ipk,  ndepitb, 32, clop, zsto, zout)
450         END DO
451
452         ! CLOSE netcdf Files
[2528]453          CALL histend( nitb, snc4set )
[1011]454
455         IF(lwp) WRITE(numout,*)
456         IF(lwp) WRITE(numout,*) 'End of NetCDF Initialization in trcdib_wr'
457         IF(ll_print) CALL FLUSH(numout )
458         !
459      ENDIF
460
461      ! Start writing data
462      ! ------------------
463
464      ! biological trends
[2528]465      IF( lwp .AND. MOD( itmod, nn_writebio ) == 0 ) THEN
[1011]466         WRITE(numout,*) 'trcdit_wr : write NetCDF biological trends at ', kt, 'time-step'
467         WRITE(numout,*) '~~~~~~ '
468      ENDIF
469
[1450]470      DO jl = 1, jpdiabio
[2715]471         cltra  = TRIM( ctrbio(jl) )   ! short title for biological diagnostic
[1450]472         CALL histwrite(nitb, cltra, it, trbio(:,:,:,jl), ndimt50,ndext50)
[1011]473      END DO
474
475      ! Closing all files
476      ! -----------------
[3294]477      IF( kt == nitend )   CALL histclo( nitb )
[1011]478      !
479   END SUBROUTINE trcdib_wr
480
[335]481#else
[945]482   !!----------------------------------------------------------------------
483   !!  Dummy module :                                     No passive tracer
484   !!----------------------------------------------------------------------
[335]485CONTAINS
[1457]486   SUBROUTINE trc_dia( kt )                      ! Empty routine   
487      INTEGER, INTENT(in) :: kt
[335]488   END SUBROUTINE trc_dia   
489#endif
490
[945]491   !!======================================================================
[335]492END MODULE trcdia
Note: See TracBrowser for help on using the repository browser.