/[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.25 - (hide annotations) (download)
Sat Sep 2 22:47:10 2006 UTC (17 years, 9 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint58p_post
Changes since 1.24: +2 -2 lines
avoid writing negative index using "(I1)" format (was giving an error msg)

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

  ViewVC Help
Powered by ViewVC 1.1.22