/[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.34 - (hide annotations) (download)
Thu Oct 11 19:15:18 2012 UTC (11 years, 8 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint64a, checkpoint64c, checkpoint64b, checkpoint64d
Changes since 1.33: +8 -2 lines
- add S/R to flush IO unit (if intrinsic S/R flush is available)
- flush standard & error msg unit before MPI termination
- if debugMode, flush IO unit after printing msg

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

  ViewVC Help
Powered by ViewVC 1.1.22