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

Last change on this file since 1070 was 1011, checked in by cetlod, 16 years ago

re-organization of TOP initialization and outputs phases see ticket 171

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 28.9 KB
Line 
1MODULE trcdia
2   !!======================================================================
3   !!                       *** MODULE trcdia ***
4   !! TOP :   Output of passive tracers
5   !!======================================================================
6   !! History :    -   !  1995-01 (M. Levy)  Original code
7   !!              -   !  1998-01 (C. Levy) NETCDF format using ioipsl interface
8   !!              -   !  1999-01 (M.A. Foujols) adapted for passive tracer
9   !!              -   !  1999-09 (M.A. Foujols) split into three parts
10   !!             1.0  !  2005-03 (O. Aumont, A. El Moussaoui) F90
11   !!                  !  2008-05 (C. Ethe re-organization)
12   !!----------------------------------------------------------------------
13#if defined key_top
14   !!----------------------------------------------------------------------
15   !!   'key_top'                                                TOP models
16   !!----------------------------------------------------------------------
17   !! trc_dia     : main routine of output passive tracer
18   !! trcdit_wr   : outputs of concentration fields
19   !! trcdid_wr   : outputs of dvection-diffusion trends
20   !! trcdii_wr   : outputs of additional 2D/3D diagnostics
21   !! trcdib_wr   : outputs of biological fields
22   !!----------------------------------------------------------------------
23   USE oce_trc
24   USE trc
25   USE dianam    ! build name of file (routine)
26   USE in_out_manager  ! I/O manager
27   USE lib_mpp
28   USE ioipsl
29
30   IMPLICIT NONE
31   PRIVATE
32
33   PUBLIC trc_dia     
34
35   INTEGER  ::   nit5      !: id for tracer output file
36   INTEGER  ::   ndepit5   !: id for depth mesh
37   INTEGER  ::   nhorit5   !: id for horizontal mesh
38   INTEGER  ::   ndimt50   !: number of ocean points in index array
39   INTEGER  ::   ndimt51   !: number of ocean points in index array
40   REAL(wp) ::   zjulian   !: ????   not DOCTOR !
41   INTEGER , DIMENSION (jpij*jpk) ::   ndext50   !: integer arrays for ocean 3D index
42   INTEGER , DIMENSION (jpij)     ::   ndext51   !: integer arrays for ocean surface index
43# if defined key_trc_diaadd
44   INTEGER  ::   nitd      !: id for additional array output file
45   INTEGER  ::   ndepitd   !: id for depth mesh
46   INTEGER  ::   nhoritd   !: id for horizontal mesh
47# endif
48# if defined key_trc_diatrd
49   INTEGER , DIMENSION (jptra) ::   nit6      !: id for additional array output file
50   INTEGER , DIMENSION (jptra) ::   ndepit6   !: id for depth mesh
51   INTEGER , DIMENSION (jptra) ::   nhorit6   !: id for horizontal mesh
52# endif
53# if defined key_trc_diabio
54   INTEGER  ::   ndepitb   !:  id for depth mesh
55   INTEGER  ::   nhoritb   !:  id for horizontal mesh
56# endif
57
58   !! * Substitutions
59#  include "top_substitute.h90"
60   !!----------------------------------------------------------------------
61   !! NEMO/TOP 1.0 , LOCEAN-IPSL (2005)
62   !! $Header:$
63   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
64   !!----------------------------------------------------------------------
65
66CONTAINS
67
68   SUBROUTINE trc_dia( kt, kindic ) 
69      !!---------------------------------------------------------------------
70      !!                     ***  ROUTINE trc_dia  ***
71      !!
72      !! ** Purpose :   output passive tracers fields
73      !!---------------------------------------------------------------------
74      INTEGER, INTENT( in ) :: kt, kindic
75      !!---------------------------------------------------------------------
76     
77      CALL trcdit_wr( kt, kindic )      ! outputs for tracer concentration
78     
79
80      CALL trcdid_wr( kt, kindic )      ! outputs for dynamical trends
81
82     
83      CALL trcdii_wr( kt, kindic )      ! outputs for additional arrays
84
85     
86      CALL trcdib_wr( kt, kindic )      ! outputs for biological trends
87
88      !
89   END SUBROUTINE trc_dia
90
91   SUBROUTINE trcdit_wr( kt, kindic )
92      !!----------------------------------------------------------------------
93      !!                     ***  ROUTINE trcdit_wr  ***
94      !!
95      !! ** Purpose :   Standard output of passive tracer : concentration fields
96      !!
97      !! ** Method  :   At the beginning of the first time step (nit000), define all
98      !!             the NETCDF files and fields for concentration of passive tracer
99      !!
100      !!        At each time step call histdef to compute the mean if necessary
101      !!        Each nwritetrc time step, output the instantaneous or mean fields
102      !!
103      !!        IF kindic <0, output of fields before the model interruption.
104      !!        IF kindic =0, time step loop
105      !!        IF kindic >0, output of fields before the time step loop
106      !!----------------------------------------------------------------------
107      INTEGER, INTENT( in ) ::   kt          ! ocean time-step
108      INTEGER, INTENT( in ) ::   kindic      ! indicator of abnormal termination
109      !!
110      INTEGER ::   jn
111      LOGICAL ::   ll_print = .FALSE.
112      CHARACTER (len=40) :: clhstnam, clop
113      CHARACTER (len=20) :: cltra, cltrau
114      CHARACTER (len=80) :: cltral
115      REAL(wp) :: zsto, zout, zdt
116      INTEGER  :: iimi, iima, ijmi, ijma, ipk, it
117      !!----------------------------------------------------------------------
118
119      ! Initialisation
120      ! --------------
121
122      ! local variable for debugging
123      ll_print = .FALSE.                  ! change it to true for more control print
124      ll_print = ll_print .AND. lwp
125
126      ! Define frequency of output and means
127      zdt = rdt
128# if defined key_diainstant
129      zsto = nwritetrc * rdt
130      clop = 'inst(only(x))'
131# else
132      zsto = zdt
133      clop = 'ave(only(x))'
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, 0.0, zjulian )
154         IF(lwp)WRITE(numout,*)' ' 
155         IF(lwp)WRITE(numout,*)' Date 0 used :', nittrc000                         &
156            &                 ,' YEAR ', nyear, ' MONTH ', nmonth, ' DAY ', nday   &
157            &                 ,'Julian day : ', zjulian   
158         IF(lwp) WRITE(numout,*) ' indexes of zoom = ', iimi, iima, ijmi, ijma,  &
159            &                    ' limit storage in depth = ', ipk
160
161
162! Define the NETCDF files for passive tracer concentration
163
164         CALL dia_nam( clhstnam, nwritetrc, 'ptrc_T' )
165         IF(lwp)WRITE(numout,*)" Name of NETCDF file ", clhstnam
166! Horizontal grid : glamt and gphit
167         CALL histbeg( clhstnam, jpi, glamt, jpj, gphit,     &
168            &          iimi, iima-iimi+1, ijmi, ijma-ijmi+1,         & 
169            &          0, zjulian, zdt, nhorit5, nit5 , domain_id=nidom)
170! Vertical grid for tracer : gdept
171         CALL histvert( nit5, 'deptht', 'Vertical T levels', &
172            &            'm', ipk, gdept_0, ndepit5)
173
174! Index of ocean points in 3D and 2D (surface)
175         CALL wheneq( jpi*jpj*ipk,tmask,1,1.,ndext50,ndimt50 )
176         CALL wheneq( jpi*jpj,tmask,1,1.,ndext51,ndimt51 )
177
178! Declare all the output fields as NETCDF variables
179
180! tracer concentrations
181         DO jn = 1, jptra
182            IF( lutsav(jn) ) THEN
183               cltra  = ctrcnm(jn)   ! short title for tracer
184               cltral = ctrcnl(jn)   ! long title for tracer
185               cltrau = ctrcun(jn)   ! UNIT for tracer
186               CALL histdef( nit5, cltra, cltral, cltrau, jpi, jpj, nhorit5,  &
187                  &               ipk, 1, ipk,  ndepit5, 32, clop, zsto, zout) 
188            ENDIF
189         END DO
190
191         ! end netcdf files header
192         CALL histend( nit5 )
193         IF(lwp) WRITE(numout,*)
194         IF(lwp) WRITE(numout,*) 'End of NetCDF Initialization in trcdit_wr'
195         IF( ll_print )   CALL FLUSH(numout )
196
197      ENDIF
198
199      ! Start writing the tracer concentrations
200      ! ---------------------------------------
201
202      IF( lwp .AND. MOD( kt, nwritetrc ) == 0 ) THEN
203         WRITE(numout,*) 'trcdit_wr : write NetCDF passive tracer concentrations at ', kt, 'time-step'
204         WRITE(numout,*) '~~~~~~~~~ '
205      ENDIF
206
207      DO jn = 1, jptra
208         IF( lutsav(jn) ) THEN
209            cltra = ctrcnm(jn)      ! short title for tracer
210            CALL histwrite( nit5, cltra, it, trn(:,:,:,jn), ndimt50, ndext50 )
211         ENDIF
212      END DO
213
214      ! synchronise file
215      IF( MOD( kt, nwritetrc ) == 0 .OR. kindic < 0 )   CALL histsync( nit5 )
216
217
218      ! close the file
219      ! --------------
220      IF( kt == nitend .OR. kindic < 0 )   CALL histclo( nit5 )
221      !
222   END SUBROUTINE trcdit_wr
223
224# if defined key_trc_diatrd
225
226   SUBROUTINE trcdid_wr( kt, kindic )
227      !!----------------------------------------------------------------------
228      !!                     ***  ROUTINE trcdid_wr  ***
229      !!
230      !! ** Purpose :   output of passive tracer : advection-diffusion trends
231      !!
232      !! ** Method  :   At the beginning of the first time step (nit000), define all
233      !!             the NETCDF files and fields for concentration of passive tracer
234      !!
235      !!        At each time step call histdef to compute the mean if necessary
236      !!        Each nwritetrc time step, output the instantaneous or mean fields
237      !!
238      !!        IF kindic <0, output of fields before the model interruption.
239      !!        IF kindic =0, time step loop
240      !!        IF kindic >0, output of fields before the time step loop
241      !!----------------------------------------------------------------------
242      INTEGER, INTENT( in ) ::   kt          ! ocean time-step
243      INTEGER, INTENT( in ) ::   kindic      ! indicator of abnormal termination
244      !!
245      LOGICAL ::   ll_print = .FALSE.
246      CHARACTER (len=40) ::   clhstnam, clop
247      CHARACTER (len=20) ::   cltra, cltrau
248      CHARACTER (len=80) ::   cltral
249      CHARACTER (len=10) ::   csuff
250      INTEGER  ::   jn, jl
251      INTEGER  ::   iimi, iima, ijmi, ijma, ipk, it
252      REAL(wp) ::   zsto, zout, zdt
253      !!----------------------------------------------------------------------
254
255      ! 0. Initialisation
256      ! -----------------
257
258      ! local variable for debugging
259      ll_print = .FALSE.
260      ll_print = ll_print .AND. lwp
261      !
262      ! Define frequency of output and means
263      zdt = rdt
264#  if defined key_diainstant
265      zsto = nwritetrd * rdt
266      clop = 'inst(only(x))'
267#  else
268      zsto = zdt
269      clop = 'ave(only(x))'
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_trc_ldfeiv
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( kt, 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)   &
439                  &          ,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  &
593            &           ,ndext50)
594      END DO
595
596      ! more 2D horizontal arrays
597      DO jn = 1, jpdia2d
598         cltra = ctrc2d(jn)   ! short title for 2D diagnostic
599         CALL histwrite(nitd, cltra, it, trc2d(:,:,jn), ndimt51    &
600            &   ,ndext51)
601      END DO
602
603      ! synchronise FILE
604      IF( MOD( kt, nwritedia ) == 0 .OR. kindic < 0 )   CALL histsync( nitd )
605
606      ! Closing all files
607      ! -----------------
608      IF( kt == nitend .OR. kindic < 0 )   CALL histclo(nitd)
609      !
610   END SUBROUTINE trcdii_wr
611
612# else
613
614   SUBROUTINE trcdii_wr( kt, kindic )                      ! Dummy routine
615      INTEGER, INTENT ( in ) :: kt, kindic
616   END SUBROUTINE trcdii_wr
617
618# endif
619
620# if defined key_trc_diabio
621
622   SUBROUTINE trcdib_wr( kt, kindic )
623      !!----------------------------------------------------------------------
624      !!                     ***  ROUTINE trcdib_wr  ***
625      !!
626      !! ** Purpose :   output of passive tracer : biological fields
627      !!
628      !! ** Method  :   At the beginning of the first time step (nit000), define all
629      !!             the NETCDF files and fields for concentration of passive tracer
630      !!
631      !!        At each time step call histdef to compute the mean if necessary
632      !!        Each nwritetrc time step, output the instantaneous or mean fields
633      !!
634      !!        IF kindic <0, output of fields before the model interruption.
635      !!        IF kindic =0, time step loop
636      !!        IF kindic >0, output of fields before the time step loop
637      !!----------------------------------------------------------------------
638      USE sms
639      !!
640      INTEGER, INTENT( in ) ::   kt          ! ocean time-step
641      INTEGER, INTENT( in ) ::   kindic      ! indicator of abnormal termination
642      !!
643      LOGICAL ::   ll_print = .FALSE.
644      CHARACTER (len=40) ::   clhstnam, clop
645      CHARACTER (len=20) ::   cltra, cltrau
646      CHARACTER (len=80) ::   cltral
647      INTEGER  ::   ji, jj, jk, jn
648      INTEGER  ::   iimi, iima, ijmi, ijma, ipk, it
649      REAL(wp) ::   zsto, zout, zdt
650      !!----------------------------------------------------------------------
651
652      ! Initialisation
653      ! --------------
654
655      ! local variable for debugging
656      ll_print = .FALSE.
657      ll_print = ll_print .AND. lwp
658
659      ! Define frequency of output and means
660      zdt = rdt
661#        if defined key_diainstant
662      zsto=nwritebio*zdt
663      clop='inst(only(x))'
664#        else
665      zsto=zdt
666      clop='ave(only(x))'
667#        endif
668      zout=nwritebio*zdt
669
670      ! Define indices of the horizontal output zoom and vertical limit storage      iimi = 1      ;      iima = jpi
671      iimi = 1      ;      iima = jpi
672      ijmi = 1      ;      ijma = jpj
673      ipk = jpk
674
675      ! define time axis
676      it = kt - nittrc000 + 1
677
678      ! Define NETCDF files and fields at beginning of first time step
679      ! --------------------------------------------------------------
680
681      IF(ll_print) WRITE(numout,*)'trcdib_wr kt=',kt,' kindic ',kindic
682
683      IF( kt == nittrc000 ) THEN
684
685         ! Define the NETCDF files for biological trends
686
687         CALL dia_nam(clhstnam,nwrite,'biolog')
688         IF(lwp)WRITE(numout,*) " Name of NETCDF file for biological trends ", clhstnam
689         ! Horizontal grid : glamt and gphit
690         CALL histbeg(clhstnam, jpi, glamt, jpj, gphit,      &
691            &    iimi, iima-iimi+1, ijmi, ijma-ijmi+1,          &
692            &    0, zjulian, rdt, nhoritb, nitb , domain_id=nidom)
693         ! Vertical grid for biological trends
694         CALL histvert(nitb, 'deptht', 'Vertical T levels',  &
695            &    'm', ipk, gdept_0, ndepitb)
696
697         ! Declare all the output fields as NETCDF variables
698         ! biological trends
699         DO jn = 1, jpdiabio
700            cltra  = ctrbio(jn)   ! short title for biological diagnostic
701            cltral = ctrbil(jn)   ! long title for biological diagnostic
702            cltrau = ctrbiu(jn)   ! UNIT for biological diagnostic
703            CALL histdef(nitb, cltra, cltral, cltrau, jpi, jpj, nhoritb,  &
704               &         ipk, 1, ipk,  ndepitb, 32, clop, zsto, zout)
705         END DO
706
707         ! CLOSE netcdf Files
708          CALL histend(nitb)
709
710         IF(lwp) WRITE(numout,*)
711         IF(lwp) WRITE(numout,*) 'End of NetCDF Initialization in trcdib_wr'
712         IF(ll_print) CALL FLUSH(numout )
713         !
714      ENDIF
715
716      ! Start writing data
717      ! ------------------
718
719      ! biological trends
720      IF( lwp .AND. MOD( kt, nwritebio ) == 0 ) THEN
721         WRITE(numout,*) 'trcdit_wr : write NetCDF biological trends at ', kt, 'time-step'
722         WRITE(numout,*) '~~~~~~ '
723      ENDIF
724
725      DO jn = 1, jpdiabio
726         cltra=ctrbio(jn)  ! short title for biological diagnostic
727         CALL histwrite(nitb, cltra, it, trbio(:,:,:,jn), ndimt50,ndext50)
728      END DO
729
730      ! synchronise FILE
731      IF( MOD( kt, nwritebio ) == 0 .OR. kindic < 0 )   CALL histsync( nitb )
732
733      ! Closing all files
734      ! -----------------
735      IF( kt == nitend .OR. kindic < 0 )   CALL histclo( nitb )
736      !
737   END SUBROUTINE trcdib_wr
738
739# else
740
741   SUBROUTINE trcdib_wr( kt, kindic )                      ! Dummy routine
742      INTEGER, INTENT ( in ) ::   kt, kindic
743   END SUBROUTINE trcdib_wr
744
745# endif 
746
747#else
748   !!----------------------------------------------------------------------
749   !!  Dummy module :                                     No passive tracer
750   !!----------------------------------------------------------------------
751CONTAINS
752   SUBROUTINE trc_dia                      ! Empty routine   
753   END SUBROUTINE trc_dia   
754
755#endif
756
757   !!======================================================================
758END MODULE trcdia
Note: See TracBrowser for help on using the repository browser.