/[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.53 - (show annotations) (download)
Tue Jun 14 00:18:37 2011 UTC (12 years, 10 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint62z
Changes since 1.52: +14 -3 lines
first attempt to compute Velocity Potential (from UVELMASS & VVELMASS diags).

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

  ViewVC Help
Powered by ViewVC 1.1.22