/[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.21 - (show annotations) (download)
Sat Jul 30 23:53:48 2005 UTC (18 years, 10 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint57s_post, checkpoint57r_post, checkpoint57t_post, checkpoint57p_post, checkpint57u_post, checkpoint57q_post
Changes since 1.20: +1 -5 lines
move ${PKG}_MNC_INIT from ${PKG}_READ_PARAMS to ${PKG}_INIT_FIXED
(already the case for some pkgs, including recent _MNC_init, e.g. thsice)

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

  ViewVC Help
Powered by ViewVC 1.1.22