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 branches/CMIP5_IPSL/NEMO/TOP_SRC – NEMO

source: branches/CMIP5_IPSL/NEMO/TOP_SRC/trcdia.F90 @ 1846

Last change on this file since 1846 was 1846, checked in by mafoipsl, 14 years ago

Increase length of characters string to allow long name of experiments.

  • Property svn:eol-style set to native
  • Property svn:keywords set to Id
File size: 28.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 && ! defined key_iomput
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 dom_oce         ! ocean space and time domain variables
24   USE oce_trc
25   USE trp_trc
26   USE trc
27   USE par_trc
28   USE trctrp
29   USE trdmld_trc_oce, ONLY : luttrd
30   USE iom
31   USE dianam    ! build name of file (routine)
32   USE in_out_manager  ! I/O manager
33   USE lib_mpp
34   USE ioipsl
35
36   IMPLICIT NONE
37   PRIVATE
38
39   PUBLIC trc_dia     
40
41   INTEGER  ::   nit5      !: id for tracer output file
42   INTEGER  ::   ndepit5   !: id for depth mesh
43   INTEGER  ::   nhorit5   !: id for horizontal mesh
44   INTEGER  ::   ndimt50   !: number of ocean points in index array
45   INTEGER  ::   ndimt51   !: number of ocean points in index array
46   REAL(wp) ::   zjulian   !: ????   not DOCTOR !
47   INTEGER , DIMENSION (jpij*jpk) ::   ndext50   !: integer arrays for ocean 3D index
48   INTEGER , DIMENSION (jpij)     ::   ndext51   !: integer arrays for ocean surface index
49# if defined key_trc_diaadd
50   INTEGER  ::   nitd      !: id for additional array output file
51   INTEGER  ::   ndepitd   !: id for depth mesh
52   INTEGER  ::   nhoritd   !: id for horizontal mesh
53# endif
54# if defined key_trc_diatrd
55   INTEGER , DIMENSION (jptra) ::   nit6      !: id for additional array output file
56   INTEGER , DIMENSION (jptra) ::   ndepit6   !: id for depth mesh
57   INTEGER , DIMENSION (jptra) ::   nhorit6   !: id for horizontal mesh
58# endif
59# if defined key_trc_diabio
60   INTEGER  ::   nitb        !:         id.         for additional array output file
61   INTEGER  ::   ndepitb   !:  id for depth mesh
62   INTEGER  ::   nhoritb   !:  id for horizontal mesh
63# endif
64
65   !! * Substitutions
66#  include "top_substitute.h90"
67   !!----------------------------------------------------------------------
68   !! NEMO/TOP 1.0 , LOCEAN-IPSL (2005)
69   !! $Header:$
70   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
71   !!----------------------------------------------------------------------
72
73CONTAINS
74
75   SUBROUTINE trc_dia( kt, kindic ) 
76      !!---------------------------------------------------------------------
77      !!                     ***  ROUTINE trc_dia  ***
78      !!
79      !! ** Purpose :   output passive tracers fields
80      !!---------------------------------------------------------------------
81      INTEGER, INTENT( in ) :: kt
82      INTEGER         :: kindic
83      !!---------------------------------------------------------------------
84     
85      CALL trcdit_wr( kt, kindic )      ! outputs for tracer concentration
86      CALL trcdid_wr( kt, kindic )      ! outputs for dynamical trends
87      CALL trcdii_wr( kt, kindic )      ! outputs for additional arrays
88      CALL trcdib_wr( kt, kindic )      ! outputs for biological trends
89
90      !
91   END SUBROUTINE trc_dia
92
93   SUBROUTINE trcdit_wr( kt, kindic )
94      !!----------------------------------------------------------------------
95      !!                     ***  ROUTINE trcdit_wr  ***
96      !!
97      !! ** Purpose :   Standard output of passive tracer : concentration fields
98      !!
99      !! ** Method  :   At the beginning of the first time step (nit000), define all
100      !!             the NETCDF files and fields for concentration of passive tracer
101      !!
102      !!        At each time step call histdef to compute the mean if necessary
103      !!        Each nwritetrc time step, output the instantaneous or mean fields
104      !!
105      !!        IF kindic <0, output of fields before the model interruption.
106      !!        IF kindic =0, time step loop
107      !!        IF kindic >0, output of fields before the time step loop
108      !!----------------------------------------------------------------------
109      INTEGER, INTENT( in ) ::   kt          ! ocean time-step
110      INTEGER, INTENT( in ) ::   kindic      ! indicator of abnormal termination
111      !!
112      INTEGER ::   jn
113      LOGICAL ::   ll_print = .FALSE.
114      CHARACTER (len=72) :: clhstnam, clop
115      CHARACTER (len=20) :: cltra, cltrau
116      CHARACTER (len=80) :: cltral
117      REAL(wp) :: zsto, zout, zdt
118      INTEGER  :: iimi, iima, ijmi, ijma, ipk, it
119      !!----------------------------------------------------------------------
120
121      ! Initialisation
122      ! --------------
123
124      ! local variable for debugging
125      ll_print = .FALSE.                  ! change it to true for more control print
126      ll_print = ll_print .AND. lwp
127
128      ! Define frequency of output and means
129      zdt = rdt
130# if defined key_diainstant
131      zsto = nwritetrc * rdt
132      clop = 'inst(only(x))'
133# else
134      zsto = zdt
135      clop = 'ave(only(x))'
136# endif
137      zout = nwritetrc * zdt
138
139      ! Define indices of the horizontal output zoom and vertical limit storage
140      iimi = 1      ;      iima = jpi
141      ijmi = 1      ;      ijma = jpj
142      ipk = jpk
143
144      ! define time axis
145      it = kt - nittrc000 + 1
146
147      ! Define NETCDF files and fields at beginning of first time step
148      ! --------------------------------------------------------------
149
150      IF(ll_print)WRITE(numout,*)'trcdit_wr kt=',kt,' kindic ',kindic
151     
152      IF( kt == nittrc000 ) THEN
153
154         ! Compute julian date from starting date of the run
155         CALL ymds2ju( nyear, nmonth, nday, 0.0, zjulian )
156         IF(lwp)WRITE(numout,*)' ' 
157         IF(lwp)WRITE(numout,*)' Date 0 used :', nittrc000                         &
158            &                 ,' YEAR ', nyear, ' MONTH ', nmonth, ' DAY ', nday   &
159            &                 ,'Julian day : ', zjulian   
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            &          0, zjulian, 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)
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( kt, 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      ! synchronise file
217      IF( MOD( kt, nwritetrc ) == 0 .OR. kindic < 0 )   CALL histsync( nit5 )
218
219
220      ! close the file
221      ! --------------
222      IF( kt == nitend .OR. kindic < 0 )   CALL histclo( nit5 )
223      !
224   END SUBROUTINE trcdit_wr
225
226# if defined key_trc_diatrd
227
228   SUBROUTINE trcdid_wr( kt, kindic )
229      !!----------------------------------------------------------------------
230      !!                     ***  ROUTINE trcdid_wr  ***
231      !!
232      !! ** Purpose :   output of passive tracer : advection-diffusion trends
233      !!
234      !! ** Method  :   At the beginning of the first time step (nit000), define all
235      !!             the NETCDF files and fields for concentration of passive tracer
236      !!
237      !!        At each time step call histdef to compute the mean if necessary
238      !!        Each nwritetrc time step, output the instantaneous or mean fields
239      !!
240      !!        IF kindic <0, output of fields before the model interruption.
241      !!        IF kindic =0, time step loop
242      !!        IF kindic >0, output of fields before the time step loop
243      !!----------------------------------------------------------------------
244      INTEGER, INTENT( in ) ::   kt          ! ocean time-step
245      INTEGER, INTENT( in ) ::   kindic      ! indicator of abnormal termination
246      !!
247      LOGICAL ::   ll_print = .FALSE.
248      CHARACTER (len=72) ::   clhstnam, clop
249      CHARACTER (len=20) ::   cltra, cltrau
250      CHARACTER (len=80) ::   cltral
251      CHARACTER (len=10) ::   csuff
252      INTEGER  ::   jn, jl, ikn
253      INTEGER  ::   iimi, iima, ijmi, ijma, ipk, it
254      REAL(wp) ::   zsto, zout, zdt
255      !!----------------------------------------------------------------------
256
257      ! 0. Initialisation
258      ! -----------------
259
260      ! local variable for debugging
261      ll_print = .FALSE.
262      ll_print = ll_print .AND. lwp
263      !
264      ! Define frequency of output and means
265      zdt = rdt
266#  if defined key_diainstant
267      zsto = nwritetrd * rdt
268      clop = 'inst(only(x))'
269#  else
270      zsto = zdt
271      clop = 'ave(only(x))'
272#  endif
273      zout = nwritetrd * zdt
274
275      ! Define indices of the horizontal output zoom and vertical limit storage
276      iimi = 1      ;      iima = jpi
277      ijmi = 1      ;      ijma = jpj
278      ipk = jpk
279
280      ! define time axis
281      it = 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                  &          0, zjulian, 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) ) 
308             END IF
309          END DO
310
311          ! Declare all the output fields as NETCDF variables
312          DO jn = 1, jptra
313            IF( luttrd(jn) ) THEN
314                DO jl = 1, jpdiatrc
315                  IF( jl == jptrc_xad ) 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)') ctrcnl(jn)(1:58)
319                  END IF
320                  IF( jl == jptrc_yad ) THEN
321                      ! short and long title for y advection for tracer
322                      WRITE (cltra,'("YAD_",16a)') ctrcnm(jn)
323                      WRITE (cltral,'("Y advective trend for ",58a)') ctrcnl(jn)(1:58)
324                  END IF
325                  IF( jl == jptrc_zad ) THEN
326                      ! short and long title for Z advection for tracer
327                      WRITE (cltra,'("ZAD_",16a)') ctrcnm(jn)
328                      WRITE (cltral,'("Z advective trend for ",58a)') ctrcnl(jn)(1:58)
329                  END IF
330                  IF( jl == jptrc_xdf ) THEN
331                      ! short and long title for X diffusion for tracer
332                      WRITE (cltra,'("XDF_",16a)') ctrcnm(jn)
333                      WRITE (cltral,'("X diffusion trend for ",58a)') ctrcnl(jn)(1:58)
334                  END IF
335                  IF( jl == jptrc_ydf ) THEN
336                      ! short and long title for Y diffusion for tracer
337                      WRITE (cltra,'("YDF_",16a)') ctrcnm(jn)
338                      WRITE (cltral,'("Y diffusion trend for ",58a)') ctrcnl(jn)(1:58)
339                  END IF
340                  IF( jl == jptrc_zdf ) THEN
341                      ! short and long title for Z diffusion for tracer
342                      WRITE (cltra,'("ZDF_",16a)') ctrcnm(jn)
343                      WRITE (cltral,'("Z diffusion trend for ",58a)') ctrcnl(jn)(1:58)
344                  END IF
345# if defined key_trcldf_eiv
346                  IF( jl == jptrc_xei ) THEN
347                      ! short and long title for x gent velocity for tracer
348                      WRITE (cltra,'("XGV_",16a)') ctrcnm(jn)
349                      WRITE (cltral,'("X gent velocity trend for ",53a)') ctrcnl(jn)(1:53)
350                  END IF
351                  IF( jl == jptrc_yei ) THEN
352                      ! short and long title for y gent velocity for tracer
353                      WRITE (cltra,'("YGV_",16a)') ctrcnm(jn)
354                      WRITE (cltral,'("Y gent velocity trend for ",53a)') ctrcnl(jn)(1:53)
355                  END IF
356                  IF( jl == jptrc_zei ) THEN
357                      ! short and long title for Z gent velocity for tracer
358                      WRITE (cltra,'("ZGV_",16a)') ctrcnm(jn)
359                      WRITE (cltral,'("Z gent velocity trend for ",53a)') ctrcnl(jn)(1:53)
360                  END IF
361# endif
362# if defined key_trcdmp
363                  IF( jl == jptrc_dmp ) THEN
364                      ! last trends for tracer damping : short and long title
365                      WRITE (cltra,'("TDM_",16a)') ctrcnm(jn)
366                      WRITE (cltral,'("Tracer damping trend for ",55a)') ctrcnl(jn)(1:55)
367                  END IF
368# endif
369                  IF( jl == jptrc_sbc ) THEN
370                      ! last trends for tracer damping : short and long title
371                      WRITE (cltra,'("SBC_",16a)') ctrcnm(jn)
372                      WRITE (cltral,'("Surface boundary flux ",58a)') ctrcnl(jn)(1:55)
373                  END IF
374                      WRITE (cltral,'("Surface boundary flux ",58a)') ctrcnl(jn)(1:55)
375                  END IF
376                  CALL FLUSH( numout )
377                  cltrau = ctrcun(jn)      ! UNIT for tracer /trends
378                  CALL histdef( nit6(jn), cltra, cltral, cltrau, jpi,jpj,  &
379                     &          nhorit6(jn), ipk, 1, ipk,  ndepit6(jn), 32, clop ,  &
380                     &          zsto,zout )
381               END DO
382            END IF
383         END DO
384
385         ! CLOSE netcdf Files
386          DO jn = 1, jptra
387             IF( luttrd(jn) )   CALL histend( nit6(jn) )
388          END DO
389
390         IF(lwp) WRITE(numout,*)
391         IF(lwp) WRITE(numout,*) 'End of NetCDF Initialization in trcdid'
392         IF(ll_print) CALL FLUSH(numout )
393         !
394      ENDIF
395
396      ! SOME diagnostics to DO first time
397
398      ! Start writing data
399      ! ---------------------
400
401      ! trends for tracer concentrations
402
403      IF( lwp .AND. MOD( kt, nwritetrd ) == 0 ) THEN
404         WRITE(numout,*) 'trcdid_wr : write NetCDF dynamical trends at ', kt, 'time-step'
405         WRITE(numout,*) '~~~~~~ '
406      ENDIF
407
408      DO jn = 1, jptra
409         IF( luttrd(jn) ) THEN
410            ikn = ikeep(jn)
411            DO jl = 1, jpdiatrc
412               ! short titles
413               IF( jl == jptrc_xad)   WRITE (cltra,'("XAD_",16a)') ctrcnm(jn)
414               IF( jl == jptrc_yad)   WRITE (cltra,'("YAD_",16a)') ctrcnm(jn)
415               IF( jl == jptrc_zad)   WRITE (cltra,'("ZAD_",16a)') ctrcnm(jn)
416               IF( jl == jptrc_xdf)   WRITE (cltra,'("XDF_",16a)') ctrcnm(jn)
417               IF( jl == jptrc_ydf)   WRITE (cltra,'("YDF_",16a)') ctrcnm(jn)
418               IF( jl == jptrc_zdf)   WRITE (cltra,'("ZDF_",16a)') ctrcnm(jn)
419# if defined key_trcldf_eiv
420               IF( jl == jptrc_xei)   WRITE (cltra,'("XGV_",16a)') ctrcnm(jn)
421               IF( jl == jptrc_yei)   WRITE (cltra,'("YGV_",16a)') ctrcnm(jn)
422               IF( jl == jptrc_zei)   WRITE (cltra,'("ZGV_",16a)') ctrcnm(jn)
423# endif
424# if defined key_trcdmp
425               IF( jl == jptrc_dmp )  WRITE (cltra,'("TDM_",16a)') ctrcnm(jn)
426# endif
427               IF( jl == jptrc_sbc )  WRITE (cltra,'("SBC_",16a)') ctrcnm(jn)
428               !
429               CALL histwrite(nit6(jn), cltra, it, trtrd(:,:,:,ikn,jl),ndimt50, ndext50)
430            END DO
431         END IF
432      END DO
433
434      ! synchronise FILE
435      IF( MOD( kt, nwritetrd ) == 0 .OR. kindic < 0 ) THEN
436         DO jn = 1, jptra
437            IF (luttrd(jn))   CALL histsync( nit6(jn) )
438         END DO
439      ENDIF
440
441      ! Closing all files
442      ! -----------------
443      IF( kt == nitend .OR. kindic < 0 ) THEN
444         DO jn = 1, jptra
445            IF( luttrd(jn) )   CALL histclo( nit6(jn) )
446         END DO
447      ENDIF
448      !
449   END SUBROUTINE trcdid_wr
450
451# else
452
453   SUBROUTINE trcdid_wr( kt, kindic )                      ! Dummy routine
454      INTEGER, INTENT ( in ) ::   kt, kindic
455   END SUBROUTINE trcdid_wr
456
457# endif
458
459#if defined key_trc_diaadd
460
461   SUBROUTINE trcdii_wr( kt, kindic )
462      !!----------------------------------------------------------------------
463      !!                     ***  ROUTINE trcdii_wr  ***
464      !!
465      !! ** Purpose :   output of passive tracer : additional 2D and 3D arrays
466      !!
467      !! ** Method  :   At the beginning of the first time step (nit000), define all
468      !!             the NETCDF files and fields for concentration of passive tracer
469      !!
470      !!        At each time step call histdef to compute the mean if necessary
471      !!        Each nwritetrc time step, output the instantaneous or mean fields
472      !!
473      !!        IF kindic <0, output of fields before the model interruption.
474      !!        IF kindic =0, time step loop
475      !!        IF kindic >0, output of fields before the time step loop
476      !!----------------------------------------------------------------------
477      INTEGER, INTENT( in ) ::   kt          ! ocean time-step
478      INTEGER, INTENT( in ) ::   kindic      ! indicator of abnormal termination
479      !!
480      LOGICAL ::   ll_print = .FALSE.
481      CHARACTER (len=72) ::   clhstnam, clop
482      CHARACTER (len=20) ::   cltra, cltrau
483      CHARACTER (len=80) ::   cltral
484      INTEGER  ::   jn
485      INTEGER  ::   iimi, iima, ijmi, ijma, ipk, it
486      REAL(wp) ::   zsto, zout, zdt
487      !!----------------------------------------------------------------------
488
489      ! Initialisation
490      ! --------------
491
492      ! local variable for debugging
493      ll_print = .FALSE.
494      ll_print = ll_print .AND. lwp
495      !
496      ! Define frequency of output and means
497      zdt = rdt
498#  if defined key_diainstant
499      zsto=nwritedia*zdt
500      clop='inst(only(x))'
501#  else
502      zsto=zdt
503      clop='ave(only(x))'
504#  endif
505      zout=nwritedia*zdt
506
507      ! Define indices of the horizontal output zoom and vertical limit storage
508      iimi = 1      ;      iima = jpi
509      ijmi = 1      ;      ijma = jpj
510      ipk = jpk
511
512      ! define time axis
513      it = kt - nittrc000 + 1
514
515      ! 1. Define NETCDF files and fields at beginning of first time step
516      ! -----------------------------------------------------------------
517
518      IF( ll_print ) WRITE(numout,*) 'trcdii_wr kt=', kt, ' kindic ', kindic
519
520      IF( kt == nittrc000 ) THEN
521
522         ! Define the NETCDF files for additional arrays : 2D or 3D
523
524         ! Define the T grid file for tracer auxiliary files
525
526         CALL dia_nam( clhstnam, nwrite, 'diad_T' )
527         IF(lwp) WRITE(numout,*) " Name of NETCDF file ", clhstnam
528
529         ! Define a netcdf FILE for 2d and 3d arrays
530
531         CALL histbeg( clhstnam, jpi, glamt, jpj, gphit,             &
532            &          iimi, iima-iimi+1, ijmi, ijma-ijmi+1,         &
533            &          0, zjulian, zdt, nhoritd, nitd , domain_id=nidom )
534
535         ! Vertical grid for 2d and 3d arrays
536
537         CALL histvert( nitd, 'deptht', 'Vertical T levels',   &
538            &           'm', ipk, gdept_0, ndepitd)
539
540         ! Declare all the output fields as NETCDF variables
541
542         ! more 3D horizontal arrays
543         DO jn = 1, jpdia3d
544            cltra  = ctrc3d(jn)   ! short title for 3D diagnostic
545            cltral = ctrc3l(jn)   ! long title for 3D diagnostic
546            cltrau = ctrc3u(jn)   ! UNIT for 3D diagnostic
547            CALL histdef( nitd, cltra, cltral, cltrau, jpi, jpj, nhoritd,   &
548               &          ipk, 1, ipk,  ndepitd, 32, clop, zsto, zout )
549         END DO
550
551         ! more 2D horizontal arrays
552         DO jn = 1, jpdia2d
553            cltra  = ctrc2d(jn)    ! short title for 2D diagnostic
554            cltral = ctrc2l(jn)   ! long title for 2D diagnostic
555            cltrau = ctrc2u(jn)   ! UNIT for 2D diagnostic
556            CALL histdef( nitd, cltra, cltral, cltrau, jpi, jpj, nhoritd,  &
557               &          1, 1, 1,  -99, 32, clop, zsto, zout )
558         END DO
559
560         ! TODO: more 2D vertical sections arrays : I or J indice fixed
561
562         ! CLOSE netcdf Files
563         CALL histend( nitd )
564
565         IF(lwp) WRITE(numout,*)
566         IF(lwp) WRITE(numout,*) 'End of NetCDF Initialization in trcdii_wr'
567         IF( ll_print )   CALL FLUSH(numout )
568         !
569      ENDIF
570
571      ! 2. Start writing data
572      ! ---------------------
573
574      IF( lwp .AND. MOD( kt, nwritedia ) == 0 ) THEN
575         WRITE(numout,*) 'trcdii_wr : write NetCDF additional arrays at ', kt, 'time-step'
576         WRITE(numout,*) '~~~~~~ '
577      ENDIF
578
579      ! more 3D horizontal arrays
580      DO jn = 1, jpdia3d
581         cltra = ctrc3d(jn)   ! short title for 3D diagnostic
582         CALL histwrite( nitd, cltra, it, trc3d(:,:,:,jn), ndimt50 ,ndext50)
583      END DO
584
585      ! more 2D horizontal arrays
586      DO jn = 1, jpdia2d
587         cltra = ctrc2d(jn)   ! short title for 2D diagnostic
588         CALL histwrite(nitd, cltra, it, trc2d(:,:,jn), ndimt51  ,ndext51)
589      END DO
590
591      ! synchronise FILE
592      IF( MOD( kt, nwritedia ) == 0 .OR. kindic < 0 )   CALL histsync( nitd )
593
594      ! Closing all files
595      ! -----------------
596      IF( kt == nitend .OR. kindic < 0 )   CALL histclo(nitd)
597      !
598   END SUBROUTINE trcdii_wr
599
600# else
601
602   SUBROUTINE trcdii_wr( kt, kindic )                      ! Dummy routine
603      INTEGER, INTENT ( in ) :: kt, kindic
604   END SUBROUTINE trcdii_wr
605
606# endif
607
608# if defined key_trc_diabio
609
610   SUBROUTINE trcdib_wr( kt, kindic )
611      !!----------------------------------------------------------------------
612      !!                     ***  ROUTINE trcdib_wr  ***
613      !!
614      !! ** Purpose :   output of passive tracer : biological fields
615      !!
616      !! ** Method  :   At the beginning of the first time step (nit000), define all
617      !!             the NETCDF files and fields for concentration of passive tracer
618      !!
619      !!        At each time step call histdef to compute the mean if necessary
620      !!        Each nwritetrc time step, output the instantaneous or mean fields
621      !!
622      !!        IF kindic <0, output of fields before the model interruption.
623      !!        IF kindic =0, time step loop
624      !!        IF kindic >0, output of fields before the time step loop
625      !!----------------------------------------------------------------------
626      !!
627      INTEGER, INTENT( in ) ::   kt          ! ocean time-step
628      INTEGER, INTENT( in ) ::   kindic      ! indicator of abnormal termination
629      !!
630      LOGICAL ::   ll_print = .FALSE.
631      CHARACTER (len=72) ::   clhstnam, clop
632      CHARACTER (len=20) ::   cltra, cltrau
633      CHARACTER (len=80) ::   cltral
634      INTEGER  ::   ji, jj, jk, jn
635      INTEGER  ::   iimi, iima, ijmi, ijma, ipk, it
636      REAL(wp) ::   zsto, zout, zdt
637      !!----------------------------------------------------------------------
638
639      ! Initialisation
640      ! --------------
641
642      ! local variable for debugging
643      ll_print = .FALSE.
644      ll_print = ll_print .AND. lwp
645
646      ! Define frequency of output and means
647      zdt = rdt
648#        if defined key_diainstant
649      zsto=nwritebio*zdt
650      clop='inst(only(x))'
651#        else
652      zsto=zdt
653      clop='ave(only(x))'
654#        endif
655      zout=nwritebio*zdt
656
657      ! Define indices of the horizontal output zoom and vertical limit storage      iimi = 1      ;      iima = jpi
658      iimi = 1      ;      iima = jpi
659      ijmi = 1      ;      ijma = jpj
660      ipk = jpk
661
662      ! define time axis
663      it = kt - nittrc000 + 1
664
665      ! Define NETCDF files and fields at beginning of first time step
666      ! --------------------------------------------------------------
667
668      IF(ll_print) WRITE(numout,*)'trcdib_wr kt=',kt,' kindic ',kindic
669
670      IF( kt == nittrc000 ) THEN
671
672         ! Define the NETCDF files for biological trends
673
674         CALL dia_nam(clhstnam,nwrite,'biolog')
675         IF(lwp)WRITE(numout,*) " Name of NETCDF file for biological trends ", clhstnam
676         ! Horizontal grid : glamt and gphit
677         CALL histbeg(clhstnam, jpi, glamt, jpj, gphit,      &
678            &    iimi, iima-iimi+1, ijmi, ijma-ijmi+1,          &
679            &    0, zjulian, rdt, nhoritb, nitb , domain_id=nidom)
680         ! Vertical grid for biological trends
681         CALL histvert(nitb, 'deptht', 'Vertical T levels',  &
682            &    'm', ipk, gdept_0, ndepitb)
683
684         ! Declare all the output fields as NETCDF variables
685         ! biological trends
686         DO jn = 1, jpdiabio
687            cltra  = ctrbio(jn)   ! short title for biological diagnostic
688            cltral = ctrbil(jn)   ! long title for biological diagnostic
689            cltrau = ctrbiu(jn)   ! UNIT for biological diagnostic
690            CALL histdef(nitb, cltra, cltral, cltrau, jpi, jpj, nhoritb,  &
691               &         ipk, 1, ipk,  ndepitb, 32, clop, zsto, zout)
692         END DO
693
694         ! CLOSE netcdf Files
695          CALL histend(nitb)
696
697         IF(lwp) WRITE(numout,*)
698         IF(lwp) WRITE(numout,*) 'End of NetCDF Initialization in trcdib_wr'
699         IF(ll_print) CALL FLUSH(numout )
700         !
701      ENDIF
702
703      ! Start writing data
704      ! ------------------
705
706      ! biological trends
707      IF( lwp .AND. MOD( kt, nwritebio ) == 0 ) THEN
708         WRITE(numout,*) 'trcdit_wr : write NetCDF biological trends at ', kt, 'time-step'
709         WRITE(numout,*) '~~~~~~ '
710      ENDIF
711
712      DO jn = 1, jpdiabio
713         cltra=ctrbio(jn)  ! short title for biological diagnostic
714         CALL histwrite(nitb, cltra, it, trbio(:,:,:,jn), ndimt50,ndext50)
715      END DO
716
717      ! synchronise FILE
718      IF( MOD( kt, nwritebio ) == 0 .OR. kindic < 0 )   CALL histsync( nitb )
719
720      ! Closing all files
721      ! -----------------
722      IF( kt == nitend .OR. kindic < 0 )   CALL histclo( nitb )
723      !
724   END SUBROUTINE trcdib_wr
725
726# else
727
728   SUBROUTINE trcdib_wr( kt, kindic )                      ! Dummy routine
729      INTEGER, INTENT ( in ) ::   kt, kindic
730   END SUBROUTINE trcdib_wr
731
732# endif 
733
734#else
735   !!----------------------------------------------------------------------
736   !!  Dummy module :                                     No passive tracer
737   !!----------------------------------------------------------------------
738CONTAINS
739   SUBROUTINE trc_dia( kt )                      ! Empty routine
740      INTEGER, INTENT(in) :: kt
741   END SUBROUTINE trc_dia
742
743#endif
744
745   !!======================================================================
746END MODULE trcdia
Note: See TracBrowser for help on using the repository browser.