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 @ 1711

Last change on this file since 1711 was 1656, checked in by cetlod, 15 years ago

Creation of the date.file in OFFLINE mode, see ticket:551

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