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 @ 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.6 KB
Line 
1
2CCC $Header$ 
3CCC  TOP 1.0 , LOCEAN-IPSL (2005) 
4C This software is governed by CeCILL licence see modipsl/doc/NEMO_CeCILL.txt 
5C ---------------------------------------------------------------------------
6CDIR$ LIST
7      SUBROUTINE trcdit(kt,kindic)
8CCC---------------------------------------------------------------------
9CCC
10CCC                       ROUTINE trcdit
11CCC                     ******************
12CCC
13CCC  Purpose :
14CCC  ---------
15CCC     Standard output of passive tracer : concentration fields
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
50CC
51CC
52CC   Workspace :
53CC   ---------
54CC      local
55CC
56CC   EXTERNAL :
57CC   --------
58CC prihre, hist..., dianam
59CC
60CC   MODIFICATIONS:
61CC   --------------
62CC      original  : 95-01  passive tracers  (M. Levy)
63CC      additions : 98-01 (C. Levy) NETCDF format using ioipsl interface
64CC      additions : 99-01 (M.A. Foujols) adapted for passive tracer
65CC      additions : 99-09 (M.A. Foujols) split into three parts
66CC----------------------------------------------------------------------
67CC parameters and commons
68CC ======================
69      USE ioipsl
70CDIR$ NOLIST
71      USE oce_trc
72      USE trc
73      USE dianam    ! build name of file (routine)
74      IMPLICIT NONE
75CDIR$ LIST
76CC----------------------------------------------------------------------
77CC local declarations
78CC ==================
79      INTEGER kt, kindic
80      REAL xjulian
81
82#    if defined key_passivetrc
83
84      INTEGER jn
85      LOGICAL clp
86C
87      CHARACTER*40 clhstnam
88      CHARACTER*40 clop
89      CHARACTER*20 cltra, cltrau
90      CHARACTER*80 cltral
91
92      REAL zsto, zout, zsec
93      INTEGER iyear,imonth,iday,iimi, iima, ijmi, ijma, ipk
94C
95C
96C 0. Initialisation
97C -----------------
98C
99C
100C local variable for debugging
101      clp=.false.
102      clp=clp.and.lwp
103C
104C Define frequency of output and means
105C
106#        if defined key_diainstant
107      zsto=nwritetrc*rdt
108      clop='inst(only(x))'
109#        else
110      zsto=rdt
111      clop='ave(only(x))'
112#        endif
113      zout=nwritetrc*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
122
123C
124C
125C 1. Define NETCDF files and fields at beginning of first time step
126C -----------------------------------------------------------------
127C
128      IF(clp)WRITE(numout,*)'trcdit kt=',kt,' kindic ',kindic
129      IF (kt.eq.nit000.and.kindic.eq.1) THEN
130
131          WRITE(numout,*)" indexes of zoom = ", 
132     $      iimi, iima, ijmi, ijma
133          WRITE(numout,*)" limit storage in depth = ", ipk
134c
135c   choose calendar for ioipsl
136c
137          IF (nleapy .eq. 1) THEN
138              CALL ioconf_calendar('gregorian')
139          ELSE IF  (nleapy .eq. 0) THEN
140              CALL ioconf_calendar('noleap')
141          ELSE IF (nleapy .eq. 30) THEN
142              CALL ioconf_calendar('360d')
143          ENDIF
144C
145C Compute julian date from starting date of the run
146C
147          iyear = ijulian/10000
148          imonth = ijulian/100 - iyear*100
149          iday = ijulian - imonth*100 - iyear*10000
150          iyear = ijulian/10000
151          zsec=0.
152          CALL ymds2ju(iyear,imonth,iday,zsec,xjulian)
153
154          iyear = ndastp/10000
155          imonth = ndastp/100 - iyear*100
156          iday = ndastp - imonth*100 - iyear*10000
157          iyear = ndastp/10000
158          zsec=0.
159          CALL ymds2ju(iyear,imonth,iday,zsec,djulian)
160          write(0,*) iyear,imonth,iday,zsec,djulian
161          IF(lwp)WRITE(numout,*)' ' 
162          IF(lwp)WRITE(numout,*)' Date 0 used :',nit000
163     $        ,' YEAR ',iyear,' MONTH ',imonth,' DAY ',iday
164     $        ,'Julian day : ',djulian
165     $        ,'XJulian day : ',xjulian
166C
167C Define the NETCDF files for passive tracer concentration
168C
169          CALL dia_nam(clhstnam,nwrite,'ptrc_T')
170
171          IF(lwp)WRITE(numout,*)" Name of NETCDF file ",
172     $        clhstnam
173C Horizontal grid : glamt and gphit
174C 
175          CALL histbeg(clhstnam, jpi, glamt, jpj, gphit,
176     $        iimi, iima-iimi+1, ijmi, ijma-ijmi+1, 
177c     $        nit000-1, xjulian, rdt, nhorit5, nit5)
178     $        nit000-1, djulian, rdt, nhorit5, nit5)
179C Vertical grid for tracer : gdept
180          CALL histvert(nit5, 'deptht', 'Vertical T levels',
181     $        'm', ipk, gdept, ndepit5)
182
183C Index of ocean points in 3D and 2D (surface)
184          CALL wheneq(jpi*jpj*ipk,tmask,1,1.,ndext50,ndimt50)
185          CALL wheneq(jpi*jpj,tmask,1,1.,ndext51,ndimt51)
186C
187C Declare all the output fields as NETCDF variables
188C
189C tracer concentrations
190C
191          DO jn=1,jptra
192            cltra=ctrcnm(jn)    ! short title for tracer
193            cltral=ctrcnl(jn)   ! long title for tracer
194            cltrau=ctrcun(jn)   ! UNIT for tracer
195            CALL histdef(nit5, cltra, cltral, cltrau, jpi, jpj, nhorit5,
196     $          ipk, 1, ipk,  ndepit5, 32, clop, zsto, zout) 
197          END DO           
198C
199C CLOSE netcdf Files
200C         
201          CALL histend(nit5)
202C
203C SOME diagnostics to DO first time
204C
205      ELSE
206C
207C
208C 2. Start writing data
209C ---------------------
210C
211C tracer concentrations
212C
213          DO jn=1,jptra
214            cltra=ctrcnm(jn) ! short title for tracer
215            CALL histwrite(nit5, cltra, kt,trn(:,:,:,jn), ndimt50,
216     $          ndext50)
217          END DO
218C
219C synchronise FILE
220C
221          IF(lwp .and. mod( kt, nwritetrc ).EQ.0) THEN
222              WRITE(numout,*)
223     $        '**** trcdit : write NetCDF passive tracer concentration' 
224              CALL histsync(nit5)
225          ENDIF
226      ENDIF
227C
228C 3. Closing all files
229C --------------------
230      IF (kt.EQ.nitend.OR.kindic.LT.0) THEN
231          CALL histclo(nit5)
232      ENDIF
233
234#    else
235C
236C no passive tracers
237C
238#    endif
239
240C
241C 
242      RETURN
243      END
Note: See TracBrowser for help on using the repository browser.