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

source: trunk/NEMO/TOP_SRC/trcdit.F90 @ 1004

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

Update modules for new version of TOP model, see ticket 144

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