/[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.27 by jmc, Tue Mar 20 23:42:16 2007 UTC revision 1.28 by jmc, Wed Jul 25 21:05:37 2007 UTC
# Line 523  C     !INTERFACE: Line 523  C     !INTERFACE:
523       I       kMin, kMax,   kStr,       I       kMin, kMax,   kStr,
524       I      bxMin, bxMax,  bxStr,       I      bxMin, bxMax,  bxStr,
525       I      byMin, byMax,  byStr )       I      byMin, byMax,  byStr )
526        IMPLICIT NONE  
527  C     !DESCRIPTION:  C     !DESCRIPTION:
528  C     *==========================================================*  C     *==========================================================*
529  C     | SUBROUTINE PRINT\_MAPRS                                      C     | SUBROUTINE PRINT\_MAPRS
530  C     | o Does textual mapping printing of a field.                C     | o Does textual mapping printing of a field.
531  C     *==========================================================*  C     *==========================================================*
532  C     | This routine does the actual formatting of the data        C     | This routine does the actual formatting of the data
533  C     | and printing to a file. It assumes an array using the      C     | and printing to a file. It assumes an array using the
534  C     | MITgcm UV indexing scheme and base index variables.        C     | MITgcm UV indexing scheme and base index variables.
535  C     | User code should call an interface routine like            C     | User code should call an interface routine like
536  C     | PLOT\_FIELD\_XYRS( ... ) rather than this code directly.      C     | PLOT\_FIELD\_XYRS( ... ) rather than this code directly.
537  C     | Text plots can be oriented XY, YZ, XZ. An orientation      C     | Text plots can be oriented XY, YZ, XZ. An orientation
538  C     | is specficied through the "plotMode" argument. All the      C     | is specficied through the "plotMode" argument. All the
539  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
540  C     | same contour interval. The plot range (iMin,...,byStr)      C     | same contour interval. The plot range (iMin,...,byStr)
541  C     | can be three-dimensional. A separate plot is made for      C     | can be three-dimensional. A separate plot is made for
542  C     | each point in the plot range normal to the orientation.    C     | each point in the plot range normal to the orientation.
543  C     | e.g. if the orientation is XY (plotMode = PRINT\_MAP\_XY).    C     | e.g. if the orientation is XY (plotMode = PRINT\_MAP\_XY).
544  C     |      kMin =1, kMax = 5 and kStr = 2 will produce three XY  C     |      kMin =1, kMax = 5 and kStr = 2 will produce three XY
545  C     |      plots - one for K=1, one for K=3 and one for K=5.      C     |      plots - one for K=1, one for K=3 and one for K=5.
546  C     |      Each plot would have extents iMin:iMax step iStr      C     |      Each plot would have extents iMin:iMax step iStr
547  C     |      and jMin:jMax step jStr.                              C     |      and jMin:jMax step jStr.
548  C     *==========================================================*  C     *==========================================================*
549    
550  C     !USES:  C     !USES:
551          IMPLICIT NONE
552    
553  C     == Global variables ==  C     == Global variables ==
554  #include "SIZE.h"  #include "SIZE.h"
555  #include "EEPARAMS.h"  #include "EEPARAMS.h"
# Line 610  C               Min  - Start index withi Line 612  C               Min  - Start index withi
612  C               Max  - End index within block  C               Max  - End index within block
613  C               Str  - stride within block  C               Str  - stride within block
614        INTEGER MAX_LEN_PLOTBUF        INTEGER MAX_LEN_PLOTBUF
615        PARAMETER ( MAX_LEN_PLOTBUF = MAX_LEN_MBUF-4 )        PARAMETER ( MAX_LEN_PLOTBUF = MAX_LEN_MBUF-20 )
616        CHARACTER*(MAX_LEN_PLOTBUF) plotBuf        CHARACTER*(MAX_LEN_PLOTBUF) plotBuf
617        CHARACTER*(MAX_LEN_MBUF) msgBuf        CHARACTER*(MAX_LEN_MBUF) msgBuf
618        INTEGER lChList        INTEGER lChList
# Line 661  C--   Calculate field range Line 663  C--   Calculate field range
663         ENDDO         ENDDO
664        ENDDO        ENDDO
665        fRange = fMax-fMin        fRange = fMax-fMin
666        IF ( fRange .GT. small .AND.        IF ( fRange .GT. small ) validRange = .TRUE.
      &     (MAX_LEN_PLOTBUF-35) .GT. sNx*nSx .AND.  
      &     (MAX_LEN_PLOTBUF-35) .GT. sNy*nSy ) validRange = .TRUE.  
667    
668  C--   Write field title and statistics  C--   Write field title and statistics
669        msgBuf =        msgBuf =
# Line 730  C--   Write field title and statistics Line 730  C--   Write field title and statistics
730        CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,        CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
731       &                   SQUEEZE_RIGHT, 1)       &                   SQUEEZE_RIGHT, 1)
732    
733        if (Nx.gt.MAX_LEN_PLOTBUF-20) THEN  c     if (Nx.gt.MAX_LEN_PLOTBUF-20) THEN
734         msgBuf =  c      msgBuf =
735       &  'Model domain too big to print to terminal - skipping I/O'  c    &  'Model domain too big to print to terminal - skipping I/O'
736         CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,  c      CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
737       &                   SQUEEZE_RIGHT, 1)  c    &                   SQUEEZE_RIGHT, 1)
738         RETURN  c      RETURN
739        endif  c     endif
740    
741  C--   Write field  C--   Write field
742  C     Figure out slice type and set plotting parameters appropriately  C     Figure out slice type and set plotting parameters appropriately
# Line 830  C      X across, Z down slice Line 830  C      X across, Z down slice
830         pltStep = sNy         pltStep = sNy
831         pltLab  = 'J ='         pltLab  = 'J ='
832        ENDIF        ENDIF
833    C-    check if it fits into buffer (-10 should be enough but -12 is safer):
834          IF ( (accMax-accMin+1)*(accBhi-accBlo+1).GT.MAX_LEN_PLOTBUF-12
835         &     .AND. validRange ) THEN
836           msgBuf =
837         &  'Model domain too big to print to terminal - skipping I/O'
838           CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
839         &                   SQUEEZE_RIGHT, 1)
840           validRange = .FALSE.
841          ENDIF
842        IF ( validRange ) THEN        IF ( validRange ) THEN
843  C      Header  C      Header
844  C      Data  C      Data
# Line 946  C     !INTERFACE: Line 955  C     !INTERFACE:
955       I       kMin, kMax,   kStr,       I       kMin, kMax,   kStr,
956       I      bxMin, bxMax,  bxStr,       I      bxMin, bxMax,  bxStr,
957       I      byMin, byMax,  byStr )       I      byMin, byMax,  byStr )
       IMPLICIT NONE  
958    
959  C     !DESCRIPTION:  C     !DESCRIPTION:
960  C     *==========================================================*  C     *==========================================================*
961  C     | SUBROUTINE PRINT\_MAPRL                                      C     | SUBROUTINE PRINT\_MAPRL
962  C     | o Does textual mapping printing of a field.                C     | o Does textual mapping printing of a field.
963  C     *==========================================================*  C     *==========================================================*
964  C     | This routine does the actual formatting of the data        C     | This routine does the actual formatting of the data
965  C     | and printing to a file. It assumes an array using the      C     | and printing to a file. It assumes an array using the
966  C     | MITgcm UV indexing scheme and base index variables.        C     | MITgcm UV indexing scheme and base index variables.
967  C     | User code should call an interface routine like            C     | User code should call an interface routine like
968  C     | PLOT\_FIELD\_XYRL( ... ) rather than this code directly.      C     | PLOT\_FIELD\_XYRL( ... ) rather than this code directly.
969  C     | Text plots can be oriented XY, YZ, XZ. An orientation      C     | Text plots can be oriented XY, YZ, XZ. An orientation
970  C     | is specficied through the "plotMode" argument. All the      C     | is specficied through the "plotMode" argument. All the
971  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
972  C     | same contour interval. The plot range (iMin,...,byStr)      C     | same contour interval. The plot range (iMin,...,byStr)
973  C     | can be three-dimensional. A separate plot is made for      C     | can be three-dimensional. A separate plot is made for
974  C     | each point in the plot range normal to the orientation.    C     | each point in the plot range normal to the orientation.
975  C     | e.g. if the orientation is XY (plotMode = PRINT\_MAP\_XY).    C     | e.g. if the orientation is XY (plotMode = PRINT\_MAP\_XY).
976  C     |      kMin =1, kMax = 5 and kStr = 2 will produce three XY  C     |      kMin =1, kMax = 5 and kStr = 2 will produce three XY
977  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.
978  C     |      Each plot would have extents iMin:iMax step iStr      C     |      Each plot would have extents iMin:iMax step iStr
979  C     |      and jMin:jMax step jStr.                              C     |      and jMin:jMax step jStr.
980  C     *==========================================================*  C     *==========================================================*
981    
982  C     !USES:  C     !USES:
983          IMPLICIT NONE
984    
985  C     == Global variables ==  C     == Global variables ==
986  #include "SIZE.h"  #include "SIZE.h"
987  #include "EEPARAMS.h"  #include "EEPARAMS.h"
# Line 1034  C               Min  - Start index withi Line 1044  C               Min  - Start index withi
1044  C               Max  - End index within block  C               Max  - End index within block
1045  C               Str  - stride within block  C               Str  - stride within block
1046        INTEGER MAX_LEN_PLOTBUF        INTEGER MAX_LEN_PLOTBUF
1047        PARAMETER ( MAX_LEN_PLOTBUF = MAX_LEN_MBUF-4 )        PARAMETER ( MAX_LEN_PLOTBUF = MAX_LEN_MBUF-20 )
1048        CHARACTER*(MAX_LEN_PLOTBUF) plotBuf        CHARACTER*(MAX_LEN_PLOTBUF) plotBuf
1049        CHARACTER*(MAX_LEN_MBUF) msgBuf        CHARACTER*(MAX_LEN_MBUF) msgBuf
1050        INTEGER lChList        INTEGER lChList
# Line 1086  C--   Calculate field range Line 1096  C--   Calculate field range
1096         ENDDO         ENDDO
1097        ENDDO        ENDDO
1098        fRange = fMax-fMin        fRange = fMax-fMin
1099        IF ( fRange .GT. small .AND.        IF ( fRange .GT. small ) validRange = .TRUE.
      &     (MAX_LEN_PLOTBUF-35) .GT. sNx*nSx .AND.  
      &     (MAX_LEN_PLOTBUF-35) .GT. sNy*nSy ) validRange = .TRUE.  
1100    
1101  C--   Write field title and statistics  C--   Write field title and statistics
1102        msgBuf =        msgBuf =
# Line 1155  C--   Write field title and statistics Line 1163  C--   Write field title and statistics
1163        CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,        CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
1164       &                   SQUEEZE_RIGHT, 1)       &                   SQUEEZE_RIGHT, 1)
1165    
1166        if (Nx.gt.MAX_LEN_PLOTBUF-20) THEN  c     if (Nx.gt.MAX_LEN_PLOTBUF-20) THEN
1167         msgBuf =  c      msgBuf =
1168       &  'Model domain too big to print to terminal - skipping I/O'  c    &  'Model domain too big to print to terminal - skipping I/O'
1169         CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,  c      CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
1170       &                   SQUEEZE_RIGHT, 1)  c    &                   SQUEEZE_RIGHT, 1)
1171         RETURN  c      RETURN
1172        endif  c     endif
1173    
1174  C--   Write field  C--   Write field
1175  C     Figure out slice type and set plotting parameters appropriately  C     Figure out slice type and set plotting parameters appropriately
# Line 1255  C      X across, Z down slice Line 1263  C      X across, Z down slice
1263         pltStep = sNy         pltStep = sNy
1264         pltLab  = 'J ='         pltLab  = 'J ='
1265        ENDIF        ENDIF
1266    C-    check if it fits into buffer (-10 should be enough but -12 is safer):
1267          IF ( (accMax-accMin+1)*(accBhi-accBlo+1).GT.MAX_LEN_PLOTBUF-12
1268         &     .AND. validRange ) THEN
1269           msgBuf =
1270         &  'Model domain too big to print to terminal - skipping I/O'
1271           CALL PRINT_MESSAGE(msgBuf, standardMessageUnit,
1272         &                   SQUEEZE_RIGHT, 1)
1273           validRange = .FALSE.
1274          ENDIF
1275        IF ( validRange ) THEN        IF ( validRange ) THEN
1276  C      Header  C      Header
1277  C      Data  C      Data

Legend:
Removed from v.1.27  
changed lines
  Added in v.1.28

  ViewVC Help
Powered by ViewVC 1.1.22