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

source: trunk/NEMO/TOP_SRC/trcdia.F90 @ 1737

Last change on this file since 1737 was 1715, checked in by smasson, 15 years ago

move daymod public variables in dom_oce, see ticket:590

  • Property svn:eol-style set to native
  • Property svn:keywords set to Id
File size: 30.1 KB
RevLine 
[268]1MODULE trcdia
[945]2   !!======================================================================
[268]3   !!                       *** MODULE trcdia ***
[945]4   !! TOP :   Output of passive tracers
5   !!======================================================================
[1011]6   !! History :    -   !  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   !!             1.0  !  2005-03 (O. Aumont, A. El Moussaoui) F90
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   !! trcdid_wr   : outputs of dvection-diffusion trends
20   !! trcdii_wr   : outputs of additional 2D/3D diagnostics
21   !! trcdib_wr   : outputs of biological fields
[945]22   !!----------------------------------------------------------------------
[1715]23   USE dom_oce         ! ocean space and time domain variables
[1011]24   USE oce_trc
25   USE trc
[1119]26   USE trp_trc
[1189]27   USE trdmld_trc_oce, ONLY : luttrd
[1011]28   USE dianam    ! build name of file (routine)
29   USE in_out_manager  ! I/O manager
30   USE lib_mpp
31   USE ioipsl
[268]32
33   IMPLICIT NONE
34   PRIVATE
35
[1011]36   PUBLIC trc_dia     
[268]37
[1011]38   INTEGER  ::   nit5      !: id for tracer output file
39   INTEGER  ::   ndepit5   !: id for depth mesh
40   INTEGER  ::   nhorit5   !: id for horizontal mesh
41   INTEGER  ::   ndimt50   !: number of ocean points in index array
42   INTEGER  ::   ndimt51   !: number of ocean points in index array
[1329]43   REAL(wp) ::   xjulian   !: ????   not DOCTOR !
[1011]44   INTEGER , DIMENSION (jpij*jpk) ::   ndext50   !: integer arrays for ocean 3D index
45   INTEGER , DIMENSION (jpij)     ::   ndext51   !: integer arrays for ocean surface index
46# if defined key_trc_diaadd
47   INTEGER  ::   nitd      !: id for additional array output file
48   INTEGER  ::   ndepitd   !: id for depth mesh
49   INTEGER  ::   nhoritd   !: id for horizontal mesh
50# endif
51# if defined key_trc_diatrd
52   INTEGER , DIMENSION (jptra) ::   nit6      !: id for additional array output file
53   INTEGER , DIMENSION (jptra) ::   ndepit6   !: id for depth mesh
54   INTEGER , DIMENSION (jptra) ::   nhorit6   !: id for horizontal mesh
55# endif
56# if defined key_trc_diabio
[1077]57   INTEGER  ::   nitb        !:         id.         for additional array output file
[1011]58   INTEGER  ::   ndepitb   !:  id for depth mesh
59   INTEGER  ::   nhoritb   !:  id for horizontal mesh
60# endif
61
62   !! * Substitutions
63#  include "top_substitute.h90"
[945]64   !!----------------------------------------------------------------------
65   !! NEMO/TOP 1.0 , LOCEAN-IPSL (2005)
[1152]66   !! $Id$
[945]67   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
68   !!----------------------------------------------------------------------
[268]69
70CONTAINS
71
[1457]72   SUBROUTINE trc_dia( kt ) 
[945]73      !!---------------------------------------------------------------------
74      !!                     ***  ROUTINE trc_dia  ***
[335]75      !!
[945]76      !! ** Purpose :   output passive tracers fields
77      !!---------------------------------------------------------------------
[1457]78      INTEGER, INTENT( in ) :: kt
79      INTEGER               :: kindic
[945]80      !!---------------------------------------------------------------------
81     
82      CALL trcdit_wr( kt, kindic )      ! outputs for tracer concentration
83      CALL trcdid_wr( kt, kindic )      ! outputs for dynamical trends
84      CALL trcdii_wr( kt, kindic )      ! outputs for additional arrays
85      CALL trcdib_wr( kt, kindic )      ! outputs for biological trends
[1011]86
[945]87      !
[335]88   END SUBROUTINE trc_dia
[268]89
[1011]90   SUBROUTINE trcdit_wr( kt, kindic )
91      !!----------------------------------------------------------------------
92      !!                     ***  ROUTINE trcdit_wr  ***
93      !!
94      !! ** Purpose :   Standard output of passive tracer : concentration fields
95      !!
96      !! ** Method  :   At the beginning of the first time step (nit000), define all
97      !!             the NETCDF files and fields for concentration of passive tracer
98      !!
99      !!        At each time step call histdef to compute the mean if necessary
100      !!        Each nwritetrc time step, output the instantaneous or mean fields
101      !!
102      !!        IF kindic <0, output of fields before the model interruption.
103      !!        IF kindic =0, time step loop
104      !!        IF kindic >0, output of fields before the time step loop
105      !!----------------------------------------------------------------------
106      INTEGER, INTENT( in ) ::   kt          ! ocean time-step
107      INTEGER, INTENT( in ) ::   kindic      ! indicator of abnormal termination
108      !!
109      INTEGER ::   jn
110      LOGICAL ::   ll_print = .FALSE.
111      CHARACTER (len=40) :: clhstnam, clop
[1656]112#if defined key_off_tra
113      INTEGER ::   inum = 11             ! temporary logical unit
114#endif
[1011]115      CHARACTER (len=20) :: cltra, cltrau
116      CHARACTER (len=80) :: cltral
117      REAL(wp) :: zsto, zout, zdt
[1334]118      INTEGER  :: iimi, iima, ijmi, ijma, ipk, it, itmod
[1011]119      !!----------------------------------------------------------------------
120
121      ! Initialisation
122      ! --------------
123
124      ! local variable for debugging
125      ll_print = .FALSE.                  ! change it to true for more control print
126      ll_print = ll_print .AND. lwp
127
128      ! Define frequency of output and means
129      zdt = rdt
[1312]130      IF( ln_mskland )   THEN   ;   clop = "only(x)"   ! put 1.e+20 on land (very expensive!!)
131      ELSE                      ;   clop = "x"         ! no use of the mask value (require less cpu time)
132      ENDIF
[1011]133# if defined key_diainstant
134      zsto = nwritetrc * rdt
[1312]135      clop = "inst("//TRIM(clop)//")"
[1011]136# else
137      zsto = zdt
[1312]138      clop = "ave("//TRIM(clop)//")"
[1011]139# endif
140      zout = nwritetrc * zdt
141
142      ! Define indices of the horizontal output zoom and vertical limit storage
143      iimi = 1      ;      iima = jpi
144      ijmi = 1      ;      ijma = jpj
145      ipk = jpk
146
147      ! define time axis
[1334]148      itmod = kt - nittrc000 + 1
[1353]149      it    = kt
[1011]150
151      ! Define NETCDF files and fields at beginning of first time step
152      ! --------------------------------------------------------------
153
154      IF(ll_print)WRITE(numout,*)'trcdit_wr kt=',kt,' kindic ',kindic
155     
156      IF( kt == nittrc000 ) THEN
157
158         ! Compute julian date from starting date of the run
[1329]159         CALL ymds2ju( nyear, nmonth, nday, rdt, xjulian )
160         xjulian = xjulian - adatrj   !   set calendar origin to the beginning of the experiment
[1011]161         IF(lwp)WRITE(numout,*)' ' 
162         IF(lwp)WRITE(numout,*)' Date 0 used :', nittrc000                         &
163            &                 ,' YEAR ', nyear, ' MONTH ', nmonth, ' DAY ', nday   &
[1353]164            &                 ,'Julian day : ', xjulian 
165 
[1011]166         IF(lwp) WRITE(numout,*) ' indexes of zoom = ', iimi, iima, ijmi, ijma,  &
167            &                    ' limit storage in depth = ', ipk
168
[1656]169#if defined key_off_tra
170        ! WRITE root name in date.file for use by postpro
171         IF(lwp) THEN
172            CALL dia_nam( clhstnam, nwritetrc,' ' )
173            CALL ctl_opn( inum, 'date.file', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp, narea )
174            WRITE(inum,*) clhstnam
175            CLOSE(inum)
176         ENDIF
177#endif
[1011]178
[1353]179         ! Define the NETCDF files for passive tracer concentration
[1011]180         CALL dia_nam( clhstnam, nwritetrc, 'ptrc_T' )
181         IF(lwp)WRITE(numout,*)" Name of NETCDF file ", clhstnam
[1353]182
183         ! Horizontal grid : glamt and gphit
[1011]184         CALL histbeg( clhstnam, jpi, glamt, jpj, gphit,     &
185            &          iimi, iima-iimi+1, ijmi, ijma-ijmi+1,         & 
[1353]186            &          nittrc000-ndttrc, xjulian, zdt, nhorit5, nit5 , domain_id=nidom)
[1011]187
[1353]188         ! Vertical grid for tracer : gdept
189         CALL histvert( nit5, 'deptht', 'Vertical T levels', 'm', ipk, gdept_0, ndepit5)
[1011]190
[1353]191         ! Index of ocean points in 3D and 2D (surface)
192         CALL wheneq( jpi*jpj*ipk, tmask, 1, 1., ndext50, ndimt50 )
193         CALL wheneq( jpi*jpj    , tmask, 1, 1., ndext51, ndimt51 )
[1011]194
[1353]195         ! Declare all the output fields as NETCDF variables
[1011]196         DO jn = 1, jptra
197            IF( lutsav(jn) ) THEN
198               cltra  = ctrcnm(jn)   ! short title for tracer
199               cltral = ctrcnl(jn)   ! long title for tracer
200               cltrau = ctrcun(jn)   ! UNIT for tracer
201               CALL histdef( nit5, cltra, cltral, cltrau, jpi, jpj, nhorit5,  &
[1353]202                  &          ipk, 1, ipk,  ndepit5, 32, clop, zsto, zout ) 
[1011]203            ENDIF
204         END DO
205
206         ! end netcdf files header
207         CALL histend( nit5 )
208         IF(lwp) WRITE(numout,*)
209         IF(lwp) WRITE(numout,*) 'End of NetCDF Initialization in trcdit_wr'
210         IF( ll_print )   CALL FLUSH(numout )
211
212      ENDIF
213
214      ! Start writing the tracer concentrations
215      ! ---------------------------------------
216
[1334]217      IF( lwp .AND. MOD( itmod, nwritetrc ) == 0 ) THEN
[1011]218         WRITE(numout,*) 'trcdit_wr : write NetCDF passive tracer concentrations at ', kt, 'time-step'
219         WRITE(numout,*) '~~~~~~~~~ '
220      ENDIF
221
222      DO jn = 1, jptra
[1450]223         cltra = ctrcnm(jn)      ! short title for tracer
224         IF( lutsav(jn) ) CALL histwrite( nit5, cltra, it, trn(:,:,:,jn), ndimt50, ndext50 )
[1011]225      END DO
226
227      ! close the file
228      ! --------------
229      IF( kt == nitend .OR. kindic < 0 )   CALL histclo( nit5 )
230      !
[1450]231
[1011]232   END SUBROUTINE trcdit_wr
233
234# if defined key_trc_diatrd
235
236   SUBROUTINE trcdid_wr( kt, kindic )
237      !!----------------------------------------------------------------------
238      !!                     ***  ROUTINE trcdid_wr  ***
239      !!
240      !! ** Purpose :   output of passive tracer : advection-diffusion trends
241      !!
242      !! ** Method  :   At the beginning of the first time step (nit000), define all
243      !!             the NETCDF files and fields for concentration of passive tracer
244      !!
245      !!        At each time step call histdef to compute the mean if necessary
[1391]246      !!        Each nwritetrd time step, output the instantaneous or mean fields
[1011]247      !!
248      !!        IF kindic <0, output of fields before the model interruption.
249      !!        IF kindic =0, time step loop
250      !!        IF kindic >0, output of fields before the time step loop
251      !!----------------------------------------------------------------------
252      INTEGER, INTENT( in ) ::   kt          ! ocean time-step
253      INTEGER, INTENT( in ) ::   kindic      ! indicator of abnormal termination
254      !!
255      LOGICAL ::   ll_print = .FALSE.
256      CHARACTER (len=40) ::   clhstnam, clop
257      CHARACTER (len=20) ::   cltra, cltrau
258      CHARACTER (len=80) ::   cltral
259      CHARACTER (len=10) ::   csuff
260      INTEGER  ::   jn, jl
[1334]261      INTEGER  ::   iimi, iima, ijmi, ijma, ipk, it, itmod
[1011]262      REAL(wp) ::   zsto, zout, zdt
263      !!----------------------------------------------------------------------
264
265      ! 0. Initialisation
266      ! -----------------
[1450]267     
[1011]268
269      ! local variable for debugging
270      ll_print = .FALSE.
271      ll_print = ll_print .AND. lwp
272      !
273      ! Define frequency of output and means
274      zdt = rdt
[1316]275      IF( ln_mskland )   THEN   ;   clop = "only(x)"   ! put 1.e+20 on land (very expensive!!)
276      ELSE                      ;   clop = "x"         ! no use of the mask value (require less cpu time)
277      ENDIF
[1011]278#  if defined key_diainstant
279      zsto = nwritetrd * rdt
[1316]280      clop = "inst("//TRIM(clop)//")"
[1011]281#  else
282      zsto = zdt
[1316]283      clop = "ave("//TRIM(clop)//")"
[1011]284#  endif
285      zout = nwritetrd * zdt
286
287      ! Define indices of the horizontal output zoom and vertical limit storage
288      iimi = 1      ;      iima = jpi
289      ijmi = 1      ;      ijma = jpj
290      ipk = jpk
291
292      ! define time axis
[1334]293      itmod = kt - nittrc000 + 1
[1353]294      it    = kt
[1011]295
296      ! Define the NETCDF files (one per tracer)
297      IF( ll_print ) WRITE(numout,*) 'trcdid kt=', kt, ' kindic ', kindic
298     
299     
300      IF( kt == nittrc000 ) THEN
301
302         DO jn = 1, jptra
303            !
304            IF( luttrd(jn) ) THEN      ! Define the file for dynamical trends - one per each tracer IF required
305
306               IF(lwp)WRITE(numout,*) ' indexes of zoom = ', iimi, iima, ijmi, ijma,  &
307                   &                   ' limit storage in depth = ', ipk
308               csuff='DY_'//ctrcnm(jn)
309               CALL dia_nam( clhstnam, nwritetrd, csuff )
310               IF(lwp)WRITE(numout,*)   " Name of NETCDF file for dynamical trends",   &
311                  &                     " of tracer number : ",clhstnam
312
313               CALL histbeg( clhstnam, jpi, glamt, jpj, gphit,       &
314                  &          iimi, iima-iimi+1, ijmi, ijma-ijmi+1,   &
[1353]315                  &          nittrc000-ndttrc, xjulian, zdt, nhorit6(jn),  &
[1011]316                  &          nit6(jn) , domain_id=nidom )
317
318               ! Vertical grid for tracer trend - one per each tracer IF needed
[1353]319               CALL histvert( nit6(jn), 'deptht', 'Vertical T levels', 'm', ipk, gdept_0, ndepit6(jn) ) 
[1011]320             END IF
321          END DO
322
323          ! Declare all the output fields as NETCDF variables
324
325          ! trends for tracer concentrations
326          DO jn = 1, jptra
327            IF( luttrd(jn) ) THEN
328                DO jl = 1, jpdiatrc
329                  IF( jl == 1 ) THEN
330                      ! short and long title for x advection for tracer
331                      WRITE (cltra,'("XAD_",16a)') ctrcnm(jn)
332                      WRITE (cltral,'("X advective trend for ",58a)')  &
333                         &      ctrcnl(jn)(1:58)
334                  END IF
335                  IF( jl == 2 ) THEN
336                      ! short and long title for y advection for tracer
337                      WRITE (cltra,'("YAD_",16a)') ctrcnm(jn)
338                      WRITE (cltral,'("Y advective trend for ",58a)')  &
339                         &      ctrcnl(jn)(1:58)
340                  END IF
341                  IF( jl == 3 ) THEN
342                      ! short and long title for Z advection for tracer
343                      WRITE (cltra,'("ZAD_",16a)') ctrcnm(jn)
344                      WRITE (cltral,'("Z advective trend for ",58a)')  &
345                         &      ctrcnl(jn)(1:58)
346                  END IF
347                  IF( jl == 4 ) THEN
348                      ! short and long title for X diffusion for tracer
349                      WRITE (cltra,'("XDF_",16a)') ctrcnm(jn)
350                      WRITE (cltral,'("X diffusion trend for ",58a)')  &
351                         &      ctrcnl(jn)(1:58)
352                  END IF
353                  IF( jl == 5 ) THEN
354                      ! short and long title for Y diffusion for tracer
355                      WRITE (cltra,'("YDF_",16a)') ctrcnm(jn)
356                      WRITE (cltral,'("Y diffusion trend for ",58a)')  &
357                         &      ctrcnl(jn)(1:58)
358                  END IF
359                  IF( jl == 6 ) THEN
360                      ! short and long title for Z diffusion for tracer
361                      WRITE (cltra,'("ZDF_",16a)') ctrcnm(jn)
362                      WRITE (cltral,'("Z diffusion trend for ",58a)')  &
363                         &      ctrcnl(jn)(1:58)
364                  END IF
[1167]365# if defined key_trcldf_eiv
[1011]366                  IF( jl == 7 ) THEN
367                      ! short and long title for x gent velocity for tracer
368                      WRITE (cltra,'("XGV_",16a)') ctrcnm(jn)
369                      WRITE (cltral,'("X gent velocity trend for ",53a)')  &
370                         &      ctrcnl(jn)(1:53)
371                  END IF
372                  IF( jl == 8 ) THEN
373                      ! short and long title for y gent velocity for tracer
374                      WRITE (cltra,'("YGV_",16a)') ctrcnm(jn)
375                      WRITE (cltral,'("Y gent velocity trend for ",53a)')  &
376                         &      ctrcnl(jn)(1:53)
377                  END IF
378                  IF( jl == 9 ) THEN
379                      ! short and long title for Z gent velocity for tracer
380                      WRITE (cltra,'("ZGV_",16a)') ctrcnm(jn)
381                      WRITE (cltral,'("Z gent velocity trend for ",53a)')  &
382                         &      ctrcnl(jn)(1:53)
383                  END IF
384# endif
385# if defined key_trcdmp
386                  IF( jl == jpdiatrc - 1 ) THEN
387                      ! last trends for tracer damping : short and long title
388                      WRITE (cltra,'("TDM_",16a)') ctrcnm(jn)
389                      WRITE (cltral,'("Tracer damping trend for ",55a)')  &
390                         &      ctrcnl(jn)(1:55)
391                  END IF
392# endif
393                  IF( jl == jpdiatrc ) THEN
394                      ! last trends for tracer damping : short and long title
395                      WRITE (cltra,'("SBC_",16a)') ctrcnm(jn)
396                      WRITE (cltral,'("Surface boundary flux ",58a)')  &
397                      &      ctrcnl(jn)(1:58)
398                  END IF
399
400                  CALL FLUSH( numout )
401                  cltrau = ctrcun(jn)      ! UNIT for tracer /trends
402                  CALL histdef( nit6(jn), cltra, cltral, cltrau, jpi,jpj,  &
403                     &          nhorit6(jn), ipk, 1, ipk,  ndepit6(jn), 32, clop ,  &
404                     &          zsto,zout )
405               END DO
406            END IF
407         END DO
408
409         ! CLOSE netcdf Files
410          DO jn = 1, jptra
411             IF( luttrd(jn) )   CALL histend( nit6(jn) )
412          END DO
413
414         IF(lwp) WRITE(numout,*)
415         IF(lwp) WRITE(numout,*) 'End of NetCDF Initialization in trcdid'
416         IF(ll_print) CALL FLUSH(numout )
417         !
418      ENDIF
419
420      ! SOME diagnostics to DO first time
421
422      ! Start writing data
423      ! ---------------------
424
425      ! trends for tracer concentrations
426
[1334]427      IF( lwp .AND. MOD( itmod, nwritetrd ) == 0 ) THEN
[1011]428         WRITE(numout,*) 'trcdid_wr : write NetCDF dynamical trends at ', kt, 'time-step'
429         WRITE(numout,*) '~~~~~~ '
430      ENDIF
431
432      DO jn = 1, jptra
433         IF( luttrd(jn) ) THEN
434            DO jl = 1, jpdiatrc
435               ! short titles
436               IF( jl == 1)   WRITE (cltra,'("XAD_",16a)') ctrcnm(jn)      ! x advection for tracer
437               IF( jl == 2)   WRITE (cltra,'("YAD_",16a)') ctrcnm(jn)      ! z advection for tracer
438               IF( jl == 3)   WRITE (cltra,'("ZAD_",16a)') ctrcnm(jn)      ! z advection for tracer
439               IF( jl == 4)   WRITE (cltra,'("XDF_",16a)') ctrcnm(jn)      ! x diffusion for tracer
440               IF( jl == 5)   WRITE (cltra,'("YDF_",16a)') ctrcnm(jn)      ! y diffusion for tracer
441               IF( jl == 6)   WRITE (cltra,'("ZDF_",16a)') ctrcnm(jn)      ! z diffusion for tracer
442# if defined key_trcldf_eiv
443               IF( jl == 7)   WRITE (cltra,'("XGV_",16a)') ctrcnm(jn)      ! x gent velocity for tracer
444               IF( jl == 8)   WRITE (cltra,'("YGV_",16a)') ctrcnm(jn)      ! y gent velocity for tracer
445               IF( jl == 9)   WRITE (cltra,'("ZGV_",16a)') ctrcnm(jn)      ! z gent velocity for tracer
446# endif
447# if defined key_trcdmp
448               IF( jl == jpdiatrc - 1 )   WRITE (cltra,'("TDM_",16a)') ctrcnm(jn)      ! damping
449# endif
450               IF( jl == jpdiatrc )   WRITE (cltra,'("SBC_",a)') ctrcnm(jn)      ! surface boundary conditions
451               !
[1119]452               CALL histwrite(nit6(jn), cltra, it, trtrd(:,:,:,ikeep(jn),jl),ndimt50, ndext50)
[1011]453            END DO
454         END IF
455      END DO
456
457      ! Closing all files
458      ! -----------------
459      IF( kt == nitend .OR. kindic < 0 ) THEN
460         DO jn = 1, jptra
461            IF( luttrd(jn) )   CALL histclo( nit6(jn) )
462         END DO
463      ENDIF
464      !
[1450]465
[1011]466   END SUBROUTINE trcdid_wr
467
468# else
469
470   SUBROUTINE trcdid_wr( kt, kindic )                      ! Dummy routine
471      INTEGER, INTENT ( in ) ::   kt, kindic
472   END SUBROUTINE trcdid_wr
473
474# endif
475
476#if defined key_trc_diaadd
477
478   SUBROUTINE trcdii_wr( kt, kindic )
479      !!----------------------------------------------------------------------
480      !!                     ***  ROUTINE trcdii_wr  ***
481      !!
482      !! ** Purpose :   output of passive tracer : additional 2D and 3D arrays
483      !!
484      !! ** Method  :   At the beginning of the first time step (nit000), define all
485      !!             the NETCDF files and fields for concentration of passive tracer
486      !!
487      !!        At each time step call histdef to compute the mean if necessary
[1391]488      !!        Each nwritedia time step, output the instantaneous or mean fields
[1011]489      !!
490      !!        IF kindic <0, output of fields before the model interruption.
491      !!        IF kindic =0, time step loop
492      !!        IF kindic >0, output of fields before the time step loop
493      !!----------------------------------------------------------------------
494      INTEGER, INTENT( in ) ::   kt          ! ocean time-step
495      INTEGER, INTENT( in ) ::   kindic      ! indicator of abnormal termination
496      !!
497      LOGICAL ::   ll_print = .FALSE.
498      CHARACTER (len=40) ::   clhstnam, clop
499      CHARACTER (len=20) ::   cltra, cltrau
500      CHARACTER (len=80) ::   cltral
[1450]501      INTEGER  ::   jl
[1334]502      INTEGER  ::   iimi, iima, ijmi, ijma, ipk, it, itmod
[1011]503      REAL(wp) ::   zsto, zout, zdt
504      !!----------------------------------------------------------------------
505
506      ! Initialisation
507      ! --------------
[1450]508     
[1011]509      ! local variable for debugging
510      ll_print = .FALSE.
511      ll_print = ll_print .AND. lwp
512      !
513      ! Define frequency of output and means
514      zdt = rdt
[1316]515      IF( ln_mskland )   THEN   ;   clop = "only(x)"   ! put 1.e+20 on land (very expensive!!)
516      ELSE                      ;   clop = "x"         ! no use of the mask value (require less cpu time)
517      ENDIF
[1011]518#  if defined key_diainstant
[1353]519      zsto = nwritedia * zdt
[1316]520      clop = "inst("//TRIM(clop)//")"
[1011]521#  else
[1353]522      zsto = zdt
[1316]523      clop = "ave("//TRIM(clop)//")"
[1011]524#  endif
[1353]525      zout = nwritedia * zdt
[1011]526
527      ! Define indices of the horizontal output zoom and vertical limit storage
528      iimi = 1      ;      iima = jpi
529      ijmi = 1      ;      ijma = jpj
530      ipk = jpk
531
532      ! define time axis
[1334]533      itmod = kt - nittrc000 + 1
[1353]534      it    = kt
[1011]535
536      ! 1. Define NETCDF files and fields at beginning of first time step
537      ! -----------------------------------------------------------------
538
539      IF( ll_print ) WRITE(numout,*) 'trcdii_wr kt=', kt, ' kindic ', kindic
540
541      IF( kt == nittrc000 ) THEN
542
543         ! Define the NETCDF files for additional arrays : 2D or 3D
544
545         ! Define the T grid file for tracer auxiliary files
546
[1391]547         CALL dia_nam( clhstnam, nwritedia, 'diad_T' )
[1011]548         IF(lwp) WRITE(numout,*) " Name of NETCDF file ", clhstnam
549
550         ! Define a netcdf FILE for 2d and 3d arrays
551
552         CALL histbeg( clhstnam, jpi, glamt, jpj, gphit,             &
553            &          iimi, iima-iimi+1, ijmi, ijma-ijmi+1,         &
[1353]554            &          nittrc000-ndttrc, xjulian, zdt, nhoritd, nitd , domain_id=nidom )
[1011]555
556         ! Vertical grid for 2d and 3d arrays
557
[1353]558         CALL histvert( nitd, 'deptht', 'Vertical T levels','m', ipk, gdept_0, ndepitd)
[1011]559
560         ! Declare all the output fields as NETCDF variables
561
562         ! more 3D horizontal arrays
[1450]563         DO jl = 1, jpdia3d
564            cltra  = ctrc3d(jl)   ! short title for 3D diagnostic
565            cltral = ctrc3l(jl)   ! long title for 3D diagnostic
566            cltrau = ctrc3u(jl)   ! UNIT for 3D diagnostic
[1011]567            CALL histdef( nitd, cltra, cltral, cltrau, jpi, jpj, nhoritd,   &
568               &          ipk, 1, ipk,  ndepitd, 32, clop, zsto, zout )
569         END DO
570
571         ! more 2D horizontal arrays
[1450]572         DO jl = 1, jpdia2d
573            cltra  = ctrc2d(jl)    ! short title for 2D diagnostic
574            cltral = ctrc2l(jl)   ! long title for 2D diagnostic
575            cltrau = ctrc2u(jl)   ! UNIT for 2D diagnostic
[1011]576            CALL histdef( nitd, cltra, cltral, cltrau, jpi, jpj, nhoritd,  &
577               &          1, 1, 1,  -99, 32, clop, zsto, zout )
578         END DO
579
580         ! TODO: more 2D vertical sections arrays : I or J indice fixed
581
582         ! CLOSE netcdf Files
583         CALL histend( nitd )
584
585         IF(lwp) WRITE(numout,*)
586         IF(lwp) WRITE(numout,*) 'End of NetCDF Initialization in trcdii_wr'
587         IF( ll_print )   CALL FLUSH(numout )
588         !
589      ENDIF
590
591      ! 2. Start writing data
592      ! ---------------------
593
[1334]594      IF( lwp .AND. MOD( itmod, nwritedia ) == 0 ) THEN
[1011]595         WRITE(numout,*) 'trcdii_wr : write NetCDF additional arrays at ', kt, 'time-step'
596         WRITE(numout,*) '~~~~~~ '
597      ENDIF
598
599      ! more 3D horizontal arrays
[1450]600      DO jl = 1, jpdia3d
601         cltra = ctrc3d(jl)   ! short title for 3D diagnostic
602         CALL histwrite( nitd, cltra, it, trc3d(:,:,:,jl), ndimt50 ,ndext50)
[1011]603      END DO
604
605      ! more 2D horizontal arrays
[1450]606      DO jl = 1, jpdia2d
607         cltra = ctrc2d(jl)   ! short title for 2D diagnostic
608         CALL histwrite(nitd, cltra, it, trc2d(:,:,jl), ndimt51  ,ndext51)
[1011]609      END DO
610
611      ! Closing all files
612      ! -----------------
613      IF( kt == nitend .OR. kindic < 0 )   CALL histclo(nitd)
614      !
[1450]615
[1011]616   END SUBROUTINE trcdii_wr
617
618# else
619
620   SUBROUTINE trcdii_wr( kt, kindic )                      ! Dummy routine
621      INTEGER, INTENT ( in ) :: kt, kindic
622   END SUBROUTINE trcdii_wr
623
624# endif
625
626# if defined key_trc_diabio
627
628   SUBROUTINE trcdib_wr( kt, kindic )
629      !!----------------------------------------------------------------------
630      !!                     ***  ROUTINE trcdib_wr  ***
631      !!
632      !! ** Purpose :   output of passive tracer : biological fields
633      !!
634      !! ** Method  :   At the beginning of the first time step (nit000), define all
635      !!             the NETCDF files and fields for concentration of passive tracer
636      !!
637      !!        At each time step call histdef to compute the mean if necessary
[1391]638      !!        Each nwritebio time step, output the instantaneous or mean fields
[1011]639      !!
640      !!        IF kindic <0, output of fields before the model interruption.
641      !!        IF kindic =0, time step loop
642      !!        IF kindic >0, output of fields before the time step loop
643      !!----------------------------------------------------------------------
644      !!
645      INTEGER, INTENT( in ) ::   kt          ! ocean time-step
646      INTEGER, INTENT( in ) ::   kindic      ! indicator of abnormal termination
647      !!
648      LOGICAL ::   ll_print = .FALSE.
649      CHARACTER (len=40) ::   clhstnam, clop
650      CHARACTER (len=20) ::   cltra, cltrau
651      CHARACTER (len=80) ::   cltral
[1450]652      INTEGER  ::   ji, jj, jk, jl
[1334]653      INTEGER  ::   iimi, iima, ijmi, ijma, ipk, it, itmod
[1011]654      REAL(wp) ::   zsto, zout, zdt
655      !!----------------------------------------------------------------------
656
657      ! Initialisation
658      ! --------------
659
[1450]660     
[1011]661      ! local variable for debugging
662      ll_print = .FALSE.
663      ll_print = ll_print .AND. lwp
664
665      ! Define frequency of output and means
666      zdt = rdt
[1316]667      IF( ln_mskland )   THEN   ;   clop = "only(x)"   ! put 1.e+20 on land (very expensive!!)
668      ELSE                      ;   clop = "x"         ! no use of the mask value (require less cpu time)
669      ENDIF
[1011]670#        if defined key_diainstant
[1353]671      zsto = nwritebio * zdt
[1316]672      clop = "inst("//TRIM(clop)//")"
[1011]673#        else
[1353]674      zsto = zdt
[1316]675      clop = "ave("//TRIM(clop)//")"
[1011]676#        endif
[1353]677      zout = nwritebio * zdt
[1011]678
[1353]679      ! Define indices of the horizontal output zoom and vertical limit storage
[1011]680      iimi = 1      ;      iima = jpi
681      ijmi = 1      ;      ijma = jpj
682      ipk = jpk
683
684      ! define time axis
[1334]685      itmod = kt - nittrc000 + 1
[1353]686      it    = kt
[1011]687
688      ! Define NETCDF files and fields at beginning of first time step
689      ! --------------------------------------------------------------
690
691      IF(ll_print) WRITE(numout,*)'trcdib_wr kt=',kt,' kindic ',kindic
692
693      IF( kt == nittrc000 ) THEN
694
695         ! Define the NETCDF files for biological trends
696
[1391]697         CALL dia_nam(clhstnam,nwritebio,'biolog')
[1011]698         IF(lwp)WRITE(numout,*) " Name of NETCDF file for biological trends ", clhstnam
699         ! Horizontal grid : glamt and gphit
[1353]700         CALL histbeg( clhstnam, jpi, glamt, jpj, gphit,      &
[1011]701            &    iimi, iima-iimi+1, ijmi, ijma-ijmi+1,          &
[1353]702            &    nittrc000-ndttrc, xjulian, zdt, nhoritb, nitb , domain_id=nidom )
[1011]703         ! Vertical grid for biological trends
[1353]704         CALL histvert(nitb, 'deptht', 'Vertical T levels', 'm', ipk, gdept_0, ndepitb)
[1011]705
706         ! Declare all the output fields as NETCDF variables
707         ! biological trends
[1450]708         DO jl = 1, jpdiabio
709            cltra  = ctrbio(jl)   ! short title for biological diagnostic
710            cltral = ctrbil(jl)   ! long title for biological diagnostic
711            cltrau = ctrbiu(jl)   ! UNIT for biological diagnostic
[1353]712            CALL histdef( nitb, cltra, cltral, cltrau, jpi, jpj, nhoritb,  &
[1011]713               &         ipk, 1, ipk,  ndepitb, 32, clop, zsto, zout)
714         END DO
715
716         ! CLOSE netcdf Files
[1353]717          CALL histend( nitb )
[1011]718
719         IF(lwp) WRITE(numout,*)
720         IF(lwp) WRITE(numout,*) 'End of NetCDF Initialization in trcdib_wr'
721         IF(ll_print) CALL FLUSH(numout )
722         !
723      ENDIF
724
725      ! Start writing data
726      ! ------------------
727
728      ! biological trends
[1334]729      IF( lwp .AND. MOD( itmod, nwritebio ) == 0 ) THEN
[1011]730         WRITE(numout,*) 'trcdit_wr : write NetCDF biological trends at ', kt, 'time-step'
731         WRITE(numout,*) '~~~~~~ '
732      ENDIF
733
[1450]734      DO jl = 1, jpdiabio
735         cltra = ctrbio(jl)  ! short title for biological diagnostic
736         CALL histwrite(nitb, cltra, it, trbio(:,:,:,jl), ndimt50,ndext50)
[1011]737      END DO
738
739      ! Closing all files
740      ! -----------------
741      IF( kt == nitend .OR. kindic < 0 )   CALL histclo( nitb )
742      !
[1450]743
[1011]744   END SUBROUTINE trcdib_wr
745
746# else
747
748   SUBROUTINE trcdib_wr( kt, kindic )                      ! Dummy routine
749      INTEGER, INTENT ( in ) ::   kt, kindic
750   END SUBROUTINE trcdib_wr
751
752# endif 
753
[335]754#else
[945]755   !!----------------------------------------------------------------------
756   !!  Dummy module :                                     No passive tracer
757   !!----------------------------------------------------------------------
[335]758CONTAINS
[1457]759   SUBROUTINE trc_dia( kt )                      ! Empty routine   
760      INTEGER, INTENT(in) :: kt
[335]761   END SUBROUTINE trc_dia   
[1011]762
[335]763#endif
764
[945]765   !!======================================================================
[335]766END MODULE trcdia
Note: See TracBrowser for help on using the repository browser.