/[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.27 - (hide annotations) (download)
Tue Mar 20 23:42:16 2007 UTC (17 years, 2 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint59, checkpoint58y_post, checkpoint59d, checkpoint59a, checkpoint59c, checkpoint59b, checkpoint58x_post
Changes since 1.26: +21 -12 lines
avoid internal write error in PRINT_LIST_R8 when index range exceeds 1000

1 jmc 1.27 C $Header: /u/gcmpack/MITgcm/eesupp/src/print.F,v 1.26 2006/10/10 19:18:47 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 jmc 1.26 C-- o print_maprs Formats ABCD... contour map of a Real(_RS) field
17 cnh 1.4 C-- Uses print_message for writing
18 jmc 1.26 C-- o print_maprl Formats ABCD... contour map of a Real(_RL) field
19 cnh 1.1 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 jmc 1.27 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 jmc 1.27 CHARACTER*25 fmt1, fmt2
446 cnh 1.4 INTEGER K
447 cnh 1.18 CEOP
448 cnh 1.4
449     IF ( index_type .EQ. INDEX_I ) THEN
450     index_lab = 'I ='
451     ELSEIF ( index_type .EQ. INDEX_J ) THEN
452     index_lab = 'J ='
453     ELSEIF ( index_type .EQ. INDEX_K ) THEN
454     index_lab = 'K ='
455     ELSE
456     index_lab = '?='
457     ENDIF
458 jmc 1.27 C- fortran format to write 1 or 2 indices:
459     fmt1='(A,1X,A,I3,1X,A)'
460     fmt2='(A,1X,A,I3,A,I3,1X,A)'
461     IF ( lFld.GE.1000 ) THEN
462     K = 1+INT(LOG10(FLOAT(lFld)))
463     WRITE(fmt1,'(A,I1,A)') '(A,1X,A,I',K,',1X,A)'
464     WRITE(fmt2,'(A,I1,A,I1,A)') '(A,1X,A,I',K,',A,I',K,',1X,A)'
465     ENDIF
466 cnh 1.4 commOpen = '/*'
467     commClose = '*/'
468     iLo = 1
469     iHi = 1
470     punc = ','
471     xOld = fld(1)
472     DO K=2,lFld
473     xNew = fld(K )
474 adcroft 1.16 IF ( .NOT. compact .OR. (xNew .NE. xOld) ) THEN
475 cnh 1.4 nDup = iHi-iLo+1
476     IF ( nDup .EQ. 1 ) THEN
477     WRITE(msgBuf,'(A,1PE23.15,A)') ' ',xOld,punc
478 jmc 1.27 IF ( index_type .NE. INDEX_NONE )
479     & WRITE(msgBuf(45:),fmt1)
480 cnh 1.12 & commOpen,index_lab,iLo,commClose
481 cnh 1.4 ELSE
482 cnh 1.12 WRITE(msgBuf,'(I5,'' '',A,1PE23.15,A)') nDup,'@',xOld,punc
483 jmc 1.27 IF ( index_type .NE. INDEX_NONE )
484     & WRITE(msgBuf(45:),fmt2)
485 cnh 1.4 & commOpen,index_lab,iLo,':',iHi,commClose
486     ENDIF
487 jmc 1.27 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
488 cnh 1.12 & SQUEEZE_RIGHT , 1)
489 cnh 1.4 iLo = K
490     iHi = K
491     xOld = xNew
492     ELSE
493     iHi = K
494     ENDIF
495     ENDDO
496     punc = ' '
497 adcroft 1.9 IF ( markEnd ) punc = ','
498 cnh 1.4 nDup = iHi-iLo+1
499     IF ( nDup .EQ. 1 ) THEN
500     WRITE(msgBuf,'(A,1PE23.15,A)') ' ',xOld,punc
501 jmc 1.27 IF ( index_type .NE. INDEX_NONE )
502     & WRITE(msgBuf(45:),fmt1)
503 cnh 1.12 & commOpen,index_lab,iLo,commClose
504 cnh 1.4 ELSEIF( nDup .GT. 1 ) THEN
505 cnh 1.12 WRITE(msgBuf,'(I5,'' '',A,1PE23.15,A)') nDup,'@',xOld,punc
506 jmc 1.27 IF ( index_type .NE. INDEX_NONE )
507     & WRITE(msgBuf(45:),fmt2)
508 cnh 1.4 & commOpen,index_lab,iLo,':',iHi,commClose
509     ENDIF
510 jmc 1.27 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
511 cnh 1.12 & SQUEEZE_RIGHT , 1)
512 cnh 1.4
513 cnh 1.1 RETURN
514     END
515    
516 cnh 1.18 CBOP
517     C !ROUTINE: PRINT_MAPRS
518     C !INTERFACE:
519 cnh 1.8 SUBROUTINE PRINT_MAPRS ( fld, fldTitle, plotMode,
520 cnh 1.1 I iLo, iHi, jLo, jHi, kLo, kHi, nBx, nBy,
521     I iMin, iMax, iStr,
522     I jMin, jMax, jStr,
523     I kMin, kMax, kStr,
524     I bxMin, bxMax, bxStr,
525     I byMin, byMax, byStr )
526 adcroft 1.14 IMPLICIT NONE
527 cnh 1.18 C !DESCRIPTION:
528     C *==========================================================*
529 jmc 1.26 C | SUBROUTINE PRINT\_MAPRS
530 cnh 1.18 C | o Does textual mapping printing of a field.
531     C *==========================================================*
532     C | This routine does the actual formatting of the data
533     C | and printing to a file. It assumes an array using the
534     C | MITgcm UV indexing scheme and base index variables.
535     C | User code should call an interface routine like
536 jmc 1.26 C | PLOT\_FIELD\_XYRS( ... ) rather than this code directly.
537 cnh 1.18 C | Text plots can be oriented XY, YZ, XZ. An orientation
538     C | is specficied through the "plotMode" argument. All the
539     C | plots made by a single call to this routine will use the
540     C | same contour interval. The plot range (iMin,...,byStr)
541     C | can be three-dimensional. A separate plot is made for
542     C | each point in the plot range normal to the orientation.
543 edhill 1.23 C | e.g. if the orientation is XY (plotMode = PRINT\_MAP\_XY).
544 cnh 1.18 C | kMin =1, kMax = 5 and kStr = 2 will produce three XY
545     C | plots - one for K=1, one for K=3 and one for K=5.
546     C | Each plot would have extents iMin:iMax step iStr
547     C | and jMin:jMax step jStr.
548     C *==========================================================*
549 cnh 1.1
550 cnh 1.18 C !USES:
551 cnh 1.1 C == Global variables ==
552     #include "SIZE.h"
553     #include "EEPARAMS.h"
554     #include "EESUPPORT.h"
555 cnh 1.18 INTEGER IFNBLNK
556     EXTERNAL IFNBLNK
557     INTEGER ILNBLNK
558     EXTERNAL ILNBLNK
559 cnh 1.1
560 cnh 1.18 C !INPUT/OUTPUT PARAMETERS:
561 cnh 1.1 C == Routine arguments ==
562     C fld - Real*4 array holding data to be plotted
563     C fldTitle - Name of field to be plotted
564     C plotMode - Text string indicating plot orientation
565     C ( see - EEPARAMS.h for valid values ).
566     C iLo, iHi, - Dimensions of array fld. fld is assumed to
567     C jLo, jHi be five-dimensional.
568     C kLo, kHi
569     C nBx, nBy
570     C iMin, iMax - Indexing for points to plot. Points from
571     C iStr iMin -> iMax in steps of iStr are plotted
572     C jMin. jMax and similarly for jMin, jMax, jStr and
573     C jStr kMin, kMax, kStr and bxMin, bxMax, bxStr
574     C kMin, kMax byMin, byMax, byStr.
575     C kStr
576     CHARACTER*(*) fldTitle
577     CHARACTER*(*) plotMode
578     INTEGER iLo, iHi
579     INTEGER jLo, jHi
580     INTEGER kLo, kHi
581     INTEGER nBx, nBy
582 cnh 1.8 _RS fld(iLo:iHi,jLo:jHi,kLo:kHi,nBx,nBy)
583 cnh 1.1 INTEGER iMin, iMax, iStr
584     INTEGER jMin, jMax, jStr
585     INTEGER kMin, kMax, kStr
586     INTEGER bxMin, bxMax, bxStr
587     INTEGER byMin, byMax, byStr
588    
589 cnh 1.18 C !LOCAL VARIABLES:
590 cnh 1.1 C == Local variables ==
591     C plotBuf - Buffer for building plot record
592     C chList - Character string used for plot
593     C fMin, fMax - Contour min, max and range
594     C fRange
595     C val - Value of element to be "plotted"
596     C small - Lowest range for which contours are plotted
597     C accXXX - Variables used in indexing accross page records.
598     C dwnXXX Variables used in indexing down the page.
599     C pltXXX Variables used in indexing multiple plots ( multiple
600     C plots use same contour range).
601     C Lab - Label
602     C Base - Base number for element indexing
603     C The process bottom, left coordinate in the
604     C global domain.
605     C Step - Block size
606     C Blo - Start block
607     C Bhi - End block
608     C Bstr - Block stride
609     C Min - Start index within block
610     C Max - End index within block
611     C Str - stride within block
612     INTEGER MAX_LEN_PLOTBUF
613     PARAMETER ( MAX_LEN_PLOTBUF = MAX_LEN_MBUF-4 )
614     CHARACTER*(MAX_LEN_PLOTBUF) plotBuf
615     CHARACTER*(MAX_LEN_MBUF) msgBuf
616     INTEGER lChList
617     PARAMETER ( lChList = 28 )
618     CHARACTER*(lChList) chList
619 cnh 1.13 _RL fMin
620     _RL fMax
621     _RL fRange
622     _RL val
623     _RL small
624 cnh 1.1 CHARACTER*2 accLab
625     CHARACTER*7 dwnLab
626     CHARACTER*3 pltLab
627     INTEGER accBase, dwnBase, pltBase
628     INTEGER accStep, dwnStep, pltStep
629     INTEGER accBlo, dwnBlo, pltBlo
630     INTEGER accBhi, dwnBhi, pltBhi
631     INTEGER accBstr, dwnBstr, pltBstr
632     INTEGER accMin, dwnMin, pltMin
633     INTEGER accMax, dwnMax, pltMax
634     INTEGER accStr, dwnStr, pltStr
635     INTEGER I, J, K, iStrngLo, iStrngHi, iBuf, iDx
636     INTEGER bi, bj, bk
637     LOGICAL validRange
638 cnh 1.18 CEOP
639 cnh 1.1
640     chList = '-abcdefghijklmnopqrstuvwxyz+'
641 cnh 1.13 small = 1. _d -15
642     fMin = 1. _d 32
643     fMax = -1. _d 32
644 cnh 1.1 validRange = .FALSE.
645    
646     C-- Calculate field range
647     DO bj=byMin, byMax, byStr
648     DO bi=bxMin, bxMax, bxStr
649     DO K=kMin, kMax, kStr
650     DO J=jMin, jMax, jStr
651     DO I=iMin, iMax, iStr
652 cnh 1.11 IF (printMapIncludesZeros .OR. fld(I,J,K,bi,bj) .NE. 0.) THEN
653 cnh 1.1 IF ( fld(I,J,K,bi,bj) .LT. fMin )
654     & fMin = fld(I,J,K,bi,bj)
655     IF ( fld(I,J,K,bi,bj) .GT. fMax )
656     & fMax = fld(I,J,K,bi,bj)
657     ENDIF
658     ENDDO
659     ENDDO
660     ENDDO
661     ENDDO
662     ENDDO
663     fRange = fMax-fMin
664 dimitri 1.20 IF ( fRange .GT. small .AND.
665     & (MAX_LEN_PLOTBUF-35) .GT. sNx*nSx .AND.
666     & (MAX_LEN_PLOTBUF-35) .GT. sNy*nSy ) validRange = .TRUE.
667 cnh 1.1
668     C-- Write field title and statistics
669 cnh 1.12 msgBuf =
670     & '// ======================================================='
671 cnh 1.1 CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
672     & SQUEEZE_RIGHT, 1)
673     iStrngLo = IFNBLNK(fldTitle)
674     iStrngHi = ILNBLNK(fldTitle)
675     IF ( iStrngLo .LE. iStrngHi ) THEN
676     WRITE(msgBuf,'(A)') fldTitle(iStrngLo:iStrngHi)
677     ELSE
678     msgBuf = '// UNKNOWN FIELD'
679     ENDIF
680     CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
681     & SQUEEZE_RIGHT, 1)
682     WRITE(msgBuf,'(A,1PE30.15)')
683     & '// CMIN = ', fMin
684     CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
685     & SQUEEZE_RIGHT, 1)
686     WRITE(msgBuf,'(A,1PE30.15)')
687     & '// CMAX = ', fMax
688     CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
689     & SQUEEZE_RIGHT, 1)
690 cnh 1.11 IF ( validRange ) THEN
691     WRITE(msgBuf,'(A,1PE30.15)')
692     & '// CINT = ', fRange/FLOAT(lChlist-1)
693     ELSE
694     WRITE(msgBuf,'(A,1PE30.15)')
695     & '// CINT = ', 0.
696     ENDIF
697 cnh 1.1 CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
698     & SQUEEZE_RIGHT, 1)
699     WRITE(msgBuf,'(A,1024A1)')
700     & '// SYMBOLS (CMIN->CMAX): ',(chList(I:I),I=1,lChList)
701     CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
702     & SQUEEZE_RIGHT, 1)
703     WRITE(msgBuf,'(A,1024A1)')
704     & '// 0.0: ','.'
705     CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
706     & SQUEEZE_RIGHT, 1)
707     WRITE(msgBuf,'(A,3(A,I4),A)')
708     & '// RANGE I (Lo:Hi:Step):',
709     & '(',myXGlobalLo-1+(bxMin-1)*sNx+iMin,
710     & ':',myXGlobalLo-1+(bxMax-1)*sNx+iMax,
711     & ':',iStr,')'
712     CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
713     & SQUEEZE_RIGHT, 1)
714     WRITE(msgBuf,'(A,3(A,I4),A)')
715     & '// RANGE J (Lo:Hi:Step):',
716     & '(',myYGlobalLo-1+(byMin-1)*sNy+jMin,
717     & ':',myYGlobalLo-1+(byMax-1)*sNy+jMax,
718     & ':',jStr,')'
719     CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
720     & SQUEEZE_RIGHT, 1)
721     WRITE(msgBuf,'(A,3(A,I4),A)')
722     & '// RANGE K (Lo:Hi:Step):',
723     & '(',kMin,
724     & ':',kMax,
725     & ':',kStr,')'
726     CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
727     & SQUEEZE_RIGHT, 1)
728 cnh 1.12 msgBuf =
729     & '// ======================================================='
730 cnh 1.1 CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
731     & SQUEEZE_RIGHT, 1)
732    
733 adcroft 1.22 if (Nx.gt.MAX_LEN_PLOTBUF-20) THEN
734     msgBuf =
735     & 'Model domain too big to print to terminal - skipping I/O'
736     CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
737     & SQUEEZE_RIGHT, 1)
738     RETURN
739     endif
740    
741 cnh 1.1 C-- Write field
742     C Figure out slice type and set plotting parameters appropriately
743     C acc = accross the page
744     C dwn = down the page
745     IF ( plotMode .EQ. PRINT_MAP_XY ) THEN
746     C X across, Y down slice
747     accLab = 'I='
748     accBase = myXGlobalLo
749     accStep = sNx
750     accBlo = bxMin
751     accBhi = bxMax
752     accBStr = bxStr
753     accMin = iMin
754     accMax = iMax
755     accStr = iStr
756     dwnLab = '|--J--|'
757     dwnBase = myYGlobalLo
758     dwnStep = sNy
759     dwnBlo = byMin
760     dwnBhi = byMax
761     dwnBStr = byStr
762     dwnMin = jMin
763     dwnMax = jMax
764     dwnStr = jStr
765     pltBlo = 1
766     pltBhi = 1
767     pltBstr = 1
768     pltMin = kMin
769     pltMax = kMax
770     pltStr = kStr
771     pltBase = 1
772     pltStep = 1
773     pltLab = 'K ='
774     ELSEIF ( plotMode .EQ. PRINT_MAP_YZ ) THEN
775     C Y across, Z down slice
776     accLab = 'J='
777     accBase = myYGlobalLo
778     accStep = sNy
779     accBlo = byMin
780     accBhi = byMax
781     accBStr = byStr
782     accMin = jMin
783     accMax = jMax
784     accStr = jStr
785     dwnLab = '|--K--|'
786     dwnBase = 1
787     dwnStep = 1
788     dwnBlo = 1
789     dwnBhi = 1
790     dwnBStr = 1
791     dwnMin = kMin
792     dwnMax = kMax
793     dwnStr = kStr
794     pltBlo = bxMin
795     pltBhi = bxMax
796     pltBstr = bxStr
797     pltMin = iMin
798     pltMax = iMax
799     pltStr = iStr
800     pltBase = myXGlobalLo
801     pltStep = sNx
802     pltLab = 'I ='
803     ELSEIF ( plotMode .EQ. PRINT_MAP_XZ ) THEN
804     C X across, Z down slice
805     accLab = 'I='
806     accBase = myXGlobalLo
807     accStep = sNx
808     accBlo = bxMin
809     accBhi = bxMax
810     accBStr = bxStr
811     accMin = iMin
812     accMax = iMax
813     accStr = iStr
814     dwnLab = '|--K--|'
815     dwnBase = 1
816     dwnStep = 1
817     dwnBlo = 1
818     dwnBhi = 1
819     dwnBStr = 1
820     dwnMin = kMin
821     dwnMax = kMax
822     dwnStr = kStr
823     pltBlo = byMin
824     pltBhi = byMax
825     pltBstr = byStr
826     pltMin = jMin
827     pltMax = jMax
828     pltStr = jStr
829     pltBase = myYGlobalLo
830     pltStep = sNy
831     pltLab = 'J ='
832     ENDIF
833 dimitri 1.20 IF ( validRange ) THEN
834 cnh 1.1 C Header
835     C Data
836     DO bk=pltBlo, pltBhi, pltBstr
837     DO K=pltMin,pltMax,pltStr
838 cnh 1.12 WRITE(plotBuf,'(A,I4,I4,I4,I4)') pltLab,
839 cnh 1.1 & pltBase-1+(bk-1)*pltStep+K
840     CALL PRINT_MESSAGE(plotBuf, standardMessageUnit,
841     & SQUEEZE_RIGHT, 1)
842     plotBuf = ' '
843     iBuf = 6
844     DO bi=accBlo, accBhi, accBstr
845     DO I=accMin, accMax, accStr
846     iDx = accBase-1+(bi-1)*accStep+I
847     iBuf = iBuf + 1
848     IF ( 10*((iBuf-6)/10) .EQ. iBuf-6 ) THEN
849     IF ( iDx. LT. 10 ) THEN
850     WRITE(plotBuf(iBuf:),'(A,I1)') accLab,iDx
851     ELSEIF ( iDx. LT. 100 ) THEN
852     WRITE(plotBuf(iBuf:),'(A,I2)') accLab,iDx
853     ELSEIF ( iDx. LT. 1000 ) THEN
854     WRITE(plotBuf(iBuf:),'(A,I3)') accLab,iDx
855     ELSEIF ( iDx. LT. 10000 ) THEN
856     WRITE(plotBuf(iBuf:),'(A,I4)') accLab,iDx
857     ENDIF
858     ENDIF
859     ENDDO
860     ENDDO
861     WRITE(msgBuf,'(A,A)') '// ',plotBuf
862     CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
863     & SQUEEZE_RIGHT, 1)
864     plotBuf = dwnLab
865     iBuf = 7
866     DO bi=accBlo, accBhi, accBstr
867     DO I=accMin, accMax, accStr
868     iDx = accBase-1+(bi-1)*accStep+I
869     iBuf = iBuf+1
870     IF ( 10*((iBuf-7)/10) .EQ. iBuf-7 ) THEN
871     WRITE(plotBuf(iBuf:),'(A)') '|'
872     ELSE
873 jmc 1.25 WRITE(plotBuf(iBuf:iBuf),'(I1)') MOD(ABS(iDx),10)
874 cnh 1.1 ENDIF
875     ENDDO
876     ENDDO
877     WRITE(msgBuf,'(A,A)') '// ',plotBuf
878     CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
879     & SQUEEZE_RIGHT, 1)
880     DO bj=dwnBlo, dwnBhi, dwnBStr
881     DO J=dwnMin, dwnMax, dwnStr
882     WRITE(plotBuf,'(1X,I5,1X)')
883     & dwnBase-1+(bj-1)*dwnStep+J
884     iBuf = 7
885     DO bi=accBlo,accBhi,accBstr
886     DO I=accMin,accMax,accStr
887     iBuf = iBuf + 1
888     IF ( plotMode .EQ. PRINT_MAP_XY ) THEN
889     val = fld(I,J,K,bi,bj)
890     ELSEIF ( plotMode .EQ. PRINT_MAP_XZ ) THEN
891     val = fld(I,K,J,bi,bk)
892     ELSEIF ( plotMode .EQ. PRINT_MAP_YZ ) THEN
893     val = fld(K,I,J,bk,bi)
894     ENDIF
895 cnh 1.13 IF ( validRange .AND. val .NE. 0. ) THEN
896 cnh 1.11 IDX = NINT(
897 cnh 1.1 & FLOAT( lChList-1 )*( val-fMin ) / (fRange)
898     & )+1
899 cnh 1.11 ELSE
900     IDX = 1
901     ENDIF
902 cnh 1.1 IF ( iBuf .LE. MAX_LEN_PLOTBUF )
903     & plotBuf(iBuf:iBuf) = chList(IDX:IDX)
904     IF ( val .EQ. 0. ) THEN
905     IF ( iBuf .LE. MAX_LEN_PLOTBUF )
906     & plotBuf(iBuf:iBuf) = '.'
907     ENDIF
908     ENDDO
909     ENDDO
910     WRITE(msgBuf,'(A,A)') '// ',plotBuf
911     CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
912     & SQUEEZE_RIGHT, 1)
913     ENDDO
914     ENDDO
915     ENDDO
916     ENDDO
917 dimitri 1.20 ENDIF
918 cnh 1.1 C-- Write delimiter
919 cnh 1.12 msgBuf =
920     & '// ======================================================='
921 cnh 1.1 CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
922     & SQUEEZE_RIGHT, 1)
923 cnh 1.12 msgBuf =
924     & '// END OF FIELD ='
925 cnh 1.1 CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
926     & SQUEEZE_RIGHT, 1)
927 cnh 1.12 msgBuf =
928     & '// ======================================================='
929 cnh 1.1 CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
930     & SQUEEZE_RIGHT, 1)
931     msgBuf = ' '
932     CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
933     & SQUEEZE_RIGHT, 1)
934    
935     RETURN
936     END
937    
938 cnh 1.18 CBOP
939     C !ROUTINE: PRINT_MAPRL
940    
941     C !INTERFACE:
942 cnh 1.8 SUBROUTINE PRINT_MAPRL ( fld, fldTitle, plotMode,
943 cnh 1.1 I iLo, iHi, jLo, jHi, kLo, kHi, nBx, nBy,
944     I iMin, iMax, iStr,
945     I jMin, jMax, jStr,
946     I kMin, kMax, kStr,
947     I bxMin, bxMax, bxStr,
948     I byMin, byMax, byStr )
949 adcroft 1.14 IMPLICIT NONE
950 cnh 1.1
951 cnh 1.18 C !DESCRIPTION:
952     C *==========================================================*
953 edhill 1.23 C | SUBROUTINE PRINT\_MAPRL
954 cnh 1.18 C | o Does textual mapping printing of a field.
955     C *==========================================================*
956     C | This routine does the actual formatting of the data
957     C | and printing to a file. It assumes an array using the
958     C | MITgcm UV indexing scheme and base index variables.
959     C | User code should call an interface routine like
960 jmc 1.26 C | PLOT\_FIELD\_XYRL( ... ) rather than this code directly.
961 cnh 1.18 C | Text plots can be oriented XY, YZ, XZ. An orientation
962     C | is specficied through the "plotMode" argument. All the
963     C | plots made by a single call to this routine will use the
964     C | same contour interval. The plot range (iMin,...,byStr)
965     C | can be three-dimensional. A separate plot is made for
966     C | each point in the plot range normal to the orientation.
967 edhill 1.23 C | e.g. if the orientation is XY (plotMode = PRINT\_MAP\_XY).
968 cnh 1.18 C | kMin =1, kMax = 5 and kStr = 2 will produce three XY
969     C | plots - one for K=1, one for K=3 and one for K=5.
970     C | Each plot would have extents iMin:iMax step iStr
971     C | and jMin:jMax step jStr.
972     C *==========================================================*
973    
974     C !USES:
975 cnh 1.1 C == Global variables ==
976     #include "SIZE.h"
977     #include "EEPARAMS.h"
978     #include "EESUPPORT.h"
979 cnh 1.18 INTEGER IFNBLNK
980     EXTERNAL IFNBLNK
981     INTEGER ILNBLNK
982     EXTERNAL ILNBLNK
983 cnh 1.1
984 cnh 1.18 C !INPUT/OUTPUT PARAMETERS:
985 cnh 1.1 C == Routine arguments ==
986     C fld - Real*8 array holding data to be plotted
987     C fldTitle - Name of field to be plotted
988     C plotMode - Text string indicating plot orientation
989     C ( see - EEPARAMS.h for valid values ).
990     C iLo, iHi, - Dimensions of array fld. fld is assumed to
991     C jLo, jHi be five-dimensional.
992     C kLo, kHi
993     C nBx, nBy
994     C iMin, iMax - Indexing for points to plot. Points from
995     C iStr iMin -> iMax in steps of iStr are plotted
996     C jMin. jMax and similarly for jMin, jMax, jStr and
997     C jStr kMin, kMax, kStr and bxMin, bxMax, bxStr
998     C kMin, kMax byMin, byMax, byStr.
999     C kStr
1000     CHARACTER*(*) fldTitle
1001     CHARACTER*(*) plotMode
1002     INTEGER iLo, iHi
1003     INTEGER jLo, jHi
1004     INTEGER kLo, kHi
1005     INTEGER nBx, nBy
1006 cnh 1.8 _RL fld(iLo:iHi,jLo:jHi,kLo:kHi,nBx,nBy)
1007 cnh 1.1 INTEGER iMin, iMax, iStr
1008     INTEGER jMin, jMax, jStr
1009     INTEGER kMin, kMax, kStr
1010     INTEGER bxMin, bxMax, bxStr
1011     INTEGER byMin, byMax, byStr
1012    
1013 cnh 1.18 C !LOCAL VARIABLES:
1014 cnh 1.1 C == Local variables ==
1015     C plotBuf - Buffer for building plot record
1016     C chList - Character string used for plot
1017     C fMin, fMax - Contour min, max and range
1018     C fRange
1019     C val - Value of element to be "plotted"
1020     C small - Lowest range for which contours are plotted
1021     C accXXX - Variables used in indexing accross page records.
1022     C dwnXXX Variables used in indexing down the page.
1023     C pltXXX Variables used in indexing multiple plots ( multiple
1024     C plots use same contour range).
1025     C Lab - Label
1026     C Base - Base number for element indexing
1027     C The process bottom, left coordinate in the
1028     C global domain.
1029     C Step - Block size
1030     C Blo - Start block
1031     C Bhi - End block
1032     C Bstr - Block stride
1033     C Min - Start index within block
1034     C Max - End index within block
1035     C Str - stride within block
1036     INTEGER MAX_LEN_PLOTBUF
1037     PARAMETER ( MAX_LEN_PLOTBUF = MAX_LEN_MBUF-4 )
1038     CHARACTER*(MAX_LEN_PLOTBUF) plotBuf
1039     CHARACTER*(MAX_LEN_MBUF) msgBuf
1040     INTEGER lChList
1041     PARAMETER ( lChList = 28 )
1042     CHARACTER*(lChList) chList
1043 cnh 1.13 _RL fMin
1044     _RL fMax
1045     _RL fRange
1046     _RL val
1047     _RL small
1048 cnh 1.1 CHARACTER*2 accLab
1049     CHARACTER*7 dwnLab
1050     CHARACTER*3 pltLab
1051     INTEGER accBase, dwnBase, pltBase
1052     INTEGER accStep, dwnStep, pltStep
1053     INTEGER accBlo, dwnBlo, pltBlo
1054     INTEGER accBhi, dwnBhi, pltBhi
1055     INTEGER accBstr, dwnBstr, pltBstr
1056     INTEGER accMin, dwnMin, pltMin
1057     INTEGER accMax, dwnMax, pltMax
1058     INTEGER accStr, dwnStr, pltStr
1059     INTEGER I, J, K, iStrngLo, iStrngHi, iBuf, iDx
1060     INTEGER bi, bj, bk
1061     LOGICAL validRange
1062 cnh 1.18 CEOP
1063 cnh 1.1
1064     chList = '-abcdefghijklmnopqrstuvwxyz+'
1065     small = 1. _d -15
1066     fMin = 1. _d 32
1067     fMax = -1. _d 32
1068     validRange = .FALSE.
1069    
1070     C-- Calculate field range
1071     DO bj=byMin, byMax, byStr
1072     DO bi=bxMin, bxMax, bxStr
1073     DO K=kMin, kMax, kStr
1074     DO J=jMin, jMax, jStr
1075     DO I=iMin, iMax, iStr
1076 cnh 1.12 IF ( printMapIncludesZeros .OR. fld(I,J,K,bi,bj) .NE. 0. )
1077     & THEN
1078 cnh 1.1 IF ( fld(I,J,K,bi,bj) .LT. fMin )
1079     & fMin = fld(I,J,K,bi,bj)
1080     IF ( fld(I,J,K,bi,bj) .GT. fMax )
1081     & fMax = fld(I,J,K,bi,bj)
1082 cnh 1.11 ENDIF
1083 cnh 1.1 ENDDO
1084     ENDDO
1085     ENDDO
1086     ENDDO
1087     ENDDO
1088     fRange = fMax-fMin
1089 dimitri 1.20 IF ( fRange .GT. small .AND.
1090     & (MAX_LEN_PLOTBUF-35) .GT. sNx*nSx .AND.
1091     & (MAX_LEN_PLOTBUF-35) .GT. sNy*nSy ) validRange = .TRUE.
1092 cnh 1.1
1093     C-- Write field title and statistics
1094 cnh 1.12 msgBuf =
1095     & '// ======================================================='
1096 cnh 1.1 CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
1097     & SQUEEZE_RIGHT, 1)
1098     iStrngLo = IFNBLNK(fldTitle)
1099     iStrngHi = ILNBLNK(fldTitle)
1100     IF ( iStrngLo .LE. iStrngHi ) THEN
1101     WRITE(msgBuf,'(A)') fldTitle(iStrngLo:iStrngHi)
1102     ELSE
1103     msgBuf = '// UNKNOWN FIELD'
1104     ENDIF
1105     CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
1106     & SQUEEZE_RIGHT, 1)
1107     WRITE(msgBuf,'(A,1PE30.15)')
1108     & '// CMIN = ', fMin
1109     CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
1110     & SQUEEZE_RIGHT, 1)
1111     WRITE(msgBuf,'(A,1PE30.15)')
1112     & '// CMAX = ', fMax
1113     CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
1114     & SQUEEZE_RIGHT, 1)
1115 cnh 1.11 IF ( validRange ) THEN
1116     WRITE(msgBuf,'(A,1PE30.15)')
1117 cnh 1.1 & '// CINT = ', fRange/FLOAT(lChlist-1)
1118 cnh 1.11 ELSE
1119     WRITE(msgBuf,'(A,1PE30.15)')
1120     & '// CINT = ', 0.
1121     ENDIF
1122 cnh 1.1 CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
1123     & SQUEEZE_RIGHT, 1)
1124     WRITE(msgBuf,'(A,1024A1)')
1125     & '// SYMBOLS (CMIN->CMAX): ',(chList(I:I),I=1,lChList)
1126     CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
1127     & SQUEEZE_RIGHT, 1)
1128     WRITE(msgBuf,'(A,1024A1)')
1129     & '// 0.0: ','.'
1130     CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
1131     & SQUEEZE_RIGHT, 1)
1132     WRITE(msgBuf,'(A,3(A,I4),A)')
1133     & '// RANGE I (Lo:Hi:Step):',
1134     & '(',myXGlobalLo-1+(bxMin-1)*sNx+iMin,
1135     & ':',myXGlobalLo-1+(bxMax-1)*sNx+iMax,
1136     & ':',iStr,')'
1137     CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
1138     & SQUEEZE_RIGHT, 1)
1139     WRITE(msgBuf,'(A,3(A,I4),A)')
1140     & '// RANGE J (Lo:Hi:Step):',
1141     & '(',myYGlobalLo-1+(byMin-1)*sNy+jMin,
1142     & ':',myYGlobalLo-1+(byMax-1)*sNy+jMax,
1143     & ':',jStr,')'
1144     CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
1145     & SQUEEZE_RIGHT, 1)
1146     WRITE(msgBuf,'(A,3(A,I4),A)')
1147     & '// RANGE K (Lo:Hi:Step):',
1148     & '(',kMin,
1149     & ':',kMax,
1150     & ':',kStr,')'
1151     CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
1152     & SQUEEZE_RIGHT, 1)
1153 cnh 1.12 msgBuf =
1154     & '// ======================================================='
1155 cnh 1.1 CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
1156     & SQUEEZE_RIGHT, 1)
1157 adcroft 1.22
1158     if (Nx.gt.MAX_LEN_PLOTBUF-20) THEN
1159     msgBuf =
1160     & 'Model domain too big to print to terminal - skipping I/O'
1161     CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
1162     & SQUEEZE_RIGHT, 1)
1163     RETURN
1164     endif
1165 cnh 1.1
1166     C-- Write field
1167     C Figure out slice type and set plotting parameters appropriately
1168     C acc = accross the page
1169     C dwn = down the page
1170     IF ( plotMode .EQ. PRINT_MAP_XY ) THEN
1171     C X across, Y down slice
1172     accLab = 'I='
1173     accBase = myXGlobalLo
1174     accStep = sNx
1175     accBlo = bxMin
1176     accBhi = bxMax
1177     accBStr = bxStr
1178     accMin = iMin
1179     accMax = iMax
1180     accStr = iStr
1181     dwnLab = '|--J--|'
1182     dwnBase = myYGlobalLo
1183     dwnStep = sNy
1184     dwnBlo = byMin
1185     dwnBhi = byMax
1186     dwnBStr = byStr
1187     dwnMin = jMin
1188     dwnMax = jMax
1189     dwnStr = jStr
1190     pltBlo = 1
1191     pltBhi = 1
1192     pltBstr = 1
1193     pltMin = kMin
1194     pltMax = kMax
1195     pltStr = kStr
1196     pltBase = 1
1197     pltStep = 1
1198     pltLab = 'K ='
1199     ELSEIF ( plotMode .EQ. PRINT_MAP_YZ ) THEN
1200     C Y across, Z down slice
1201     accLab = 'J='
1202     accBase = myYGlobalLo
1203     accStep = sNy
1204     accBlo = byMin
1205     accBhi = byMax
1206     accBStr = byStr
1207     accMin = jMin
1208     accMax = jMax
1209     accStr = jStr
1210     dwnLab = '|--K--|'
1211     dwnBase = 1
1212     dwnStep = 1
1213     dwnBlo = 1
1214     dwnBhi = 1
1215     dwnBStr = 1
1216     dwnMin = kMin
1217     dwnMax = kMax
1218     dwnStr = kStr
1219     pltBlo = bxMin
1220     pltBhi = bxMax
1221     pltBstr = bxStr
1222     pltMin = iMin
1223     pltMax = iMax
1224     pltStr = iStr
1225     pltBase = myXGlobalLo
1226     pltStep = sNx
1227     pltLab = 'I ='
1228     ELSEIF ( plotMode .EQ. PRINT_MAP_XZ ) THEN
1229     C X across, Z down slice
1230     accLab = 'I='
1231     accBase = myXGlobalLo
1232     accStep = sNx
1233     accBlo = bxMin
1234     accBhi = bxMax
1235     accBStr = bxStr
1236     accMin = iMin
1237     accMax = iMax
1238     accStr = iStr
1239     dwnLab = '|--K--|'
1240     dwnBase = 1
1241     dwnStep = 1
1242     dwnBlo = 1
1243     dwnBhi = 1
1244     dwnBStr = 1
1245     dwnMin = kMin
1246     dwnMax = kMax
1247     dwnStr = kStr
1248     pltBlo = byMin
1249     pltBhi = byMax
1250     pltBstr = byStr
1251     pltMin = jMin
1252     pltMax = jMax
1253     pltStr = jStr
1254     pltBase = myYGlobalLo
1255     pltStep = sNy
1256     pltLab = 'J ='
1257     ENDIF
1258 dimitri 1.20 IF ( validRange ) THEN
1259 cnh 1.1 C Header
1260     C Data
1261     DO bk=pltBlo, pltBhi, pltBstr
1262     DO K=pltMin,pltMax,pltStr
1263 cnh 1.12 WRITE(plotBuf,'(A,I4,I4,I4,I4)') pltLab,
1264 cnh 1.1 & pltBase-1+(bk-1)*pltStep+K
1265     CALL PRINT_MESSAGE(plotBuf, standardMessageUnit,
1266     & SQUEEZE_RIGHT, 1)
1267     plotBuf = ' '
1268     iBuf = 6
1269     DO bi=accBlo, accBhi, accBstr
1270     DO I=accMin, accMax, accStr
1271     iDx = accBase-1+(bi-1)*accStep+I
1272     iBuf = iBuf + 1
1273     IF ( 10*((iBuf-6)/10) .EQ. iBuf-6 ) THEN
1274     IF ( iDx. LT. 10 ) THEN
1275     WRITE(plotBuf(iBuf:),'(A,I1)') accLab,iDx
1276     ELSEIF ( iDx. LT. 100 ) THEN
1277     WRITE(plotBuf(iBuf:),'(A,I2)') accLab,iDx
1278     ELSEIF ( iDx. LT. 1000 ) THEN
1279     WRITE(plotBuf(iBuf:),'(A,I3)') accLab,iDx
1280     ELSEIF ( iDx. LT. 10000 ) THEN
1281     WRITE(plotBuf(iBuf:),'(A,I4)') accLab,iDx
1282     ENDIF
1283     ENDIF
1284     ENDDO
1285     ENDDO
1286     CALL PRINT_MESSAGE(plotBuf, standardMessageUnit,
1287     & SQUEEZE_RIGHT, 1)
1288     plotBuf = dwnLab
1289     iBuf = 7
1290     DO bi=accBlo, accBhi, accBstr
1291     DO I=accMin, accMax, accStr
1292     iDx = accBase-1+(bi-1)*accStep+I
1293     iBuf = iBuf+1
1294     IF ( 10*((iBuf-7)/10) .EQ. iBuf-7 ) THEN
1295     WRITE(plotBuf(iBuf:),'(A)') '|'
1296     ELSE
1297 jmc 1.26 WRITE(plotBuf(iBuf:iBuf),'(I1)') MOD(ABS(iDx),10)
1298 cnh 1.1 ENDIF
1299     ENDDO
1300     ENDDO
1301     CALL PRINT_MESSAGE(plotBuf, standardMessageUnit,
1302     & SQUEEZE_RIGHT, 1)
1303     DO bj=dwnBlo, dwnBhi, dwnBStr
1304     DO J=dwnMin, dwnMax, dwnStr
1305     WRITE(plotBuf,'(1X,I5,1X)')
1306     & dwnBase-1+(bj-1)*dwnStep+J
1307     iBuf = 7
1308     DO bi=accBlo,accBhi,accBstr
1309     DO I=accMin,accMax,accStr
1310     iBuf = iBuf + 1
1311     IF ( plotMode .EQ. PRINT_MAP_XY ) THEN
1312     val = fld(I,J,K,bi,bj)
1313     ELSEIF ( plotMode .EQ. PRINT_MAP_XZ ) THEN
1314     val = fld(I,K,J,bi,bk)
1315     ELSEIF ( plotMode .EQ. PRINT_MAP_YZ ) THEN
1316     val = fld(K,I,J,bk,bi)
1317     ENDIF
1318 cnh 1.13 IF ( validRange .AND. val .NE. 0. ) THEN
1319 cnh 1.11 IDX = NINT(
1320     & FLOAT( lChList-1 )*( val-fMin ) / (fRange)
1321     & )+1
1322     ELSE
1323     IDX = 1
1324     ENDIF
1325 cnh 1.1 IF ( iBuf .LE. MAX_LEN_PLOTBUF )
1326     & plotBuf(iBuf:iBuf) = chList(IDX:IDX)
1327     IF ( val .EQ. 0. ) THEN
1328     IF ( iBuf .LE. MAX_LEN_PLOTBUF )
1329     & plotBuf(iBuf:iBuf) = '.'
1330     ENDIF
1331     ENDDO
1332     ENDDO
1333     CALL PRINT_MESSAGE(plotBuf, standardMessageUnit,
1334     & SQUEEZE_RIGHT, 1)
1335     ENDDO
1336     ENDDO
1337     ENDDO
1338     ENDDO
1339 dimitri 1.20 ENDIF
1340 cnh 1.1 C-- Write delimiter
1341 cnh 1.12 msgBuf =
1342     & '// ======================================================='
1343 cnh 1.1 CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
1344     & SQUEEZE_RIGHT, 1)
1345 cnh 1.12 msgBuf =
1346     & '// END OF FIELD ='
1347 cnh 1.1 CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
1348     & SQUEEZE_RIGHT, 1)
1349 cnh 1.12 msgBuf =
1350     & '// ======================================================='
1351 cnh 1.1 CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
1352     & SQUEEZE_RIGHT, 1)
1353     msgBuf = ' '
1354     CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
1355     & SQUEEZE_RIGHT, 1)
1356    
1357     RETURN
1358     END
1359    
1360 cnh 1.18 CBOP
1361     C !ROUTINE: PRINT_MESSAGE
1362    
1363     C !INTERFACE:
1364 cnh 1.1 SUBROUTINE PRINT_MESSAGE( message, unit, sq , myThid )
1365 adcroft 1.14 IMPLICIT NONE
1366 cnh 1.18 C !DESCRIPTION:
1367     C *============================================================*
1368 edhill 1.23 C | SUBROUTINE PRINT\_MESSAGE
1369 cnh 1.18 C | o Write out informational message using "standard" format.
1370     C *============================================================*
1371     C | Notes
1372     C | =====
1373     C | o Some system I/O is not "thread-safe". For this reason
1374 edhill 1.23 C | without the FMTFTN\_IO\_THREAD\_SAFE directive set a
1375 cnh 1.18 C | critical region is defined around the write here. In some
1376 edhill 1.23 C | cases BEGIN\_CRIT() is approximated by only doing writes
1377 cnh 1.18 C | for thread number 1 - writes for other threads are
1378     C | ignored!
1379     C | o In a non-parallel form these routines can still be used.
1380     C | to produce pretty printed output!
1381     C *============================================================*
1382    
1383     C !USES:
1384 cnh 1.1 C == Global data ==
1385     #include "SIZE.h"
1386     #include "EEPARAMS.h"
1387     #include "EESUPPORT.h"
1388 cnh 1.18 INTEGER IFNBLNK
1389     EXTERNAL IFNBLNK
1390     INTEGER ILNBLNK
1391     EXTERNAL ILNBLNK
1392    
1393     C !INPUT/OUTPUT PARAMETERS:
1394 cnh 1.1 C == Routine arguments ==
1395 cnh 1.18 C message :: Message to write
1396     C unit :: Unit number to write to
1397     C sq :: Justification option
1398 cnh 1.1 CHARACTER*(*) message
1399     INTEGER unit
1400     CHARACTER*(*) sq
1401     INTEGER myThid
1402 cnh 1.18
1403     C !LOCAL VARIABLES:
1404 cnh 1.1 C == Local variables ==
1405 cnh 1.18 C iStart, iEnd :: String indexing variables
1406     C idString :: Temp. for building prefix.
1407 cnh 1.1 INTEGER iStart
1408     INTEGER iEnd
1409     CHARACTER*9 idString
1410 cnh 1.18 CEOP
1411    
1412 cnh 1.1 C-- Find beginning and end of message
1413     IF ( sq .EQ. SQUEEZE_BOTH .OR.
1414     & sq .EQ. SQUEEZE_LEFT ) THEN
1415     iStart = IFNBLNK( message )
1416     ELSE
1417     iStart = 1
1418     ENDIF
1419     IF ( sq .EQ. SQUEEZE_BOTH .OR.
1420     & sq .EQ. SQUEEZE_RIGHT ) THEN
1421     iEnd = ILNBLNK( message )
1422     ELSE
1423     iEnd = LEN(message)
1424     ENDIF
1425     C-- Test to see if in multi-process ( or multi-threaded ) mode.
1426     C If so include process or thread identifier.
1427     IF ( numberOfProcs .EQ. 0 .AND. nThreads .EQ. 1 ) THEN
1428     C-- Write single process format
1429     IF ( message .EQ. ' ' ) THEN
1430     WRITE(unit,'(A)') ' '
1431     ELSE
1432     WRITE(unit,'(A)') message(iStart:iEnd)
1433     ENDIF
1434     ELSEIF ( pidIO .EQ. myProcId ) THEN
1435     C-- Write multi-process format
1436     #ifndef FMTFTN_IO_THREAD_SAFE
1437     _BEGIN_CRIT(myThid)
1438     #endif
1439     WRITE(idString,'(I4.4,A,I4.4)') myProcId,'.',myThid
1440     #ifndef FMTFTN_IO_THREAD_SAFE
1441     _END_CRIT(myThid)
1442     #endif
1443     IF ( message .EQ. ' ' ) THEN
1444     C PRINT can be called by several threads simultaneously.
1445     C The write statement may need to ne marked as a critical section.
1446     #ifndef FMTFTN_IO_THREAD_SAFE
1447     _BEGIN_CRIT(myThid)
1448     #endif
1449 cnh 1.6 WRITE(unit,'(A,A,A,A,A,A)',ERR=999)
1450 cnh 1.1 & '(',PROCESS_HEADER,' ',idString,')',' '
1451     #ifndef FMTFTN_IO_THREAD_SAFE
1452     _END_CRIT(myThid)
1453     #endif
1454     ELSE
1455     #ifndef FMTFTN_IO_THREAD_SAFE
1456     _BEGIN_CRIT(myThid)
1457     #endif
1458 cnh 1.6 WRITE(unit,'(A,A,A,A,A,A,A)',ERR=999)
1459 cnh 1.1 & '(',PROCESS_HEADER,' ',idString(1:ILNBLNK(idString)),')',' ',
1460     & message(iStart:iEnd)
1461     #ifndef FMTFTN_IO_THREAD_SAFE
1462     _END_CRIT(myThid)
1463     #endif
1464     ENDIF
1465     ENDIF
1466 jmc 1.21
1467     #ifndef DISABLE_WRITE_TO_UNIT_ZERO
1468     C-- if error message, also write directly to unit 0 :
1469     IF ( numberOfProcs .EQ. 1 .AND. nThreads .EQ. 1
1470     & .AND. unit.EQ.errorMessageUnit ) THEN
1471     iEnd = ILNBLNK( message )
1472     IF (iEnd.NE.0) WRITE(0,'(A)') message(1:iEnd)
1473     ENDIF
1474     #endif
1475 cnh 1.1 C
1476 cnh 1.6 1000 CONTINUE
1477 cnh 1.1 RETURN
1478 cnh 1.6 999 CONTINUE
1479     ioErrorCount(myThid) = ioErrorCount(myThid)+1
1480     GOTO 1000
1481    
1482 cnh 1.1 END

  ViewVC Help
Powered by ViewVC 1.1.22