/[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.33 - (show annotations) (download)
Wed Mar 28 20:30:26 2012 UTC (12 years, 2 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint64, checkpoint63p, checkpoint63q, checkpoint63r, checkpoint63s, checkpoint63l, checkpoint63m, checkpoint63n, checkpoint63o
Changes since 1.32: +37 -41 lines
- use OpenMP critical instruction (similar to PRINT_ERROR)
- writing to unit zero (if unit=errorMessageUnit) extended to the case
  myThid=1 (previously only if nThreads=1)

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

  ViewVC Help
Powered by ViewVC 1.1.22