/[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.23 - (show annotations) (download)
Fri Oct 14 12:45:05 2005 UTC (18 years, 8 months ago) by mlosch
Branch: MAIN
CVS Tags: checkpoint58b_post, checkpoint57y_post, checkpoint58, checkpoint58d_post, checkpoint58a_post, checkpoint57z_post, checkpoint57y_pre, checkpoint58e_post, checkpoint57w_post, checkpoint57x_post, checkpoint58c_post
Changes since 1.22: +3 -1 lines
o add namelist parameter PTRACERS_ref in analogy to tRef
  and sRef for convenience, handy, when you want to initialize
  ptracers in a large domain with a constant non-zero value. Also,
  untangle ptracers_init.F a little.

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

  ViewVC Help
Powered by ViewVC 1.1.22