/[MITgcm]/MITgcm/eesupp/src/print.F
ViewVC logotype

Contents of /MITgcm/eesupp/src/print.F

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


Revision 1.11 - (show annotations) (download)
Sat Sep 5 17:52:13 1998 UTC (25 years, 9 months ago) by cnh
Branch: MAIN
CVS Tags: checkpoint15, checkpoint14
Changes since 1.10: +33 -15 lines
Consistent isomorphism changes

1 C $Header: /u/gcmpack/models/MITgcmUV/eesupp/src/print.F,v 1.10 1998/07/15 22:16:10 adcroft Exp $
2
3 #include "CPP_EEOPTIONS.h"
4
5 C-- File printf.F: Routines for performing formatted textual I/O
6 C-- in the MITgcm UV implementation environment.
7 C-- Contents
8 C-- o print_error Does IO with **ERROR** highlighted header
9 C-- o print_list_i Prints one-deimensional list of INTEGER
10 C-- numbers.
11 C-- o print_list_l Prints one-deimensional list of LOGICAL
12 C-- variables.
13 C-- o print_list_r8 Prints one-deimensional list of Real*8
14 C-- numbers.
15 C-- o print_mapr4 Formats ABCD... contour map of a Real*4 field
16 C-- Uses print_message for writing
17 C-- o print_mapr8 Formats ABCD... contour map of a Real*8 field
18 C-- Uses print_message for writing
19 C-- o print_message Does IO with unhighlighted header
20
21 CStartOfInterface
22 SUBROUTINE PRINT_ERROR( message , myThid )
23 C /============================================================\
24 C | SUBROUTINE PRINT_ERROR |
25 C | o Write out error message using "standard" format. |
26 C | Notes |
27 C | ===== |
28 C | o Some system's I/O is not "thread-safe". For this reason |
29 C | without the FMTFTN_IO_THREAD_SAFE directive set a |
30 C | critical region is defined around the write here. In some|
31 C | cases BEGIN_CRIT() is approximated by only doing writes |
32 C | for thread number 1 - writes for other threads are |
33 C | ignored! |
34 C | o In a non-parallel form these routines can still be used. |
35 C | to produce pretty printed output! |
36 C \============================================================/
37 C == Global data ==
38 #include "SIZE.h"
39 #include "EEPARAMS.h"
40 #include "EESUPPORT.h"
41 C == Routine arguments ==
42 CHARACTER*(*) message
43 INTEGER myThid
44 CEndOfInterface
45 INTEGER IFNBLNK
46 EXTERNAL IFNBLNK
47 INTEGER ILNBLNK
48 EXTERNAL ILNBLNK
49 C == Local variables ==
50 INTEGER iStart
51 INTEGER iEnd
52 CHARACTER*9 idString
53 C-- Find beginning and end of message
54 iStart = IFNBLNK( message )
55 iEnd = ILNBLNK( message )
56 C-- Test to see if in multi-process ( or multi-threaded ) mode.
57 C If so include process or thread identifier.
58 IF ( numberOfProcs .EQ. 0 .AND. nThreads .EQ. 1 ) THEN
59 C-- Write single process format
60 IF ( message .EQ. ' ' ) THEN
61 WRITE(errorMessageUnit,'(A,1X,A)') ERROR_HEADER, ' '
62 ELSE
63 WRITE(errorMessageUnit,'(A,1X,A)') ERROR_HEADER, message(iStart:iEnd)
64 ENDIF
65 ELSEIF ( pidIO .EQ. myProcId ) THEN
66 C-- Write multi-process format
67 #ifndef FMTFTN_IO_THREAD_SAFE
68 _BEGIN_CRIT(myThid)
69 #endif
70 WRITE(idString,'(I4.4,A,I4.4)') myProcId,'.',myThid
71 #ifndef FMTFTN_IO_THREAD_SAFE
72 _END_CRIT(myThid)
73 #endif
74 IF ( message .EQ. ' ' ) THEN
75 C PRINT_ERROR can be called by several threads simulataneously.
76 C The write statement may need to be marked as a critical section.
77 #ifndef FMTFTN_IO_THREAD_SAFE
78 _BEGIN_CRIT(myThid)
79 #endif
80 WRITE(errorMessageUnit,'(A,A,1X,A,A,A,A,A)',ERR=999)
81 & '(',PROCESS_HEADER,idString,')',ERROR_HEADER,' ',
82 & ' '
83 #ifndef FMTFTN_IO_THREAD_SAFE
84 _END_CRIT(myThid)
85 #endif
86 ELSE
87 #ifndef FMTFTN_IO_THREAD_SAFE
88 _BEGIN_CRIT(myThid)
89 #endif
90 WRITE(errorMessageUnit,'(A,A,1X,A,A,A,A,A)',ERR=999)
91 & '(',PROCESS_HEADER,idString,')',ERROR_HEADER,' ',
92 & message(iStart:iEnd)
93 #ifndef FMTFTN_IO_THREAD_SAFE
94 _END_CRIT(myThid)
95 #endif
96 ENDIF
97 ENDIF
98 C
99 1000 CONTINUE
100 RETURN
101
102 999 CONTINUE
103 ioErrorCount(myThid) = ioErrorCount(myThid)+1
104 GOTO 1000
105 END
106
107 CStartofinterface
108 SUBROUTINE PRINT_LIST_I( fld, lFld, index_type, markEnd, compact, ioUnit )
109 C /==========================================================\
110 C | o SUBROUTINE PRINT_LIST_I |
111 C |==========================================================|
112 C | Routine for producing list of values for a field with |
113 C | duplicate values collected into |
114 C | n @ value |
115 C | record. |
116 C \==========================================================/
117
118 C == Global data ==
119 #include "SIZE.h"
120 #include "EEPARAMS.h"
121
122 C == Routine arguments ==
123 C fld - Data to be printed
124 C lFld - Number of elements to be printed
125 C index_type - Flag indicating which type of index to print
126 C INDEX_K => /* K = nnn */
127 C INDEX_I => /* I = nnn */
128 C INDEX_J => /* J = nnn */
129 C INDEX_NONE =>
130 C compact - Flag to control use of repeat symbol for same valued
131 C fields.
132 C markEnd - Flag to control whether there is a separator after the
133 C last element
134 C ioUnit - Unit number for IO.
135 INTEGER lFld
136 INTEGER index_type
137 INTEGER fld(lFld)
138 LOGICAL markEnd
139 LOGICAL compact
140 INTEGER ioUnit
141 CEndifinterface
142
143 C == Local variables ==
144 C iLo - Range index holders for selecting elements with
145 C iHi with the same value
146 C nDup - Number of duplicates
147 C xNew, xOld - Hold current and previous values of field
148 C punc - Field separator
149 C msgBuf - IO buffer
150 C index_lab - Index for labelling elements
151 C K - Loop counter
152 INTEGER iLo
153 INTEGER iHi
154 INTEGER nDup
155 INTEGER xNew, xOld
156 CHARACTER punc
157 CHARACTER*(MAX_LEN_MBUF) msgBuf
158 CHARACTER*2 commOpen,commClose
159 CHARACTER*3 index_lab
160 INTEGER K
161
162 IF ( index_type .EQ. INDEX_I ) THEN
163 index_lab = 'I ='
164 ELSEIF ( index_type .EQ. INDEX_J ) THEN
165 index_lab = 'J ='
166 ELSEIF ( index_type .EQ. INDEX_K ) THEN
167 index_lab = 'K ='
168 ELSE
169 index_lab = '?='
170 ENDIF
171 commOpen = '/*'
172 commClose = '*/'
173 iLo = 1
174 iHi = 1
175 punc = ','
176 xOld = fld(1)
177 DO K=2,lFld
178 xNew = fld(K )
179 IF ( .NOT. compact .OR. xNew .NE. xOld ) THEN
180 nDup = iHi-iLo+1
181 IF ( nDup .EQ. 1 ) THEN
182 WRITE(msgBuf,'(A,I9,A)') ' ',xOld,punc
183 IF ( index_type .NE. INDEX_NONE )
184 & WRITE(msgBuf(45:),'(A,1X,A,I3,1X,A)') commOpen,index_lab,iLo,commClose
185 ELSE
186 WRITE(msgBuf,'(I,'' '',A,I9,A)') nDup,'@',xOld,punc
187 IF ( index_type .NE. INDEX_NONE )
188 & WRITE(msgBuf(45:),'(A,1X,A,I3,A,I3,1X,A)')
189 & commOpen,index_lab,iLo,':',iHi,commClose
190 ENDIF
191 CALL PRINT_MESSAGE( msgBuf, ioUnit, SQUEEZE_RIGHT , 1)
192 iLo = K
193 iHi = K
194 xOld = xNew
195 ELSE
196 iHi = K
197 ENDIF
198 ENDDO
199 punc = ' '
200 IF ( markEnd ) punc = ','
201 nDup = iHi-iLo+1
202 IF ( nDup .EQ. 1 ) THEN
203 WRITE(msgBuf,'(A,I9,A)') ' ',xOld,punc
204 IF ( index_type .NE. INDEX_NONE )
205 & WRITE(msgBuf(45:),'(A,1X,A,I3,1X,A)') commOpen,index_lab,iLo,commClose
206 ELSEIF( nDup .GT. 1 ) THEN
207 WRITE(msgBuf,'(I,'' '',A,I9,A)') nDup,'@',xOld,punc
208 IF ( index_type .NE. INDEX_NONE )
209 & WRITE(msgBuf(45:),'(A,1X,A,I3,A,I3,1X,A)')
210 & commOpen,index_lab,iLo,':',iHi,commClose
211 ENDIF
212 CALL PRINT_MESSAGE( msgBuf, ioUnit, SQUEEZE_RIGHT , 1)
213
214 RETURN
215 END
216
217 CStartofinterface
218 SUBROUTINE PRINT_LIST_L( fld, lFld, index_type, markEnd, compact, ioUnit )
219 C /==========================================================\
220 C | o SUBROUTINE PRINT_LIST_L |
221 C |==========================================================|
222 C | Routine for producing list of values for a field with |
223 C | duplicate values collected into |
224 C | n @ value |
225 C | record. |
226 C \==========================================================/
227
228 C == Global data ==
229 #include "SIZE.h"
230 #include "EEPARAMS.h"
231
232 C == Routine arguments ==
233 C fld - Data to be printed
234 C lFld - Number of elements to be printed
235 C index_type - Flag indicating which type of index to print
236 C INDEX_K => /* K = nnn */
237 C INDEX_I => /* I = nnn */
238 C INDEX_J => /* J = nnn */
239 C INDEX_NONE =>
240 C compact - Flag to control use of repeat symbol for same valued
241 C fields.
242 C markEnd - Flag to control whether there is a separator after the
243 C last element
244 C ioUnit - Unit number for IO.
245 INTEGER lFld
246 INTEGER index_type
247 LOGICAL fld(lFld)
248 LOGICAL markEnd
249 LOGICAL compact
250 INTEGER ioUnit
251 CEndifinterface
252
253 C == Local variables ==
254 C iLo - Range index holders for selecting elements with
255 C iHi with the same value
256 C nDup - Number of duplicates
257 C xNew, xOld - Hold current and previous values of field
258 C punc - Field separator
259 C msgBuf - IO buffer
260 C index_lab - Index for labelling elements
261 C K - Loop counter
262 INTEGER iLo
263 INTEGER iHi
264 INTEGER nDup
265 LOGICAL xNew, xOld
266 CHARACTER punc
267 CHARACTER*(MAX_LEN_MBUF) msgBuf
268 CHARACTER*2 commOpen,commClose
269 CHARACTER*3 index_lab
270 INTEGER K
271
272 IF ( index_type .EQ. INDEX_I ) THEN
273 index_lab = 'I ='
274 ELSEIF ( index_type .EQ. INDEX_J ) THEN
275 index_lab = 'J ='
276 ELSEIF ( index_type .EQ. INDEX_K ) THEN
277 index_lab = 'K ='
278 ELSE
279 index_lab = '?='
280 ENDIF
281 commOpen = '/*'
282 commClose = '*/'
283 iLo = 1
284 iHi = 1
285 punc = ','
286 xOld = fld(1)
287 DO K=2,lFld
288 xNew = fld(K )
289 IF ( .NOT. compact .OR. xNew .NE. xOld ) THEN
290 nDup = iHi-iLo+1
291 IF ( nDup .EQ. 1 ) THEN
292 WRITE(msgBuf,'(A,L5,A)') ' ',xOld,punc
293 IF ( index_type .NE. INDEX_NONE )
294 & WRITE(msgBuf(45:),'(A,1X,A,I3,1X,A)') commOpen,index_lab,iLo,commClose
295 ELSE
296 WRITE(msgBuf,'(I,'' '',A,L5,A)') nDup,'@',xOld,punc
297 IF ( index_type .NE. INDEX_NONE )
298 & WRITE(msgBuf(45:),'(A,1X,A,L3,A,I3,1X,A)')
299 & commOpen,index_lab,iLo,':',iHi,commClose
300 ENDIF
301 CALL PRINT_MESSAGE( msgBuf, ioUnit, SQUEEZE_RIGHT , 1)
302 iLo = K
303 iHi = K
304 xOld = xNew
305 ELSE
306 iHi = K
307 ENDIF
308 ENDDO
309 punc = ' '
310 IF ( markEnd ) punc = ','
311 nDup = iHi-iLo+1
312 IF ( nDup .EQ. 1 ) THEN
313 WRITE(msgBuf,'(A,L5,A)') ' ',xOld,punc
314 IF ( index_type .NE. INDEX_NONE )
315 & WRITE(msgBuf(45:),'(A,1X,A,I3,1X,A)') commOpen,index_lab,iLo,commClose
316 ELSEIF( nDup .GT. 1 ) THEN
317 WRITE(msgBuf,'(I,'' '',A,L5,A)') nDup,'@',xOld,punc
318 IF ( index_type .NE. INDEX_NONE )
319 & WRITE(msgBuf(45:),'(A,1X,A,I3,A,I3,1X,A)')
320 & commOpen,index_lab,iLo,':',iHi,commClose
321 ENDIF
322 CALL PRINT_MESSAGE( msgBuf, ioUnit, SQUEEZE_RIGHT , 1)
323
324 RETURN
325 END
326
327 CStartofinterface
328 SUBROUTINE PRINT_LIST_R8( fld, lFld, index_type, markEnd, compact, ioUnit )
329 C /==========================================================\
330 C | o SUBROUTINE PRINT_LIST_R8 |
331 C |==========================================================|
332 C | Routine for producing list of values for a field with |
333 C | duplicate values collected into |
334 C | n @ value |
335 C | record. |
336 C \==========================================================/
337
338 C == Global data ==
339 #include "SIZE.h"
340 #include "EEPARAMS.h"
341
342 C == Routine arguments ==
343 C fld - Data to be printed
344 C lFld - Number of elements to be printed
345 C index_type - Flag indicating which type of index to print
346 C INDEX_K => /* K = nnn */
347 C INDEX_I => /* I = nnn */
348 C INDEX_J => /* J = nnn */
349 C INDEX_NONE =>
350 C compact - Flag to control use of repeat symbol for same valued
351 C fields.
352 C markEnd - Flag to control whether there is a separator after the
353 C last element
354 C ioUnit - Unit number for IO.
355 INTEGER lFld
356 INTEGER index_type
357 Real*8 fld(lFld)
358 LOGICAL markEnd
359 LOGICAL compact
360 INTEGER ioUnit
361 CEndifinterface
362
363 C == Local variables ==
364 C iLo - Range index holders for selecting elements with
365 C iHi with the same value
366 C nDup - Number of duplicates
367 C xNew, xOld - Hold current and previous values of field
368 C punc - Field separator
369 C msgBuf - IO buffer
370 C index_lab - Index for labelling elements
371 C K - Loop counter
372 INTEGER iLo
373 INTEGER iHi
374 INTEGER nDup
375 Real*8 xNew, xOld
376 CHARACTER punc
377 CHARACTER*(MAX_LEN_MBUF) msgBuf
378 CHARACTER*2 commOpen,commClose
379 CHARACTER*3 index_lab
380 INTEGER K
381
382 IF ( index_type .EQ. INDEX_I ) THEN
383 index_lab = 'I ='
384 ELSEIF ( index_type .EQ. INDEX_J ) THEN
385 index_lab = 'J ='
386 ELSEIF ( index_type .EQ. INDEX_K ) THEN
387 index_lab = 'K ='
388 ELSE
389 index_lab = '?='
390 ENDIF
391 commOpen = '/*'
392 commClose = '*/'
393 iLo = 1
394 iHi = 1
395 punc = ','
396 xOld = fld(1)
397 DO K=2,lFld
398 xNew = fld(K )
399 IF ( .NOT. compact .OR. xNew .NE. xOld ) THEN
400 nDup = iHi-iLo+1
401 IF ( nDup .EQ. 1 ) THEN
402 WRITE(msgBuf,'(A,1PE23.15,A)') ' ',xOld,punc
403 IF ( index_type .NE. INDEX_NONE )
404 & WRITE(msgBuf(45:),'(A,1X,A,I3,1X,A)') commOpen,index_lab,iLo,commClose
405 ELSE
406 WRITE(msgBuf,'(I,'' '',A,1PE23.15,A)') nDup,'@',xOld,punc
407 IF ( index_type .NE. INDEX_NONE )
408 & WRITE(msgBuf(45:),'(A,1X,A,I3,A,I3,1X,A)')
409 & commOpen,index_lab,iLo,':',iHi,commClose
410 ENDIF
411 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit, SQUEEZE_RIGHT , 1)
412 iLo = K
413 iHi = K
414 xOld = xNew
415 ELSE
416 iHi = K
417 ENDIF
418 ENDDO
419 punc = ' '
420 IF ( markEnd ) punc = ','
421 nDup = iHi-iLo+1
422 IF ( nDup .EQ. 1 ) THEN
423 WRITE(msgBuf,'(A,1PE23.15,A)') ' ',xOld,punc
424 IF ( index_type .NE. INDEX_NONE )
425 & WRITE(msgBuf(45:),'(A,1X,A,I3,1X,A)') commOpen,index_lab,iLo,commClose
426 ELSEIF( nDup .GT. 1 ) THEN
427 WRITE(msgBuf,'(I,'' '',A,1PE23.15,A)') nDup,'@',xOld,punc
428 IF ( index_type .NE. INDEX_NONE )
429 & WRITE(msgBuf(45:),'(A,1X,A,I3,A,I3,1X,A)')
430 & commOpen,index_lab,iLo,':',iHi,commClose
431 ENDIF
432 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit, SQUEEZE_RIGHT , 1)
433
434 RETURN
435 END
436
437 CStartOfInterface
438 SUBROUTINE PRINT_MAPRS ( fld, fldTitle, plotMode,
439 I iLo, iHi, jLo, jHi, kLo, kHi, nBx, nBy,
440 I iMin, iMax, iStr,
441 I jMin, jMax, jStr,
442 I kMin, kMax, kStr,
443 I bxMin, bxMax, bxStr,
444 I byMin, byMax, byStr )
445 C /==========================================================\
446 C | SUBROUTINE PRINT_MAPR4 |
447 C | o Does textual mapping printing of a field. |
448 C |==========================================================|
449 C | This routine does the actual formatting of the data |
450 C | and printing to a file. It assumes an array using the |
451 C | MITgcm UV indexing scheme and base index variables. |
452 C | User code should call an interface routine like |
453 C | PLOT_FIELD_XYR4( ... ) rather than this code directly. |
454 C | Text plots can be oriented XY, YZ, XZ. An orientation |
455 C | is specficied through the "plotMode" argument. All the |
456 C | plots made by a single call to this routine will use the |
457 C | same contour interval. The plot range (iMin,...,byStr) |
458 C | can be three-dimensional. A separate plot is made for |
459 C | each point in the plot range normal to the orientation. |
460 C | e.g. if the orientation is XY (plotMode = PRINT_MAP_XY). |
461 C | kMin =1, kMax = 5 and kStr = 2 will produce three XY|
462 C | plots - one for K=1, one for K=3 and one for K=5. |
463 C | Each plot would have extents iMin:iMax step iStr |
464 C | and jMin:jMax step jStr. |
465 C \==========================================================/
466
467 C == Global variables ==
468 #include "SIZE.h"
469 #include "EEPARAMS.h"
470 #include "EESUPPORT.h"
471
472 C == Routine arguments ==
473 C fld - Real*4 array holding data to be plotted
474 C fldTitle - Name of field to be plotted
475 C plotMode - Text string indicating plot orientation
476 C ( see - EEPARAMS.h for valid values ).
477 C iLo, iHi, - Dimensions of array fld. fld is assumed to
478 C jLo, jHi be five-dimensional.
479 C kLo, kHi
480 C nBx, nBy
481 C iMin, iMax - Indexing for points to plot. Points from
482 C iStr iMin -> iMax in steps of iStr are plotted
483 C jMin. jMax and similarly for jMin, jMax, jStr and
484 C jStr kMin, kMax, kStr and bxMin, bxMax, bxStr
485 C kMin, kMax byMin, byMax, byStr.
486 C kStr
487 CHARACTER*(*) fldTitle
488 CHARACTER*(*) plotMode
489 INTEGER iLo, iHi
490 INTEGER jLo, jHi
491 INTEGER kLo, kHi
492 INTEGER nBx, nBy
493 _RS fld(iLo:iHi,jLo:jHi,kLo:kHi,nBx,nBy)
494 INTEGER iMin, iMax, iStr
495 INTEGER jMin, jMax, jStr
496 INTEGER kMin, kMax, kStr
497 INTEGER bxMin, bxMax, bxStr
498 INTEGER byMin, byMax, byStr
499 CEndOfInterface
500 C == Local variables ==
501 INTEGER IFNBLNK
502 EXTERNAL IFNBLNK
503 INTEGER ILNBLNK
504 EXTERNAL ILNBLNK
505
506 C == Local variables ==
507 C plotBuf - Buffer for building plot record
508 C chList - Character string used for plot
509 C fMin, fMax - Contour min, max and range
510 C fRange
511 C val - Value of element to be "plotted"
512 C small - Lowest range for which contours are plotted
513 C accXXX - Variables used in indexing accross page records.
514 C dwnXXX Variables used in indexing down the page.
515 C pltXXX Variables used in indexing multiple plots ( multiple
516 C plots use same contour range).
517 C Lab - Label
518 C Base - Base number for element indexing
519 C The process bottom, left coordinate in the
520 C global domain.
521 C Step - Block size
522 C Blo - Start block
523 C Bhi - End block
524 C Bstr - Block stride
525 C Min - Start index within block
526 C Max - End index within block
527 C Str - stride within block
528 INTEGER MAX_LEN_PLOTBUF
529 PARAMETER ( MAX_LEN_PLOTBUF = MAX_LEN_MBUF-4 )
530 CHARACTER*(MAX_LEN_PLOTBUF) plotBuf
531 CHARACTER*(MAX_LEN_MBUF) msgBuf
532 INTEGER lChList
533 PARAMETER ( lChList = 28 )
534 CHARACTER*(lChList) chList
535 REAL fMin
536 REAL fMax
537 REAL fRange
538 REAL val
539 REAL small
540 CHARACTER*2 accLab
541 CHARACTER*7 dwnLab
542 CHARACTER*3 pltLab
543 INTEGER accBase, dwnBase, pltBase
544 INTEGER accStep, dwnStep, pltStep
545 INTEGER accBlo, dwnBlo, pltBlo
546 INTEGER accBhi, dwnBhi, pltBhi
547 INTEGER accBstr, dwnBstr, pltBstr
548 INTEGER accMin, dwnMin, pltMin
549 INTEGER accMax, dwnMax, pltMax
550 INTEGER accStr, dwnStr, pltStr
551 INTEGER I, J, K, iStrngLo, iStrngHi, iBuf, iDx
552 INTEGER bi, bj, bk
553 LOGICAL validRange
554
555 chList = '-abcdefghijklmnopqrstuvwxyz+'
556 small = 1. _d -15
557 fMin = 1. _d 32
558 fMax = -1. _d 32
559 validRange = .FALSE.
560
561 C-- Calculate field range
562 DO bj=byMin, byMax, byStr
563 DO bi=bxMin, bxMax, bxStr
564 DO K=kMin, kMax, kStr
565 DO J=jMin, jMax, jStr
566 DO I=iMin, iMax, iStr
567 IF (printMapIncludesZeros .OR. fld(I,J,K,bi,bj) .NE. 0.) THEN
568 IF ( fld(I,J,K,bi,bj) .LT. fMin )
569 & fMin = fld(I,J,K,bi,bj)
570 IF ( fld(I,J,K,bi,bj) .GT. fMax )
571 & fMax = fld(I,J,K,bi,bj)
572 ENDIF
573 ENDDO
574 ENDDO
575 ENDDO
576 ENDDO
577 ENDDO
578 fRange = fMax-fMin
579 IF ( fRange .GT. small ) THEN
580 validRange = .TRUE.
581 ENDIF
582
583 C-- Write field title and statistics
584 msgBuf = '// ======================================================='
585 CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
586 & SQUEEZE_RIGHT, 1)
587 iStrngLo = IFNBLNK(fldTitle)
588 iStrngHi = ILNBLNK(fldTitle)
589 IF ( iStrngLo .LE. iStrngHi ) THEN
590 WRITE(msgBuf,'(A)') fldTitle(iStrngLo:iStrngHi)
591 ELSE
592 msgBuf = '// UNKNOWN FIELD'
593 ENDIF
594 CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
595 & SQUEEZE_RIGHT, 1)
596 WRITE(msgBuf,'(A,1PE30.15)')
597 & '// CMIN = ', fMin
598 CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
599 & SQUEEZE_RIGHT, 1)
600 WRITE(msgBuf,'(A,1PE30.15)')
601 & '// CMAX = ', fMax
602 CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
603 & SQUEEZE_RIGHT, 1)
604 IF ( validRange ) THEN
605 WRITE(msgBuf,'(A,1PE30.15)')
606 & '// CINT = ', fRange/FLOAT(lChlist-1)
607 ELSE
608 WRITE(msgBuf,'(A,1PE30.15)')
609 & '// CINT = ', 0.
610 ENDIF
611 CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
612 & SQUEEZE_RIGHT, 1)
613 WRITE(msgBuf,'(A,1024A1)')
614 & '// SYMBOLS (CMIN->CMAX): ',(chList(I:I),I=1,lChList)
615 CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
616 & SQUEEZE_RIGHT, 1)
617 WRITE(msgBuf,'(A,1024A1)')
618 & '// 0.0: ','.'
619 CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
620 & SQUEEZE_RIGHT, 1)
621 WRITE(msgBuf,'(A,3(A,I4),A)')
622 & '// RANGE I (Lo:Hi:Step):',
623 & '(',myXGlobalLo-1+(bxMin-1)*sNx+iMin,
624 & ':',myXGlobalLo-1+(bxMax-1)*sNx+iMax,
625 & ':',iStr,')'
626 CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
627 & SQUEEZE_RIGHT, 1)
628 WRITE(msgBuf,'(A,3(A,I4),A)')
629 & '// RANGE J (Lo:Hi:Step):',
630 & '(',myYGlobalLo-1+(byMin-1)*sNy+jMin,
631 & ':',myYGlobalLo-1+(byMax-1)*sNy+jMax,
632 & ':',jStr,')'
633 CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
634 & SQUEEZE_RIGHT, 1)
635 WRITE(msgBuf,'(A,3(A,I4),A)')
636 & '// RANGE K (Lo:Hi:Step):',
637 & '(',kMin,
638 & ':',kMax,
639 & ':',kStr,')'
640 CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
641 & SQUEEZE_RIGHT, 1)
642 msgBuf = '// ======================================================='
643 CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
644 & SQUEEZE_RIGHT, 1)
645
646 C-- Write field
647 C Figure out slice type and set plotting parameters appropriately
648 C acc = accross the page
649 C dwn = down the page
650 IF ( plotMode .EQ. PRINT_MAP_XY ) THEN
651 C X across, Y down slice
652 accLab = 'I='
653 accBase = myXGlobalLo
654 accStep = sNx
655 accBlo = bxMin
656 accBhi = bxMax
657 accBStr = bxStr
658 accMin = iMin
659 accMax = iMax
660 accStr = iStr
661 dwnLab = '|--J--|'
662 dwnBase = myYGlobalLo
663 dwnStep = sNy
664 dwnBlo = byMin
665 dwnBhi = byMax
666 dwnBStr = byStr
667 dwnMin = jMin
668 dwnMax = jMax
669 dwnStr = jStr
670 pltBlo = 1
671 pltBhi = 1
672 pltBstr = 1
673 pltMin = kMin
674 pltMax = kMax
675 pltStr = kStr
676 pltBase = 1
677 pltStep = 1
678 pltLab = 'K ='
679 ELSEIF ( plotMode .EQ. PRINT_MAP_YZ ) THEN
680 C Y across, Z down slice
681 accLab = 'J='
682 accBase = myYGlobalLo
683 accStep = sNy
684 accBlo = byMin
685 accBhi = byMax
686 accBStr = byStr
687 accMin = jMin
688 accMax = jMax
689 accStr = jStr
690 dwnLab = '|--K--|'
691 dwnBase = 1
692 dwnStep = 1
693 dwnBlo = 1
694 dwnBhi = 1
695 dwnBStr = 1
696 dwnMin = kMin
697 dwnMax = kMax
698 dwnStr = kStr
699 pltBlo = bxMin
700 pltBhi = bxMax
701 pltBstr = bxStr
702 pltMin = iMin
703 pltMax = iMax
704 pltStr = iStr
705 pltBase = myXGlobalLo
706 pltStep = sNx
707 pltLab = 'I ='
708 ELSEIF ( plotMode .EQ. PRINT_MAP_XZ ) THEN
709 C X across, Z down slice
710 accLab = 'I='
711 accBase = myXGlobalLo
712 accStep = sNx
713 accBlo = bxMin
714 accBhi = bxMax
715 accBStr = bxStr
716 accMin = iMin
717 accMax = iMax
718 accStr = iStr
719 dwnLab = '|--K--|'
720 dwnBase = 1
721 dwnStep = 1
722 dwnBlo = 1
723 dwnBhi = 1
724 dwnBStr = 1
725 dwnMin = kMin
726 dwnMax = kMax
727 dwnStr = kStr
728 pltBlo = byMin
729 pltBhi = byMax
730 pltBstr = byStr
731 pltMin = jMin
732 pltMax = jMax
733 pltStr = jStr
734 pltBase = myYGlobalLo
735 pltStep = sNy
736 pltLab = 'J ='
737 ENDIF
738 C IF ( validRange ) THEN
739 C Header
740 C Data
741 DO bk=pltBlo, pltBhi, pltBstr
742 DO K=pltMin,pltMax,pltStr
743 WRITE(plotBuf,'(A,I,I,I,I)') pltLab,
744 & pltBase-1+(bk-1)*pltStep+K
745 CALL PRINT_MESSAGE(plotBuf, standardMessageUnit,
746 & SQUEEZE_RIGHT, 1)
747 plotBuf = ' '
748 iBuf = 6
749 DO bi=accBlo, accBhi, accBstr
750 DO I=accMin, accMax, accStr
751 iDx = accBase-1+(bi-1)*accStep+I
752 iBuf = iBuf + 1
753 IF ( 10*((iBuf-6)/10) .EQ. iBuf-6 ) THEN
754 IF ( iDx. LT. 10 ) THEN
755 WRITE(plotBuf(iBuf:),'(A,I1)') accLab,iDx
756 ELSEIF ( iDx. LT. 100 ) THEN
757 WRITE(plotBuf(iBuf:),'(A,I2)') accLab,iDx
758 ELSEIF ( iDx. LT. 1000 ) THEN
759 WRITE(plotBuf(iBuf:),'(A,I3)') accLab,iDx
760 ELSEIF ( iDx. LT. 10000 ) THEN
761 WRITE(plotBuf(iBuf:),'(A,I4)') accLab,iDx
762 ENDIF
763 ENDIF
764 ENDDO
765 ENDDO
766 WRITE(msgBuf,'(A,A)') '// ',plotBuf
767 CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
768 & SQUEEZE_RIGHT, 1)
769 plotBuf = dwnLab
770 iBuf = 7
771 DO bi=accBlo, accBhi, accBstr
772 DO I=accMin, accMax, accStr
773 iDx = accBase-1+(bi-1)*accStep+I
774 iBuf = iBuf+1
775 IF ( 10*((iBuf-7)/10) .EQ. iBuf-7 ) THEN
776 WRITE(plotBuf(iBuf:),'(A)') '|'
777 ELSE
778 WRITE(plotBuf(iBuf:iBuf),'(I1)') MOD(iDx,10)
779 ENDIF
780 ENDDO
781 ENDDO
782 WRITE(msgBuf,'(A,A)') '// ',plotBuf
783 CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
784 & SQUEEZE_RIGHT, 1)
785 DO bj=dwnBlo, dwnBhi, dwnBStr
786 DO J=dwnMin, dwnMax, dwnStr
787 WRITE(plotBuf,'(1X,I5,1X)')
788 & dwnBase-1+(bj-1)*dwnStep+J
789 iBuf = 7
790 DO bi=accBlo,accBhi,accBstr
791 DO I=accMin,accMax,accStr
792 iBuf = iBuf + 1
793 IF ( plotMode .EQ. PRINT_MAP_XY ) THEN
794 val = fld(I,J,K,bi,bj)
795 ELSEIF ( plotMode .EQ. PRINT_MAP_XZ ) THEN
796 val = fld(I,K,J,bi,bk)
797 ELSEIF ( plotMode .EQ. PRINT_MAP_YZ ) THEN
798 val = fld(K,I,J,bk,bi)
799 ENDIF
800 IF ( validRange ) THEN
801 IDX = NINT(
802 & FLOAT( lChList-1 )*( val-fMin ) / (fRange)
803 & )+1
804 ELSE
805 IDX = 1
806 ENDIF
807 IF ( iBuf .LE. MAX_LEN_PLOTBUF )
808 & plotBuf(iBuf:iBuf) = chList(IDX:IDX)
809 IF ( val .EQ. 0. ) THEN
810 IF ( iBuf .LE. MAX_LEN_PLOTBUF )
811 & plotBuf(iBuf:iBuf) = '.'
812 ENDIF
813 ENDDO
814 ENDDO
815 WRITE(msgBuf,'(A,A)') '// ',plotBuf
816 CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
817 & SQUEEZE_RIGHT, 1)
818 ENDDO
819 ENDDO
820 ENDDO
821 ENDDO
822 C ENDIF
823 C-- Write delimiter
824 msgBuf = '// ======================================================='
825 CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
826 & SQUEEZE_RIGHT, 1)
827 msgBuf = '// END OF FIELD ='
828 CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
829 & SQUEEZE_RIGHT, 1)
830 msgBuf = '// ======================================================='
831 CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
832 & SQUEEZE_RIGHT, 1)
833 msgBuf = ' '
834 CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
835 & SQUEEZE_RIGHT, 1)
836
837 RETURN
838 END
839
840 CStartOfInterface
841 SUBROUTINE PRINT_MAPRL ( fld, fldTitle, plotMode,
842 I iLo, iHi, jLo, jHi, kLo, kHi, nBx, nBy,
843 I iMin, iMax, iStr,
844 I jMin, jMax, jStr,
845 I kMin, kMax, kStr,
846 I bxMin, bxMax, bxStr,
847 I byMin, byMax, byStr )
848 C /==========================================================\
849 C | SUBROUTINE PRINT_MAPRL |
850 C | o Does textual mapping printing of a field. |
851 C |==========================================================|
852 C | This routine does the actual formatting of the data |
853 C | and printing to a file. It assumes an array using the |
854 C | MITgcm UV indexing scheme and base index variables. |
855 C | User code should call an interface routine like |
856 C | PLOT_FIELD_XYR8( ... ) rather than this code directly. |
857 C | Text plots can be oriented XY, YZ, XZ. An orientation |
858 C | is specficied through the "plotMode" argument. All the |
859 C | plots made by a single call to this routine will use the |
860 C | same contour interval. The plot range (iMin,...,byStr) |
861 C | can be three-dimensional. A separate plot is made for |
862 C | each point in the plot range normal to the orientation. |
863 C | e.g. if the orientation is XY (plotMode = PRINT_MAP_XY). |
864 C | kMin =1, kMax = 5 and kStr = 2 will produce three XY|
865 C | plots - one for K=1, one for K=3 and one for K=5. |
866 C | Each plot would have extents iMin:iMax step iStr |
867 C | and jMin:jMax step jStr. |
868 C \==========================================================/
869
870 C == Global variables ==
871 #include "SIZE.h"
872 #include "EEPARAMS.h"
873 #include "EESUPPORT.h"
874
875 C == Routine arguments ==
876 C fld - Real*8 array holding data to be plotted
877 C fldTitle - Name of field to be plotted
878 C plotMode - Text string indicating plot orientation
879 C ( see - EEPARAMS.h for valid values ).
880 C iLo, iHi, - Dimensions of array fld. fld is assumed to
881 C jLo, jHi be five-dimensional.
882 C kLo, kHi
883 C nBx, nBy
884 C iMin, iMax - Indexing for points to plot. Points from
885 C iStr iMin -> iMax in steps of iStr are plotted
886 C jMin. jMax and similarly for jMin, jMax, jStr and
887 C jStr kMin, kMax, kStr and bxMin, bxMax, bxStr
888 C kMin, kMax byMin, byMax, byStr.
889 C kStr
890 CHARACTER*(*) fldTitle
891 CHARACTER*(*) plotMode
892 INTEGER iLo, iHi
893 INTEGER jLo, jHi
894 INTEGER kLo, kHi
895 INTEGER nBx, nBy
896 _RL fld(iLo:iHi,jLo:jHi,kLo:kHi,nBx,nBy)
897 INTEGER iMin, iMax, iStr
898 INTEGER jMin, jMax, jStr
899 INTEGER kMin, kMax, kStr
900 INTEGER bxMin, bxMax, bxStr
901 INTEGER byMin, byMax, byStr
902 CEndOfInterface
903 C == Local variables ==
904 INTEGER IFNBLNK
905 EXTERNAL IFNBLNK
906 INTEGER ILNBLNK
907 EXTERNAL ILNBLNK
908
909 C == Local variables ==
910 C plotBuf - Buffer for building plot record
911 C chList - Character string used for plot
912 C fMin, fMax - Contour min, max and range
913 C fRange
914 C val - Value of element to be "plotted"
915 C small - Lowest range for which contours are plotted
916 C accXXX - Variables used in indexing accross page records.
917 C dwnXXX Variables used in indexing down the page.
918 C pltXXX Variables used in indexing multiple plots ( multiple
919 C plots use same contour range).
920 C Lab - Label
921 C Base - Base number for element indexing
922 C The process bottom, left coordinate in the
923 C global domain.
924 C Step - Block size
925 C Blo - Start block
926 C Bhi - End block
927 C Bstr - Block stride
928 C Min - Start index within block
929 C Max - End index within block
930 C Str - stride within block
931 INTEGER MAX_LEN_PLOTBUF
932 PARAMETER ( MAX_LEN_PLOTBUF = MAX_LEN_MBUF-4 )
933 CHARACTER*(MAX_LEN_PLOTBUF) plotBuf
934 CHARACTER*(MAX_LEN_MBUF) msgBuf
935 INTEGER lChList
936 PARAMETER ( lChList = 28 )
937 CHARACTER*(lChList) chList
938 REAL fMin
939 REAL fMax
940 REAL fRange
941 REAL val
942 REAL small
943 CHARACTER*2 accLab
944 CHARACTER*7 dwnLab
945 CHARACTER*3 pltLab
946 INTEGER accBase, dwnBase, pltBase
947 INTEGER accStep, dwnStep, pltStep
948 INTEGER accBlo, dwnBlo, pltBlo
949 INTEGER accBhi, dwnBhi, pltBhi
950 INTEGER accBstr, dwnBstr, pltBstr
951 INTEGER accMin, dwnMin, pltMin
952 INTEGER accMax, dwnMax, pltMax
953 INTEGER accStr, dwnStr, pltStr
954 INTEGER I, J, K, iStrngLo, iStrngHi, iBuf, iDx
955 INTEGER bi, bj, bk
956 LOGICAL validRange
957
958 chList = '-abcdefghijklmnopqrstuvwxyz+'
959 small = 1. _d -15
960 fMin = 1. _d 32
961 fMax = -1. _d 32
962 validRange = .FALSE.
963
964 C-- Calculate field range
965 DO bj=byMin, byMax, byStr
966 DO bi=bxMin, bxMax, bxStr
967 DO K=kMin, kMax, kStr
968 DO J=jMin, jMax, jStr
969 DO I=iMin, iMax, iStr
970 IF ( printMapIncludesZeros .OR. fld(I,J,K,bi,bj) .NE. 0. ) THEN
971 IF ( fld(I,J,K,bi,bj) .LT. fMin )
972 & fMin = fld(I,J,K,bi,bj)
973 IF ( fld(I,J,K,bi,bj) .GT. fMax )
974 & fMax = fld(I,J,K,bi,bj)
975 ENDIF
976 ENDDO
977 ENDDO
978 ENDDO
979 ENDDO
980 ENDDO
981 fRange = fMax-fMin
982 IF ( fRange .GT. small ) THEN
983 validRange = .TRUE.
984 ENDIF
985
986 C-- Write field title and statistics
987 msgBuf = '// ======================================================='
988 CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
989 & SQUEEZE_RIGHT, 1)
990 iStrngLo = IFNBLNK(fldTitle)
991 iStrngHi = ILNBLNK(fldTitle)
992 IF ( iStrngLo .LE. iStrngHi ) THEN
993 WRITE(msgBuf,'(A)') fldTitle(iStrngLo:iStrngHi)
994 ELSE
995 msgBuf = '// UNKNOWN FIELD'
996 ENDIF
997 CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
998 & SQUEEZE_RIGHT, 1)
999 WRITE(msgBuf,'(A,1PE30.15)')
1000 & '// CMIN = ', fMin
1001 CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
1002 & SQUEEZE_RIGHT, 1)
1003 WRITE(msgBuf,'(A,1PE30.15)')
1004 & '// CMAX = ', fMax
1005 CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
1006 & SQUEEZE_RIGHT, 1)
1007 IF ( validRange ) THEN
1008 WRITE(msgBuf,'(A,1PE30.15)')
1009 & '// CINT = ', fRange/FLOAT(lChlist-1)
1010 ELSE
1011 WRITE(msgBuf,'(A,1PE30.15)')
1012 & '// CINT = ', 0.
1013 ENDIF
1014 CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
1015 & SQUEEZE_RIGHT, 1)
1016 WRITE(msgBuf,'(A,1024A1)')
1017 & '// SYMBOLS (CMIN->CMAX): ',(chList(I:I),I=1,lChList)
1018 CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
1019 & SQUEEZE_RIGHT, 1)
1020 WRITE(msgBuf,'(A,1024A1)')
1021 & '// 0.0: ','.'
1022 CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
1023 & SQUEEZE_RIGHT, 1)
1024 WRITE(msgBuf,'(A,3(A,I4),A)')
1025 & '// RANGE I (Lo:Hi:Step):',
1026 & '(',myXGlobalLo-1+(bxMin-1)*sNx+iMin,
1027 & ':',myXGlobalLo-1+(bxMax-1)*sNx+iMax,
1028 & ':',iStr,')'
1029 CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
1030 & SQUEEZE_RIGHT, 1)
1031 WRITE(msgBuf,'(A,3(A,I4),A)')
1032 & '// RANGE J (Lo:Hi:Step):',
1033 & '(',myYGlobalLo-1+(byMin-1)*sNy+jMin,
1034 & ':',myYGlobalLo-1+(byMax-1)*sNy+jMax,
1035 & ':',jStr,')'
1036 CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
1037 & SQUEEZE_RIGHT, 1)
1038 WRITE(msgBuf,'(A,3(A,I4),A)')
1039 & '// RANGE K (Lo:Hi:Step):',
1040 & '(',kMin,
1041 & ':',kMax,
1042 & ':',kStr,')'
1043 CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
1044 & SQUEEZE_RIGHT, 1)
1045 msgBuf = '// ======================================================='
1046 CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
1047 & SQUEEZE_RIGHT, 1)
1048
1049 C-- Write field
1050 C Figure out slice type and set plotting parameters appropriately
1051 C acc = accross the page
1052 C dwn = down the page
1053 IF ( plotMode .EQ. PRINT_MAP_XY ) THEN
1054 C X across, Y down slice
1055 accLab = 'I='
1056 accBase = myXGlobalLo
1057 accStep = sNx
1058 accBlo = bxMin
1059 accBhi = bxMax
1060 accBStr = bxStr
1061 accMin = iMin
1062 accMax = iMax
1063 accStr = iStr
1064 dwnLab = '|--J--|'
1065 dwnBase = myYGlobalLo
1066 dwnStep = sNy
1067 dwnBlo = byMin
1068 dwnBhi = byMax
1069 dwnBStr = byStr
1070 dwnMin = jMin
1071 dwnMax = jMax
1072 dwnStr = jStr
1073 pltBlo = 1
1074 pltBhi = 1
1075 pltBstr = 1
1076 pltMin = kMin
1077 pltMax = kMax
1078 pltStr = kStr
1079 pltBase = 1
1080 pltStep = 1
1081 pltLab = 'K ='
1082 ELSEIF ( plotMode .EQ. PRINT_MAP_YZ ) THEN
1083 C Y across, Z down slice
1084 accLab = 'J='
1085 accBase = myYGlobalLo
1086 accStep = sNy
1087 accBlo = byMin
1088 accBhi = byMax
1089 accBStr = byStr
1090 accMin = jMin
1091 accMax = jMax
1092 accStr = jStr
1093 dwnLab = '|--K--|'
1094 dwnBase = 1
1095 dwnStep = 1
1096 dwnBlo = 1
1097 dwnBhi = 1
1098 dwnBStr = 1
1099 dwnMin = kMin
1100 dwnMax = kMax
1101 dwnStr = kStr
1102 pltBlo = bxMin
1103 pltBhi = bxMax
1104 pltBstr = bxStr
1105 pltMin = iMin
1106 pltMax = iMax
1107 pltStr = iStr
1108 pltBase = myXGlobalLo
1109 pltStep = sNx
1110 pltLab = 'I ='
1111 ELSEIF ( plotMode .EQ. PRINT_MAP_XZ ) THEN
1112 C X across, Z down slice
1113 accLab = 'I='
1114 accBase = myXGlobalLo
1115 accStep = sNx
1116 accBlo = bxMin
1117 accBhi = bxMax
1118 accBStr = bxStr
1119 accMin = iMin
1120 accMax = iMax
1121 accStr = iStr
1122 dwnLab = '|--K--|'
1123 dwnBase = 1
1124 dwnStep = 1
1125 dwnBlo = 1
1126 dwnBhi = 1
1127 dwnBStr = 1
1128 dwnMin = kMin
1129 dwnMax = kMax
1130 dwnStr = kStr
1131 pltBlo = byMin
1132 pltBhi = byMax
1133 pltBstr = byStr
1134 pltMin = jMin
1135 pltMax = jMax
1136 pltStr = jStr
1137 pltBase = myYGlobalLo
1138 pltStep = sNy
1139 pltLab = 'J ='
1140 ENDIF
1141 C IF ( validRange ) THEN
1142 C Header
1143 C Data
1144 DO bk=pltBlo, pltBhi, pltBstr
1145 DO K=pltMin,pltMax,pltStr
1146 WRITE(plotBuf,'(A,I,I,I,I)') pltLab,
1147 & pltBase-1+(bk-1)*pltStep+K
1148 CALL PRINT_MESSAGE(plotBuf, standardMessageUnit,
1149 & SQUEEZE_RIGHT, 1)
1150 plotBuf = ' '
1151 iBuf = 6
1152 DO bi=accBlo, accBhi, accBstr
1153 DO I=accMin, accMax, accStr
1154 iDx = accBase-1+(bi-1)*accStep+I
1155 iBuf = iBuf + 1
1156 IF ( 10*((iBuf-6)/10) .EQ. iBuf-6 ) THEN
1157 IF ( iDx. LT. 10 ) THEN
1158 WRITE(plotBuf(iBuf:),'(A,I1)') accLab,iDx
1159 ELSEIF ( iDx. LT. 100 ) THEN
1160 WRITE(plotBuf(iBuf:),'(A,I2)') accLab,iDx
1161 ELSEIF ( iDx. LT. 1000 ) THEN
1162 WRITE(plotBuf(iBuf:),'(A,I3)') accLab,iDx
1163 ELSEIF ( iDx. LT. 10000 ) THEN
1164 WRITE(plotBuf(iBuf:),'(A,I4)') accLab,iDx
1165 ENDIF
1166 ENDIF
1167 ENDDO
1168 ENDDO
1169 CALL PRINT_MESSAGE(plotBuf, standardMessageUnit,
1170 & SQUEEZE_RIGHT, 1)
1171 plotBuf = dwnLab
1172 iBuf = 7
1173 DO bi=accBlo, accBhi, accBstr
1174 DO I=accMin, accMax, accStr
1175 iDx = accBase-1+(bi-1)*accStep+I
1176 iBuf = iBuf+1
1177 IF ( 10*((iBuf-7)/10) .EQ. iBuf-7 ) THEN
1178 WRITE(plotBuf(iBuf:),'(A)') '|'
1179 ELSE
1180 WRITE(plotBuf(iBuf:iBuf),'(I1)') MOD(iDx,10)
1181 ENDIF
1182 ENDDO
1183 ENDDO
1184 CALL PRINT_MESSAGE(plotBuf, standardMessageUnit,
1185 & SQUEEZE_RIGHT, 1)
1186 DO bj=dwnBlo, dwnBhi, dwnBStr
1187 DO J=dwnMin, dwnMax, dwnStr
1188 WRITE(plotBuf,'(1X,I5,1X)')
1189 & dwnBase-1+(bj-1)*dwnStep+J
1190 iBuf = 7
1191 DO bi=accBlo,accBhi,accBstr
1192 DO I=accMin,accMax,accStr
1193 iBuf = iBuf + 1
1194 IF ( plotMode .EQ. PRINT_MAP_XY ) THEN
1195 val = fld(I,J,K,bi,bj)
1196 ELSEIF ( plotMode .EQ. PRINT_MAP_XZ ) THEN
1197 val = fld(I,K,J,bi,bk)
1198 ELSEIF ( plotMode .EQ. PRINT_MAP_YZ ) THEN
1199 val = fld(K,I,J,bk,bi)
1200 ENDIF
1201 IF ( validRange ) THEN
1202 IDX = NINT(
1203 & FLOAT( lChList-1 )*( val-fMin ) / (fRange)
1204 & )+1
1205 ELSE
1206 IDX = 1
1207 ENDIF
1208 IF ( iBuf .LE. MAX_LEN_PLOTBUF )
1209 & plotBuf(iBuf:iBuf) = chList(IDX:IDX)
1210 IF ( val .EQ. 0. ) THEN
1211 IF ( iBuf .LE. MAX_LEN_PLOTBUF )
1212 & plotBuf(iBuf:iBuf) = '.'
1213 ENDIF
1214 ENDDO
1215 ENDDO
1216 CALL PRINT_MESSAGE(plotBuf, standardMessageUnit,
1217 & SQUEEZE_RIGHT, 1)
1218 ENDDO
1219 ENDDO
1220 ENDDO
1221 ENDDO
1222 C ENDIF
1223 C-- Write delimiter
1224 msgBuf = '// ======================================================='
1225 CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
1226 & SQUEEZE_RIGHT, 1)
1227 msgBuf = '// END OF FIELD ='
1228 CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
1229 & SQUEEZE_RIGHT, 1)
1230 msgBuf = '// ======================================================='
1231 CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
1232 & SQUEEZE_RIGHT, 1)
1233 msgBuf = ' '
1234 CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
1235 & SQUEEZE_RIGHT, 1)
1236
1237 RETURN
1238 END
1239
1240 CStartOfInterface
1241 SUBROUTINE PRINT_MESSAGE( message, unit, sq , myThid )
1242 C /============================================================\
1243 C | SUBROUTINE PRINT_MESSAGE |
1244 C | o Write out informational message using "standard" format. |
1245 C | Notes |
1246 C | ===== |
1247 C | o Some system's I/O is not "thread-safe". For this reason |
1248 C | without the FMTFTN_IO_THREAD_SAFE directive set a |
1249 C | critical region is defined around the write here. In some|
1250 C | cases BEGIN_CRIT() is approximated by only doing writes |
1251 C | for thread number 1 - writes for other threads are |
1252 C | ignored! |
1253 C | o In a non-parallel form these routines can still be used. |
1254 C | to produce pretty printed output! |
1255 C \============================================================/
1256 C == Global data ==
1257 #include "SIZE.h"
1258 #include "EEPARAMS.h"
1259 #include "EESUPPORT.h"
1260 C == Routine arguments ==
1261 C message - Message to write
1262 C unit - Unit number to write to
1263 C sq - Justification option
1264 CHARACTER*(*) message
1265 INTEGER unit
1266 CHARACTER*(*) sq
1267 INTEGER myThid
1268 CEndOfInterface
1269 INTEGER IFNBLNK
1270 EXTERNAL IFNBLNK
1271 INTEGER ILNBLNK
1272 EXTERNAL ILNBLNK
1273 C == Local variables ==
1274 INTEGER iStart
1275 INTEGER iEnd
1276 CHARACTER*9 idString
1277 C-- Find beginning and end of message
1278 IF ( sq .EQ. SQUEEZE_BOTH .OR.
1279 & sq .EQ. SQUEEZE_LEFT ) THEN
1280 iStart = IFNBLNK( message )
1281 ELSE
1282 iStart = 1
1283 ENDIF
1284 IF ( sq .EQ. SQUEEZE_BOTH .OR.
1285 & sq .EQ. SQUEEZE_RIGHT ) THEN
1286 iEnd = ILNBLNK( message )
1287 ELSE
1288 iEnd = LEN(message)
1289 ENDIF
1290 C-- Test to see if in multi-process ( or multi-threaded ) mode.
1291 C If so include process or thread identifier.
1292 IF ( numberOfProcs .EQ. 0 .AND. nThreads .EQ. 1 ) THEN
1293 C-- Write single process format
1294 IF ( message .EQ. ' ' ) THEN
1295 WRITE(unit,'(A)') ' '
1296 ELSE
1297 WRITE(unit,'(A)') message(iStart:iEnd)
1298 ENDIF
1299 ELSEIF ( pidIO .EQ. myProcId ) THEN
1300 C-- Write multi-process format
1301 #ifndef FMTFTN_IO_THREAD_SAFE
1302 _BEGIN_CRIT(myThid)
1303 #endif
1304 WRITE(idString,'(I4.4,A,I4.4)') myProcId,'.',myThid
1305 #ifndef FMTFTN_IO_THREAD_SAFE
1306 _END_CRIT(myThid)
1307 #endif
1308 IF ( message .EQ. ' ' ) THEN
1309 C PRINT can be called by several threads simultaneously.
1310 C The write statement may need to ne marked as a critical section.
1311 #ifndef FMTFTN_IO_THREAD_SAFE
1312 _BEGIN_CRIT(myThid)
1313 #endif
1314 WRITE(unit,'(A,A,A,A,A,A)',ERR=999)
1315 & '(',PROCESS_HEADER,' ',idString,')',' '
1316 #ifndef FMTFTN_IO_THREAD_SAFE
1317 _END_CRIT(myThid)
1318 #endif
1319 ELSE
1320 #ifndef FMTFTN_IO_THREAD_SAFE
1321 _BEGIN_CRIT(myThid)
1322 #endif
1323 WRITE(unit,'(A,A,A,A,A,A,A)',ERR=999)
1324 & '(',PROCESS_HEADER,' ',idString(1:ILNBLNK(idString)),')',' ',
1325 & message(iStart:iEnd)
1326 #ifndef FMTFTN_IO_THREAD_SAFE
1327 _END_CRIT(myThid)
1328 #endif
1329 ENDIF
1330 ENDIF
1331 C
1332 1000 CONTINUE
1333 RETURN
1334 999 CONTINUE
1335 ioErrorCount(myThid) = ioErrorCount(myThid)+1
1336 GOTO 1000
1337
1338 END

  ViewVC Help
Powered by ViewVC 1.1.22