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

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

supress useless call to histsync, see ticket:340

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