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/UKMO/dev_r5518_GO6_under_ice_relax_dr_hook/NEMOGCM/NEMO/TOP_SRC – NEMO

source: branches/UKMO/dev_r5518_GO6_under_ice_relax_dr_hook/NEMOGCM/NEMO/TOP_SRC/trcdia.F90 @ 11738

Last change on this file since 11738 was 11738, checked in by marc, 5 years ago

The Dr Hook changes from my perl code.

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