/[MITgcm]/MITgcm/pkg/diagnostics/diagnostics_out.F
ViewVC logotype

Contents of /MITgcm/pkg/diagnostics/diagnostics_out.F

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


Revision 1.52 - (show annotations) (download)
Sun Jun 12 19:16:09 2011 UTC (12 years, 11 months ago) by jmc
Branch: MAIN
Changes since 1.51: +30 -31 lines
- declare qtmp2 in diagnostics_out.F and pass it as arg. to diagnostics_interp_vert
- change arguments and name of S/R GETDIAG (now: DIAGNOSTICS_GET_DIAG)

1 C $Header: /u/gcmpack/MITgcm/pkg/diagnostics/diagnostics_out.F,v 1.51 2011/06/12 13:58:33 jmc Exp $
2 C $Name: $
3
4 #include "DIAG_OPTIONS.h"
5
6 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
7 CBOP 0
8 C !ROUTINE: DIAGNOSTICS_OUT
9
10 C !INTERFACE:
11 SUBROUTINE DIAGNOSTICS_OUT(
12 I listId,
13 I myTime,
14 I myIter,
15 I myThid )
16
17 C !DESCRIPTION:
18 C Write output for diagnostics fields.
19
20 C !USES:
21 IMPLICIT NONE
22 #include "SIZE.h"
23 #include "EEPARAMS.h"
24 #include "PARAMS.h"
25 #include "GRID.h"
26 #include "DIAGNOSTICS_SIZE.h"
27 #include "DIAGNOSTICS.h"
28
29 INTEGER NrMax
30 PARAMETER( NrMax = numLevels )
31
32 C !INPUT PARAMETERS:
33 C listId :: Diagnostics list number being written
34 C myIter :: current iteration number
35 C myTime :: current time of simulation (s)
36 C myThid :: my Thread Id number
37 _RL myTime
38 INTEGER listId, myIter, myThid
39 CEOP
40
41 C !FUNCTIONS:
42 INTEGER ILNBLNK
43 EXTERNAL ILNBLNK
44 #ifdef ALLOW_FIZHI
45 _RL getcon
46 EXTERNAL getcon
47 #endif
48
49 C !LOCAL VARIABLES:
50 C i,j,k :: loop indices
51 C bi,bj :: tile indices
52 C lm :: loop index (averageCycle)
53 C md :: field number in the list "listId".
54 C ndId :: diagnostics Id number (in available diagnostics list)
55 C mate :: counter mate Id number (in available diagnostics list)
56 C ip :: diagnostics pointer to storage array
57 C im :: counter-mate pointer to storage array
58 C nLevOutp :: number of levels to write in output file
59 C
60 C-- COMMON /LOCAL_DIAGNOSTICS_OUT/ local common block (for multi-threaded)
61 C qtmp1 :: temporary array; used to store a copy of diag. output field.
62 C qtmp2 :: temporary array; used to store a copy of a 2nd diag. field.
63 C- Note: local common block no longer needed.
64 c COMMON /LOCAL_DIAGNOSTICS_OUT/ qtmp1
65 _RL qtmp1(1-OLx:sNx+OLx,1-OLy:sNy+OLy,NrMax,nSx,nSy)
66 _RL qtmp2(1-OLx:sNx+OLx,1-OLy:sNy+OLy,NrMax,nSx,nSy)
67
68 INTEGER i, j, k, lm
69 INTEGER bi, bj
70 INTEGER md, ndId, ip, im
71 INTEGER mate, mVec
72 CHARACTER*10 gcode
73 _RL undefRL
74 INTEGER nLevOutp, kLev
75
76 INTEGER iLen
77 INTEGER ioUnit
78 CHARACTER*(MAX_LEN_FNAM) fn
79 CHARACTER*(MAX_LEN_MBUF) suff
80 CHARACTER*(MAX_LEN_MBUF) msgBuf
81 INTEGER prec, nRec, nTimRec
82 _RL timeRec(2)
83 _RL tmpLoc
84 #ifdef ALLOW_MDSIO
85 LOGICAL glf
86 #endif
87 #ifdef ALLOW_MNC
88 INTEGER ll, llMx, jj, jjMx
89 CHARACTER*(MAX_LEN_FNAM) diag_mnc_bn
90 LOGICAL useMissingValue
91 REAL*8 misValLoc
92 #endif /* ALLOW_MNC */
93
94 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
95
96 C--- set file properties
97 ioUnit= standardMessageUnit
98 undefRL = UNSET_RL
99 #ifdef ALLOW_FIZHI
100 IF ( useFIZHI ) undefRL = getcon('UNDEF')
101 #endif
102 WRITE(suff,'(I10.10)') myIter
103 iLen = ILNBLNK(fnames(listId))
104 WRITE( fn, '(A,A,A)' ) fnames(listId)(1:iLen),'.',suff(1:10)
105 C- for now, if integrate vertically, output field has just 1 level:
106 nLevOutp = nlevels(listId)
107 IF ( fflags(listId)(2:2).EQ.'I' ) nLevOutp = 1
108
109 C-- Set time information:
110 IF ( freq(listId).LT.0. ) THEN
111 C- Snap-shot: store a unique time (which is consistent with State-Var timing)
112 nTimRec = 1
113 timeRec(1) = myTime
114 ELSE
115 C- Time-average: store the 2 edges of the time-averaging interval.
116 C this time is consitent with intermediate Var (i.e., non-state, e.g, flux,
117 C tendencies) timing. For State-Var, this is shifted by + halt time-step.
118 nTimRec = 2
119
120 C- end of time-averaging interval:
121 timeRec(2) = myTime
122
123 C- begining of time-averaging interval:
124 c timeRec(1) = myTime - freq(listId)
125 C a) find the time of the previous multiple of output freq:
126 timeRec(1) = myTime-deltaTClock*0.5 _d 0
127 timeRec(1) = (timeRec(1)-phase(listId))/freq(listId)
128 i = INT( timeRec(1) )
129 IF ( timeRec(1).LT.0. ) THEN
130 tmpLoc = FLOAT(i)
131 IF ( timeRec(1).NE.tmpLoc ) i = i - 1
132 ENDIF
133 timeRec(1) = phase(listId) + freq(listId)*FLOAT(i)
134 c if ( listId.eq.2 ) write(0,*) 'f',i,timeRec(1)/deltaTClock
135 timeRec(1) = MAX( timeRec(1), startTime )
136
137 C b) round off to nearest multiple of time-step:
138 timeRec(1) = (timeRec(1)-baseTime)/deltaTClock
139 i = NINT( timeRec(1) )
140 C if just half way, NINT will return the next time-step: correct this
141 tmpLoc = FLOAT(i) - 0.5 _d 0
142 IF ( timeRec(1).EQ.tmpLoc ) i = i - 1
143 timeRec(1) = baseTime + deltaTClock*FLOAT(i)
144 c if ( listId.eq.2 ) write(0,*) i,timeRec(1)/deltaTClock
145 ENDIF
146 C-- Convert time to iteration number (debug)
147 c DO i=1,nTimRec
148 c timeRec(i) = timeRec(i)/deltaTClock
149 c ENDDO
150
151 #ifdef ALLOW_MNC
152 C-- this is a trick to reverse the order of the loops on md (= field)
153 C and lm (= averagePeriod): binary output: lm loop inside md loop ;
154 C mnc ouput: md loop inside lm loop.
155 IF (useMNC .AND. diag_mnc) THEN
156 jjMx = averageCycle(listId)
157 llMx = 1
158 ELSE
159 jjMx = 1
160 llMx = averageCycle(listId)
161 ENDIF
162 DO jj=1,jjMx
163
164 IF (useMNC .AND. diag_mnc) THEN
165 misValLoc = undefRL
166 IF ( misvalFlt(listId).NE.UNSET_RL )
167 & misValLoc = misvalFlt(listId)
168 CALL DIAGNOSTICS_MNC_SET(
169 I nLevOutp, listId, jj,
170 O diag_mnc_bn, useMissingValue,
171 I misValLoc, myTime, myIter, myThid )
172 ENDIF
173 #endif /* ALLOW_MNC */
174
175 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
176
177 DO md = 1,nfields(listId)
178 ndId = jdiag(md,listId)
179 gcode = gdiag(ndId)(1:10)
180 mate = 0
181 mVec = 0
182 IF ( gcode(5:5).EQ.'C' ) THEN
183 C- Check for Mate of a Counter Diagnostic
184 mate = hdiag(ndId)
185 ELSEIF ( gcode(1:1).EQ.'U' .OR. gcode(1:1).EQ.'V' ) THEN
186 C- Check for Mate of a Vector Diagnostic
187 mVec = hdiag(ndId)
188 ENDIF
189 IF ( idiag(md,listId).NE.0 .AND. gcode(5:5).NE.'D' ) THEN
190 C-- Start processing 1 Fld :
191 #ifdef ALLOW_MNC
192 DO ll=1,llMx
193 lm = jj+ll-1
194 #else
195 DO lm=1,averageCycle(listId)
196 #endif
197
198 ip = ABS(idiag(md,listId)) + kdiag(ndId)*(lm-1)
199 im = mdiag(md,listId)
200 IF (mate.GT.0) im = im + kdiag(mate)*(lm-1)
201 IF (mVec.GT.0) im = im + kdiag(mVec)*(lm-1)
202
203 IF ( ndiag(ip,1,1).EQ.0 ) THEN
204 C- Empty diagnostics case :
205
206 _BEGIN_MASTER( myThid )
207 WRITE(msgBuf,'(A,I10)')
208 & '- WARNING - from DIAGNOSTICS_OUT at iter=', myIter
209 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
210 & SQUEEZE_RIGHT, myThid)
211 WRITE(msgBuf,'(A,I6,3A,I4,2A)')
212 & '- WARNING - diag.#',ndId, ' : ',flds(md,listId),
213 & ' (#',md,' ) in outp.Stream: ',fnames(listId)
214 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
215 & SQUEEZE_RIGHT, myThid)
216 IF ( averageCycle(listId).GT.1 ) THEN
217 WRITE(msgBuf,'(A,2(I3,A))')
218 & '- WARNING - has not been filled (ndiag(lm=',lm,')=',
219 & ndiag(ip,1,1), ' )'
220 ELSE
221 WRITE(msgBuf,'(A,2(I3,A))')
222 & '- WARNING - has not been filled (ndiag=',
223 & ndiag(ip,1,1), ' )'
224 ENDIF
225 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
226 & SQUEEZE_RIGHT, myThid)
227 WRITE(msgBuf,'(A)')
228 & 'WARNING DIAGNOSTICS_OUT => write ZEROS instead'
229 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
230 & SQUEEZE_RIGHT, myThid)
231 _END_MASTER( myThid )
232 DO bj = myByLo(myThid), myByHi(myThid)
233 DO bi = myBxLo(myThid), myBxHi(myThid)
234 DO k = 1,nLevOutp
235 DO j = 1-OLy,sNy+OLy
236 DO i = 1-OLx,sNx+OLx
237 qtmp1(i,j,k,bi,bj) = 0. _d 0
238 ENDDO
239 ENDDO
240 ENDDO
241 ENDDO
242 ENDDO
243
244 ELSE
245 C- diagnostics is not empty :
246
247 IF ( debugLevel.GE.debLevB .AND. myThid.EQ.1 ) THEN
248 WRITE(ioUnit,'(A,I6,3A,I8,2A)')
249 & ' Computing Diagnostic # ', ndId, ' ', cdiag(ndId),
250 & ' Counter:',ndiag(ip,1,1),' Parms: ',gdiag(ndId)
251 IF ( mate.GT.0 ) THEN
252 WRITE(ioUnit,'(3A,I6,2A)')
253 & ' use Counter Mate for ', cdiag(ndId),
254 & ' Diagnostic # ',mate, ' ', cdiag(mate)
255 ELSEIF ( mVec.GT.0 ) THEN
256 IF ( im.GT.0 .AND. ndiag(MAX(1,im),1,1).GT.0 ) THEN
257 WRITE(ioUnit,'(3A,I6,3A)')
258 & ' Vector Mate for ', cdiag(ndId),
259 & ' Diagnostic # ',mVec, ' ', cdiag(mVec),
260 & ' exists '
261 ELSE
262 WRITE(ioUnit,'(3A,I6,3A)')
263 & ' Vector Mate for ', cdiag(ndId),
264 & ' Diagnostic # ',mVec, ' ', cdiag(mVec),
265 & ' not enabled'
266 ENDIF
267 ENDIF
268 ENDIF
269
270 IF ( fflags(listId)(2:2).EQ.' ' ) THEN
271 C- get only selected levels:
272 DO bj = myByLo(myThid), myByHi(myThid)
273 DO bi = myBxLo(myThid), myBxHi(myThid)
274 DO k = 1,nlevels(listId)
275 kLev = NINT(levs(k,listId))
276 CALL DIAGNOSTICS_GET_DIAG(
277 I kLev, undefRL,
278 O qtmp1(1-OLx,1-OLy,k,bi,bj),
279 I ndId,mate,ip,im,bi,bj,myThid)
280 ENDDO
281 ENDDO
282 ENDDO
283 ELSE
284 C- get all the levels (for vertical post-processing)
285 DO bj = myByLo(myThid), myByHi(myThid)
286 DO bi = myBxLo(myThid), myBxHi(myThid)
287 CALL DIAGNOSTICS_GET_DIAG(
288 I 0, undefRL,
289 O qtmp1(1-OLx,1-OLy,1,bi,bj),
290 I ndId,mate,ip,im,bi,bj,myThid)
291 ENDDO
292 ENDDO
293 ENDIF
294
295 C-----------------------------------------------------------------------
296 C-- Apply specific post-processing (e.g., interpolate) before output
297 C-----------------------------------------------------------------------
298 IF ( fflags(listId)(2:2).EQ.'P' ) THEN
299 C- Do vertical interpolation:
300 IF ( fluidIsAir ) THEN
301 C jmc: for now, this can only work in an atmospheric set-up (fluidIsAir);
302 CALL DIAGNOSTICS_INTERP_VERT(
303 I listId, md, ndId, ip, im, lm,
304 U qtmp1, qtmp2,
305 I undefRL, myTime, myIter, myThid )
306 ELSE
307 WRITE(msgBuf,'(2A)') 'DIAGNOSTICS_OUT: ',
308 & 'INTERP_VERT not allowed in this config'
309 CALL PRINT_ERROR( msgBuf , myThid )
310 STOP 'ABNORMAL END: S/R DIAGNOSTICS_OUT'
311 ENDIF
312 ENDIF
313 IF ( fflags(listId)(2:2).EQ.'I' ) THEN
314 C- Integrate vertically: for now, output field has just 1 level:
315 CALL DIAGNOSTICS_SUM_LEVELS(
316 I listId, md, ndId, ip, im, lm,
317 U qtmp1,
318 I undefRL, myTime, myIter, myThid )
319 ENDIF
320
321 C-- End of empty diag / not-empty diag block
322 ENDIF
323
324 C-- Ready to write field "md", element "lm" in averageCycle(listId)
325
326 C- write to binary file, using MDSIO pkg:
327 IF ( diag_mdsio ) THEN
328 nRec = lm + (md-1)*averageCycle(listId)
329 C default precision for output files
330 prec = writeBinaryPrec
331 C fFlag(1)=R(or D): force it to be 32-bit(or 64) precision
332 IF ( fflags(listId)(1:1).EQ.'R' ) prec = precFloat32
333 IF ( fflags(listId)(1:1).EQ.'D' ) prec = precFloat64
334 C a hack not to write meta files now: pass -nRec < 0 to MDS_WRITE S/R
335 CALL WRITE_REC_LEV_RL(
336 I fn, prec,
337 I NrMax, 1, nLevOutp,
338 I qtmp1, -nRec, myIter, myThid )
339 ENDIF
340
341 #ifdef ALLOW_MNC
342 IF (useMNC .AND. diag_mnc) THEN
343 CALL DIAGNOSTICS_MNC_OUT(
344 I NrMax, nLevOutp, listId, ndId,
345 I diag_mnc_bn,
346 I useMissingValue, misValLoc,
347 I qtmp1,
348 I myTime, myIter, myThid )
349 ENDIF
350 #endif /* ALLOW_MNC */
351
352 C-- end loop on lm (or ll if ALLOW_MNC) counter
353 ENDDO
354 C-- end of Processing Fld # md
355 ENDIF
356 ENDDO
357
358 #ifdef ALLOW_MNC
359 C-- end loop on jj counter
360 ENDDO
361 #endif
362
363 #ifdef ALLOW_MDSIO
364 IF (diag_mdsio) THEN
365 C- Note: temporary: since it is a pain to add more arguments to
366 C all MDSIO S/R, uses instead this specific S/R to write only
367 C meta files but with more informations in it.
368 glf = globalFiles
369 nRec = nfields(listId)*averageCycle(listId)
370 CALL MDS_WR_METAFILES(fn, prec, glf, .FALSE.,
371 & 0, 0, nLevOutp, ' ',
372 & nfields(listId), flds(1,listId), nTimRec, timeRec,
373 & nRec, myIter, myThid)
374 ENDIF
375 #endif /* ALLOW_MDSIO */
376
377 RETURN
378 END
379
380 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|

  ViewVC Help
Powered by ViewVC 1.1.22