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

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

style of all top namelist has been modified ; update modules to take it into account, see ticket:196

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