/[MITgcm]/MITgcm/pkg/ptracers/ptracers_readparms.F
ViewVC logotype

Contents of /MITgcm/pkg/ptracers/ptracers_readparms.F

Parent Directory Parent Directory | Revision Log Revision Log | View Revision Graph Revision Graph


Revision 1.36 - (show annotations) (download)
Sun Sep 5 22:28:14 2010 UTC (13 years, 9 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint62k, checkpoint62n, checkpoint62m, checkpoint62l
Changes since 1.35: +5 -1 lines
option (flag:PTRACERS_addSrelax2EmP) to convert Salt Relax into additional EmP

1 C $Header: /u/gcmpack/MITgcm/pkg/ptracers/ptracers_readparms.F,v 1.35 2009/06/26 23:10:10 jahn Exp $
2 C $Name: $
3
4 #include "PTRACERS_OPTIONS.h"
5
6 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
7 CBOP
8 C !ROUTINE: PTRACERS_READPARMS
9
10 C !INTERFACE:
11 SUBROUTINE PTRACERS_READPARMS( myThid )
12
13 C !DESCRIPTION:
14 C Initialize PTRACERS parameters, read in data.ptracers
15
16 C !USES:
17 IMPLICIT NONE
18 #include "SIZE.h"
19 #include "EEPARAMS.h"
20 #ifdef ALLOW_LONGSTEP
21 #include "LONGSTEP_PARAMS.h"
22 #endif
23 #include "PTRACERS_SIZE.h"
24 #include "PTRACERS_PARAMS.h"
25 #include "PARAMS.h"
26 #ifdef ALLOW_MNC
27 #include "MNC_PARAMS.h"
28 #endif
29
30 C !INPUT PARAMETERS:
31 INTEGER myThid
32 CEOP
33
34 #ifdef ALLOW_PTRACERS
35
36 C !LOCAL VARIABLES:
37 C k,iTracer :: loop indices
38 C iUnit :: unit number for I/O
39 C msgBuf :: message buffer
40 INTEGER k, iTracer
41 INTEGER iUnit
42 INTEGER ic
43 CHARACTER*(MAX_LEN_MBUF) msgBuf
44 _RL PTRACERS_diffKr(PTRACERS_num)
45 _RL tauTr1ClimRelax
46
47 C PTRACERS_taveFreq :: Frequency with which time-averaged PTRACERS
48 C are written to post-processing files.
49 C tauTr1ClimRelax :: old parameter (will be removed 1 day)
50 NAMELIST /PTRACERS_PARM01/
51 & tauTr1ClimRelax,
52 & PTRACERS_dumpFreq,
53 & PTRACERS_taveFreq,
54 & PTRACERS_monitorFreq,
55 & PTRACERS_advScheme,
56 & PTRACERS_ImplVertAdv,
57 & PTRACERS_diffKh,
58 & PTRACERS_diffK4,
59 & PTRACERS_diffKr,
60 & PTRACERS_diffKrNr,
61 & PTRACERS_ref,
62 & PTRACERS_EvPrRn,
63 & PTRACERS_addSrelax2EmP,
64 & PTRACERS_useGMRedi,
65 & PTRACERS_useDWNSLP,
66 & PTRACERS_useKPP,
67 & PTRACERS_Iter0,
68 & PTRACERS_numInUse,
69 & PTRACERS_initialFile,
70 & PTRACERS_useRecords,
71 & PTRACERS_names,
72 & PTRACERS_long_names,
73 & PTRACERS_units,
74 & PTRACERS_timeave_mnc,
75 & PTRACERS_snapshot_mnc,
76 & PTRACERS_monitor_mnc,
77 & PTRACERS_pickup_write_mnc,
78 & PTRACERS_pickup_read_mnc
79
80 _BEGIN_MASTER(myThid)
81
82 C This routine has been called by the main model so we set our
83 C internal flag to indicate we are in business
84 c PTRACERSisON=.TRUE.
85 C Note(jmc): remove this flag which is not really usefull (not set properly
86 C when usePTRACERS=F and always TRUE otherwise);
87 C much better to use "usePTRACERS" flag instead.
88
89 C Set ptracer IO & diagnostics labels (2 characters long)
90 CALL PTRACERS_SET_IOLABEL(
91 O PTRACERS_ioLabel,
92 I PTRACERS_num, myThid )
93
94 C Set defaults values for parameters in PTRACERS.h
95 PTRACERS_dumpFreq = dumpFreq
96 PTRACERS_taveFreq = taveFreq
97 PTRACERS_monitorFreq = monitorFreq
98 PTRACERS_Iter0 = 0
99 PTRACERS_numInUse=-1
100 DO iTracer=1,PTRACERS_num
101 PTRACERS_advScheme(iTracer)=saltAdvScheme
102 PTRACERS_ImplVertAdv(iTracer) = .FALSE.
103 PTRACERS_diffKh(iTracer)=diffKhS
104 PTRACERS_diffK4(iTracer)=diffK4S
105 PTRACERS_diffKr(iTracer)=UNSET_RL
106 DO k=1,Nr
107 PTRACERS_diffKrNr(k,iTracer)=diffKrNrS(k)
108 PTRACERS_ref (k,iTracer)=0. _d 0
109 ENDDO
110 PTRACERS_EvPrRn(iTracer)=UNSET_RL
111 PTRACERS_useGMRedi(iTracer)=useGMRedi
112 PTRACERS_useDWNSLP(iTracer)=useDOWN_SLOPE
113 PTRACERS_useKPP(iTracer) =useKPP
114 PTRACERS_initialFile(iTracer)=' '
115 DO ic = 1,MAX_LEN_FNAM
116 PTRACERS_names(iTracer)(ic:ic) = ' '
117 PTRACERS_long_names(iTracer)(ic:ic) = ' '
118 PTRACERS_units(iTracer)(ic:ic) = ' '
119 ENDDO
120 ENDDO
121 PTRACERS_addSrelax2EmP = .FALSE.
122 PTRACERS_useRecords = .FALSE.
123 #ifdef ALLOW_MNC
124 PTRACERS_timeave_mnc = useMNC .AND. timeave_mnc
125 PTRACERS_snapshot_mnc = useMNC .AND. snapshot_mnc
126 PTRACERS_monitor_mnc = useMNC .AND. monitor_mnc
127 PTRACERS_pickup_write_mnc = useMNC .AND. pickup_write_mnc
128 PTRACERS_pickup_read_mnc = useMNC .AND. pickup_read_mnc
129 #else
130 PTRACERS_timeave_mnc = .FALSE.
131 PTRACERS_snapshot_mnc = .FALSE.
132 PTRACERS_monitor_mnc = .FALSE.
133 PTRACERS_pickup_write_mnc = .FALSE.
134 PTRACERS_pickup_read_mnc = .FALSE.
135 #endif
136 tauTr1ClimRelax = 0.
137 DO k = 1,Nr
138 #ifdef ALLOW_LONGSTEP
139 PTRACERS_dTLev(k) = LS_nIter*dTtracerLev(k)
140 #else
141 PTRACERS_dTLev(k) = dTtracerLev(k)
142 #endif
143 ENDDO
144
145 C Open and read the data.ptracers file
146 WRITE(msgBuf,'(A)') ' PTRACERS_READPARMS: opening data.ptracers'
147 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
148 & SQUEEZE_RIGHT , myThid )
149 CALL OPEN_COPY_DATA_FILE(
150 I 'data.ptracers', 'PTRACERS_READPARMS',
151 O iUnit,
152 I myThid )
153 READ(UNIT=iUnit,NML=PTRACERS_PARM01)
154 WRITE(msgBuf,'(A)')
155 & ' PTRACERS_READPARMS: finished reading data.ptracers'
156 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
157 & SQUEEZE_RIGHT , myThid )
158
159 C Close the open data file
160 CLOSE(iUnit)
161
162 C Now set-up any remaining parameters that result from the input
163 C parameters
164
165 C Tracer 1 climatology relaxation time scale (<- but the code is gone !)
166 IF ( tauTr1ClimRelax .EQ. 0. ) THEN
167 lambdaTr1ClimRelax = 0.
168 ELSE
169 lambdaTr1ClimRelax = 1./tauTr1ClimRelax
170 ENDIF
171
172 C If PTRACERS_numInUse was not set in data.ptracers then we can
173 C assume that all PTRACERS fields will be in use
174 IF (PTRACERS_numInUse.LT.0) THEN
175 PTRACERS_numInUse=PTRACERS_num
176 ENDIF
177 C Check we are not trying to use more tracers than allowed
178 IF (PTRACERS_numInUse.GT.PTRACERS_num) THEN
179 WRITE(msgBuf,'(A,I4,A,I4,A)')
180 & ' PTRACERS_READPARMS: You requested',PTRACERS_numInUse,
181 & ' tracers at run time when only',PTRACERS_num,
182 & ' were specified at compile time. Naughty! '
183 CALL PRINT_ERROR( msgBuf, myThid )
184 STOP 'ABNORMAL END: S/R PTRACERS_READPARMS'
185 ENDIF
186 C Check that enough parameters were specified
187 DO iTracer=1,PTRACERS_numInUse
188 IF (PTRACERS_advScheme(iTracer).EQ.0) THEN
189 WRITE(msgBuf,'(A,A,I3)')
190 & ' PTRACERS_READPARMS: ',
191 & 'No advect. scheme specified for tracer #',
192 & iTracer
193 CALL PRINT_ERROR( msgBuf, myThid )
194 STOP 'ABNORMAL END: S/R PTRACERS_READPARMS'
195 ENDIF
196 ENDDO
197 #ifndef INCLUDE_IMPLVERTADV_CODE
198 DO iTracer=1,PTRACERS_numInUse
199 IF ( PTRACERS_ImplVertAdv(iTracer) ) THEN
200 WRITE(msgBuf,'(A)')
201 & 'PTRACERS_READPARMS: #undef INCLUDE_IMPLVERTADV_CODE'
202 CALL PRINT_ERROR( msgBuf, myThid )
203 WRITE(msgBuf,'(2A,I3,A)') 'PTRACERS_READPARMS:',
204 & ' but pTracers_ImplVertAdv(',iTracer,' ) is TRUE'
205 CALL PRINT_ERROR( msgBuf, myThid )
206 STOP 'ABNORMAL END: S/R PTRACERS_READPARMS'
207 ENDIF
208 ENDDO
209 IF ( PTRACERS_dTLev(1).NE.PTRACERS_dTLev(Nr)
210 & .AND. implicitDiffusion ) THEN
211 WRITE(msgBuf,'(A)')
212 & 'PTRACERS_READPARMS: #undef INCLUDE_IMPLVERTADV_CODE'
213 CALL PRINT_ERROR( msgBuf , myThid)
214 WRITE(msgBuf,'(2A)') 'PTRACERS_READPARMS: ',
215 & 'but implicitDiffusion=T with non-uniform PTRACERS_dTLev'
216 CALL PRINT_ERROR( msgBuf , myThid)
217 STOP 'ABNORMAL END: S/R PTRACERS_READPARMS'
218 ENDIF
219 #endif
220 DO iTracer=1,PTRACERS_numInUse
221 IF ( PTRACERS_useGMRedi(iTracer) .AND. .NOT.useGMRedi ) THEN
222 WRITE(msgBuf,'(2A,I3,A)') 'PTRACERS_READPARMS:',
223 & ' pTracers_useGMRedi(',iTracer,' ) is TRUE'
224 CALL PRINT_ERROR( msgBuf, myThid )
225 WRITE(msgBuf,'(A,L5,A)')
226 & 'PTRACERS_READPARMS: But not useGMRedi (=',useGMRedi,')'
227 CALL PRINT_ERROR( msgBuf, myThid )
228 STOP 'ABNORMAL END: S/R PTRACERS_READPARMS'
229 ENDIF
230 IF ( PTRACERS_useDWNSLP(iTracer) .AND. .NOT.useDOWN_SLOPE ) THEN
231 WRITE(msgBuf,'(2A,I3,A)') 'PTRACERS_READPARMS:',
232 & ' pTracers_useDWNSLP(',iTracer,' ) is TRUE'
233 CALL PRINT_ERROR( msgBuf, myThid )
234 WRITE(msgBuf,'(2A,L5,A)') 'PTRACERS_READPARMS:',
235 & ' But not useDOWN_SLOPE (=', useDOWN_SLOPE, ')'
236 CALL PRINT_ERROR( msgBuf, myThid )
237 STOP 'ABNORMAL END: S/R PTRACERS_READPARMS'
238 ENDIF
239 IF ( PTRACERS_useKPP(iTracer) .AND. .NOT.useKPP ) THEN
240 WRITE(msgBuf,'(2A,I3,A)') 'PTRACERS_READPARMS:',
241 & ' pTracers_useKPP(',iTracer,' ) is TRUE'
242 CALL PRINT_ERROR( msgBuf, myThid )
243 WRITE(msgBuf,'(A,L5,A)')
244 & 'PTRACERS_READPARMS: But not useKPP (=',useKPP,')'
245 CALL PRINT_ERROR( msgBuf, myThid )
246 STOP 'ABNORMAL END: S/R PTRACERS_READPARMS'
247 ENDIF
248 IF ( PTRACERS_diffKr(iTracer).NE.UNSET_RL ) THEN
249 DO k=1,Nr
250 PTRACERS_diffKrNr(k,iTracer)=PTRACERS_diffKr(iTracer)
251 ENDDO
252 ENDIF
253 ENDDO
254
255 #ifdef ALLOW_MNC
256 PTRACERS_timeave_mnc = useMNC .AND. PTRACERS_timeave_mnc
257 PTRACERS_snapshot_mnc = useMNC .AND. PTRACERS_snapshot_mnc
258 PTRACERS_monitor_mnc = useMNC .AND. PTRACERS_monitor_mnc
259 PTRACERS_pickup_write_mnc = useMNC .AND. PTRACERS_pickup_write_mnc
260 PTRACERS_pickup_read_mnc = useMNC .AND. PTRACERS_pickup_read_mnc
261
262 PTRACERS_timeave_mdsio = (.NOT. PTRACERS_timeave_mnc)
263 & .OR. outputTypesInclusive
264 PTRACERS_snapshot_mdsio = (.NOT. PTRACERS_snapshot_mnc)
265 & .OR. outputTypesInclusive
266 PTRACERS_monitor_stdio = (.NOT. PTRACERS_monitor_mnc)
267 & .OR. outputTypesInclusive
268 PTRACERS_pickup_write_mdsio = (.NOT. PTRACERS_pickup_write_mnc)
269 & .OR. outputTypesInclusive
270 PTRACERS_pickup_read_mdsio = (.NOT. PTRACERS_pickup_read_mnc)
271 & .OR. outputTypesInclusive
272 #else
273 PTRACERS_timeave_mnc = .FALSE.
274 PTRACERS_snapshot_mnc = .FALSE.
275 PTRACERS_monitor_mnc = .FALSE.
276 PTRACERS_pickup_write_mnc = .FALSE.
277 PTRACERS_pickup_read_mnc = .FALSE.
278 PTRACERS_timeave_mdsio = .TRUE.
279 PTRACERS_snapshot_mdsio = .TRUE.
280 PTRACERS_monitor_stdio = .TRUE.
281 PTRACERS_pickup_write_mdsio = .TRUE.
282 PTRACERS_pickup_read_mdsio = .TRUE.
283 #endif
284
285 C-- Print a summary of pTracer parameter values:
286 iUnit = standardMessageUnit
287 WRITE(msgBuf,'(A)') '// ==================================='
288 CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT , myThid )
289 WRITE(msgBuf,'(A)') '// PTRACERS parameters '
290 CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT , myThid )
291 WRITE(msgBuf,'(A)') '// ==================================='
292 CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT , myThid )
293 CALL WRITE_0D_I( PTRACERS_numInUse, INDEX_NONE,
294 & 'PTRACERS_numInUse =',
295 & ' /* number of tracers */')
296 CALL WRITE_0D_I( PTRACERS_Iter0, INDEX_NONE,
297 & 'PTRACERS_Iter0 =',
298 & ' /* timestep number when tracers are initialized */')
299 CALL WRITE_0D_L( PTRACERS_addSrelax2EmP, INDEX_NONE,
300 & 'PTRACERS_addSrelax2EmP =','/* add Salt relaxation to EmP */')
301 CALL WRITE_1D_RL( PTRACERS_dTLev, Nr, INDEX_K,
302 & 'PTRACERS_dTLev =',
303 &' /* Ptracer timestep ( s ) */')
304 CALL WRITE_0D_RL(PTRACERS_dumpFreq, INDEX_NONE,
305 & 'PTRACERS_dumpFreq =',
306 & ' /* Frequency^-1 for snapshot output (s) */')
307 CALL WRITE_0D_RL(PTRACERS_taveFreq, INDEX_NONE,
308 & 'PTRACERS_taveFreq =',
309 & ' /* Frequency^-1 for time-Aver. output (s) */')
310 CALL WRITE_0D_L( PTRACERS_useRecords, INDEX_NONE,
311 & 'PTRACERS_useRecords =', ' /* all tracers in 1 file */')
312
313 CALL WRITE_0D_L( PTRACERS_timeave_mnc, INDEX_NONE,
314 & 'PTRACERS_timeave_mnc =',
315 & ' /* use MNC for Tave output */')
316 CALL WRITE_0D_L( PTRACERS_snapshot_mnc, INDEX_NONE,
317 & 'PTRACERS_snapshot_mnc =',
318 & ' /* use MNC for snapshot output */')
319 CALL WRITE_0D_L( PTRACERS_pickup_write_mnc, INDEX_NONE,
320 & 'PTRACERS_pickup_write_mnc =',
321 & ' /* use MNC for writing pickups */')
322 CALL WRITE_0D_L( PTRACERS_pickup_read_mnc, INDEX_NONE,
323 & 'PTRACERS_pickup_read_mnc =',
324 & ' /* use MNC for reading pickups */')
325
326 DO iTracer=1,PTRACERS_numInUse
327 WRITE(msgBuf,'(A)') ' -----------------------------------'
328 CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT, myThid )
329 WRITE(msgBuf,'(A,I4)') ' tracer number : ',iTracer
330 CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT, myThid )
331 CALL WRITE_0D_C( PTRACERS_ioLabel(iTracer), 0, INDEX_NONE,
332 & 'PTRACERS_ioLabel =', ' /* tracer IO Label */')
333 CALL WRITE_0D_I( PTRACERS_advScheme(iTracer), INDEX_NONE,
334 & 'PTRACERS_advScheme =', ' /* Advection Scheme */')
335 CALL WRITE_0D_L( PTRACERS_ImplVertAdv(iTracer), INDEX_NONE,
336 & 'PTRACERS_ImplVertAdv =',
337 & ' /* implicit vert. advection flag */')
338 CALL WRITE_0D_RL( PTRACERS_diffKh(iTracer), INDEX_NONE,
339 & 'PTRACERS_diffKh =', ' /* Laplacian Diffusivity */')
340 CALL WRITE_0D_RL( PTRACERS_diffK4(iTracer), INDEX_NONE,
341 & 'PTRACERS_diffK4 =', ' /* Biharmonic Diffusivity */')
342 CALL WRITE_1D_RL( PTRACERS_diffKrNr(1,iTracer), Nr, INDEX_K,
343 & 'PTRACERS_diffKrNr =', ' /* Vertical Diffusivity */')
344 CALL WRITE_0D_L( PTRACERS_useGMRedi(iTracer), INDEX_NONE,
345 & 'PTRACERS_useGMRedi =', ' /* apply GM-Redi */')
346 CALL WRITE_0D_L( PTRACERS_useDWNSLP(iTracer), INDEX_NONE,
347 & 'PTRACERS_useDWNSLP =', ' /* apply DOWN-SLOPE Flow */')
348 CALL WRITE_0D_L( PTRACERS_useKPP(iTracer), INDEX_NONE,
349 & 'PTRACERS_useKPP =', ' /* apply KPP scheme */')
350 CALL WRITE_1D_RL( PTRACERS_ref(1,iTracer), Nr, INDEX_K,
351 & 'PTRACERS_ref =', ' /* Reference vertical profile */')
352 CALL WRITE_0D_RL( PTRACERS_EvPrRn(iTracer), INDEX_NONE,
353 & 'PTRACERS_EvPrRn =', '/* tracer conc. in Evap. & Rain */')
354
355 ENDDO
356 WRITE(msgBuf,'(A)') ' -----------------------------------'
357 CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT, myThid )
358
359 _END_MASTER(myThid)
360 C Everyone else must wait for the parameters to be loaded
361 _BARRIER
362
363 #endif /* ALLOW_PTRACERS */
364
365 RETURN
366 END
367

  ViewVC Help
Powered by ViewVC 1.1.22