/[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.18 - (show annotations) (download)
Fri Sep 21 03:54:35 2001 UTC (22 years, 8 months ago) by cnh
Branch: MAIN
Changes since 1.17: +209 -143 lines
Starting to bring comments up to date and format comments
for document extraction of "prototypes".

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

  ViewVC Help
Powered by ViewVC 1.1.22