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

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

nwrite = modulo referenced to nit000 in all ouputs, see ticket:339

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