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

source: trunk/NEMOGCM/NEMO/TOP_SRC/trcdia.F90 @ 7018

Last change on this file since 7018 was 6140, checked in by timgraham, 8 years ago

Merge of branches/2015/dev_merge_2015 back into trunk. Merge excludes NEMOGCM/TOOLS/OBSTOOLS/ for now due to issues with the change of file type. Will sort these manually with further commits.

Branch merged as follows:
In the working copy of branch ran:
svn merge svn+ssh://forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/trunk@HEAD
Small conflicts due to bug fixes applied to trunk since the dev_merge_2015 was copied. Bug fixes were applied to the branch as well so these were easy to resolve.
Branch committed at this stage

In working copy run:
svn switch svn+ssh://forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/trunk
to switch working copy

Run:
svn merge --reintegrate svn+ssh://forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/branches/2015/dev_merge_2015
to merge the branch into the trunk and then commit - no conflicts at this stage.

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