/[MITgcm]/MITgcm/eesupp/src/print.F
ViewVC logotype

Annotation of /MITgcm/eesupp/src/print.F

Parent Directory Parent Directory | Revision Log Revision Log | View Revision Graph Revision Graph


Revision 1.5 - (hide annotations) (download)
Mon Apr 27 04:24:22 1998 UTC (26 years ago) by cnh
Branch: MAIN
CVS Tags: redigm, checkpoint1, kloop1, kloop2
Changes since 1.4: +212 -2 lines
Further changes to reporting of model configuration on standard output

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

  ViewVC Help
Powered by ViewVC 1.1.22