/[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.21 - (show annotations) (download)
Tue Jan 27 15:59:23 2004 UTC (20 years, 4 months ago) by jmc
Branch: MAIN
CVS Tags: hrcube4, checkpoint52j_pre, checkpoint52k_post, hrcube_3, checkpoint52j_post
Changes since 1.20: +18 -2 lines
always open errorUnit file + write to unit zero if single processor job

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

  ViewVC Help
Powered by ViewVC 1.1.22