/[MITgcm]/MITgcm/model/src/plot_field.F
ViewVC logotype

Diff of /MITgcm/model/src/plot_field.F

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

revision 1.4 by cnh, Fri Jun 12 19:33:34 1998 UTC revision 1.12 by jmc, Tue Mar 6 17:10:29 2001 UTC
# Line 1  Line 1 
1  C $Header$  C $Header$
2    C $Name$
3    
4  #include "CPP_EEOPTIONS.h"  #include "CPP_OPTIONS.h"
5    
6  C--   File plot_field.F: Routines for "formatted" I/O in the MITgcm UV  C--   File plot_field.F: Routines for "formatted" I/O in the MITgcm UV
7  C--                      implementation.  C--                      implementation.
8  C--    Contents  C--    Contents
9  C--    o plot_field_xyr4  - Writes a XY  Real*4 field  C--    o plot_field_xyrs  - Writes a XY  _RS field
10  C--    o plot_field_xyr8  - Writes a XY  Real*8 field  C--    o plot_field_xyrl  - Writes a XY  _RL field
11  C--    o plot_field_xyzr4 - Writes a XYZ Real*4 field  C--    o plot_field_xyzrs - Writes a XYZ _RS field
12  C--    o plot_field_xyzr8 - Writes a XYZ Real*8 field  C--    o plot_field_xyzrl - Writes a XYZ _RL field
13        SUBROUTINE PLOT_FIELD_XYR4(        SUBROUTINE PLOT_FIELD_XYRS(
14       I                            fld, fldNam , myIter, myThid )       I                            fld, fldNam , myIter, myThid )
15    
16  C     /==========================================================\  C     /==========================================================\
17  C     | SUBROUTINE PLOT_FIELD_XYR4                               |  C     | SUBROUTINE PLOT_FIELD_XYRS                               |
18  C     | Print out an XY Real 4 field using text map.             |  C     | Print out an XY _RS field using text map.                |
19  C     |==========================================================|  C     |==========================================================|
20  C     | This routine references "numerical model" parameters like|  C     | This routine references "numerical model" parameters like|
21  C     | like the integration time. It uses these to create a     |  C     | like the integration time. It uses these to create a     |
# Line 24  C     | This routine can also be edited Line 25  C     | This routine can also be edited
25  C     | of a field to be printed by default, or every other      |  C     | of a field to be printed by default, or every other      |
26  C     | point etc..                                              |  C     | point etc..                                              |
27  C     | Other plot formats can also be substituted here.         |  C     | Other plot formats can also be substituted here.         |
28    C     | _RS is usually REAL*4                                    |
29  C     \==========================================================/  C     \==========================================================/
30          IMPLICIT NONE
31    
32  #include "SIZE.h"  #include "SIZE.h"
33  #include "EEPARAMS.h"  #include "EEPARAMS.h"
34  #include "PARAMS.h"  #include "PARAMS.h"
 #include "CG2D.h"  
35    
36  C     == Routine arguments ==  C     == Routine arguments ==
37  C     fld - Field to plot  C     fld - Field to plot
38  C     fldNam - Name of field  C     fldNam - Name of field
39  C     myIter - Iteration number for plot  C     myIter - Iteration number for plot
40  C     myThid - Thread id of thread instance calling plot_field  C     myThid - Thread id of thread instance calling plot_field
41        Real*4 fld(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)        _RS fld(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
42        CHARACTER*(*) fldNam        CHARACTER*(*) fldNam
43        INTEGER myThid        INTEGER myThid
44        INTEGER myIter        INTEGER myIter
# Line 50  C     == Local variables == Line 53  C     == Local variables ==
53    
54  C--   To get around synchronisation and multi-threaded I/O issues  C--   To get around synchronisation and multi-threaded I/O issues
55  C--   thread 1 will do all the writes.  C--   thread 1 will do all the writes.
56          _BARRIER
57        IF ( myThid .EQ. 1 ) THEN        IF ( myThid .EQ. 1 ) THEN
58  C--    Form name for identifying "plot"  C--    Form name for identifying "plot"
59         IF ( myIter .GE. 0 ) THEN         IF ( myIter .GE. 0 ) THEN
60          WRITE(fldTitle,'(A,A,A,I10)') '// Field ', fldNam, ' at iteration ',          WRITE(fldTitle,'(A,A,A,I10)')
61         &  '// Field ', fldNam, ' at iteration ',
62       &  myIter       &  myIter
63         ELSE         ELSE
64          WRITE(fldTitle,'(A,A)') '// Field ', fldNam          WRITE(fldTitle,'(A,A)') '// Field ', fldNam
# Line 75  C      Substitute other plotting utiliti Line 80  C      Substitute other plotting utiliti
80         bjStart  =  nSy         bjStart  =  nSy
81         bjEnd    =  1             bjEnd    =  1    
82         bjStride = -1         bjStride = -1
83         CALL PRINT_MAPR4(         CALL PRINT_MAPRS(
84       I        fld, fldTitle, PRINT_MAP_XY,       I        fld, fldTitle, PRINT_MAP_XY,
85       I         1-OLx,sNx+OLx,1-OLy,sNy+OLy,1,1,  nSx,  nSy,       I         1-OLx,sNx+OLx,1-OLy,sNy+OLy,1,1,  nSx,  nSy,
86       I         iStart,   iEnd,  iStride,       I         iStart,   iEnd,  iStride,
# Line 84  C      Substitute other plotting utiliti Line 89  C      Substitute other plotting utiliti
89       I        biStart,  biEnd, biStride,       I        biStart,  biEnd, biStride,
90       I        bjStart,  bjEnd, bjStride )       I        bjStart,  bjEnd, bjStride )
91        ENDIF        ENDIF
92          _BARRIER
93    
94        RETURN        RETURN
95        END        END
96        SUBROUTINE PLOT_FIELD_XYR8(        SUBROUTINE PLOT_FIELD_XYRL(
97       I                            fld, fldNam , myIter, myThid )       I                            fld, fldNam , myIter, myThid )
98    
99  C     /==========================================================\  C     /==========================================================\
100  C     | SUBROUTINE PLOT_FIELD_XYR8                               |  C     | SUBROUTINE PLOT_FIELD_XYRL                               |
101  C     | Print out an XY Real 8 field using text map.             |  C     | Print out an XY _RL field using text map.                |
102  C     |==========================================================|  C     |==========================================================|
103  C     | This routine references "numerical model" parameters like|  C     | This routine references "numerical model" parameters like|
104  C     | like the integration time. It uses these to create a     |  C     | like the integration time. It uses these to create a     |
# Line 102  C     | This routine can also be edited Line 108  C     | This routine can also be edited
108  C     | of a field to be printed by default, or every other      |  C     | of a field to be printed by default, or every other      |
109  C     | point etc..                                              |  C     | point etc..                                              |
110  C     | Other plot formats can also be substituted here.         |  C     | Other plot formats can also be substituted here.         |
111    C     | _RL is usually REAL*8                                    |
112  C     \==========================================================/  C     \==========================================================/
113          IMPLICIT NONE
114    
115  #include "SIZE.h"  #include "SIZE.h"
116  #include "EEPARAMS.h"  #include "EEPARAMS.h"
117  #include "PARAMS.h"  #include "PARAMS.h"
 #include "CG2D.h"  
118    
119  C     == Routine arguments ==  C     == Routine arguments ==
120  C     fld - Field to plot  C     fld - Field to plot
121  C     fldNam - Name of field  C     fldNam - Name of field
122  C     myIter - Iteration number for plot  C     myIter - Iteration number for plot
123  C     myThid - Thread id of thread instance calling plot_field  C     myThid - Thread id of thread instance calling plot_field
124        REAL fld(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)        _RL fld(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
125        CHARACTER*(*) fldNam        CHARACTER*(*) fldNam
126        INTEGER myThid        INTEGER myThid
127        INTEGER myIter        INTEGER myIter
# Line 128  C     == Local variables == Line 136  C     == Local variables ==
136    
137  C--   To get around synchronisation and multi-threaded I/O issues  C--   To get around synchronisation and multi-threaded I/O issues
138  C--   thread 1 will do all the writes.  C--   thread 1 will do all the writes.
139          _BARRIER
140        IF ( myThid .EQ. 1 ) THEN        IF ( myThid .EQ. 1 ) THEN
141  C--    Form name for identifying "plot"  C--    Form name for identifying "plot"
142         IF ( myIter .GE. 0 ) THEN         IF ( myIter .GE. 0 ) THEN
143          WRITE(fldTitle,'(A,A,A,I10)') '// Field ', fldNam, ' at iteration ',          WRITE(fldTitle,'(A,A,A,I10)')
144         &  '// Field ', fldNam, ' at iteration ',
145       &  myIter       &  myIter
146         ELSE         ELSE
147          WRITE(fldTitle,'(A,A)') '// Field ', fldNam          WRITE(fldTitle,'(A,A)') '// Field ', fldNam
# Line 153  C      Substitute other plotting utiliti Line 163  C      Substitute other plotting utiliti
163         bjStart  =  nSy         bjStart  =  nSy
164         bjEnd    =  1             bjEnd    =  1    
165         bjStride = -1         bjStride = -1
166         CALL PRINT_MAPR8(         CALL PRINT_MAPRL(
167       I        fld, fldTitle, PRINT_MAP_XY,       I        fld, fldTitle, PRINT_MAP_XY,
168       I         1-OLx,sNx+OLx,1-OLy,sNy+OLy,1,1,  nSx,  nSy,       I         1-OLx,sNx+OLx,1-OLy,sNy+OLy,1,1,  nSx,  nSy,
169       I         iStart,   iEnd,  iStride,       I         iStart,   iEnd,  iStride,
# Line 162  C      Substitute other plotting utiliti Line 172  C      Substitute other plotting utiliti
172       I        biStart,  biEnd, biStride,       I        biStart,  biEnd, biStride,
173       I        bjStart,  bjEnd, bjStride )       I        bjStart,  bjEnd, bjStride )
174        ENDIF        ENDIF
175          _BARRIER
176    
177        RETURN        RETURN
178        END        END
179        SUBROUTINE PLOT_FIELD_XYZR4(        SUBROUTINE PLOT_FIELD_XYZRS(
180       I                            fld, fldNam , fldNz, myIter, myThid )       I                            fld, fldNam , fldNz, myIter, myThid )
181    
182  C     /==========================================================\  C     /==========================================================\
183  C     | SUBROUTINE PLOT_FIELD_XYZR4                              |  C     | SUBROUTINE PLOT_FIELD_XYZR4                              |
184  C     | Print out an XYZ Real 4 field using text map.            |  C     | Print out an XYZ _RS field using text map.               |
185  C     |==========================================================|  C     |==========================================================|
186  C     | This routine references "numerical model" parameters like|  C     | This routine references "numerical model" parameters like|
187  C     | like the integration time. It uses these to create a     |  C     | like the integration time. It uses these to create a     |
# Line 180  C     | This routine can also be edited Line 191  C     | This routine can also be edited
191  C     | of a field to be printed by default, or every other      |  C     | of a field to be printed by default, or every other      |
192  C     | point etc..                                              |  C     | point etc..                                              |
193  C     | Other plot formats can also be substituted here.         |  C     | Other plot formats can also be substituted here.         |
194    C     | _RS is usually a REAL*4 field                            |
195  C     \==========================================================/  C     \==========================================================/
196          IMPLICIT NONE
197    
198  #include "SIZE.h"  #include "SIZE.h"
199  #include "EEPARAMS.h"  #include "EEPARAMS.h"
200  #include "PARAMS.h"  #include "PARAMS.h"
 #include "CG2D.h"  
201    
202  C     == Routine arguments ==  C     == Routine arguments ==
203  C     fld - Field to plot  C     fld - Field to plot
# Line 196  C              (same lateral extents. Line 209  C              (same lateral extents.
209  C     myIter - Iteration number for plot  C     myIter - Iteration number for plot
210  C     myThid - Thread id of thread instance calling plot_field  C     myThid - Thread id of thread instance calling plot_field
211        INTEGER fldNz        INTEGER fldNz
212        Real*4 fld(1-OLx:sNx+OLx,1-OLy:sNy+OLy,1:fldNz,nSx,nSy)        _RS fld(1-OLx:sNx+OLx,1-OLy:sNy+OLy,1:fldNz,nSx,nSy)
213        CHARACTER*(*) fldNam        CHARACTER*(*) fldNam
214        INTEGER myThid        INTEGER myThid
215        INTEGER myIter        INTEGER myIter
# Line 211  C     == Local variables == Line 224  C     == Local variables ==
224    
225  C--   To get around synchronisation and multi-threaded I/O issues  C--   To get around synchronisation and multi-threaded I/O issues
226  C--   thread 1 will do all the writes.  C--   thread 1 will do all the writes.
227          _BARRIER
228        IF ( myThid .EQ. 1 ) THEN        IF ( myThid .EQ. 1 ) THEN
229  C--    Form name for identifying "plot"  C--    Form name for identifying "plot"
230         IF ( myIter .GE. 0 ) THEN         IF ( myIter .GE. 0 ) THEN
231          WRITE(fldTitle,'(A,A,A,I10)') '// Field ', fldNam, ' at iteration ',          WRITE(fldTitle,'(A,A,A,I10)')
232         &  '// Field ', fldNam, ' at iteration ',
233       &  myIter       &  myIter
234         ELSE         ELSE
235          WRITE(fldTitle,'(A,A)') '// Field ', fldNam          WRITE(fldTitle,'(A,A)') '// Field ', fldNam
# Line 232  C      jStart   =  sNy Line 247  C      jStart   =  sNy
247  C      jEnd     =  1  C      jEnd     =  1
248         jStride  = -1         jStride  = -1
249         kStart   =  1         kStart   =  1
250         kEnd     =  fldNz  C      kEnd     =  fldNz
251  C      kEnd     =  1         kEnd     =  1
252         kStride  =  1         kStride  =  1
253         biStart  =  1         biStart  =  1
254         biEnd    =  nSx         biEnd    =  nSx
# Line 241  C      kEnd     =  1 Line 256  C      kEnd     =  1
256         bjStart  =  nSy         bjStart  =  nSy
257         bjEnd    =  1             bjEnd    =  1    
258         bjStride = -1         bjStride = -1
259  C      CALL PRINT_MAPR8(         CALL PRINT_MAPRS(
 C    I        fld, fldTitle, PRINT_MAP_YZ,  
 C    I         1-OLx,sNx+OLx,1-OLy,sNy+OLy,1,fldNz,  nSx,  nSy,  
 C    I         iStart,   iEnd,  iStride,  
 C    I         jStart,   jEnd,  jStride,  
 C    I         kStart,   kEnd,  kStride,  
 C    I        biStart,  biEnd, biStride,  
 C    I        bjStart,  bjEnd, bjStride )  
        CALL PRINT_MAPR4(  
260       I        fld, fldTitle, PRINT_MAP_XY,       I        fld, fldTitle, PRINT_MAP_XY,
261       I         1-OLx,sNx+OLx,1-OLy,sNy+OLy,1,fldNz,  nSx,  nSy,       I         1-OLx,sNx+OLx,1-OLy,sNy+OLy,1,fldNz,  nSx,  nSy,
262       I         iStart,   iEnd,  iStride,       I         iStart,   iEnd,  iStride,
# Line 258  C    I        bjStart,  bjEnd, bjStride Line 265  C    I        bjStart,  bjEnd, bjStride
265       I        biStart,  biEnd, biStride,       I        biStart,  biEnd, biStride,
266       I        bjStart,  bjEnd, bjStride )       I        bjStart,  bjEnd, bjStride )
267        ENDIF        ENDIF
268          _BARRIER
269    
270        RETURN        RETURN
271        END        END
272        SUBROUTINE PLOT_FIELD_XYZR8(        SUBROUTINE PLOT_FIELD_XYZRL(
273       I                            fld, fldNam , fldNz, myIter, myThid )       I                            fld, fldNam , fldNz, myIter, myThid )
274    
275  C     /==========================================================\  C     /==========================================================\
276  C     | SUBROUTINE PLOT_FIELD_XYZR8                              |  C     | SUBROUTINE PLOT_FIELD_XYZRL                              |
277  C     | Print out an XYZ Real 8 field using text map.            |  C     | Print out an XYZ _RL field using text map.               |
278  C     |==========================================================|  C     |==========================================================|
279  C     | This routine references "numerical model" parameters like|  C     | This routine references "numerical model" parameters like|
280  C     | like the integration time. It uses these to create a     |  C     | like the integration time. It uses these to create a     |
# Line 276  C     | This routine can also be edited Line 284  C     | This routine can also be edited
284  C     | of a field to be printed by default, or every other      |  C     | of a field to be printed by default, or every other      |
285  C     | point etc..                                              |  C     | point etc..                                              |
286  C     | Other plot formats can also be substituted here.         |  C     | Other plot formats can also be substituted here.         |
287    C     | _RL is usually a REAL*8 field                            |
288  C     \==========================================================/  C     \==========================================================/
289          IMPLICIT NONE
290    
291  #include "SIZE.h"  #include "SIZE.h"
292  #include "EEPARAMS.h"  #include "EEPARAMS.h"
293  #include "PARAMS.h"  #include "PARAMS.h"
 #include "CG2D.h"  
294    
295  C     == Routine arguments ==  C     == Routine arguments ==
296  C     fld - Field to plot  C     fld - Field to plot
# Line 292  C              (same lateral extents. Line 302  C              (same lateral extents.
302  C     myIter - Iteration number for plot  C     myIter - Iteration number for plot
303  C     myThid - Thread id of thread instance calling plot_field  C     myThid - Thread id of thread instance calling plot_field
304        INTEGER fldNz        INTEGER fldNz
305        REAL fld(1-OLx:sNx+OLx,1-OLy:sNy+OLy,1:fldNz,nSx,nSy)        _RL fld(1-OLx:sNx+OLx,1-OLy:sNy+OLy,1:fldNz,nSx,nSy)
306        CHARACTER*(*) fldNam        CHARACTER*(*) fldNam
307        INTEGER myThid        INTEGER myThid
308        INTEGER myIter        INTEGER myIter
# Line 307  C     == Local variables == Line 317  C     == Local variables ==
317    
318  C--   To get around synchronisation and multi-threaded I/O issues  C--   To get around synchronisation and multi-threaded I/O issues
319  C--   thread 1 will do all the writes.  C--   thread 1 will do all the writes.
320          _BARRIER
321        IF ( myThid .EQ. 1 ) THEN        IF ( myThid .EQ. 1 ) THEN
322  C--    Form name for identifying "plot"  C--    Form name for identifying "plot"
323         IF ( myIter .GE. 0 ) THEN         IF ( myIter .GE. 0 ) THEN
324          WRITE(fldTitle,'(A,A,A,I10)') '// Field ', fldNam, ' at iteration ',          WRITE(fldTitle,'(A,A,A,I10)')
325         &  '// Field ', fldNam, ' at iteration ',
326       &  myIter       &  myIter
327         ELSE         ELSE
328          WRITE(fldTitle,'(A,A)') '// Field ', fldNam          WRITE(fldTitle,'(A,A)') '// Field ', fldNam
# Line 337  C      Substitute other plotting utiliti Line 349  C      Substitute other plotting utiliti
349         bjStart  =  nSy         bjStart  =  nSy
350         bjEnd    =  1             bjEnd    =  1    
351         bjStride = -1         bjStride = -1
352  C      CALL PRINT_MAPR8(         CALL PRINT_MAPRL(
 C    I        fld, fldTitle, PRINT_MAP_YZ,  
 C    I         1-OLx,sNx+OLx,1-OLy,sNy+OLy,1,fldNz,  nSx,  nSy,  
 C    I         iStart,   iEnd,  iStride,  
 C    I         jStart,   jEnd,  jStride,  
 C    I         kStart,   kEnd,  kStride,  
 C    I        biStart,  biEnd, biStride,  
 C    I        bjStart,  bjEnd, bjStride )  
        CALL PRINT_MAPR8(  
353       I        fld, fldTitle, PRINT_MAP_XY,       I        fld, fldTitle, PRINT_MAP_XY,
354       I         1-OLx,sNx+OLx,1-OLy,sNy+OLy,1,fldNz,  nSx,  nSy,       I         1-OLx,sNx+OLx,1-OLy,sNy+OLy,1,fldNz,  nSx,  nSy,
355       I         iStart,   iEnd,  iStride,       I         iStart,   iEnd,  iStride,
# Line 354  C    I        bjStart,  bjEnd, bjStride Line 358  C    I        bjStart,  bjEnd, bjStride
358       I        biStart,  biEnd, biStride,       I        biStart,  biEnd, biStride,
359       I        bjStart,  bjEnd, bjStride )       I        bjStart,  bjEnd, bjStride )
360        ENDIF        ENDIF
361          _BARRIER
362    
363        RETURN        RETURN
364        END        END

Legend:
Removed from v.1.4  
changed lines
  Added in v.1.12

  ViewVC Help
Powered by ViewVC 1.1.22