/[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.32 - (hide annotations) (download)
Tue Jul 6 23:12:51 2010 UTC (13 years, 11 months ago) by zhc
Branch: MAIN
CVS Tags: checkpoint62v, checkpoint62u, checkpoint62t, checkpoint62s, checkpoint62r, checkpoint62q, checkpoint62p, checkpoint62k, checkpoint62j, checkpoint62i, checkpoint62o, checkpoint62n, checkpoint62m, checkpoint62l, checkpoint62w, checkpoint62z, checkpoint62y, checkpoint62x, checkpoint63g, checkpoint63, checkpoint63h, checkpoint63i, checkpoint63j, checkpoint63k, checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63a, checkpoint63b, checkpoint63c
Changes since 1.31: +5 -5 lines
CS510 over I4 range (changed to I6)

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

  ViewVC Help
Powered by ViewVC 1.1.22