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

Last change on this file since 1284 was 1189, checked in by cetlod, 16 years ago

update transport modules to take into account new trends organization, see ticket:248

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