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/DEV_r2106_LOCEAN2010/NEMO/TOP_SRC – NEMO

source: branches/DEV_r2106_LOCEAN2010/NEMO/TOP_SRC/trcdia.F90 @ 3304

Last change on this file since 3304 was 2237, checked in by cetlod, 14 years ago

Update TOP routines

  • Property svn:eol-style set to native
  • Property svn:keywords set to Id
File size: 19.7 KB
RevLine 
[268]1MODULE trcdia
[945]2   !!======================================================================
[268]3   !!                       *** MODULE trcdia ***
[945]4   !! TOP :   Output of passive tracers
5   !!======================================================================
[2104]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
[2104]10   !!   NEMO      1.0  !  2005-03 (O. Aumont, A. El Moussaoui) F90
[1011]11   !!                  !  2008-05 (C. Ethe re-organization)
[274]12   !!----------------------------------------------------------------------
[1457]13#if defined key_top && ! defined key_iomput
[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   !!----------------------------------------------------------------------
[1715]22   USE dom_oce         ! ocean space and time domain variables
[1011]23   USE oce_trc
24   USE trc
[1970]25   USE par_trc
[1011]26   USE dianam    ! build name of file (routine)
27   USE in_out_manager  ! I/O manager
28   USE lib_mpp
29   USE ioipsl
[268]30
31   IMPLICIT NONE
32   PRIVATE
33
[2104]34   PUBLIC   trc_dia   ! called by XXX module
[268]35
[1011]36   INTEGER  ::   nit5      !: id for tracer output file
37   INTEGER  ::   ndepit5   !: id for depth mesh
38   INTEGER  ::   nhorit5   !: id for horizontal mesh
39   INTEGER  ::   ndimt50   !: number of ocean points in index array
40   INTEGER  ::   ndimt51   !: number of ocean points in index array
[1970]41   REAL(wp) ::   zjulian   !: ????   not DOCTOR !
[1011]42   INTEGER , DIMENSION (jpij*jpk) ::   ndext50   !: integer arrays for ocean 3D index
43   INTEGER , DIMENSION (jpij)     ::   ndext51   !: integer arrays for ocean surface index
[2038]44# if defined key_diatrc
[1011]45   INTEGER  ::   nitd      !: id for additional array output file
46   INTEGER  ::   ndepitd   !: id for depth mesh
47   INTEGER  ::   nhoritd   !: id for horizontal mesh
48# endif
[2038]49# if defined key_diabio
[1077]50   INTEGER  ::   nitb        !:         id.         for additional array output file
[1011]51   INTEGER  ::   ndepitb   !:  id for depth mesh
52   INTEGER  ::   nhoritb   !:  id for horizontal mesh
53# endif
54
55   !! * Substitutions
56#  include "top_substitute.h90"
[945]57   !!----------------------------------------------------------------------
[2104]58   !! NEMO/TOP 3.3 , LOCEAN-IPSL (2010)
[1152]59   !! $Id$
[2237]60   !! Software governed by the CeCILL licence  (NEMOGCM/License_CeCILL.txt)
[945]61   !!----------------------------------------------------------------------
[268]62CONTAINS
63
[1457]64   SUBROUTINE trc_dia( kt ) 
[945]65      !!---------------------------------------------------------------------
66      !!                     ***  ROUTINE trc_dia  ***
[335]67      !!
[945]68      !! ** Purpose :   output passive tracers fields
69      !!---------------------------------------------------------------------
[1457]70      INTEGER, INTENT( in ) :: kt
71      INTEGER               :: kindic
[945]72      !!---------------------------------------------------------------------
[2104]73      !
[945]74      CALL trcdit_wr( kt, kindic )      ! outputs for tracer concentration
75      CALL trcdii_wr( kt, kindic )      ! outputs for additional arrays
76      CALL trcdib_wr( kt, kindic )      ! outputs for biological trends
77      !
[335]78   END SUBROUTINE trc_dia
[268]79
[2104]80
[1011]81   SUBROUTINE trcdit_wr( kt, kindic )
82      !!----------------------------------------------------------------------
83      !!                     ***  ROUTINE trcdit_wr  ***
84      !!
85      !! ** Purpose :   Standard output of passive tracer : concentration fields
86      !!
87      !! ** Method  :   At the beginning of the first time step (nit000), define all
88      !!             the NETCDF files and fields for concentration of passive tracer
89      !!
90      !!        At each time step call histdef to compute the mean if necessary
91      !!        Each nwritetrc time step, output the instantaneous or mean fields
92      !!
93      !!        IF kindic <0, output of fields before the model interruption.
94      !!        IF kindic =0, time step loop
95      !!        IF kindic >0, output of fields before the time step loop
96      !!----------------------------------------------------------------------
97      INTEGER, INTENT( in ) ::   kt          ! ocean time-step
98      INTEGER, INTENT( in ) ::   kindic      ! indicator of abnormal termination
99      !!
100      INTEGER ::   jn
101      LOGICAL ::   ll_print = .FALSE.
102      CHARACTER (len=40) :: clhstnam, clop
[2038]103#if defined key_offline
[1656]104      INTEGER ::   inum = 11             ! temporary logical unit
105#endif
[1011]106      CHARACTER (len=20) :: cltra, cltrau
107      CHARACTER (len=80) :: cltral
108      REAL(wp) :: zsto, zout, zdt
[2104]109      INTEGER  :: iimi, iima, ijmi, ijma, ipk, it, itmod, iiter
[1011]110      !!----------------------------------------------------------------------
111
112      ! Initialisation
113      ! --------------
114
115      ! local variable for debugging
116      ll_print = .FALSE.                  ! change it to true for more control print
117      ll_print = ll_print .AND. lwp
118
119      ! Define frequency of output and means
120      zdt = rdt
[1312]121      IF( ln_mskland )   THEN   ;   clop = "only(x)"   ! put 1.e+20 on land (very expensive!!)
122      ELSE                      ;   clop = "x"         ! no use of the mask value (require less cpu time)
123      ENDIF
[1011]124# if defined key_diainstant
[2038]125      zsto = nn_writetrc * rdt
[1312]126      clop = "inst("//TRIM(clop)//")"
[1011]127# else
128      zsto = zdt
[1312]129      clop = "ave("//TRIM(clop)//")"
[1011]130# endif
[2038]131      zout = nn_writetrc * zdt
[1011]132
133      ! Define indices of the horizontal output zoom and vertical limit storage
134      iimi = 1      ;      iima = jpi
135      ijmi = 1      ;      ijma = jpj
136      ipk = jpk
137
138      ! define time axis
[2104]139      itmod = kt - nit000 + 1
[1353]140      it    = kt
[2104]141      iiter = ( nit000 - 1 ) / nn_dttrc
[1011]142
143      ! Define NETCDF files and fields at beginning of first time step
144      ! --------------------------------------------------------------
145
146      IF(ll_print)WRITE(numout,*)'trcdit_wr kt=',kt,' kindic ',kindic
147     
[2104]148      IF( kt == nit000 ) THEN
[1011]149
150         ! Compute julian date from starting date of the run
[1970]151         CALL ymds2ju( nyear, nmonth, nday, rdt, zjulian )
152         zjulian = zjulian - adatrj   !   set calendar origin to the beginning of the experiment
[1011]153         IF(lwp)WRITE(numout,*)' ' 
[2104]154         IF(lwp)WRITE(numout,*)' Date 0 used :', nit000                         &
[1011]155            &                 ,' YEAR ', nyear, ' MONTH ', nmonth, ' DAY ', nday   &
[1970]156            &                 ,'Julian day : ', zjulian 
[1353]157 
[1011]158         IF(lwp) WRITE(numout,*) ' indexes of zoom = ', iimi, iima, ijmi, ijma,  &
159            &                    ' limit storage in depth = ', ipk
160
[2038]161#if defined key_offline
[1656]162        ! WRITE root name in date.file for use by postpro
163         IF(lwp) THEN
[2038]164            CALL dia_nam( clhstnam, nn_writetrc,' ' )
[1970]165            CALL ctlopn( inum, 'date.file', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', 1, numout, lwp, narea )
[1656]166            WRITE(inum,*) clhstnam
167            CLOSE(inum)
168         ENDIF
169#endif
[1011]170
[1353]171         ! Define the NETCDF files for passive tracer concentration
[2038]172         CALL dia_nam( clhstnam, nn_writetrc, 'ptrc_T' )
[1011]173         IF(lwp)WRITE(numout,*)" Name of NETCDF file ", clhstnam
[1353]174
175         ! Horizontal grid : glamt and gphit
[1011]176         CALL histbeg( clhstnam, jpi, glamt, jpj, gphit,     &
177            &          iimi, iima-iimi+1, ijmi, ijma-ijmi+1,         & 
[2104]178            &          iiter, zjulian, zdt, nhorit5, nit5 , domain_id=nidom)
[1011]179
[1353]180         ! Vertical grid for tracer : gdept
181         CALL histvert( nit5, 'deptht', 'Vertical T levels', 'm', ipk, gdept_0, ndepit5)
[1011]182
[1353]183         ! Index of ocean points in 3D and 2D (surface)
184         CALL wheneq( jpi*jpj*ipk, tmask, 1, 1., ndext50, ndimt50 )
185         CALL wheneq( jpi*jpj    , tmask, 1, 1., ndext51, ndimt51 )
[1011]186
[1353]187         ! Declare all the output fields as NETCDF variables
[1011]188         DO jn = 1, jptra
189            IF( lutsav(jn) ) THEN
190               cltra  = ctrcnm(jn)   ! short title for tracer
191               cltral = ctrcnl(jn)   ! long title for tracer
192               cltrau = ctrcun(jn)   ! UNIT for tracer
193               CALL histdef( nit5, cltra, cltral, cltrau, jpi, jpj, nhorit5,  &
[1353]194                  &          ipk, 1, ipk,  ndepit5, 32, clop, zsto, zout ) 
[1011]195            ENDIF
196         END DO
197
198         ! end netcdf files header
199         CALL histend( nit5 )
200         IF(lwp) WRITE(numout,*)
201         IF(lwp) WRITE(numout,*) 'End of NetCDF Initialization in trcdit_wr'
202         IF( ll_print )   CALL FLUSH(numout )
203
204      ENDIF
205
206      ! Start writing the tracer concentrations
207      ! ---------------------------------------
208
[2038]209      IF( lwp .AND. MOD( itmod, nn_writetrc ) == 0 ) THEN
[1011]210         WRITE(numout,*) 'trcdit_wr : write NetCDF passive tracer concentrations at ', kt, 'time-step'
211         WRITE(numout,*) '~~~~~~~~~ '
212      ENDIF
213
214      DO jn = 1, jptra
[1450]215         cltra = ctrcnm(jn)      ! short title for tracer
216         IF( lutsav(jn) ) CALL histwrite( nit5, cltra, it, trn(:,:,:,jn), ndimt50, ndext50 )
[1011]217      END DO
218
219      ! close the file
220      ! --------------
221      IF( kt == nitend .OR. kindic < 0 )   CALL histclo( nit5 )
222      !
[1450]223
[1011]224   END SUBROUTINE trcdit_wr
225
[2038]226#if defined key_diatrc
[1011]227
228   SUBROUTINE trcdii_wr( kt, kindic )
229      !!----------------------------------------------------------------------
230      !!                     ***  ROUTINE trcdii_wr  ***
231      !!
232      !! ** Purpose :   output of passive tracer : additional 2D and 3D arrays
233      !!
234      !! ** Method  :   At the beginning of the first time step (nit000), define all
235      !!             the NETCDF files and fields for concentration of passive tracer
236      !!
237      !!        At each time step call histdef to compute the mean if necessary
[1391]238      !!        Each nwritedia time step, output the instantaneous or mean fields
[1011]239      !!
240      !!        IF kindic <0, output of fields before the model interruption.
241      !!        IF kindic =0, time step loop
242      !!        IF kindic >0, output of fields before the time step loop
243      !!----------------------------------------------------------------------
244      INTEGER, INTENT( in ) ::   kt          ! ocean time-step
245      INTEGER, INTENT( in ) ::   kindic      ! indicator of abnormal termination
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
[2104]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
[2038]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
[2038]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
[2104]283      itmod = kt - nit000 + 1
[1353]284      it    = kt
[2104]285      iiter = ( nit000 - 1 ) / nn_dttrc
[1011]286
287      ! 1. Define NETCDF files and fields at beginning of first time step
288      ! -----------------------------------------------------------------
289
290      IF( ll_print ) WRITE(numout,*) 'trcdii_wr kt=', kt, ' kindic ', kindic
291
[2104]292      IF( kt == nit000 ) 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
[2038]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,         &
[2104]305            &          iiter, zjulian, zdt, nhoritd, nitd , domain_id=nidom )
[1011]306
307         ! Vertical grid for 2d and 3d arrays
308
[1353]309         CALL histvert( nitd, 'deptht', 'Vertical T levels','m', ipk, gdept_0, ndepitd)
[1011]310
311         ! Declare all the output fields as NETCDF variables
312
313         ! more 3D horizontal arrays
[1450]314         DO jl = 1, jpdia3d
315            cltra  = ctrc3d(jl)   ! short title for 3D diagnostic
316            cltral = ctrc3l(jl)   ! long title for 3D diagnostic
317            cltrau = 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
324            cltra  = ctrc2d(jl)    ! short title for 2D diagnostic
325            cltral = ctrc2l(jl)   ! long title for 2D diagnostic
326            cltrau = 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
334         CALL histend( nitd )
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
[2038]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
352         cltra = ctrc3d(jl)   ! short title for 3D diagnostic
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
358         cltra = ctrc2d(jl)   ! short title for 2D diagnostic
359         CALL histwrite(nitd, cltra, it, trc2d(:,:,jl), ndimt51  ,ndext51)
[1011]360      END DO
361
362      ! Closing all files
363      ! -----------------
364      IF( kt == nitend .OR. kindic < 0 )   CALL histclo(nitd)
365      !
[1450]366
[1011]367   END SUBROUTINE trcdii_wr
368
369# else
370   SUBROUTINE trcdii_wr( kt, kindic )                      ! Dummy routine
371      INTEGER, INTENT ( in ) :: kt, kindic
372   END SUBROUTINE trcdii_wr
373# endif
374
[2038]375# if defined key_diabio
[1011]376
377   SUBROUTINE trcdib_wr( kt, kindic )
378      !!----------------------------------------------------------------------
379      !!                     ***  ROUTINE trcdib_wr  ***
380      !!
381      !! ** Purpose :   output of passive tracer : biological fields
382      !!
383      !! ** Method  :   At the beginning of the first time step (nit000), define all
384      !!             the NETCDF files and fields for concentration of passive tracer
385      !!
386      !!        At each time step call histdef to compute the mean if necessary
[1391]387      !!        Each nwritebio time step, output the instantaneous or mean fields
[1011]388      !!
389      !!        IF kindic <0, output of fields before the model interruption.
390      !!        IF kindic =0, time step loop
391      !!        IF kindic >0, output of fields before the time step loop
392      !!----------------------------------------------------------------------
393      INTEGER, INTENT( in ) ::   kt          ! ocean time-step
394      INTEGER, INTENT( in ) ::   kindic      ! indicator of abnormal termination
395      !!
396      LOGICAL ::   ll_print = .FALSE.
397      CHARACTER (len=40) ::   clhstnam, clop
398      CHARACTER (len=20) ::   cltra, cltrau
399      CHARACTER (len=80) ::   cltral
[1450]400      INTEGER  ::   ji, jj, jk, jl
[2104]401      INTEGER  ::   iimi, iima, ijmi, ijma, ipk, it, itmod, iiter
[1011]402      REAL(wp) ::   zsto, zout, zdt
403      !!----------------------------------------------------------------------
404
405      ! Initialisation
406      ! --------------
407
[1450]408     
[1011]409      ! local variable for debugging
410      ll_print = .FALSE.
411      ll_print = ll_print .AND. lwp
412
413      ! Define frequency of output and means
414      zdt = rdt
[1316]415      IF( ln_mskland )   THEN   ;   clop = "only(x)"   ! put 1.e+20 on land (very expensive!!)
416      ELSE                      ;   clop = "x"         ! no use of the mask value (require less cpu time)
417      ENDIF
[1011]418#        if defined key_diainstant
[2038]419      zsto = nn_writebio * zdt
[1316]420      clop = "inst("//TRIM(clop)//")"
[1011]421#        else
[1353]422      zsto = zdt
[1316]423      clop = "ave("//TRIM(clop)//")"
[1011]424#        endif
[2038]425      zout = nn_writebio * zdt
[1011]426
[1353]427      ! Define indices of the horizontal output zoom and vertical limit storage
[1011]428      iimi = 1      ;      iima = jpi
429      ijmi = 1      ;      ijma = jpj
430      ipk = jpk
431
432      ! define time axis
[2104]433      itmod = kt - nit000 + 1
[1353]434      it    = kt
[2104]435      iiter = ( nit000 - 1 ) / nn_dttrc
[1011]436
437      ! Define NETCDF files and fields at beginning of first time step
438      ! --------------------------------------------------------------
439
440      IF(ll_print) WRITE(numout,*)'trcdib_wr kt=',kt,' kindic ',kindic
441
[2104]442      IF( kt == nit000 ) THEN
[1011]443
444         ! Define the NETCDF files for biological trends
445
[2038]446         CALL dia_nam(clhstnam,nn_writebio,'biolog')
[1011]447         IF(lwp)WRITE(numout,*) " Name of NETCDF file for biological trends ", clhstnam
448         ! Horizontal grid : glamt and gphit
[1353]449         CALL histbeg( clhstnam, jpi, glamt, jpj, gphit,      &
[1011]450            &    iimi, iima-iimi+1, ijmi, ijma-ijmi+1,          &
[2104]451            &    iiter, zjulian, zdt, nhoritb, nitb , domain_id=nidom )
[1011]452         ! Vertical grid for biological trends
[1353]453         CALL histvert(nitb, 'deptht', 'Vertical T levels', 'm', ipk, gdept_0, ndepitb)
[1011]454
455         ! Declare all the output fields as NETCDF variables
456         ! biological trends
[1450]457         DO jl = 1, jpdiabio
458            cltra  = ctrbio(jl)   ! short title for biological diagnostic
459            cltral = ctrbil(jl)   ! long title for biological diagnostic
460            cltrau = ctrbiu(jl)   ! UNIT for biological diagnostic
[1353]461            CALL histdef( nitb, cltra, cltral, cltrau, jpi, jpj, nhoritb,  &
[1011]462               &         ipk, 1, ipk,  ndepitb, 32, clop, zsto, zout)
463         END DO
464
465         ! CLOSE netcdf Files
[1353]466          CALL histend( nitb )
[1011]467
468         IF(lwp) WRITE(numout,*)
469         IF(lwp) WRITE(numout,*) 'End of NetCDF Initialization in trcdib_wr'
470         IF(ll_print) CALL FLUSH(numout )
471         !
472      ENDIF
473
474      ! Start writing data
475      ! ------------------
476
477      ! biological trends
[2038]478      IF( lwp .AND. MOD( itmod, nn_writebio ) == 0 ) THEN
[1011]479         WRITE(numout,*) 'trcdit_wr : write NetCDF biological trends at ', kt, 'time-step'
480         WRITE(numout,*) '~~~~~~ '
481      ENDIF
482
[1450]483      DO jl = 1, jpdiabio
484         cltra = ctrbio(jl)  ! short title for biological diagnostic
485         CALL histwrite(nitb, cltra, it, trbio(:,:,:,jl), ndimt50,ndext50)
[1011]486      END DO
487
488      ! Closing all files
489      ! -----------------
490      IF( kt == nitend .OR. kindic < 0 )   CALL histclo( nitb )
491      !
[1450]492
[1011]493   END SUBROUTINE trcdib_wr
494
495# else
496
497   SUBROUTINE trcdib_wr( kt, kindic )                      ! Dummy routine
498      INTEGER, INTENT ( in ) ::   kt, kindic
499   END SUBROUTINE trcdib_wr
500
501# endif 
502
[335]503#else
[945]504   !!----------------------------------------------------------------------
505   !!  Dummy module :                                     No passive tracer
506   !!----------------------------------------------------------------------
[335]507CONTAINS
[1457]508   SUBROUTINE trc_dia( kt )                      ! Empty routine   
509      INTEGER, INTENT(in) :: kt
[335]510   END SUBROUTINE trc_dia   
511#endif
512
[945]513   !!======================================================================
[335]514END MODULE trcdia
Note: See TracBrowser for help on using the repository browser.