/[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.12 - (show annotations) (download)
Wed Oct 28 03:11:35 1998 UTC (25 years, 6 months ago) by cnh
Branch: MAIN
CVS Tags: checkpoint17, checkpoint16
Changes since 1.11: +54 -31 lines
Changes to support
 - g77 compilation under Linux
 - LR(1) form of 64-bit is D or E for constants
 - Modified adjoint of exch with adjoint variables
   acuumulated.

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

  ViewVC Help
Powered by ViewVC 1.1.22