/[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.29 - (hide annotations) (download)
Tue Apr 21 16:02:42 2009 UTC (15 years, 2 months ago) by jmc
Branch: MAIN
Changes since 1.28: +315 -288 lines
add argument to PRINT_LIST_* S/R for 1rst element to print

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

  ViewVC Help
Powered by ViewVC 1.1.22