/[MITgcm]/MITgcm/eesupp/src/print.F
ViewVC logotype

Diff of /MITgcm/eesupp/src/print.F

Parent Directory Parent Directory | Revision Log Revision Log | View Revision Graph Revision Graph | View Patch Patch

revision 1.19 by adcroft, Fri Sep 21 14:31:12 2001 UTC revision 1.23 by edhill, Sat Mar 27 03:51:51 2004 UTC
# Line 29  C     !INTERFACE: Line 29  C     !INTERFACE:
29    
30  C     !DESCRIPTION:  C     !DESCRIPTION:
31  C     *============================================================*  C     *============================================================*
32  C     | SUBROUTINE PRINT_ERROR                                        C     | SUBROUTINE PRINT\_ERROR                                      
33  C     | o Write out error message using "standard" format.            C     | o Write out error message using "standard" format.          
34  C     *============================================================*  C     *============================================================*
35  C     | Notes                                                        C     | Notes                                                      
36  C     | =====                                                        C     | =====                                                      
37  C     | o Some system   I/O is not "thread-safe". For this reason    C     | o Some system   I/O is not "thread-safe". For this reason  
38  C     |   without the FMTFTN_IO_THREAD_SAFE directive set a          C     |   without the FMTFTN\_IO\_THREAD\_SAFE directive set a        
39  C     |   critical region is defined around the write here. In some  C     |   critical region is defined around the write here. In some
40  C     |   cases  BEGIN_CRIT() is approximated by only doing writes    C     |   cases  BEGIN\_CRIT() is approximated by only doing writes  
41  C     |   for thread number 1 - writes for other threads are          C     |   for thread number 1 - writes for other threads are        
42  C     |   ignored!                                                    C     |   ignored!                                                  
43  C     | o In a non-parallel form these routines are still used    C     | o In a non-parallel form these routines are still used  
# Line 117  C       The write statement may need to Line 117  C       The write statement may need to
117  #endif  #endif
118         ENDIF         ENDIF
119        ENDIF        ENDIF
120  C  
121    #ifndef DISABLE_WRITE_TO_UNIT_ZERO
122    C--   also write directly to unit 0 :
123          IF ( numberOfProcs .EQ. 1 .AND. nThreads .EQ. 1 ) THEN
124            IF (iEnd.NE.0) WRITE(0,'(A)') message(1:iEnd)
125          ENDIF
126    #endif
127    
128   1000 CONTINUE   1000 CONTINUE
129        RETURN        RETURN
130    
# Line 135  C     !INTERFACE: Line 142  C     !INTERFACE:
142        IMPLICIT NONE        IMPLICIT NONE
143  C     !DESCRIPTION:  C     !DESCRIPTION:
144  C     *==========================================================*  C     *==========================================================*
145  C     | o SUBROUTINE PRINT_LIST_I                                  C     | o SUBROUTINE PRINT\_LIST\_I                                
146  C     *==========================================================*  C     *==========================================================*
147  C     | Routine for producing list of values for a field with      C     | Routine for producing list of values for a field with    
148  C     | duplicate values collected into                            C     | duplicate values collected into                          
149  C     |    n @ value                                                C     |    n \@ value                                              
150  C     | record.                                                    C     | record.                                                  
151  C     *==========================================================*  C     *==========================================================*
152    
# Line 256  C     !INTERFACE: Line 263  C     !INTERFACE:
263        IMPLICIT NONE        IMPLICIT NONE
264  C     !DESCRIPTION:  C     !DESCRIPTION:
265  C     *==========================================================*  C     *==========================================================*
266  C     | o SUBROUTINE PRINT_LIST_L                                  C     | o SUBROUTINE PRINT\_LIST\_L                                
267  C     *==========================================================*  C     *==========================================================*
268  C     | Routine for producing list of values for a field with      C     | Routine for producing list of values for a field with    
269  C     | duplicate values collected into                            C     | duplicate values collected into                          
270  C     |    n @ value                                                C     |    n \@ value                                              
271  C     | record.                                                    C     | record.                                                  
272  C     *==========================================================*  C     *==========================================================*
273    
# Line 376  C     !INTERFACE: Line 383  C     !INTERFACE:
383        IMPLICIT NONE        IMPLICIT NONE
384  C     !DESCRIPTION:  C     !DESCRIPTION:
385  C     *==========================================================*  C     *==========================================================*
386  C     | o SUBROUTINE PRINT_LIST_R8                                  C     | o SUBROUTINE PRINT\_LIST\_R8                                
387  C     *==========================================================*  C     *==========================================================*
388  C     | Routine for producing list of values for a field with      C     | Routine for producing list of values for a field with    
389  C     | duplicate values collected into                            C     | duplicate values collected into                          
390  C     |    n @ value                                                C     |    n \@ value                                              
391  C     | record.                                                    C     | record.                                                  
392  C     *==========================================================*  C     *==========================================================*
393    
# Line 503  C     !INTERFACE: Line 510  C     !INTERFACE:
510        IMPLICIT NONE        IMPLICIT NONE
511  C     !DESCRIPTION:  C     !DESCRIPTION:
512  C     *==========================================================*  C     *==========================================================*
513  C     | SUBROUTINE PRINT_MAPR4                                      C     | SUBROUTINE PRINT\_MAPR4                                    
514  C     | o Does textual mapping printing of a field.                C     | o Does textual mapping printing of a field.              
515  C     *==========================================================*  C     *==========================================================*
516  C     | This routine does the actual formatting of the data        C     | This routine does the actual formatting of the data      
517  C     | and printing to a file. It assumes an array using the      C     | and printing to a file. It assumes an array using the    
518  C     | MITgcm UV indexing scheme and base index variables.        C     | MITgcm UV indexing scheme and base index variables.      
519  C     | User code should call an interface routine like            C     | User code should call an interface routine like          
520  C     | PLOT_FIELD_XYR4( ... ) rather than this code directly.      C     | PLOT\_FIELD\_XYR4( ... ) rather than this code directly.    
521  C     | Text plots can be oriented XY, YZ, XZ. An orientation      C     | Text plots can be oriented XY, YZ, XZ. An orientation    
522  C     | is specficied through the "plotMode" argument. All the      C     | is specficied through the "plotMode" argument. All the    
523  C     | plots made by a single call to this routine will use the    C     | plots made by a single call to this routine will use the  
524  C     | same contour interval. The plot range (iMin,...,byStr)      C     | same contour interval. The plot range (iMin,...,byStr)    
525  C     | can be three-dimensional. A separate plot is made for      C     | can be three-dimensional. A separate plot is made for    
526  C     | each point in the plot range normal to the orientation.    C     | each point in the plot range normal to the orientation.  
527  C     | e.g. if the orientation is XY (plotMode = PRINT_MAP_XY).    C     | e.g. if the orientation is XY (plotMode = PRINT\_MAP\_XY).  
528  C     |      kMin =1, kMax = 5 and kStr = 2 will produce three XY  C     |      kMin =1, kMax = 5 and kStr = 2 will produce three XY
529  C     |      plots - one for K=1, one for K=3 and one for K=5.      C     |      plots - one for K=1, one for K=3 and one for K=5.    
530  C     |      Each plot would have extents iMin:iMax step iStr      C     |      Each plot would have extents iMin:iMax step iStr    
# Line 638  C--   Calculate field range Line 645  C--   Calculate field range
645         ENDDO         ENDDO
646        ENDDO        ENDDO
647        fRange = fMax-fMin        fRange = fMax-fMin
648        IF ( fRange .GT. small ) THEN        IF ( fRange .GT. small .AND.
649         validRange = .TRUE.       &     (MAX_LEN_PLOTBUF-35) .GT. sNx*nSx .AND.
650        ENDIF       &     (MAX_LEN_PLOTBUF-35) .GT. sNy*nSy ) validRange = .TRUE.
651    
652  C--   Write field title and statistics  C--   Write field title and statistics
653        msgBuf =        msgBuf =
# Line 707  C--   Write field title and statistics Line 714  C--   Write field title and statistics
714        CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,        CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
715       &                   SQUEEZE_RIGHT, 1)       &                   SQUEEZE_RIGHT, 1)
716    
717          if (Nx.gt.MAX_LEN_PLOTBUF-20) THEN
718           msgBuf =
719         &  'Model domain too big to print to terminal - skipping I/O'
720           CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
721         &                   SQUEEZE_RIGHT, 1)
722           RETURN
723          endif
724    
725  C--   Write field  C--   Write field
726  C     Figure out slice type and set plotting parameters appropriately  C     Figure out slice type and set plotting parameters appropriately
727  C     acc = accross the page  C     acc = accross the page
# Line 799  C      X across, Z down slice Line 814  C      X across, Z down slice
814         pltStep = sNy         pltStep = sNy
815         pltLab  = 'J ='         pltLab  = 'J ='
816        ENDIF        ENDIF
817  C     IF ( validRange ) THEN        IF ( validRange ) THEN
818  C      Header  C      Header
819  C      Data  C      Data
820         DO bk=pltBlo, pltBhi, pltBstr         DO bk=pltBlo, pltBhi, pltBstr
# Line 883  C      Data Line 898  C      Data
898           ENDDO           ENDDO
899          ENDDO          ENDDO
900         ENDDO         ENDDO
901  C     ENDIF        ENDIF
902  C--   Write delimiter  C--   Write delimiter
903        msgBuf =        msgBuf =
904       & '// ======================================================='       & '// ======================================================='
# Line 919  C     !INTERFACE: Line 934  C     !INTERFACE:
934    
935  C     !DESCRIPTION:  C     !DESCRIPTION:
936  C     *==========================================================*  C     *==========================================================*
937  C     | SUBROUTINE PRINT_MAPRL                                      C     | SUBROUTINE PRINT\_MAPRL                                    
938  C     | o Does textual mapping printing of a field.                C     | o Does textual mapping printing of a field.              
939  C     *==========================================================*  C     *==========================================================*
940  C     | This routine does the actual formatting of the data        C     | This routine does the actual formatting of the data      
941  C     | and printing to a file. It assumes an array using the      C     | and printing to a file. It assumes an array using the    
942  C     | MITgcm UV indexing scheme and base index variables.        C     | MITgcm UV indexing scheme and base index variables.      
943  C     | User code should call an interface routine like            C     | User code should call an interface routine like          
944  C     | PLOT_FIELD_XYR8( ... ) rather than this code directly.      C     | PLOT\_FIELD\_XYR8( ... ) rather than this code directly.    
945  C     | Text plots can be oriented XY, YZ, XZ. An orientation      C     | Text plots can be oriented XY, YZ, XZ. An orientation    
946  C     | is specficied through the "plotMode" argument. All the      C     | is specficied through the "plotMode" argument. All the    
947  C     | plots made by a single call to this routine will use the    C     | plots made by a single call to this routine will use the  
948  C     | same contour interval. The plot range (iMin,...,byStr)      C     | same contour interval. The plot range (iMin,...,byStr)    
949  C     | can be three-dimensional. A separate plot is made for      C     | can be three-dimensional. A separate plot is made for    
950  C     | each point in the plot range normal to the orientation.    C     | each point in the plot range normal to the orientation.  
951  C     | e.g. if the orientation is XY (plotMode = PRINT_MAP_XY).    C     | e.g. if the orientation is XY (plotMode = PRINT\_MAP\_XY).  
952  C     |      kMin =1, kMax = 5 and kStr = 2 will produce three XY  C     |      kMin =1, kMax = 5 and kStr = 2 will produce three XY
953  C     |      plots - one for K=1, one for K=3 and one for K=5.      C     |      plots - one for K=1, one for K=3 and one for K=5.    
954  C     |      Each plot would have extents iMin:iMax step iStr      C     |      Each plot would have extents iMin:iMax step iStr    
# Line 1055  C--   Calculate field range Line 1070  C--   Calculate field range
1070         ENDDO         ENDDO
1071        ENDDO        ENDDO
1072        fRange = fMax-fMin        fRange = fMax-fMin
1073        IF ( fRange .GT. small ) THEN        IF ( fRange .GT. small .AND.
1074         validRange = .TRUE.       &     (MAX_LEN_PLOTBUF-35) .GT. sNx*nSx .AND.
1075        ENDIF       &     (MAX_LEN_PLOTBUF-35) .GT. sNy*nSy ) validRange = .TRUE.
1076    
1077  C--   Write field title and statistics  C--   Write field title and statistics
1078        msgBuf =        msgBuf =
# Line 1124  C--   Write field title and statistics Line 1139  C--   Write field title and statistics
1139        CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,        CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
1140       &                   SQUEEZE_RIGHT, 1)       &                   SQUEEZE_RIGHT, 1)
1141    
1142          if (Nx.gt.MAX_LEN_PLOTBUF-20) THEN
1143           msgBuf =
1144         &  'Model domain too big to print to terminal - skipping I/O'
1145           CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
1146         &                   SQUEEZE_RIGHT, 1)
1147           RETURN
1148          endif
1149    
1150  C--   Write field  C--   Write field
1151  C     Figure out slice type and set plotting parameters appropriately  C     Figure out slice type and set plotting parameters appropriately
1152  C     acc = accross the page  C     acc = accross the page
# Line 1216  C      X across, Z down slice Line 1239  C      X across, Z down slice
1239         pltStep = sNy         pltStep = sNy
1240         pltLab  = 'J ='         pltLab  = 'J ='
1241        ENDIF        ENDIF
1242  C     IF ( validRange ) THEN        IF ( validRange ) THEN
1243  C      Header  C      Header
1244  C      Data  C      Data
1245         DO bk=pltBlo, pltBhi, pltBstr         DO bk=pltBlo, pltBhi, pltBstr
# Line 1297  C      Data Line 1320  C      Data
1320           ENDDO           ENDDO
1321          ENDDO          ENDDO
1322         ENDDO         ENDDO
1323  C     ENDIF        ENDIF
1324  C--   Write delimiter  C--   Write delimiter
1325        msgBuf =        msgBuf =
1326       & '// ======================================================='       & '// ======================================================='
# Line 1326  C     !INTERFACE: Line 1349  C     !INTERFACE:
1349        IMPLICIT NONE        IMPLICIT NONE
1350  C     !DESCRIPTION:  C     !DESCRIPTION:
1351  C     *============================================================*  C     *============================================================*
1352  C     | SUBROUTINE PRINT_MESSAGE                                      C     | SUBROUTINE PRINT\_MESSAGE                                    
1353  C     | o Write out informational message using "standard" format.    C     | o Write out informational message using "standard" format.  
1354  C     *============================================================*  C     *============================================================*
1355  C     | Notes                                                        C     | Notes                                                      
1356  C     | =====                                                        C     | =====                                                      
1357  C     | o Some system   I/O is not "thread-safe". For this reason    C     | o Some system   I/O is not "thread-safe". For this reason  
1358  C     |   without the FMTFTN_IO_THREAD_SAFE directive set a          C     |   without the FMTFTN\_IO\_THREAD\_SAFE directive set a        
1359  C     |   critical region is defined around the write here. In some  C     |   critical region is defined around the write here. In some
1360  C     |   cases  BEGIN_CRIT() is approximated by only doing writes    C     |   cases  BEGIN\_CRIT() is approximated by only doing writes  
1361  C     |   for thread number 1 - writes for other threads are          C     |   for thread number 1 - writes for other threads are        
1362  C     |   ignored!                                                    C     |   ignored!                                                  
1363  C     | o In a non-parallel form these routines can still be used.    C     | o In a non-parallel form these routines can still be used.  
# Line 1424  C       The write statement may need to Line 1447  C       The write statement may need to
1447  #endif  #endif
1448         ENDIF         ENDIF
1449        ENDIF        ENDIF
1450    
1451    #ifndef DISABLE_WRITE_TO_UNIT_ZERO
1452    C--   if error message, also write directly to unit 0 :
1453          IF ( numberOfProcs .EQ. 1 .AND. nThreads .EQ. 1
1454         &     .AND. unit.EQ.errorMessageUnit ) THEN
1455            iEnd   = ILNBLNK( message )
1456            IF (iEnd.NE.0) WRITE(0,'(A)') message(1:iEnd)
1457          ENDIF
1458    #endif
1459  C  C
1460   1000 CONTINUE   1000 CONTINUE
1461        RETURN        RETURN

Legend:
Removed from v.1.19  
changed lines
  Added in v.1.23

  ViewVC Help
Powered by ViewVC 1.1.22