/[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.16 - (show annotations) (download)
Mon May 24 15:26:08 1999 UTC (25 years ago) by adcroft
Branch: MAIN
CVS Tags: checkpoint28, checkpoint29, checkpoint23, checkpoint24, checkpoint25, checkpoint27, branch-atmos-merge-freeze, branch-atmos-merge-start, checkpoint26, branch-atmos-merge-shapiro, checkpoint33, checkpoint32, checkpoint31, checkpoint30, checkpoint34, branch-atmos-merge-zonalfilt, branch-atmos-merge-phase5, branch-atmos-merge-phase4, branch-atmos-merge-phase7, branch-atmos-merge-phase6, branch-atmos-merge-phase1, branch-atmos-merge-phase3, branch-atmos-merge-phase2
Branch point for: branch-atmos-merge
Changes since 1.15: +4 -4 lines
Added parenthesis to help adjoint (?) compiler.

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

  ViewVC Help
Powered by ViewVC 1.1.22