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

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

distribution of iom_put in TOP routines, see ticket:437

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