/[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.25 - (show annotations) (download)
Tue Aug 8 21:20:26 2006 UTC (17 years, 10 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint59, checkpoint58y_post, checkpoint58t_post, checkpoint58w_post, checkpoint58o_post, checkpoint58p_post, checkpoint58q_post, checkpoint58r_post, checkpoint58n_post, checkpoint59e, checkpoint59d, checkpoint59g, checkpoint59f, checkpoint59a, checkpoint59c, checkpoint59b, checkpoint58v_post, checkpoint58x_post, checkpoint58u_post, checkpoint58s_post
Changes since 1.24: +35 -39 lines
safer for multi-threaded run.

1 C $Header: /u/gcmpack/MITgcm/pkg/ptracers/ptracers_readparms.F,v 1.24 2006/05/23 23:32:41 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.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 PTRACERSisON=.TRUE.
77
78 C Set defaults values for parameters in PTRACERS.h
79 PTRACERS_dumpFreq = dumpFreq
80 PTRACERS_taveFreq = taveFreq
81 PTRACERS_monitorFreq = monitorFreq
82 PTRACERS_Iter0 = 0
83 PTRACERS_numInUse=-1
84 DO iTracer=1,PTRACERS_num
85 PTRACERS_advScheme(iTracer)=saltAdvScheme
86 PTRACERS_ImplVertAdv(iTracer) = .FALSE.
87 PTRACERS_diffKh(iTracer)=diffKhS
88 PTRACERS_diffK4(iTracer)=diffK4S
89 PTRACERS_diffKr(iTracer)=UNSET_RL
90 DO k=1,Nr
91 PTRACERS_diffKrNr(k,iTracer)=diffKrNrS(k)
92 PTRACERS_ref (k,iTracer)=0. _d 0
93 ENDDO
94 PTRACERS_EvPrRn(iTracer)=UNSET_RL
95 PTRACERS_useGMRedi(iTracer)=useGMRedi
96 PTRACERS_useKPP(iTracer)=useKPP
97 PTRACERS_initialFile(iTracer)=' '
98 DO ic = 1,MAX_LEN_FNAM
99 PTRACERS_names(iTracer)(ic:ic) = ' '
100 PTRACERS_long_names(iTracer)(ic:ic) = ' '
101 PTRACERS_units(iTracer)(ic:ic) = ' '
102 ENDDO
103 ENDDO
104 PTRACERS_useRecords = .FALSE.
105 #ifdef ALLOW_MNC
106 PTRACERS_timeave_mnc = useMNC .AND. timeave_mnc
107 PTRACERS_snapshot_mnc = useMNC .AND. snapshot_mnc
108 PTRACERS_monitor_mnc = useMNC .AND. monitor_mnc
109 PTRACERS_pickup_write_mnc = useMNC .AND. pickup_write_mnc
110 PTRACERS_pickup_read_mnc = useMNC .AND. pickup_read_mnc
111 #else
112 PTRACERS_timeave_mnc = .FALSE.
113 PTRACERS_snapshot_mnc = .FALSE.
114 PTRACERS_monitor_mnc = .FALSE.
115 PTRACERS_pickup_write_mnc = .FALSE.
116 PTRACERS_pickup_read_mnc = .FALSE.
117 #endif
118
119 C Open and read the data.ptracers file
120 WRITE(msgBuf,'(A)') ' PTRACERS_READPARMS: opening data.ptracers'
121 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
122 & SQUEEZE_RIGHT , myThid )
123 CALL OPEN_COPY_DATA_FILE(
124 I 'data.ptracers', 'PTRACERS_READPARMS',
125 O iUnit,
126 I myThid )
127 READ(UNIT=iUnit,NML=PTRACERS_PARM01)
128 WRITE(msgBuf,'(A)')
129 & ' PTRACERS_READPARMS: finished reading data.ptracers'
130 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
131 & SQUEEZE_RIGHT , myThid )
132
133 C Close the open data file
134 CLOSE(iUnit)
135
136 C Now set-up any remaining parameters that result from the input
137 C parameters
138
139 C If PTRACERS_numInUse was not set in data.ptracers then we can
140 C assume that all PTRACERS fields will be in use
141 IF (PTRACERS_numInUse.LT.0) THEN
142 PTRACERS_numInUse=PTRACERS_num
143 ENDIF
144 C Check we are not trying to use more tracers than allowed
145 IF (PTRACERS_numInUse.GT.PTRACERS_num) THEN
146 WRITE(msgBuf,'(A,I2,A,I2,A)')
147 & ' PTRACERS_READPARMS: You requested ',PTRACERS_numInUse,
148 & ' tracers at run time when only ',PTRACERS_num,
149 & ' were specified at compile time. Naughty! '
150 CALL PRINT_ERROR( msgBuf, myThid )
151 STOP 'ABNORMAL END: S/R PTRACERS_READPARMS'
152 ENDIF
153 C Check that enough parameters were specified
154 DO iTracer=1,PTRACERS_numInUse
155 IF (PTRACERS_advScheme(iTracer).EQ.0) THEN
156 WRITE(msgBuf,'(A,A,I2)')
157 & ' PTRACERS_READPARMS: ',
158 & 'No advect. scheme specified for tracer #',
159 & iTracer
160 CALL PRINT_ERROR( msgBuf, myThid )
161 STOP 'ABNORMAL END: S/R PTRACERS_READPARMS'
162 ENDIF
163 ENDDO
164 #ifndef INCLUDE_IMPLVERTADV_CODE
165 DO iTracer=1,PTRACERS_numInUse
166 IF ( PTRACERS_ImplVertAdv(iTracer) ) THEN
167 WRITE(msgBuf,'(A)')
168 & 'PTRACERS_READPARMS: #undef INCLUDE_IMPLVERTADV_CODE'
169 CALL PRINT_ERROR( msgBuf, myThid )
170 WRITE(msgBuf,'(2A,I2,A)') 'PTRACERS_READPARMS:',
171 & ' but pTracers_ImplVertAdv(',iTracer,' ) is TRUE'
172 CALL PRINT_ERROR( msgBuf, myThid )
173 STOP 'ABNORMAL END: S/R PTRACERS_READPARMS'
174 ENDIF
175 ENDDO
176 #endif
177 DO iTracer=1,PTRACERS_numInUse
178 PTRACERS_useGMRedi(iTracer) = PTRACERS_useGMRedi(iTracer)
179 & .AND.useGMRedi
180 PTRACERS_useKPP(iTracer) = PTRACERS_useKPP(iTracer)
181 & .AND.useKPP
182 IF ( PTRACERS_diffKr(iTracer).NE.UNSET_RL ) THEN
183 DO k=1,Nr
184 PTRACERS_diffKrNr(k,iTracer)=PTRACERS_diffKr(iTracer)
185 ENDDO
186 ENDIF
187 ENDDO
188
189 #ifdef ALLOW_MNC
190 PTRACERS_timeave_mnc = useMNC .AND. PTRACERS_timeave_mnc
191 PTRACERS_snapshot_mnc = useMNC .AND. PTRACERS_snapshot_mnc
192 PTRACERS_monitor_mnc = useMNC .AND. PTRACERS_monitor_mnc
193 PTRACERS_pickup_write_mnc = useMNC .AND. PTRACERS_pickup_write_mnc
194 PTRACERS_pickup_read_mnc = useMNC .AND. PTRACERS_pickup_read_mnc
195
196 PTRACERS_timeave_mdsio = (.NOT. PTRACERS_timeave_mnc)
197 & .OR. outputTypesInclusive
198 PTRACERS_snapshot_mdsio = (.NOT. PTRACERS_snapshot_mnc)
199 & .OR. outputTypesInclusive
200 PTRACERS_monitor_stdio = (.NOT. PTRACERS_monitor_mnc)
201 & .OR. outputTypesInclusive
202 PTRACERS_pickup_write_mdsio = (.NOT. PTRACERS_pickup_write_mnc)
203 & .OR. outputTypesInclusive
204 PTRACERS_pickup_read_mdsio = (.NOT. PTRACERS_pickup_read_mnc)
205 & .OR. outputTypesInclusive
206 #else
207 PTRACERS_timeave_mnc = .FALSE.
208 PTRACERS_snapshot_mnc = .FALSE.
209 PTRACERS_monitor_mnc = .FALSE.
210 PTRACERS_pickup_write_mnc = .FALSE.
211 PTRACERS_pickup_read_mnc = .FALSE.
212 PTRACERS_timeave_mdsio = .TRUE.
213 PTRACERS_snapshot_mdsio = .TRUE.
214 PTRACERS_monitor_stdio = .TRUE.
215 PTRACERS_pickup_write_mdsio = .TRUE.
216 PTRACERS_pickup_read_mdsio = .TRUE.
217 #endif
218
219 C-- Print a summary of pTracer parameter values:
220 iUnit = standardMessageUnit
221 WRITE(msgBuf,'(A)') '// ==================================='
222 CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT , myThid )
223 WRITE(msgBuf,'(A)') '// PTRACERS parameters '
224 CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT , myThid )
225 WRITE(msgBuf,'(A)') '// ==================================='
226 CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT , myThid )
227 CALL WRITE_0D_I( PTRACERS_numInUse, INDEX_NONE,
228 & 'PTRACERS_numInUse =',
229 & ' /* number of tracers */')
230 CALL WRITE_0D_I( PTRACERS_Iter0, INDEX_NONE,
231 & 'PTRACERS_Iter0 =',
232 & ' /* timestep number when tracers are initialized */')
233 CALL WRITE_0D_R8(PTRACERS_dumpFreq, INDEX_NONE,
234 & 'PTRACERS_dumpFreq =',
235 & ' /* Frequency^-1 for snapshot output (s) */')
236 CALL WRITE_0D_R8(PTRACERS_taveFreq, INDEX_NONE,
237 & 'PTRACERS_taveFreq =',
238 & ' /* Frequency^-1 for time-Aver. output (s) */')
239 CALL WRITE_0D_L( PTRACERS_useRecords, INDEX_NONE,
240 & 'PTRACERS_useRecords =', ' /* all tracers in 1 file */')
241
242 CALL WRITE_0D_L( PTRACERS_timeave_mnc, INDEX_NONE,
243 & 'PTRACERS_timeave_mnc =',
244 & ' /* use MNC for Tave output */')
245 CALL WRITE_0D_L( PTRACERS_snapshot_mnc, INDEX_NONE,
246 & 'PTRACERS_snapshot_mnc =',
247 & ' /* use MNC for snapshot output */')
248 CALL WRITE_0D_L( PTRACERS_pickup_write_mnc, INDEX_NONE,
249 & 'PTRACERS_pickup_write_mnc =',
250 & ' /* use MNC for writing pickups */')
251 CALL WRITE_0D_L( PTRACERS_pickup_read_mnc, INDEX_NONE,
252 & 'PTRACERS_pickup_read_mnc =',
253 & ' /* use MNC for reading pickups */')
254
255 DO iTracer=1,PTRACERS_numInUse
256 WRITE(msgBuf,'(A)') ' -----------------------------------'
257 CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT, myThid )
258 WRITE(msgBuf,'(A,I4)') ' tracer number : ',iTracer
259 CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT, myThid )
260 CALL WRITE_0D_I( PTRACERS_advScheme(iTracer), INDEX_NONE,
261 & 'PTRACERS_advScheme =', ' /* Advection Scheme */')
262 CALL WRITE_0D_L( PTRACERS_ImplVertAdv(iTracer), INDEX_NONE,
263 & 'PTRACERS_ImplVertAdv =',
264 & ' /* implicit vert. advection flag */')
265 CALL WRITE_0D_R8( PTRACERS_diffKh(iTracer), INDEX_NONE,
266 & 'PTRACERS_diffKh =', ' /* Laplacian Diffusivity */')
267 CALL WRITE_0D_R8( PTRACERS_diffK4(iTracer), INDEX_NONE,
268 & 'PTRACERS_diffK4 =', ' /* Biharmonic Diffusivity */')
269 CALL WRITE_1D_R8( PTRACERS_diffKrNr(1,iTracer), Nr, INDEX_K,
270 & 'PTRACERS_diffKrNr =', ' /* Vertical Diffusivity */')
271 CALL WRITE_0D_L( PTRACERS_useGMRedi(iTracer), INDEX_NONE,
272 & 'PTRACERS_useGMRedi =', ' /* apply GM-Redi */')
273 CALL WRITE_0D_L( PTRACERS_useKPP(iTracer), INDEX_NONE,
274 & 'PTRACERS_useKPP =', ' /* apply KPP scheme */')
275 CALL WRITE_1D_R8( PTRACERS_ref(1,iTracer), Nr, INDEX_K,
276 & 'PTRACERS_ref =', ' /* Reference vertical profile */')
277 CALL WRITE_0D_R8( PTRACERS_EvPrRn(iTracer), INDEX_NONE,
278 & 'PTRACERS_EvPrRn =', '/* tracer conc. in Evap. & Rain */')
279
280 ENDDO
281 WRITE(msgBuf,'(A)') ' -----------------------------------'
282 CALL PRINT_MESSAGE( msgBuf, iUnit, SQUEEZE_RIGHT, myThid )
283
284 _END_MASTER(myThid)
285 C Everyone else must wait for the parameters to be loaded
286 _BARRIER
287
288 #endif /* ALLOW_PTRACERS */
289
290 RETURN
291 END
292

  ViewVC Help
Powered by ViewVC 1.1.22