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.
trcdit.F90 in branches/dev_001_GM/NEMO/TOP_SRC – NEMO

source: branches/dev_001_GM/NEMO/TOP_SRC/trcdit.F90 @ 768

Last change on this file since 768 was 768, checked in by gm, 16 years ago

dev_001_GM - create 1 trclsm_ module by trc model (CFC, LOBSTER, PISCES..) + some bug corrections

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