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

source: trunk/NEMO/TOP_SRC/trcdit.F @ 186

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

CL + CE : NEMO TRC_SRC start

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