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

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

complete work on time origin in outputs (ticket:335) + downward vertical axis (ticket:357)

  • 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
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, 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, itmod
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
144      itmod = kt - nittrc000 + 1
145
146      ! Define NETCDF files and fields at beginning of first time step
147      ! --------------------------------------------------------------
148
149      IF(ll_print)WRITE(numout,*)'trcdit_wr kt=',kt,' kindic ',kindic
150     
151      IF( kt == nittrc000 ) THEN
152
153         ! Compute julian date from starting date of the run
154         CALL ymds2ju( nyear, nmonth, nday, rdt, xjulian )
155         xjulian = xjulian - adatrj   !   set calendar origin to the beginning of the experiment
156         IF(lwp)WRITE(numout,*)' ' 
157         IF(lwp)WRITE(numout,*)' Date 0 used :', nittrc000                         &
158            &                 ,' YEAR ', nyear, ' MONTH ', nmonth, ' DAY ', nday   &
159            &                 ,'Julian day : ', xjulian   
160         IF(lwp) WRITE(numout,*) ' indexes of zoom = ', iimi, iima, ijmi, ijma,  &
161            &                    ' limit storage in depth = ', ipk
162
163
164! Define the NETCDF files for passive tracer concentration
165
166         CALL dia_nam( clhstnam, nwritetrc, 'ptrc_T' )
167         IF(lwp)WRITE(numout,*)" Name of NETCDF file ", clhstnam
168! Horizontal grid : glamt and gphit
169         CALL histbeg( clhstnam, jpi, glamt, jpj, gphit,     &
170            &          iimi, iima-iimi+1, ijmi, ijma-ijmi+1,         & 
171            &          nittrc000-1, xjulian, zdt, nhorit5, nit5 , domain_id=nidom)
172! Vertical grid for tracer : gdept
173         CALL histvert( nit5, 'deptht', 'Vertical T levels', &
174            &            'm', ipk, gdept_0, ndepit5, 'down')
175
176! Index of ocean points in 3D and 2D (surface)
177         CALL wheneq( jpi*jpj*ipk,tmask,1,1.,ndext50,ndimt50 )
178         CALL wheneq( jpi*jpj,tmask,1,1.,ndext51,ndimt51 )
179
180! Declare all the output fields as NETCDF variables
181
182! tracer concentrations
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         IF( lutsav(jn) ) THEN
211            cltra = ctrcnm(jn)      ! short title for tracer
212            CALL histwrite( nit5, cltra, it, trn(:,:,:,jn), ndimt50, ndext50 )
213         ENDIF
214      END DO
215
216      ! close the file
217      ! --------------
218      IF( kt == nitend .OR. kindic < 0 )   CALL histclo( nit5 )
219      !
220   END SUBROUTINE trcdit_wr
221
222# if defined key_trc_diatrd
223
224   SUBROUTINE trcdid_wr( kt, kindic )
225      !!----------------------------------------------------------------------
226      !!                     ***  ROUTINE trcdid_wr  ***
227      !!
228      !! ** Purpose :   output of passive tracer : advection-diffusion trends
229      !!
230      !! ** Method  :   At the beginning of the first time step (nit000), define all
231      !!             the NETCDF files and fields for concentration of passive tracer
232      !!
233      !!        At each time step call histdef to compute the mean if necessary
234      !!        Each nwritetrc time step, output the instantaneous or mean fields
235      !!
236      !!        IF kindic <0, output of fields before the model interruption.
237      !!        IF kindic =0, time step loop
238      !!        IF kindic >0, output of fields before the time step loop
239      !!----------------------------------------------------------------------
240      INTEGER, INTENT( in ) ::   kt          ! ocean time-step
241      INTEGER, INTENT( in ) ::   kindic      ! indicator of abnormal termination
242      !!
243      LOGICAL ::   ll_print = .FALSE.
244      CHARACTER (len=40) ::   clhstnam, clop
245      CHARACTER (len=20) ::   cltra, cltrau
246      CHARACTER (len=80) ::   cltral
247      CHARACTER (len=10) ::   csuff
248      INTEGER  ::   jn, jl
249      INTEGER  ::   iimi, iima, ijmi, ijma, ipk, it, itmod
250      REAL(wp) ::   zsto, zout, zdt
251      !!----------------------------------------------------------------------
252
253      ! 0. Initialisation
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      it = kt
281      itmod = kt - nittrc000 + 1
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-1, xjulian, rdt, 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',   &
307                  &           'm', ipk, gdept_0, ndepit6(jn), 'down' ) 
308             END IF
309          END DO
310
311          ! Declare all the output fields as NETCDF variables
312
313          ! trends for tracer concentrations
314          DO jn = 1, jptra
315            IF( luttrd(jn) ) THEN
316                DO jl = 1, jpdiatrc
317                  IF( jl == 1 ) THEN
318                      ! short and long title for x advection for tracer
319                      WRITE (cltra,'("XAD_",16a)') ctrcnm(jn)
320                      WRITE (cltral,'("X advective trend for ",58a)')  &
321                         &      ctrcnl(jn)(1:58)
322                  END IF
323                  IF( jl == 2 ) THEN
324                      ! short and long title for y advection for tracer
325                      WRITE (cltra,'("YAD_",16a)') ctrcnm(jn)
326                      WRITE (cltral,'("Y advective trend for ",58a)')  &
327                         &      ctrcnl(jn)(1:58)
328                  END IF
329                  IF( jl == 3 ) THEN
330                      ! short and long title for Z advection for tracer
331                      WRITE (cltra,'("ZAD_",16a)') ctrcnm(jn)
332                      WRITE (cltral,'("Z advective trend for ",58a)')  &
333                         &      ctrcnl(jn)(1:58)
334                  END IF
335                  IF( jl == 4 ) THEN
336                      ! short and long title for X diffusion for tracer
337                      WRITE (cltra,'("XDF_",16a)') ctrcnm(jn)
338                      WRITE (cltral,'("X diffusion trend for ",58a)')  &
339                         &      ctrcnl(jn)(1:58)
340                  END IF
341                  IF( jl == 5 ) THEN
342                      ! short and long title for Y diffusion for tracer
343                      WRITE (cltra,'("YDF_",16a)') ctrcnm(jn)
344                      WRITE (cltral,'("Y diffusion trend for ",58a)')  &
345                         &      ctrcnl(jn)(1:58)
346                  END IF
347                  IF( jl == 6 ) THEN
348                      ! short and long title for Z diffusion for tracer
349                      WRITE (cltra,'("ZDF_",16a)') ctrcnm(jn)
350                      WRITE (cltral,'("Z diffusion trend for ",58a)')  &
351                         &      ctrcnl(jn)(1:58)
352                  END IF
353# if defined key_trcldf_eiv
354                  IF( jl == 7 ) THEN
355                      ! short and long title for x gent velocity for tracer
356                      WRITE (cltra,'("XGV_",16a)') ctrcnm(jn)
357                      WRITE (cltral,'("X gent velocity trend for ",53a)')  &
358                         &      ctrcnl(jn)(1:53)
359                  END IF
360                  IF( jl == 8 ) THEN
361                      ! short and long title for y gent velocity for tracer
362                      WRITE (cltra,'("YGV_",16a)') ctrcnm(jn)
363                      WRITE (cltral,'("Y gent velocity trend for ",53a)')  &
364                         &      ctrcnl(jn)(1:53)
365                  END IF
366                  IF( jl == 9 ) THEN
367                      ! short and long title for Z gent velocity for tracer
368                      WRITE (cltra,'("ZGV_",16a)') ctrcnm(jn)
369                      WRITE (cltral,'("Z gent velocity trend for ",53a)')  &
370                         &      ctrcnl(jn)(1:53)
371                  END IF
372# endif
373# if defined key_trcdmp
374                  IF( jl == jpdiatrc - 1 ) THEN
375                      ! last trends for tracer damping : short and long title
376                      WRITE (cltra,'("TDM_",16a)') ctrcnm(jn)
377                      WRITE (cltral,'("Tracer damping trend for ",55a)')  &
378                         &      ctrcnl(jn)(1:55)
379                  END IF
380# endif
381                  IF( jl == jpdiatrc ) THEN
382                      ! last trends for tracer damping : short and long title
383                      WRITE (cltra,'("SBC_",16a)') ctrcnm(jn)
384                      WRITE (cltral,'("Surface boundary flux ",58a)')  &
385                      &      ctrcnl(jn)(1:58)
386                  END IF
387
388                  CALL FLUSH( numout )
389                  cltrau = ctrcun(jn)      ! UNIT for tracer /trends
390                  CALL histdef( nit6(jn), cltra, cltral, cltrau, jpi,jpj,  &
391                     &          nhorit6(jn), ipk, 1, ipk,  ndepit6(jn), 32, clop ,  &
392                     &          zsto,zout )
393               END DO
394            END IF
395         END DO
396
397         ! CLOSE netcdf Files
398          DO jn = 1, jptra
399             IF( luttrd(jn) )   CALL histend( nit6(jn) )
400          END DO
401
402         IF(lwp) WRITE(numout,*)
403         IF(lwp) WRITE(numout,*) 'End of NetCDF Initialization in trcdid'
404         IF(ll_print) CALL FLUSH(numout )
405         !
406      ENDIF
407
408      ! SOME diagnostics to DO first time
409
410      ! Start writing data
411      ! ---------------------
412
413      ! trends for tracer concentrations
414
415      IF( lwp .AND. MOD( itmod, nwritetrd ) == 0 ) THEN
416         WRITE(numout,*) 'trcdid_wr : write NetCDF dynamical trends at ', kt, 'time-step'
417         WRITE(numout,*) '~~~~~~ '
418      ENDIF
419
420      DO jn = 1, jptra
421         IF( luttrd(jn) ) THEN
422            DO jl = 1, jpdiatrc
423               ! short titles
424               IF( jl == 1)   WRITE (cltra,'("XAD_",16a)') ctrcnm(jn)      ! x advection for tracer
425               IF( jl == 2)   WRITE (cltra,'("YAD_",16a)') ctrcnm(jn)      ! z advection for tracer
426               IF( jl == 3)   WRITE (cltra,'("ZAD_",16a)') ctrcnm(jn)      ! z advection for tracer
427               IF( jl == 4)   WRITE (cltra,'("XDF_",16a)') ctrcnm(jn)      ! x diffusion for tracer
428               IF( jl == 5)   WRITE (cltra,'("YDF_",16a)') ctrcnm(jn)      ! y diffusion for tracer
429               IF( jl == 6)   WRITE (cltra,'("ZDF_",16a)') ctrcnm(jn)      ! z diffusion for tracer
430# if defined key_trcldf_eiv
431               IF( jl == 7)   WRITE (cltra,'("XGV_",16a)') ctrcnm(jn)      ! x gent velocity for tracer
432               IF( jl == 8)   WRITE (cltra,'("YGV_",16a)') ctrcnm(jn)      ! y gent velocity for tracer
433               IF( jl == 9)   WRITE (cltra,'("ZGV_",16a)') ctrcnm(jn)      ! z gent velocity for tracer
434# endif
435# if defined key_trcdmp
436               IF( jl == jpdiatrc - 1 )   WRITE (cltra,'("TDM_",16a)') ctrcnm(jn)      ! damping
437# endif
438               IF( jl == jpdiatrc )   WRITE (cltra,'("SBC_",a)') ctrcnm(jn)      ! surface boundary conditions
439               !
440               CALL histwrite(nit6(jn), cltra, it, trtrd(:,:,:,ikeep(jn),jl),ndimt50, ndext50)
441            END DO
442         END IF
443      END DO
444
445      ! Closing all files
446      ! -----------------
447      IF( kt == nitend .OR. kindic < 0 ) THEN
448         DO jn = 1, jptra
449            IF( luttrd(jn) )   CALL histclo( nit6(jn) )
450         END DO
451      ENDIF
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 nwritetrc 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  ::   jn
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      it = kt
521      itmod = kt - nittrc000 + 1
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, nwrite, '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-1, 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',   &
546            &           'm', ipk, gdept_0, ndepitd, 'down')
547
548         ! Declare all the output fields as NETCDF variables
549
550         ! more 3D horizontal arrays
551         DO jn = 1, jpdia3d
552            cltra  = ctrc3d(jn)   ! short title for 3D diagnostic
553            cltral = ctrc3l(jn)   ! long title for 3D diagnostic
554            cltrau = ctrc3u(jn)   ! UNIT for 3D diagnostic
555            CALL histdef( nitd, cltra, cltral, cltrau, jpi, jpj, nhoritd,   &
556               &          ipk, 1, ipk,  ndepitd, 32, clop, zsto, zout )
557         END DO
558
559         ! more 2D horizontal arrays
560         DO jn = 1, jpdia2d
561            cltra  = ctrc2d(jn)    ! short title for 2D diagnostic
562            cltral = ctrc2l(jn)   ! long title for 2D diagnostic
563            cltrau = ctrc2u(jn)   ! UNIT for 2D diagnostic
564            CALL histdef( nitd, cltra, cltral, cltrau, jpi, jpj, nhoritd,  &
565               &          1, 1, 1,  -99, 32, clop, zsto, zout )
566         END DO
567
568         ! TODO: more 2D vertical sections arrays : I or J indice fixed
569
570         ! CLOSE netcdf Files
571         CALL histend( nitd )
572
573         IF(lwp) WRITE(numout,*)
574         IF(lwp) WRITE(numout,*) 'End of NetCDF Initialization in trcdii_wr'
575         IF( ll_print )   CALL FLUSH(numout )
576         !
577      ENDIF
578
579      ! 2. Start writing data
580      ! ---------------------
581
582      IF( lwp .AND. MOD( itmod, nwritedia ) == 0 ) THEN
583         WRITE(numout,*) 'trcdii_wr : write NetCDF additional arrays at ', kt, 'time-step'
584         WRITE(numout,*) '~~~~~~ '
585      ENDIF
586
587      ! more 3D horizontal arrays
588      DO jn = 1, jpdia3d
589         cltra = ctrc3d(jn)   ! short title for 3D diagnostic
590         CALL histwrite( nitd, cltra, it, trc3d(:,:,:,jn), ndimt50 ,ndext50)
591      END DO
592
593      ! more 2D horizontal arrays
594      DO jn = 1, jpdia2d
595         cltra = ctrc2d(jn)   ! short title for 2D diagnostic
596         CALL histwrite(nitd, cltra, it, trc2d(:,:,jn), ndimt51  ,ndext51)
597      END DO
598
599      ! Closing all files
600      ! -----------------
601      IF( kt == nitend .OR. kindic < 0 )   CALL histclo(nitd)
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 nwritetrc 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, jn
640      INTEGER  ::   iimi, iima, ijmi, ijma, ipk, it, itmod
641      REAL(wp) ::   zsto, zout, zdt
642      !!----------------------------------------------------------------------
643
644      ! Initialisation
645      ! --------------
646
647      ! local variable for debugging
648      ll_print = .FALSE.
649      ll_print = ll_print .AND. lwp
650
651      ! Define frequency of output and means
652      zdt = rdt
653      IF( ln_mskland )   THEN   ;   clop = "only(x)"   ! put 1.e+20 on land (very expensive!!)
654      ELSE                      ;   clop = "x"         ! no use of the mask value (require less cpu time)
655      ENDIF
656#        if defined key_diainstant
657      zsto=nwritebio*zdt
658      clop = "inst("//TRIM(clop)//")"
659#        else
660      zsto=zdt
661      clop = "ave("//TRIM(clop)//")"
662#        endif
663      zout=nwritebio*zdt
664
665      ! Define indices of the horizontal output zoom and vertical limit storage      iimi = 1      ;      iima = jpi
666      iimi = 1      ;      iima = jpi
667      ijmi = 1      ;      ijma = jpj
668      ipk = jpk
669
670      ! define time axis
671      it = kt
672      itmod = kt - nittrc000 + 1
673
674      ! Define NETCDF files and fields at beginning of first time step
675      ! --------------------------------------------------------------
676
677      IF(ll_print) WRITE(numout,*)'trcdib_wr kt=',kt,' kindic ',kindic
678
679      IF( kt == nittrc000 ) THEN
680
681         ! Define the NETCDF files for biological trends
682
683         CALL dia_nam(clhstnam,nwrite,'biolog')
684         IF(lwp)WRITE(numout,*) " Name of NETCDF file for biological trends ", clhstnam
685         ! Horizontal grid : glamt and gphit
686    CALL histbeg(clhstnam, jpi, glamt, jpj, gphit,      &
687            &    iimi, iima-iimi+1, ijmi, ijma-ijmi+1,          &
688            &    nittrc000-1, xjulian, rdt, nhoritb, nitb , domain_id=nidom)
689         ! Vertical grid for biological trends
690         CALL histvert(nitb, 'deptht', 'Vertical T levels',  &
691            &    'm', ipk, gdept_0, ndepitb, 'down')
692
693         ! Declare all the output fields as NETCDF variables
694         ! biological trends
695         DO jn = 1, jpdiabio
696            cltra  = ctrbio(jn)   ! short title for biological diagnostic
697            cltral = ctrbil(jn)   ! long title for biological diagnostic
698            cltrau = ctrbiu(jn)   ! 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 jn = 1, jpdiabio
722         cltra=ctrbio(jn)  ! short title for biological diagnostic
723         CALL histwrite(nitb, cltra, it, trbio(:,:,:,jn), ndimt50,ndext50)
724      END DO
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.