/[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.50 - (show annotations) (download)
Sat Jun 11 23:29:44 2011 UTC (12 years, 11 months ago) by jmc
Branch: MAIN
Changes since 1.49: +19 -279 lines
move MNC code out of diagnostics_out.F into 2 S/R (in diagnostics_mnc_out.F)

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

  ViewVC Help
Powered by ViewVC 1.1.22