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

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

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


Revision 1.11 - (show annotations) (download)
Thu May 8 19:50:09 2008 UTC (16 years, 1 month ago) by jahn
Branch: MAIN
Changes since 1.10: +51 -2 lines
add second-order moment advection schemes (80 and 81);
this uses a dynamically allocated internal state data structure
(#define PTRACERS_ALLOW_DYN_STATE in PTRACERS_OPTIONS.h)
and requires a fortran 90 compiler

1 C $Header: /u/gcmpack/MITgcm/pkg/ptracers/ptracers_read_pickup.F,v 1.10 2008/01/27 19:35:42 jmc Exp $
2 C $Name: $
3
4 #include "GAD_OPTIONS.h"
5 #include "PTRACERS_OPTIONS.h"
6
7 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
8 CBOP
9 C !ROUTINE: PTRACERS_READ_PICKUP
10
11 C !INTERFACE:
12 SUBROUTINE PTRACERS_READ_PICKUP( myIter, myThid )
13
14 C !DESCRIPTION:
15 C Reads current state of passive tracers from a pickup file
16
17 C !USES:
18 #include "PTRACERS_MOD.h"
19 IMPLICIT NONE
20 #include "SIZE.h"
21 #include "EEPARAMS.h"
22 #include "PARAMS.h"
23 #include "GAD.h"
24 #include "PTRACERS_SIZE.h"
25 #include "PTRACERS_PARAMS.h"
26 #include "PTRACERS_RESTART.h"
27 #include "PTRACERS_FIELDS.h"
28
29 C !INPUT PARAMETERS:
30 C myIter :: time-step number
31 C myThid :: thread number
32 INTEGER myIter
33 INTEGER myThid
34
35 #ifdef ALLOW_PTRACERS
36
37 C !LOCAL VARIABLES:
38 C iTracer :: tracer index
39 C iRec :: record number
40 C fn :: character buffer for creating filename
41 C prec :: precision of pickup files
42 C filePrec :: pickup-file precision (read from meta file)
43 C nbFields :: number of fields in pickup file (read from meta file)
44 C fldName :: Name of the field to read
45 C missFldList :: List of missing fields (attempted to read but not found)
46 C missFldDim :: Dimension of missing fields list array: missFldList
47 C nMissing :: Number of missing fields (attempted to read but not found)
48 C j :: loop index
49 C nj :: record number
50 C ioUnit :: temp for writing msg unit
51 C msgBuf :: Informational/error message buffer
52 INTEGER iTracer, iRec, prec, n
53 INTEGER filePrec, nbFields
54 INTEGER missFldDim, nMissing
55 INTEGER nj, ioUnit
56 PARAMETER( missFldDim = 2*PTRACERS_num )
57 CHARACTER*(MAX_LEN_FNAM) fn
58 CHARACTER*(8) fldName, missFldList(missFldDim)
59 CHARACTER*(MAX_LEN_MBUF) msgBuf
60 CEOP
61
62 _BARRIER
63
64 #ifdef ALLOW_MNC
65 IF ( PTRACERS_pickup_read_mnc ) THEN
66 C Read variables from the pickup file
67 WRITE(fn,'(a)') 'pickup_ptracers'
68 CALL MNC_FILE_CLOSE_ALL_MATCHING(fn, myThid)
69 CALL MNC_CW_SET_UDIM(fn, 1, myThid)
70 CALL MNC_CW_SET_CITER(fn, 3, 3, myIter, -1, myThid)
71 DO iTracer = 1, PTRACERS_numInUse
72 CALL MNC_CW_RL_R('D',fn,0,0, PTRACERS_names(iTracer),
73 & gpTrNm1(1-OLx,1-OLy,1,1,1,iTracer),myThid)
74 CALL EXCH_3D_RL( gpTrNm1(1-Olx,1-Oly,1,1,1,iTracer),
75 & Nr, myThid )
76 ENDDO
77 CALL MNC_CW_SET_UDIM(fn, 2, myThid)
78 DO iTracer = 1, PTRACERS_numInUse
79 CALL MNC_CW_RL_R('D',fn,0,0, PTRACERS_names(iTracer),
80 & pTracer(1-OLx,1-OLy,1,1,1,iTracer),myThid)
81 CALL EXCH_3D_RL( pTracer(1-Olx,1-Oly,1,1,1,iTracer),
82 & Nr, myThid )
83 ENDDO
84 ENDIF
85 #ifdef GAD_ALLOW_SOM_ADVECT
86 IF ( useMNC .AND. PTRACERS_pickup_read_mnc ) THEN
87 DO iTracer = 1, PTRACERS_numInUse
88 IF ( PTRACERS_SOM_Advection(iTracer) ) THEN
89 WRITE(msgBuf,'(3A)')'PTRACERS_READ_PICKUP: MNC not yet coded',
90 & ' for SOM advection',
91 & ' => read bin file instead'
92 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
93 & SQUEEZE_RIGHT, myThid)
94 ENDIF
95 ENDDO
96 ENDIF
97 #endif /* GAD_ALLOW_SOM_ADVECT */
98 #endif /* ALLOW_MNC */
99
100 IF ( PTRACERS_pickup_read_mdsio ) THEN
101
102 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
103
104 IF ( pickupSuff.EQ.' ' ) THEN
105 WRITE(fn,'(A,I10.10)') 'pickup_ptracers.',myIter
106 ELSE
107 WRITE(fn,'(A,A10)') 'pickup_ptracers.',pickupSuff
108 ENDIF
109 prec = precFloat64
110
111 CALL READ_MFLDS_SET(
112 I fn,
113 O nbFields, filePrec,
114 I Nr, myIter, myThid )
115 _BEGIN_MASTER( myThid )
116 c IF ( filePrec.NE.0 .AND. filePrec.NE.prec ) THEN
117 IF ( nbFields.GE.0 .AND. filePrec.NE.prec ) THEN
118 WRITE(msgBuf,'(2A,I4)') 'PTRACERS_READ_PICKUP: ',
119 & 'pickup-file binary precision do not match !'
120 CALL PRINT_ERROR( msgBuf, myThid )
121 WRITE(msgBuf,'(A,2(A,I4))') 'PTRACERS_READ_PICKUP: ',
122 & 'file prec.=', filePrec, ' but expecting prec.=', prec
123 CALL PRINT_ERROR( msgBuf, myThid )
124 STOP 'ABNORMAL END: S/R PTRACERS_READ_PICKUP (data-prec Pb)'
125 ENDIF
126 _END_MASTER( myThid )
127
128 IF ( nbFields.LE.0 ) THEN
129 C- No meta-file or old meta-file without List of Fields
130 ioUnit = errorMessageUnit
131 IF ( pickupStrictlyMatch ) THEN
132 WRITE(msgBuf,'(4A)') 'PTRACERS_READ_PICKUP: ',
133 & 'no field-list found in meta-file',
134 & ' => cannot check for strick-matching'
135 CALL PRINT_ERROR( msgBuf, myThid )
136 WRITE(msgBuf,'(4A)') 'PTRACERS_READ_PICKUP: ',
137 & 'try with " pickupStrictlyMatch=.FALSE.,"',
138 & ' in file: "data", NameList: "PARM03"'
139 CALL PRINT_MESSAGE( msgBuf, ioUnit, SQUEEZE_RIGHT, myThid )
140 STOP 'ABNORMAL END: S/R PTRACERS_READ_PICKUP'
141 ELSE
142 WRITE(msgBuf,'(4A)') 'WARNING >> PTRACERS_READ_PICKUP: ',
143 & ' no field-list found'
144 CALL PRINT_MESSAGE( msgBuf, ioUnit, SQUEEZE_RIGHT, myThid )
145 IF ( nbFields.EQ.-1 ) THEN
146 C- No meta-file
147 WRITE(msgBuf,'(4A)') 'WARNING >> ',
148 & ' try to read pickup as currently written'
149 CALL PRINT_MESSAGE( msgBuf, ioUnit, SQUEEZE_RIGHT, myThid )
150 ELSE
151 C- Old meta-file without List of Fields
152 WRITE(msgBuf,'(4A)') 'WARNING >> ',
153 & ' try to read pickup as it used to be written'
154 CALL PRINT_MESSAGE( msgBuf, ioUnit, SQUEEZE_RIGHT, myThid )
155 WRITE(msgBuf,'(4A)') 'WARNING >> ',
156 & ' until checkpoint59l (2007 Dec 17)'
157 CALL PRINT_MESSAGE( msgBuf, ioUnit, SQUEEZE_RIGHT, myThid )
158 ENDIF
159 ENDIF
160 ENDIF
161
162 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
163
164 C--- Very Old way to read ptracer pickup:
165 IF ( nbFields.EQ.0 .AND. usePickupBeforeC54 ) THEN
166 C Read fields as consecutive records
167 DO iTracer = 1, PTRACERS_numInUse
168 iRec = iTracer
169 CALL READ_REC_3D_RL( fn, prec, Nr,
170 O pTracer(1-Olx,1-Oly,1,1,1,iTracer),
171 I iRec, myIter, myThid )
172 CALL EXCH_3D_RL( pTracer(1-Olx,1-Oly,1,1,1,iTracer),
173 & Nr, myThid )
174 ENDDO
175
176 C Read historical tendencies as consecutive records
177 c DO iTracer = 1,PTRACERS_numInUse
178 c iRec = iTracer + PTRACERS_num
179 c CALL READ_REC_3D_RL( fn, prec, Nr,
180 c O gPtr(1-Olx,1-Oly,1,1,1,iTracer),
181 c I iRec, myIter, myThid )
182 c CALL EXCH_3D_RL( gPtr(1-Olx,1-Oly,1,1,1,iTracer),
183 c & Nr, myThid )
184 c ENDDO
185 DO iTracer = 1, PTRACERS_numInUse
186 iRec = iTracer + PTRACERS_num*2
187 CALL READ_REC_3D_RL( fn, prec, Nr,
188 O gpTrNm1(1-Olx,1-Oly,1,1,1,iTracer),
189 I iRec, myIter, myThid )
190 CALL EXCH_3D_RL( gpTrNm1(1-Olx,1-Oly,1,1,1,iTracer),
191 & Nr, myThid )
192 ENDDO
193
194 ELSEIF ( nbFields.EQ.0 ) THEN
195 C--- Old way to read ptracer pickup:
196 C Read fields & tendencies (needed for AB) as consecutive records,
197 C one tracer after the other, only for tracers "InUse". Note:
198 C this allow to restart from a pickup with a different number of
199 C tracers, with write_pickup dumping all of them (PTRACERS_num).
200 DO iTracer = 1, PTRACERS_numInUse
201 iRec = 2*iTracer -1
202 CALL READ_REC_3D_RL( fn, prec, Nr,
203 O pTracer(1-Olx,1-Oly,1,1,1,iTracer),
204 I iRec, myIter, myThid )
205 iRec = 2*iTracer
206 CALL READ_REC_3D_RL( fn, prec, Nr,
207 O gpTrNm1(1-Olx,1-Oly,1,1,1,iTracer),
208 I iRec, myIter, myThid )
209 CALL EXCH_3D_RL( pTracer(1-Olx,1-Oly,1,1,1,iTracer),
210 & Nr, myThid )
211 CALL EXCH_3D_RL( gpTrNm1(1-Olx,1-Oly,1,1,1,iTracer),
212 & Nr, myThid )
213 ENDDO
214
215 ELSE
216 C--- New way to read ptracer pickup:
217 nj = 0
218 DO iTracer = 1, PTRACERS_numInUse
219 C--- read pTracer 3-D fields for restart
220 fldName = 'pTr'//PTRACERS_ioLabel(iTracer)//' '
221 CALL READ_MFLDS_3D_RL( fldName,
222 O pTracer(1-Olx,1-Oly,1,1,1,iTracer),
223 & nj, prec, Nr, myIter, myThid )
224 CALL EXCH_3D_RL( pTracer(1-Olx,1-Oly,1,1,1,iTracer),
225 & Nr, myThid )
226 ENDDO
227 DO iTracer = 1, PTRACERS_numInUse
228 C--- read pTracer 3-D tendencies for AB-restart
229 IF ( PTRACERS_AdamsBashGtr(iTracer) ) THEN
230 fldName = 'gPtr'//PTRACERS_ioLabel(iTracer)//'m1'
231 CALL READ_MFLDS_3D_RL( fldName,
232 O gpTrNm1(1-Olx,1-Oly,1,1,1,iTracer),
233 & nj, prec, Nr, myIter, myThid )
234 CALL EXCH_3D_RL( gpTrNm1(1-Olx,1-Oly,1,1,1,iTracer),
235 & Nr, myThid )
236 ENDIF
237 ENDDO
238
239 C-- end: new way to read pickup file
240 ENDIF
241
242 C-- Check for missing fields:
243 nMissing = missFldDim
244 CALL READ_MFLDS_CHECK(
245 O missFldList,
246 U nMissing,
247 I myIter, myThid )
248 IF ( nMissing.GT.missFldDim ) THEN
249 WRITE(msgBuf,'(2A,I4)') 'PTRACERS_READ_PICKUP: ',
250 & 'missing fields list has been truncated to', missFldDim
251 CALL PRINT_ERROR( msgBuf, myThid )
252 STOP 'ABNORMAL END: S/R PTRACERS_READ_PICKUP (list-size Pb)'
253 ENDIF
254 CALL PTRACERS_CHECK_PICKUP(
255 I missFldList,
256 I nMissing, nbFields,
257 I myIter, myThid )
258
259 #if defined(GAD_ALLOW_SOM_ADVECT) && defined(PTRACERS_ALLOW_DYN_STATE)
260 C-- Read pickup file with 2nd.Order moment fields
261 DO iTracer = 1, PTRACERS_numInUse
262 IF ( PTRACERS_SOM_Advection(iTracer) ) THEN
263
264 IF (pickupSuff .EQ. ' ') THEN
265 WRITE(fn,'(3A,I10.10)') 'pickup_somTRAC',
266 & PTRACERS_ioLabel(iTracer),'.', myIter
267 ELSE
268 WRITE(fn,'(3A,A10)') 'pickup_somTRAC',
269 & PTRACERS_ioLabel(iTracer),'.', pickupSuff
270 ENDIF
271 WRITE(msgBuf,'(A,I3,A)')'PTRACERS_READ_PICKUP: iTracer = ',
272 & iTracer,
273 & ' : reading 2nd-order moments from file '
274 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
275 & SQUEEZE_RIGHT, myThid)
276 CALL PRINT_MESSAGE( fn, standardMessageUnit,
277 & SQUEEZE_RIGHT, myThid)
278 prec = precFloat64
279 C Read 2nd Order moments as consecutive records
280 DO n=1,nSOM
281 iRec = n
282 CALL READ_REC_3D_RL( fn, prec, Nr,
283 O _Ptracers_som(1-Olx,1-Oly,1,1,1,n,iTracer),
284 I iRec, myIter, myThid )
285 ENDDO
286 CALL GAD_EXCH_SOM( _Ptracers_som(1-Olx,1-Oly,1,1,1,1,iTracer),
287 & Nr, myThid )
288 ENDIF
289 ENDDO
290 #endif /* GAD_ALLOW_SOM_ADVECT && PTRACERS_ALLOW_DYN_STATE */
291 _BARRIER
292
293 C-- end: pickup_read_mdsio
294 ENDIF
295
296 #endif /* ALLOW_PTRACERS */
297
298 RETURN
299 END

  ViewVC Help
Powered by ViewVC 1.1.22