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

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

dev_001_GM - small error corrections

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