/[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.29 - (show annotations) (download)
Mon Dec 17 22:03:15 2007 UTC (16 years, 6 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint59m, checkpoint59l, checkpoint59o, checkpoint59n
Changes since 1.28: +5 -2 lines
add internal parameter and flags:
a) ptracer multi-Dim advection flag and AdamsBashforth flag
b) starting AdamsBashforth flag (in new header file: PTRACERS_RESTART.h)

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

  ViewVC Help
Powered by ViewVC 1.1.22