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

Last change on this file since 941 was 724, checked in by cetlod, 17 years ago

Update modules for passive tracers transport trends computation, see ticket:13

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 29.7 KB
Line 
1MODULE trcdit
2   !!----------------------------------------------------------------------
3   !!  TOP 1.0,  LOCEAN-IPSL (2005)
4   !! $Header: /home/opalod/NEMOCVSROOT/NEMO/TOP_SRC/trcdit.F90,v 1.9 2007/10/12 09:22:19 opalod Exp $
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-1)  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                  IF (jl.eq.jpdiatrc)  THEN
446! last trends for tracer damping : short and long title
447                      WRITE (cltra,'("SBC_",16a)') ctrcnm(jn)
448                      WRITE (cltral,'("Surface boundary flux ",58a)')  &
449                      &      ctrcnl(jn)(1:58)
450                  END IF
451
452                  call flush(numout)
453                  cltrau=ctrcun(jn) ! UNIT for tracer /trends
454                  CALL histdef(nit6(jn), cltra, cltral, cltrau, jpi,jpj,  &
455                  &   nhorit6(jn), ipk, 1, ipk,  ndepit6(jn), 32, clop ,  &
456                  &   zsto,zout)
457                END DO
458            END IF
459          END DO
460
461! CLOSE netcdf Files
462
463          DO jn=1,jptra
464             IF (luttrd(jn)) CALL histend(nit6(jn))
465          END DO
466
467         IF(lwp) WRITE(numout,*)
468         IF(lwp) WRITE(numout,*) 'End of NetCDF Initialization in trcdid'
469         IF(ll_print) CALL FLUSH(numout )
470
471      ENDIF
472
473! SOME diagnostics to DO first time
474
475! 2. Start writing data
476! ---------------------
477
478! trends for tracer concentrations
479
480      IF( lwp .AND. MOD( kt, nwritetrd ) == 0 ) THEN
481         WRITE(numout,*) 'trcdid_wr : write NetCDF dynamical trends at ', kt, 'time-step'
482         WRITE(numout,*) '~~~~~~ '
483      ENDIF
484
485          DO jn=1,jptra
486            IF (luttrd(jn)) THEN
487                DO jl=1,jpdiatrc
488                  IF (jl.eq.1) THEN
489! short title for x advection for tracer
490                      WRITE (cltra,'("XAD_",16a)') ctrcnm(jn)
491                  END IF
492                  IF (jl.eq.2)  THEN
493! short title for y advection for tracer
494                      WRITE (cltra,'("YAD_",16a)') ctrcnm(jn)
495                  END IF
496                  IF (jl.eq.3)  THEN
497! short title for z advection for tracer
498                      WRITE (cltra,'("ZAD_",16a)') ctrcnm(jn)
499                  END IF
500                  IF (jl.eq.4)  THEN
501! short title for x diffusion for tracer
502                      WRITE (cltra,'("XDF_",16a)') ctrcnm(jn)
503                  END IF
504                  IF (jl.eq.5)  THEN
505! short title for y diffusion for tracer
506                      WRITE (cltra,'("YDF_",16a)') ctrcnm(jn)
507                  END IF
508                  IF (jl.eq.6)  THEN
509! short title for z diffusion for tracer
510                      WRITE (cltra,'("ZDF_",16a)') ctrcnm(jn)
511                  END IF
512# if defined key_trcldf_eiv
513                  IF (jl.eq.7) THEN
514! short for x gent velocity for tracer
515                      WRITE (cltra,'("XGV_",16a)') ctrcnm(jn)
516                  END IF
517                  IF (jl.eq.8)  THEN
518! short for y gent velocity for tracer
519                      WRITE (cltra,'("YGV_",16a)') ctrcnm(jn)
520                  END IF
521                  IF (jl.eq.9)  THEN
522! short title for Z gent velocity for tracer
523                      WRITE (cltra,'("ZGV_",16a)') ctrcnm(jn)
524                  END IF
525# endif
526# if defined key_trcdmp
527                  IF (jl.eq.jpdiatrc-1) THEN
528! short for x gent velocity for tracer
529                      WRITE (cltra,'("TDM_",16a)') ctrcnm(jn)
530                  END IF
531# endif
532                  IF (jl.eq.jpdiatrc) THEN
533! short for surface boundary conditions for tracer
534                      WRITE (cltra,'("SBC_",a)') ctrcnm(jn)
535                  END IF
536
537                  CALL histwrite(nit6(jn), cltra, it, trtrd(:,:,:,ikeep(jn),jl)  &
538                  &    ,ndimt50, ndext50)
539                END DO
540            END IF
541          END DO
542
543! synchronise FILE
544
545      IF( MOD( kt, nwritetrd ) == 0 .OR. kindic < 0 ) THEN
546          DO jn=1,jptra
547             IF (luttrd(jn)) CALL histsync(nit6(jn))
548          END DO
549      ENDIF
550
551! 3. Closing all files
552! --------------------
553
554      IF( kt == nitend .OR. kindic < 0 ) THEN
555          DO jn=1,jptra
556             IF (luttrd(jn)) CALL histclo(nit6(jn))
557          END DO
558      ENDIF
559
560END SUBROUTINE trcdid_wr
561
562#    else
563
564SUBROUTINE trcdid_wr(kt,kindic)
565     !!! no passive tracers
566     INTEGER, INTENT ( in ) :: kt, kindic
567     WRITE(*,*) 'trcdid_wr: You should not have seen this print! error?', kt, kindic
568END SUBROUTINE trcdid_wr
569
570#    endif
571
572#    if defined key_passivetrc && defined key_trc_diaadd
573
574      SUBROUTINE trcdii_wr(kt,kindic)
575   !!===========================================================================================
576   !!
577   !!                       ROUTINE trcdii_wr
578   !!===========================================================================================
579   !!
580   !! Purpose :
581   !!---------
582   !!          output of passive tracer : additional 2D and 3D arrays
583   !!
584   !!
585   !! Method :
586   !! -------
587   !!
588   !!        At the beginning of the first time step (nit000), define all
589   !!        the NETCDF files and fields for additional arrays
590   !!
591   !!        At each time step call histdef to compute the mean if necessary
592   !!        Each nwritetrc time step, output the instantaneous or mean fields
593   !!
594   !!
595   !!        IF kindic <0, output of fields before the model interruption.
596   !!        IF kindic =0, time step loop
597   !!        IF kindic >0, output of fields before the time step loop
598   !!
599   !! Input :
600   !! -----
601   !!   argument
602   !!           kt              : time step
603   !!           kindic          : indicator of abnormal termination
604   !!
605   !! EXTERNAL :
606   !! --------
607   !! prihre, hist..., dianam
608   !!
609   !! History:
610   !! --------
611   !!   original  : 95-01  passive tracers  (M. Levy)
612   !!   additions : 98-01 (C. Levy) NETCDF format using ioipsl interface
613   !!   additions : 99-01 (M.A. Foujols) adapted for passive tracer
614   !!   additions : 99-09 (M.A. Foujols) split into three parts
615   !!   05-03 (O. Aumont and A. El Moussaoui) F90
616   !!==================================================================================================!
617
618      !! Modules used
619      USE ioipsl
620
621      !! * Arguments
622      INTEGER, INTENT( in ) ::   kt,kindic         ! ocean time-step
623
624      INTEGER :: jn
625      LOGICAL :: ll_print = .FALSE.
626
627      CHARACTER (len=40) :: clhstnam, clop
628      CHARACTER (len=20) :: cltra, cltrau
629      CHARACTER (len=80) :: cltral
630
631      REAL(wp) :: zsto, zout, zdt
632      INTEGER :: iimi, iima, ijmi, ijma, ipk, it
633
634!
635! 0. Initialisation
636! -----------------
637
638! local variable for debugging
639      ll_print = .FALSE.
640      ll_print = ll_print .AND. lwp
641!
642! Define frequency of output and means
643!
644      zdt = rdt
645#        if defined key_diainstant
646      zsto=nwriteadd*zdt
647      clop='inst(only(x))'
648#        else
649      zsto=zdt
650      clop='ave(only(x))'
651#        endif
652      zout=nwriteadd*zdt
653
654      ! Define indices of the horizontal output zoom and vertical limit storage
655      iimi = 1      ;      iima = jpi
656      ijmi = 1      ;      ijma = jpj
657      ipk = jpk
658
659      ! define time axis
660      it = kt - nittrc000 + 1
661
662! 1. Define NETCDF files and fields at beginning of first time step
663! -----------------------------------------------------------------
664
665      IF(ll_print)WRITE(numout,*)'trcdii_wr kt=',kt,' kindic ',kindic
666      IF(kt == nittrc000) THEN
667
668! Define the NETCDF files for additional arrays : 2D or 3D
669
670! Define the T grid file for tracer auxiliary files
671
672          CALL dia_nam(clhstnam,nwrite,'diad_T')
673          IF(lwp)WRITE(numout,*)" Name of NETCDF file ", clhstnam
674
675! Define a netcdf FILE for 2d and 3d arrays
676
677          CALL histbeg(clhstnam, jpi, glamt, jpj, gphit,     &
678          &    iimi, iima-iimi+1, ijmi, ijma-ijmi+1,         &
679          &    0, zjulian, zdt, nhoritd, nitd , domain_id=nidom)
680
681! Vertical grid for 2d and 3d arrays
682
683          CALL histvert(nitd, 'deptht', 'Vertical T levels', &
684          &    'm', ipk, gdept_0, ndepitd)
685
686
687! Declare all the output fields as NETCDF variables
688
689! more 3D horizontal arrays
690
691          DO jn=1,jpdia3d
692            cltra=ctrc3d(jn)    ! short title for 3D diagnostic
693            cltral=ctrc3l(jn)   ! long title for 3D diagnostic
694            cltrau=ctrc3u(jn)   ! UNIT for 3D diagnostic
695            CALL histdef(nitd, cltra, cltral, cltrau, jpi, jpj, nhoritd,  &
696            &    ipk, 1, ipk,  ndepitd, 32, clop, zsto, zout)
697          END DO
698
699
700! more 2D horizontal arrays
701
702          DO jn=1,jpdia2d
703            cltra=ctrc2d(jn)    ! short title for 2D diagnostic
704            cltral=ctrc2l(jn)   ! long title for 2D diagnostic
705            cltrau=ctrc2u(jn)   ! UNIT for 2D diagnostic
706            CALL histdef(nitd, cltra, cltral, cltrau, jpi, jpj, nhoritd,  &
707            &    1, 1, 1,  -99, 32, clop, zsto, zout)
708          END DO
709
710! TODO: more 2D vertical sections arrays : I or J indice fixed
711
712! CLOSE netcdf Files
713
714          CALL histend(nitd)
715
716         IF(lwp) WRITE(numout,*)
717         IF(lwp) WRITE(numout,*) 'End of NetCDF Initialization in trcdii_wr'
718         IF(ll_print) CALL FLUSH(numout )
719
720      ENDIF
721
722! 2. Start writing data
723! ---------------------
724
725      IF( lwp .AND. MOD( kt, nwriteadd ) == 0 ) THEN
726         WRITE(numout,*) 'trcdii_wr : write NetCDF additional arrays at ', kt, 'time-step'
727         WRITE(numout,*) '~~~~~~ '
728      ENDIF
729
730! more 3D horizontal arrays
731
732          DO jn=1,jpdia3d
733            cltra=ctrc3d(jn) ! short title for 3D diagnostic
734            CALL histwrite(nitd, cltra, it, trc3d(:,:,:,jn), ndimt50  &
735            &   ,ndext50)
736          END DO
737
738! more 2D horizontal arrays
739
740          DO jn=1,jpdia2d
741            cltra=ctrc2d(jn) ! short title for 2D diagnostic
742            CALL histwrite(nitd, cltra, it, trc2d(:,:,jn), ndimt51    &
743            &   ,ndext51)
744          END DO
745
746! synchronise FILE
747
748      IF( MOD( kt, nwriteadd ) == 0 .OR. kindic < 0 ) THEN
749              CALL histsync(nitd)
750      ENDIF
751
752! 3. Closing all files
753! --------------------
754
755      IF( kt == nitend .OR. kindic < 0 ) THEN
756          CALL histclo(nitd)
757      ENDIF
758
759END SUBROUTINE trcdii_wr
760
761#    else
762
763SUBROUTINE trcdii_wr(kt,kindic)
764     !!! no passive tracers
765     INTEGER, INTENT ( in ) :: kt, kindic
766     WRITE(*,*) 'trcdii_wr: You should not have seen this print! error?', kt, kindic
767END SUBROUTINE trcdii_wr
768
769#    endif
770
771#    if defined key_passivetrc && defined key_trc_diabio
772
773      SUBROUTINE trcdib_wr(kt,kindic)
774 !!===========================================================================================
775   !!
776   !!                       ROUTINE trcdib_wr
777   !!===========================================================================================
778   !!
779   !! Purpose :
780   !!---------
781   !!          Specific output of opa: biological fields
782   !!
783   !!
784   !! Method :
785   !! -------
786   !!
787   !!        At the beginning of the first time step (nit000), define all
788   !!        the NETCDF files and fields for biological fields
789   !!
790   !!        At each time step call histdef to compute the mean if necessary
791   !!        Each nwritetrd time step, output the instantaneous or mean fields
792   !!
793   !!        IF kindic <0, output of fields before the model interruption.
794   !!        IF kindic =0, time step loop
795   !!        IF kindic >0, output of fields before the time step loop
796   !!
797   !! Input :
798   !! -----
799   !!   argument
800   !!           kt              : time step
801   !!           kindic          : indicator of abnormal termination
802   !!
803   !! Output :
804   !! ------
805   !!   file
806   !!           "histname" files : at least one file for each grid
807   !!
808   !! History:
809   !! --------
810   !!   original  : 95-01  passive tracers  (M. Levy)
811   !!   additions : 98-01 (C. Levy) NETCDF format using ioipsl interface
812   !!   additions : 99-01 (M.A. Foujols) adapted for passive tracer
813   !!   additions : 99-09 (M.A. Foujols) split into three parts
814   !!   additions : 01-06 (E Kestenare) assign a parameter to name
815   !!                                          individual tracers
816   !!   additions : 05-03 (O. Aumont and A El Moussaoui) F90
817   !!==================================================================================================!
818
819      !! Modules used
820      USE ioipsl
821      USE sms
822
823      !! * Arguments
824      INTEGER, INTENT( in ) ::   kt,kindic         ! ocean time-step
825
826      INTEGER :: ji, jj, jk, jn
827      LOGICAL :: ll_print = .FALSE.
828
829      CHARACTER (len=40) :: clhstnam, clop
830      CHARACTER (len=20) :: cltra, cltrau
831      CHARACTER (len=80) :: cltral
832
833      REAL(wp) :: zsto, zout, zdt
834      INTEGER  :: iimi, iima, ijmi, ijma, ipk, it
835
836!
837! 0. Initialisation
838! -----------------
839
840! local variable for debugging
841      ll_print = .FALSE.
842      ll_print = ll_print .AND. lwp
843!
844! Define frequency of output and means
845!
846      zdt = rdt
847#        if defined key_diainstant
848      zsto=nwritebio*zdt
849      clop='inst(only(x))'
850#        else
851      zsto=zdt
852      clop='ave(only(x))'
853#        endif
854      zout=nwritebio*zdt
855
856      ! Define indices of the horizontal output zoom and vertical limit storage      iimi = 1      ;      iima = jpi
857      iimi = 1      ;      iima = jpi
858      ijmi = 1      ;      ijma = jpj
859      ipk = jpk
860
861      ! define time axis
862      it = kt - nittrc000 + 1
863
864! 1. Define NETCDF files and fields at beginning of first time step
865! -----------------------------------------------------------------
866
867      IF(ll_print)WRITE(numout,*)'trcdib_wr kt=',kt,' kindic ',kindic
868      IF(kt == nittrc000) THEN
869
870! Define the NETCDF files for biological trends
871
872          CALL dia_nam(clhstnam,nwrite,'biolog')
873          IF(lwp)WRITE(numout,*)        &
874          &      " Name of NETCDF file for biological trends ",clhstnam
875! Horizontal grid : glamt and gphit
876          CALL histbeg(clhstnam, jpi, glamt, jpj, gphit,      &
877          &    iimi, iima-iimi+1, ijmi, ijma-ijmi+1,          &
878          &    0, zjulian, rdt, nhoritb, nitb , domain_id=nidom)
879! Vertical grid for biological trends
880          CALL histvert(nitb, 'deptht', 'Vertical T levels',  &
881          &    'm', ipk, gdept_0, ndepitb)
882
883! Declare all the output fields as NETCDF variables
884
885! biological trends
886
887          DO jn=1,jpdiabio
888            cltra=ctrbio(jn)    ! short title for biological diagnostic
889            cltral=ctrbil(jn)   ! long title for biological diagnostic
890            cltrau=ctrbiu(jn)   ! UNIT for biological diagnostic
891            CALL histdef(nitb, cltra, cltral, cltrau, jpi, jpj, nhoritb,  &
892            &    ipk, 1, ipk,  ndepitb, 32, clop, zsto, zout)
893          END DO
894
895! CLOSE netcdf Files
896
897          CALL histend(nitb)
898
899         IF(lwp) WRITE(numout,*)
900         IF(lwp) WRITE(numout,*) 'End of NetCDF Initialization in trcdib_wr'
901         IF(ll_print) CALL FLUSH(numout )
902
903     ENDIF
904
905! 2. Start writing data
906! ---------------------
907
908! biological trends
909
910      IF( lwp .AND. MOD( kt, nwritebio ) == 0 ) THEN
911         WRITE(numout,*) 'trcdit_wr : write NetCDF biological trends at ', kt, 'time-step'
912         WRITE(numout,*) '~~~~~~ '
913      ENDIF
914
915
916      DO jn=1,jpdiabio
917         cltra=ctrbio(jn)  ! short title for biological diagnostic
918         CALL histwrite(nitb, cltra, it, trbio(:,:,:,jn), ndimt50,ndext50)
919      END DO
920
921! synchronise FILE
922
923      IF( MOD( kt, nwritebio ) == 0 .OR. kindic < 0 ) THEN
924              CALL histsync(nitb)
925      ENDIF
926
927! 3. Closing all files
928! --------------------
929      IF( kt == nitend .OR. kindic < 0 ) THEN
930          CALL histclo(nitb)
931      ENDIF
932
933END SUBROUTINE trcdib_wr
934
935#    else
936
937SUBROUTINE trcdib_wr(kt,kindic)
938     !!! no passive tracers
939     INTEGER, INTENT ( in ) :: kt, kindic
940     WRITE(*,*) 'trcdib_wr: You should not have seen this print! error?', kt, kindic
941END SUBROUTINE trcdib_wr
942
943#    endif
944
945END MODULE trcdit
Note: See TracBrowser for help on using the repository browser.