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

Last change on this file since 489 was 489, checked in by opalod, 18 years ago

nemo_v1_bugfix_052:CE+RB: correct time step parameter in histwrite call

  • 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   !!  TOP 1.0,  LOCEAN-IPSL (2005)
4   !! $Header$
5   !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt
6   !!----------------------------------------------------------------------
7   !! * Modules used
8   !! ==============
9   USE oce_trc
10   USE trc
11   USE dianam    ! build name of file (routine)
12   USE in_out_manager  ! I/O manager
13   USE lib_mpp
14
15   IMPLICIT NONE
16   PRIVATE
17
18   !! * Accessibility
19   PUBLIC trcdit_wr
20   PUBLIC trcdid_wr
21   PUBLIC trcdii_wr
22   PUBLIC trcdib_wr
23
24   !! * Module variables
25   INTEGER            ::  &
26      nit5     ,  &   !!: id for tracer output file
27      ndepit5  ,  &   !!: id for depth mesh
28      nhorit5  ,  &   !!: id for horizontal mesh
29      ndimt50  ,  &   !!: number of ocean points in index array
30      ndimt51         !!: number of ocean points in index array
31   REAL(wp) :: zjulian
32   INTEGER , DIMENSION (jpij*jpk) ::  ndext50 !!: integer arrays for ocean 3D index
33   INTEGER , DIMENSION (jpij)     ::  ndext51 !!: integer arrays for ocean surface index
34#    if defined key_passivetrc && defined key_trc_diaadd
35   INTEGER            :: &
36      nitd     ,  &   !!: id for additional array output file
37      ndepitd  ,  &   !!: id for depth mesh
38      nhoritd         !!: id for horizontal mesh
39#    endif
40#    if defined key_passivetrc && defined key_trc_diatrd
41   INTEGER , DIMENSION (jptra)  :: &
42      nit6    ,   &   !!: id for additional array output file
43      ndepit6 ,   &   !!: id for depth mesh
44      nhorit6         !!: id for horizontal mesh
45#    endif
46#    if defined key_passivetrc && defined key_trc_diabio
47   INTEGER            :: &
48      nitb     ,   &  !!:  id for additional array output FILE
49      ndepitb  ,   &  !!:  id for depth mesh
50      nhoritb         !!:  id for horizontal mesh
51
52#    endif
53
54
55   !! * Substitutions
56#  include "passivetrc_substitute.h90"
57
58CONTAINS
59
60#    if defined key_passivetrc
61
62      SUBROUTINE trcdit_wr(kt,kindic)
63   !!===========================================================================================
64   !!
65   !!                       ROUTINE trcdit_wr
66   !!===========================================================================================
67   !!
68   !! Purpose :
69   !!---------
70   !!          Standard output of passive tracer : concentration fields
71   !!
72   !!
73   !! Method :
74   !! -------
75   !!
76   !!        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   !! Input :
87   !! -----
88   !!   argument
89   !!           kt              : time step
90   !!           kindic          : indicator of abnormal termination
91   !!
92   !! EXTERNAL :
93   !! --------
94   !! prihre, hist..., dianam
95   !!
96   !! History:
97   !! --------
98   !!   original  : 95-01  passive tracers  (M. Levy)
99   !!   additions : 98-01 (C. Levy) NETCDF format using ioipsl interface
100   !!   additions : 99-01 (M.A. Foujols) adapted for passive tracer
101   !!   additions : 99-09 (M.A. Foujols) split into three parts
102   !!   05-03 (O. Aumont and A. El Moussaoui) F90
103   !!==================================================================================================!
104
105      !! Modules used
106      USE ioipsl
107
108
109      !! * Arguments
110      INTEGER, INTENT( in ) ::   kt,kindic         ! ocean time-step
111
112      !! * Local declarations
113      INTEGER :: jn
114      LOGICAL :: ll_print = .FALSE.
115
116      CHARACTER (len=40) :: clhstnam, clop
117      CHARACTER (len=20) :: cltra, cltrau
118      CHARACTER (len=80) :: cltral
119
120      REAL(wp) :: zsto, zout, zdt
121      INTEGER  :: iimi, iima, ijmi, ijma, ipk, it
122!
123! 0. Initialisation
124! -----------------
125
126! local variable for debugging
127      ll_print = .FALSE.
128      ll_print = ll_print .AND. lwp
129
130! Define frequency of output and means
131
132      zdt = rdt
133#        if defined key_diainstant
134      zsto=nwritetrc*rdt
135      clop='inst(only(x))'
136#        else
137      zsto=zdt
138      clop='ave(only(x))'
139#        endif
140      zout=nwritetrc*zdt
141
142      ! Define indices of the horizontal output zoom and vertical limit storage
143      iimi = 1      ;      iima = jpi
144      ijmi = 1      ;      ijma = jpj
145      ipk = jpk
146
147      ! define time axis
148      it = kt - nittrc000 + 1
149
150! 1. Define NETCDF files and fields at beginning of first time step
151! -----------------------------------------------------------------
152
153      IF(ll_print)WRITE(numout,*)'trcdit_wr kt=',kt,' kindic ',kindic
154      IF(kt == nittrc000) THEN
155
156! Compute julian date from starting date of the run
157
158         CALL ymds2ju(nyear,nmonth,nday,0.0,zjulian)
159         IF(lwp)WRITE(numout,*)' ' 
160         IF(lwp)WRITE(numout,*)' Date 0 used :',nittrc000     &
161       &     ,' YEAR ',nyear,' MONTH ',nmonth,' DAY ',nday   &
162       &     ,'Julian day : ',zjulian   
163         IF(lwp)WRITE(numout,*) ' indexes of zoom = ', iimi, iima, ijmi, ijma,  &
164                                 ' limit storage in depth = ', ipk
165
166
167! Define the NETCDF files for passive tracer concentration
168
169         CALL dia_nam(clhstnam,nwritetrc,'ptrc_T')
170
171         IF(lwp)WRITE(numout,*)" Name of NETCDF file ", clhstnam
172! Horizontal grid : glamt and gphit
173 
174         CALL histbeg(clhstnam, jpi, glamt, jpj, gphit,     &
175         &    iimi, iima-iimi+1, ijmi, ijma-ijmi+1,         & 
176         &    0, zjulian, zdt, nhorit5, nit5 , domain_id=nidom)
177! Vertical grid for tracer : gdept
178         CALL histvert(nit5, 'deptht', 'Vertical T levels', &
179         &    'm', ipk, gdept_0, ndepit5)
180
181! Index of ocean points in 3D and 2D (surface)
182         CALL wheneq(jpi*jpj*ipk,tmask,1,1.,ndext50,ndimt50)
183         CALL wheneq(jpi*jpj,tmask,1,1.,ndext51,ndimt51)
184
185! Declare all the output fields as NETCDF variables
186
187! tracer concentrations
188
189         DO jn=1,jptra
190           cltra=ctrcnm(jn)    ! short title for tracer
191           cltral=ctrcnl(jn)   ! long title for tracer
192           cltrau=ctrcun(jn)   ! UNIT for tracer
193           CALL histdef(nit5, cltra, cltral, cltrau, jpi, jpj, nhorit5,  &
194         &          ipk, 1, ipk,  ndepit5, 32, clop, zsto, zout) 
195         END DO           
196
197! CLOSE netcdf Files
198         
199         CALL histend(nit5)
200
201         IF(lwp) WRITE(numout,*)
202         IF(lwp) WRITE(numout,*) 'End of NetCDF Initialization in trcdit_wr'
203         IF(ll_print) CALL FLUSH(numout )
204
205      ENDIF
206
207! 2. Start writing data
208! ---------------------
209
210! tracer concentrations
211
212      IF( lwp .AND. MOD( kt, nwritetrc ) == 0 ) THEN
213         WRITE(numout,*) 'trcdit_wr : write NetCDF passive tracer concentrations at ', kt, 'time-step'
214         WRITE(numout,*) '~~~~~~ '
215      ENDIF
216
217      DO jn=1,jptra
218         cltra=ctrcnm(jn) ! short title for tracer
219         CALL histwrite(nit5, cltra, it, trn(:,:,:,jn), ndimt50,   &
220      &          ndext50)
221      END DO 
222
223! synchronise FILE
224
225      IF( MOD( kt, nwritetrc ) == 0 .OR. kindic < 0 ) THEN
226              CALL histsync(nit5)
227      ENDIF
228
229! 3. Closing all files
230! --------------------
231      IF( kt == nitend .OR. kindic < 0 ) THEN
232          CALL histclo(nit5)
233      ENDIF
234
235END SUBROUTINE trcdit_wr
236
237#    else
238
239! no passive tracers
240
241SUBROUTINE trcdit_wr(kt,kindic)
242     !!! no passive tracers
243     INTEGER, INTENT ( in ) :: kt, kindic
244     WRITE(*,*) 'trcdit_wr: You should not have seen this print! error?', kt, kindic
245END SUBROUTINE trcdit_wr
246
247#    endif
248
249#    if defined key_passivetrc && defined key_trc_diatrd
250
251      SUBROUTINE trcdid_wr(kt,kindic)
252 !!===========================================================================================
253   !!
254   !!                       ROUTINE trcdid_wr
255   !!===========================================================================================
256   !!
257   !! Purpose :
258   !!---------
259   !!          output of opa: passive tracer dynamical trends
260   !!
261   !!
262   !! Method :
263   !! -------
264   !!
265   !!        At the beginning of the first time step (nit000), define all
266   !!        the NETCDF files and fields for dynamical trends of tracers
267   !!
268   !!        At each time step call histdef to compute the mean if necessary
269   !!        Each nwritetrd time step, output the instantaneous or mean fields
270   !!
271   !!        IF kindic <0, output of fields before the model interruption.
272   !!        IF kindic =0, time step loop
273   !!        IF kindic >0, output of fields before the time step loop
274   !!
275   !! Input :
276   !! -----
277   !!   argument
278   !!           kt              : time step
279   !!           kindic          : indicator of abnormal termination
280   !!
281   !! Output :
282   !! ------
283   !!   file
284   !!           "clhstnam" files : one for concentration
285   !!
286   !! History:
287   !! --------
288   !!   original  : 95-01  passive tracers  (M. Levy)
289   !!   additions : 98-01 (C. Levy) NETCDF format using ioipsl interface
290   !!   additions : 99-01 (M.A. Foujols) adapted for passive tracer
291   !!   additions : 99-09 (M.A. Foujols) split into three parts
292   !!   additions : 01-06 (Mehdi B, Elodie K): suppress initialization
293   !!                                          of nit6,nhorit6,ndepit6
294   !!   05-03 (O. Aumont and A. El Moussaoui) F90
295   !!==================================================================================================!
296
297      !! Modules used
298      USE ioipsl
299
300      !! * Arguments
301      INTEGER, INTENT( in ) ::   kt,kindic         ! ocean time-step
302
303      INTEGER :: jn, jl
304      LOGICAL :: ll_print = .FALSE.
305
306      CHARACTER (len=40) :: clhstnam, clop
307      CHARACTER (len=20) :: cltra, cltrau
308      CHARACTER (len=80) :: cltral
309      CHARACTER (len=10) :: csuff
310
311      REAL(wp) :: zsto, zout, zdt
312      INTEGER :: iimi, iima, ijmi, ijma, ipk, it
313
314!
315! 0. Initialisation
316! -----------------
317
318! local variable for debugging
319      ll_print = .FALSE.
320      ll_print = ll_print .AND. lwp
321!
322! Define frequency of output and means
323!
324      zdt = rdt
325#        if defined key_diainstant
326      zsto=nwritetrd*rdt
327      clop='inst(only(x))'
328#        else
329      zsto=zdt
330      clop='ave(only(x))'
331#        endif
332      zout=nwritetrd*zdt
333
334      ! Define indices of the horizontal output zoom and vertical limit storage
335      iimi = 1      ;      iima = jpi
336      ijmi = 1      ;      ijma = jpj
337      ipk = jpk
338
339      ! define time axis
340      it = kt - nittrc000 + 1
341
342! Define the NETCDF files (one per tracer)
343!
344      IF(ll_print)WRITE(numout,*)'trcdid kt=',kt,' kindic ',kindic
345      IF(kt == nittrc000) THEN
346
347          DO jn=1,jptra
348
349            IF (luttrd(jn)) THEN
350
351! Define the file for dynamical trends - one per each tracer IF required
352
353         IF(lwp)WRITE(numout,*) ' indexes of zoom = ', iimi, iima, ijmi, ijma,  &
354                                 ' limit storage in depth = ', ipk
355                csuff='DY_'//ctrcnm(jn)
356                CALL dia_nam(clhstnam,nwritetrd,csuff)
357                IF(lwp)WRITE(numout,*)     &
358                &      " Name of NETCDF file for dynamical trends",   &
359                &      " of tracer number : ",clhstnam
360
361                CALL histbeg(clhstnam, jpi, glamt, jpj, gphit,   &
362                &    iimi, iima-iimi+1, ijmi, ijma-ijmi+1,       &
363                &    0, zjulian, rdt, nhorit6(jn),               &
364                &    nit6(jn) , domain_id=nidom)
365
366! Vertical grid for tracer trend - one per each tracer IF needed
367                CALL histvert(nit6(jn), 'deptht', 'Vertical T levels',  &
368                &    'm', ipk, gdept_0, ndepit6(jn)) 
369
370
371            END IF
372          END DO
373
374! Declare all the output fields as NETCDF variables
375
376
377! trends for tracer concentrations
378          DO jn=1,jptra
379            IF (luttrd(jn)) THEN
380                DO jl=1,jpdiatrc
381                  IF (jl.eq.1) THEN
382! short and long title for x advection for tracer
383                      WRITE (cltra,'("XAD_",16a)') ctrcnm(jn)
384                      WRITE (cltral,'("X advective trend for ",58a)')  &
385                      &      ctrcnl(jn)(1:58)
386                  END IF
387                  IF (jl.eq.2)  THEN
388! short and long title for y advection for tracer
389                      WRITE (cltra,'("YAD_",16a)') ctrcnm(jn)
390                      WRITE (cltral,'("Y advective trend for ",58a)')  &
391                      &      ctrcnl(jn)(1:58)
392                  END IF
393                  IF (jl.eq.3)  THEN
394! short and long title for Z advection for tracer
395                      WRITE (cltra,'("ZAD_",16a)') ctrcnm(jn)
396                      WRITE (cltral,'("Z advective trend for ",58a)')  &
397                      &      ctrcnl(jn)(1:58)
398                  END IF
399                  IF (jl.eq.4)  THEN
400! short and long title for X diffusion for tracer
401                      WRITE (cltra,'("XDF_",16a)') ctrcnm(jn)
402                      WRITE (cltral,'("X diffusion trend for ",58a)')  &
403                      &      ctrcnl(jn)(1:58)
404                  END IF
405                  IF (jl.eq.5)  THEN
406! short and long title for Y diffusion for tracer
407                      WRITE (cltra,'("YDF_",16a)') ctrcnm(jn)
408                      WRITE (cltral,'("Y diffusion trend for ",58a)')  &
409                      &      ctrcnl(jn)(1:58)
410                  END IF
411                  IF (jl.eq.6)  THEN
412! short and long title for Z diffusion for tracer
413                      WRITE (cltra,'("ZDF_",16a)') ctrcnm(jn)
414                      WRITE (cltral,'("Z diffusion trend for ",58a)')  &
415                      &      ctrcnl(jn)(1:58)
416                  END IF
417# if defined key_trc_ldfeiv
418                  IF (jl.eq.7) THEN
419! short and long title for x gent velocity for tracer
420                      WRITE (cltra,'("XGV",16a)') ctrcnm(jn)
421                      WRITE (cltral,'("X gent velocity trend for ",53a)')  &
422                      &      ctrcnl(jn)(1:53)
423                  END IF
424                  IF (jl.eq.8)  THEN
425! short and long title for y gent velocity for tracer
426                      WRITE (cltra,'("YGV_",16a)') ctrcnm(jn)
427                      WRITE (cltral,'("Y gent velocity trend for ",53a)')  &
428                      &      ctrcnl(jn)(1:53)
429                  END IF
430                  IF (jl.eq.9)  THEN
431! short and long title for Z gent velocity for tracer
432                      WRITE (cltra,'("ZGV_",16a)') ctrcnm(jn)
433                      WRITE (cltral,'("Z gent velocity trend for ",53a)')  &
434                      &      ctrcnl(jn)(1:53)
435                  END IF
436# endif
437# if defined key_trcdmp
438                  IF (jl.eq.jpdiatrc)  THEN
439! last trends for tracer damping : short and long title
440                      WRITE (cltra,'("TDM_",16a)') ctrcnm(jn)
441                      WRITE (cltral,'("Tracer damping trend for ",55a)')  &
442                      &      ctrcnl(jn)(1:55)
443                  END IF
444# endif
445                  call flush(numout)
446                  cltrau=ctrcun(jn) ! UNIT for tracer /trends
447                  CALL histdef(nit6(jn), cltra, cltral, cltrau, jpi,jpj,  &
448                  &   nhorit6(jn), ipk, 1, ipk,  ndepit6(jn), 32, clop ,  &
449                  &   zsto,zout)
450                END DO
451            END IF
452          END DO
453
454! CLOSE netcdf Files
455
456          DO jn=1,jptra
457             IF (luttrd(jn)) CALL histend(nit6(jn))
458          END DO
459
460         IF(lwp) WRITE(numout,*)
461         IF(lwp) WRITE(numout,*) 'End of NetCDF Initialization in trcdid'
462         IF(ll_print) CALL FLUSH(numout )
463
464      ENDIF
465
466! SOME diagnostics to DO first time
467
468! 2. Start writing data
469! ---------------------
470
471! trends for tracer concentrations
472
473      IF( lwp .AND. MOD( kt, nwritetrd ) == 0 ) THEN
474         WRITE(numout,*) 'trcdid_wr : write NetCDF dynamical trends at ', kt, 'time-step'
475         WRITE(numout,*) '~~~~~~ '
476      ENDIF
477
478          DO jn=1,jptra
479            IF (luttrd(jn)) THEN
480                DO jl=1,jpdiatrc
481                  IF (jl.eq.1) THEN
482! short title for x advection for tracer
483                      WRITE (cltra,'("XAD_",16a)') ctrcnm(jn)
484                  END IF
485                  IF (jl.eq.2)  THEN
486! short title for y advection for tracer
487                      WRITE (cltra,'("YAD_",16a)') ctrcnm(jn)
488                  END IF
489                  IF (jl.eq.3)  THEN
490! short title for z advection for tracer
491                      WRITE (cltra,'("ZAD_",16a)') ctrcnm(jn)
492                  END IF
493                  IF (jl.eq.4)  THEN
494! short title for x diffusion for tracer
495                      WRITE (cltra,'("XDF_",16a)') ctrcnm(jn)
496                  END IF
497                  IF (jl.eq.5)  THEN
498! short title for y diffusion for tracer
499                      WRITE (cltra,'("YDF_",16a)') ctrcnm(jn)
500                  END IF
501                  IF (jl.eq.6)  THEN
502! short title for z diffusion for tracer
503                      WRITE (cltra,'("ZDF_",16a)') ctrcnm(jn)
504                  END IF
505# if defined key_trc_ldfeiv
506                  IF (jl.eq.7) THEN
507! short for x gent velocity for tracer
508                      WRITE (cltra,'("XGV_",16a)') ctrcnm(jn)
509                  END IF
510                  IF (jl.eq.8)  THEN
511! short for y gent velocity for tracer
512                      WRITE (cltra,'("YGV_",16a)') ctrcnm(jn)
513                  END IF
514                  IF (jl.eq.9)  THEN
515! short title for Z gent velocity for tracer
516                      WRITE (cltra,'("ZGV_",16a)') ctrcnm(jn)
517                  END IF
518# endif
519# if defined key_trcdmp
520                  IF (jl.eq.jpdiatrc) THEN
521! short for x gent velocity for tracer
522                      WRITE (cltra,'("TDM_",16a)') ctrcnm(jn)
523                  END IF
524# endif
525
526                  CALL histwrite(nit6(jn), cltra, it, trtrd(:,:,:,ikeep(jn),jl)  &
527                  &    ,ndimt50, ndext50)
528                END DO
529            END IF
530          END DO
531
532! synchronise FILE
533
534      IF( MOD( kt, nwritetrd ) == 0 .OR. kindic < 0 ) THEN
535          DO jn=1,jptra
536             IF (luttrd(jn)) CALL histsync(nit6(jn))
537          END DO
538      ENDIF
539
540! 3. Closing all files
541! --------------------
542
543      IF( kt == nitend .OR. kindic < 0 ) THEN
544          DO jn=1,jptra
545             IF (luttrd(jn)) CALL histclo(nit6(jn))
546          END DO
547      ENDIF
548
549END SUBROUTINE trcdid_wr
550
551#    else
552
553SUBROUTINE trcdid_wr(kt,kindic)
554     !!! no passive tracers
555     INTEGER, INTENT ( in ) :: kt, kindic
556     WRITE(*,*) 'trcdid_wr: You should not have seen this print! error?', kt, kindic
557END SUBROUTINE trcdid_wr
558
559#    endif
560
561#    if defined key_passivetrc && defined key_trc_diaadd
562
563      SUBROUTINE trcdii_wr(kt,kindic)
564   !!===========================================================================================
565   !!
566   !!                       ROUTINE trcdii_wr
567   !!===========================================================================================
568   !!
569   !! Purpose :
570   !!---------
571   !!          output of passive tracer : additional 2D and 3D arrays
572   !!
573   !!
574   !! Method :
575   !! -------
576   !!
577   !!        At the beginning of the first time step (nit000), define all
578   !!        the NETCDF files and fields for additional arrays
579   !!
580   !!        At each time step call histdef to compute the mean if necessary
581   !!        Each nwritetrc time step, output the instantaneous or mean fields
582   !!
583   !!
584   !!        IF kindic <0, output of fields before the model interruption.
585   !!        IF kindic =0, time step loop
586   !!        IF kindic >0, output of fields before the time step loop
587   !!
588   !! Input :
589   !! -----
590   !!   argument
591   !!           kt              : time step
592   !!           kindic          : indicator of abnormal termination
593   !!
594   !! EXTERNAL :
595   !! --------
596   !! prihre, hist..., dianam
597   !!
598   !! History:
599   !! --------
600   !!   original  : 95-01  passive tracers  (M. Levy)
601   !!   additions : 98-01 (C. Levy) NETCDF format using ioipsl interface
602   !!   additions : 99-01 (M.A. Foujols) adapted for passive tracer
603   !!   additions : 99-09 (M.A. Foujols) split into three parts
604   !!   05-03 (O. Aumont and A. El Moussaoui) F90
605   !!==================================================================================================!
606
607      !! Modules used
608      USE ioipsl
609
610      !! * Arguments
611      INTEGER, INTENT( in ) ::   kt,kindic         ! ocean time-step
612
613      INTEGER :: jn
614      LOGICAL :: ll_print = .FALSE.
615
616      CHARACTER (len=40) :: clhstnam, clop
617      CHARACTER (len=20) :: cltra, cltrau
618      CHARACTER (len=80) :: cltral
619
620      REAL(wp) :: zsto, zout, zdt
621      INTEGER :: iimi, iima, ijmi, ijma, ipk, it
622
623!
624! 0. Initialisation
625! -----------------
626
627! local variable for debugging
628      ll_print = .FALSE.
629      ll_print = ll_print .AND. lwp
630!
631! Define frequency of output and means
632!
633      zdt = rdt
634#        if defined key_diainstant
635      zsto=nwriteadd*zdt
636      clop='inst(only(x))'
637#        else
638      zsto=zdt
639      clop='ave(only(x))'
640#        endif
641      zout=nwriteadd*zdt
642
643      ! Define indices of the horizontal output zoom and vertical limit storage
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! 1. Define NETCDF files and fields at beginning of first time step
652! -----------------------------------------------------------------
653
654      IF(ll_print)WRITE(numout,*)'trcdii_wr kt=',kt,' kindic ',kindic
655      IF(kt == nittrc000) THEN
656
657! Define the NETCDF files for additional arrays : 2D or 3D
658
659! Define the T grid file for tracer auxiliary files
660
661          CALL dia_nam(clhstnam,nwrite,'diad_T')
662          IF(lwp)WRITE(numout,*)" Name of NETCDF file ", clhstnam
663
664! Define a netcdf FILE for 2d and 3d arrays
665
666          CALL histbeg(clhstnam, jpi, glamt, jpj, gphit,     &
667          &    iimi, iima-iimi+1, ijmi, ijma-ijmi+1,         &
668          &    0, zjulian, zdt, nhoritd, nitd , domain_id=nidom)
669
670! Vertical grid for 2d and 3d arrays
671
672          CALL histvert(nitd, 'deptht', 'Vertical T levels', &
673          &    'm', ipk, gdept_0, ndepitd)
674
675
676! Declare all the output fields as NETCDF variables
677
678! more 3D horizontal arrays
679
680          DO jn=1,jpdia3d
681            cltra=ctrc3d(jn)    ! short title for 3D diagnostic
682            cltral=ctrc3l(jn)   ! long title for 3D diagnostic
683            cltrau=ctrc3u(jn)   ! UNIT for 3D diagnostic
684            CALL histdef(nitd, cltra, cltral, cltrau, jpi, jpj, nhoritd,  &
685            &    ipk, 1, ipk,  ndepitd, 32, clop, zsto, zout)
686          END DO
687
688
689! more 2D horizontal arrays
690
691          DO jn=1,jpdia2d
692            cltra=ctrc2d(jn)    ! short title for 2D diagnostic
693            cltral=ctrc2l(jn)   ! long title for 2D diagnostic
694            cltrau=ctrc2u(jn)   ! UNIT for 2D diagnostic
695            CALL histdef(nitd, cltra, cltral, cltrau, jpi, jpj, nhoritd,  &
696            &    1, 1, 1,  -99, 32, clop, zsto, zout)
697          END DO
698
699! TODO: more 2D vertical sections arrays : I or J indice fixed
700
701! CLOSE netcdf Files
702
703          CALL histend(nitd)
704
705         IF(lwp) WRITE(numout,*)
706         IF(lwp) WRITE(numout,*) 'End of NetCDF Initialization in trcdii_wr'
707         IF(ll_print) CALL FLUSH(numout )
708
709      ENDIF
710
711! 2. Start writing data
712! ---------------------
713
714      IF( lwp .AND. MOD( kt, nwriteadd ) == 0 ) THEN
715         WRITE(numout,*) 'trcdii_wr : write NetCDF additional arrays at ', kt, 'time-step'
716         WRITE(numout,*) '~~~~~~ '
717      ENDIF
718
719! more 3D horizontal arrays
720
721          DO jn=1,jpdia3d
722            cltra=ctrc3d(jn) ! short title for 3D diagnostic
723            CALL histwrite(nitd, cltra, it, trc3d(:,:,:,jn), ndimt50  &
724            &   ,ndext50)
725          END DO
726
727! more 2D horizontal arrays
728
729          DO jn=1,jpdia2d
730            cltra=ctrc2d(jn) ! short title for 2D diagnostic
731            CALL histwrite(nitd, cltra, it, trc2d(:,:,jn), ndimt51    &
732            &   ,ndext51)
733          END DO
734
735! synchronise FILE
736
737      IF( MOD( kt, nwriteadd ) == 0 .OR. kindic < 0 ) THEN
738              CALL histsync(nitd)
739      ENDIF
740
741! 3. Closing all files
742! --------------------
743
744      IF( kt == nitend .OR. kindic < 0 ) THEN
745          CALL histclo(nitd)
746      ENDIF
747
748END SUBROUTINE trcdii_wr
749
750#    else
751
752SUBROUTINE trcdii_wr(kt,kindic)
753     !!! no passive tracers
754     INTEGER, INTENT ( in ) :: kt, kindic
755     WRITE(*,*) 'trcdii_wr: You should not have seen this print! error?', kt, kindic
756END SUBROUTINE trcdii_wr
757
758#    endif
759
760#    if defined key_passivetrc && defined key_trc_diabio
761
762      SUBROUTINE trcdib_wr(kt,kindic)
763 !!===========================================================================================
764   !!
765   !!                       ROUTINE trcdib_wr
766   !!===========================================================================================
767   !!
768   !! Purpose :
769   !!---------
770   !!          Specific output of opa: biological fields
771   !!
772   !!
773   !! Method :
774   !! -------
775   !!
776   !!        At the beginning of the first time step (nit000), define all
777   !!        the NETCDF files and fields for biological fields
778   !!
779   !!        At each time step call histdef to compute the mean if necessary
780   !!        Each nwritetrd time step, output the instantaneous or mean fields
781   !!
782   !!        IF kindic <0, output of fields before the model interruption.
783   !!        IF kindic =0, time step loop
784   !!        IF kindic >0, output of fields before the time step loop
785   !!
786   !! Input :
787   !! -----
788   !!   argument
789   !!           kt              : time step
790   !!           kindic          : indicator of abnormal termination
791   !!
792   !! Output :
793   !! ------
794   !!   file
795   !!           "histname" files : at least one file for each grid
796   !!
797   !! History:
798   !! --------
799   !!   original  : 95-01  passive tracers  (M. Levy)
800   !!   additions : 98-01 (C. Levy) NETCDF format using ioipsl interface
801   !!   additions : 99-01 (M.A. Foujols) adapted for passive tracer
802   !!   additions : 99-09 (M.A. Foujols) split into three parts
803   !!   additions : 01-06 (E Kestenare) assign a parameter to name
804   !!                                          individual tracers
805   !!   additions : 05-03 (O. Aumont and A El Moussaoui) F90
806   !!==================================================================================================!
807
808      !! Modules used
809      USE ioipsl
810      USE sms
811
812      !! * Arguments
813      INTEGER, INTENT( in ) ::   kt,kindic         ! ocean time-step
814
815      INTEGER :: ji, jj, jk, jn
816      LOGICAL :: ll_print = .FALSE.
817
818      CHARACTER (len=40) :: clhstnam, clop
819      CHARACTER (len=20) :: cltra, cltrau
820      CHARACTER (len=80) :: cltral
821
822      REAL(wp) :: zsto, zout, zdt
823      INTEGER  :: iimi, iima, ijmi, ijma, ipk, it
824
825!
826! 0. Initialisation
827! -----------------
828
829! local variable for debugging
830      ll_print = .FALSE.
831      ll_print = ll_print .AND. lwp
832!
833! Define frequency of output and means
834!
835      zdt = rdt
836#        if defined key_diainstant
837      zsto=nwritebio*zdt
838      clop='inst(only(x))'
839#        else
840      zsto=zdt
841      clop='ave(only(x))'
842#        endif
843      zout=nwritebio*zdt
844
845      ! Define indices of the horizontal output zoom and vertical limit storage      iimi = 1      ;      iima = jpi
846      iimi = 1      ;      iima = jpi
847      ijmi = 1      ;      ijma = jpj
848      ipk = jpk
849
850      ! define time axis
851      it = kt - nittrc000 + 1
852
853! 1. Define NETCDF files and fields at beginning of first time step
854! -----------------------------------------------------------------
855
856      IF(ll_print)WRITE(numout,*)'trcdib_wr kt=',kt,' kindic ',kindic
857      IF(kt == nittrc000) THEN
858
859! Define the NETCDF files for biological trends
860
861          CALL dia_nam(clhstnam,nwrite,'biolog')
862          IF(lwp)WRITE(numout,*)        &
863          &      " Name of NETCDF file for biological trends ",clhstnam
864! Horizontal grid : glamt and gphit
865          CALL histbeg(clhstnam, jpi, glamt, jpj, gphit,      &
866          &    iimi, iima-iimi+1, ijmi, ijma-ijmi+1,          &
867          &    0, zjulian, rdt, nhoritb, nitb , domain_id=nidom)
868! Vertical grid for biological trends
869          CALL histvert(nitb, 'deptht', 'Vertical T levels',  &
870          &    'm', ipk, gdept_0, ndepitb)
871
872! Declare all the output fields as NETCDF variables
873
874! biological trends
875
876          DO jn=1,jpdiabio
877            cltra=ctrbio(jn)    ! short title for biological diagnostic
878            cltral=ctrbil(jn)   ! long title for biological diagnostic
879            cltrau=ctrbiu(jn)   ! UNIT for biological diagnostic
880            CALL histdef(nitb, cltra, cltral, cltrau, jpi, jpj, nhoritb,  &
881            &    ipk, 1, ipk,  ndepitb, 32, clop, zsto, zout)
882          END DO
883
884! CLOSE netcdf Files
885
886          CALL histend(nitb)
887
888         IF(lwp) WRITE(numout,*)
889         IF(lwp) WRITE(numout,*) 'End of NetCDF Initialization in trcdib_wr'
890         IF(ll_print) CALL FLUSH(numout )
891
892     ENDIF
893
894! 2. Start writing data
895! ---------------------
896
897! biological trends
898
899      IF( lwp .AND. MOD( kt, nwritebio ) == 0 ) THEN
900         WRITE(numout,*) 'trcdit_wr : write NetCDF biological trends at ', kt, 'time-step'
901         WRITE(numout,*) '~~~~~~ '
902      ENDIF
903
904
905      DO jn=1,jpdiabio
906         cltra=ctrbio(jn)  ! short title for biological diagnostic
907         CALL histwrite(nitb, cltra, it, trbio(:,:,:,jn), ndimt50,ndext50)
908      END DO
909
910! synchronise FILE
911
912      IF( MOD( kt, nwritebio ) == 0 .OR. kindic < 0 ) THEN
913              CALL histsync(nitb)
914      ENDIF
915
916! 3. Closing all files
917! --------------------
918      IF( kt == nitend .OR. kindic < 0 ) THEN
919          CALL histclo(nitb)
920      ENDIF
921
922END SUBROUTINE trcdib_wr
923
924#    else
925
926SUBROUTINE trcdib_wr(kt,kindic)
927     !!! no passive tracers
928     INTEGER, INTENT ( in ) :: kt, kindic
929     WRITE(*,*) 'trcdib_wr: You should not have seen this print! error?', kt, kindic
930END SUBROUTINE trcdib_wr
931
932#    endif
933
934END MODULE trcdit
Note: See TracBrowser for help on using the repository browser.