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

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

add a namelist logical to mask land points in NetCDF outputs, see ticket:322

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