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.
trcdii.F in trunk/NEMO/TOP_SRC – NEMO

source: trunk/NEMO/TOP_SRC/trcdii.F @ 247

Last change on this file since 247 was 247, checked in by opalod, 19 years ago

CL : Add CVS Header and CeCILL licence information

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 6.0 KB
Line 
1CCC $Header$ 
2CCC  TOP 1.0 , LOCEAN-IPSL (2005) 
3C This software is governed by CeCILL licence see modipsl/doc/NEMO_CeCILL.txt 
4C ---------------------------------------------------------------------------
5
6CDIR$ LIST
7      SUBROUTINE trcdii(kt,kindic)
8CCC---------------------------------------------------------------------
9CCC
10CCC                       ROUTINE trcdii
11CCC                     ******************
12CCC
13CCC  Purpose :
14CCC  ---------
15CCC     output of passive tracer : additional 2D and 3D arrays
16CCC
17CCC
18CC   Method :
19CC   -------
20CC
21CC At the beginning of the first time step (nit000), define all
22CC the NETCDF files and fields for concentration of passive tracer
23CC
24CC      At each time step call histdef to compute the mean if necessary
25CC Each nwrite time step, output the instantaneous or mean fields
26CC
27CC IF kindic <0, output of fields before the model interruption.
28CC      IF kindic =0, time step loop
29CC      IF kindic >0, output of fields before the time step loop
30CC
31CC
32CC
33CC   Input :
34CC   -----
35CC      argument
36CC              kt              : time step
37CC    kindic      : indicator of abnormal termination
38CC      COMMON
39CC            /comcoh/          : orthogonal curvilinear coordinates
40CC                                and scale factors
41CC            /comask/          : masks, bathymetry
42CC            /cottrc/          : passive tracers fields (before,now
43CC                                  ,after)
44CC            /citcdf/     : NETCDF variables
45CC
46CC   Output :
47CC   ------
48CC      file
49CC              "clhstnam" files : one for concentration, one for
50CC                                 aditional 2D and 3D arrays
51CC
52CC
53CC   Workspace :
54CC   ---------
55CC      local
56CC
57CC   EXTERNAL :
58CC   --------
59CC prihre, hist..., dianam
60CC
61CC   MODIFICATIONS:
62CC   --------------
63CC      original  : 95-01  passive tracers  (M. Levy)
64CC      additions : 98-01 (C. Levy) NETCDF format using ioipsl interface
65CC      additions : 99-01 (M.A. Foujols) adapted for passive tracer
66CC      additions : 99-09 (M.A. Foujols) split into three parts
67CC----------------------------------------------------------------------
68CC parameters and commons
69CC ======================
70      USE ioipsl
71CDIR$ NOLIST
72      USE oce_trc
73      USE trc
74      USE dianam    ! build name of file (routine)
75CDIR$ LIST
76CC----------------------------------------------------------------------
77CC local declarations
78CC ==================
79      INTEGER kt, kindic
80
81#    if defined key_passivetrc && defined key_trc_diaadd
82
83      INTEGER jn
84      LOGICAL clp
85C
86      CHARACTER*40 clhstnam
87      CHARACTER*40 clop
88      CHARACTER*20 cltra, cltrau
89      CHARACTER*80 cltral
90
91      REAL zsto, zout
92      INTEGER iimi, iima, ijmi, ijma, ipk
93C
94CC----------------------------------------------------------------------
95C
96C 0. Initialisation
97C -----------------
98C
99C
100C local variable for debugging
101      clp=.true.
102      clp=clp.and.lwp
103C
104C Define frequency of output and means
105C
106#        if defined key_diainstant
107      zsto=nwriteadd*rdt
108      clop='inst(only(x))'
109#        else
110      zsto=rdt
111      clop='ave(only(x))'
112#        endif
113      zout=nwriteadd*rdt
114C
115C Define indexes of the horizontal output zoom
116      iimi=1
117      iima=jpi
118      ijmi=1
119      ijma=jpj
120c ipk limit storage in depth
121      ipk = jpk
122C
123C
124C 1. Define NETCDF files and fields at beginning of first time step
125C -----------------------------------------------------------------
126C
127      IF(clp)WRITE(numout,*)'trcdii kt=',kt,' kindic ',kindic
128      IF (kt.eq.nit000.and.kindic.eq.1) THEN
129       
130C
131C Define the NETCDF files for additional arrays : 2D or 3D
132C
133C Define the T grid file for tracer auxiliary files
134C
135          CALL dia_nam(clhstnam,nwrite,'diad_T')
136          IF(lwp)WRITE(numout,*)" Name of NETCDF file ",
137     $        clhstnam
138C Define a netcdf FILE for 2d and 3d arrays
139          CALL histbeg(clhstnam, jpi, glamt, jpj, gphit,
140     $        iimi, iima-iimi+1, ijmi, ijma-ijmi+1,
141     $        nit000-1, djulian, rdt, nhoritd, nitd)
142C Vertical grid for 2d and 3d arrays
143          CALL histvert(nitd, 'deptht', 'Vertical T levels',
144     $        'm', ipk, gdept, ndepitd)
145C
146C Declare all the output fields as NETCDF variables
147C
148C more 3D horizontal arrays
149C
150          DO jn=1,jpdia3d
151            cltra=ctrc3d(jn)    ! short title for 3D diagnostic
152            cltral=ctrc3l(jn)   ! long title for 3D diagnostic
153            cltrau=ctrc3u(jn)   ! UNIT for 3D diagnostic
154            CALL histdef(nitd, cltra, cltral, cltrau, jpi, jpj, nhoritd,
155     $          ipk, 1, ipk,  ndepitd, 32, clop, zsto, zout)
156          END DO
157         
158C
159C more 2D horizontal arrays
160C
161          DO jn=1,jpdia2d
162            cltra=ctrc2d(jn)    ! short title for 2D diagnostic
163            cltral=ctrc2l(jn)   ! long title for 2D diagnostic
164            cltrau=ctrc2u(jn)   ! UNIT for 2D diagnostic
165            CALL histdef(nitd, cltra, cltral, cltrau, jpi, jpj, nhoritd,
166     $          1, 1, 1,  -99, 32, clop, zsto, zout)
167          END DO
168         
169C
170C TODO: more 2D vertical sections arrays : I or J indice fixed 
171C
172
173C
174C CLOSE netcdf Files
175C         
176          CALL histend(nitd)
177C
178C SOME diagnostics to DO first time
179C
180
181      ELSE
182C
183C
184C 2. Start writing data
185C ---------------------
186C
187C more 3D horizontal arrays
188C
189          DO jn=1,jpdia3d
190            cltra=ctrc3d(jn) ! short title for 3D diagnostic
191            CALL histwrite(nitd, cltra, kt, trc3d(:,:,:,jn), ndimt50
192     $          ,ndext50) 
193          END DO
194
195C
196C more 2D horizontal arrays
197C
198          DO jn=1,jpdia2d
199            cltra=ctrc2d(jn) ! short title for 2D diagnostic
200            CALL histwrite(nitd, cltra, kt, trc2d(:,:,jn), ndimt51
201     $          ,ndext51) 
202          END DO
203
204C
205C synchronise FILE 
206C
207          IF(lwp .and. mod( kt, nwriteadd ).EQ.0) THEN
208              WRITE(numout,*)
209     $            '**** trcdii : write NetCDF aditional arrays' 
210              CALL histsync(nitd)
211          ENDIF
212      ENDIF
213C
214C 3. Closing all files
215C --------------------
216      IF (kt.EQ.nitend.OR.kindic.LT.0) THEN
217          CALL histclo(nitd)
218      ENDIF
219
220#    else
221C
222C no passive tracers
223C
224#    endif
225
226C
227C 
228      RETURN
229      END
Note: See TracBrowser for help on using the repository browser.