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

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

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


Revision 1.5 - (hide annotations) (download)
Mon Jun 15 05:13:56 1998 UTC (25 years, 11 months ago) by cnh
Branch: MAIN
CVS Tags: checkpoint11, checkpoint10, checkpoint13, checkpoint14, checkpoint7, checkpoint9, checkpoint8, checkpoint12, branch-point-rdot
Branch point for: checkpoint7-4degree-ref, branch-rdot
Changes since 1.4: +29 -41 lines
Fairly coplete 4 degree global intercomparison
setup.
 Includes changes to make convective adjustment and hydrostatic
pressure correct as well as IO for climatological datasets

1 cnh 1.5 C $Header: /u/gcmpack/models/MITgcmUV/model/src/plot_field.F,v 1.4 1998/06/12 19:33:34 cnh Exp $
2 cnh 1.1
3     #include "CPP_EEOPTIONS.h"
4    
5     C-- File plot_field.F: Routines for "formatted" I/O in the MITgcm UV
6     C-- implementation.
7     C-- Contents
8 cnh 1.5 C-- o plot_field_xyrs - Writes a XY _RS field
9     C-- o plot_field_xyrl - Writes a XY _RL field
10     C-- o plot_field_xyzrs - Writes a XYZ _RS field
11     C-- o plot_field_xyzrl - Writes a XYZ _RL field
12     SUBROUTINE PLOT_FIELD_XYRS(
13 cnh 1.1 I fld, fldNam , myIter, myThid )
14    
15     C /==========================================================\
16 cnh 1.5 C | SUBROUTINE PLOT_FIELD_XYRS |
17     C | Print out an XY _RS field using text map. |
18 cnh 1.1 C |==========================================================|
19     C | This routine references "numerical model" parameters like|
20     C | like the integration time. It uses these to create a |
21     C | title for the field before calling a generic execution |
22     C | environment support routine. |
23     C | This routine can also be edited to cause only some region|
24     C | of a field to be printed by default, or every other |
25     C | point etc.. |
26     C | Other plot formats can also be substituted here. |
27 cnh 1.5 C | _RS is usually REAL*4 |
28 cnh 1.1 C \==========================================================/
29     #include "SIZE.h"
30     #include "EEPARAMS.h"
31     #include "PARAMS.h"
32     #include "CG2D.h"
33    
34     C == Routine arguments ==
35     C fld - Field to plot
36     C fldNam - Name of field
37     C myIter - Iteration number for plot
38     C myThid - Thread id of thread instance calling plot_field
39 cnh 1.5 _RS fld(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
40 cnh 1.1 CHARACTER*(*) fldNam
41     INTEGER myThid
42     INTEGER myIter
43    
44     C == Local variables ==
45     CHARACTER*(MAX_LEN_MBUF) fldTitle
46     INTEGER iStart, iEnd, iStride
47     INTEGER jStart, jEnd, jStride
48     INTEGER kStart, kEnd, kStride
49     INTEGER biStart, biEnd, biStride
50     INTEGER bjStart, bjEnd, bjStride
51    
52     C-- To get around synchronisation and multi-threaded I/O issues
53     C-- thread 1 will do all the writes.
54     IF ( myThid .EQ. 1 ) THEN
55     C-- Form name for identifying "plot"
56     IF ( myIter .GE. 0 ) THEN
57 cnh 1.3 WRITE(fldTitle,'(A,A,A,I10)') '// Field ', fldNam, ' at iteration ',
58 cnh 1.1 & myIter
59     ELSE
60     WRITE(fldTitle,'(A,A)') '// Field ', fldNam
61     ENDIF
62     C-- Do "plot" using textual contour map "execution environment" routine
63     C Substitute other plotting utilities here!
64     iStart = 1-OLx
65     iEnd = sNx+OLx
66     iStride = 1
67     jStart = sNy+OLy
68     jEnd = 1-OLy
69     jStride = -1
70     kStart = 1
71     kEnd = 1
72     kStride = 1
73     biStart = 1
74     biEnd = nSx
75     biStride = 1
76     bjStart = nSy
77     bjEnd = 1
78     bjStride = -1
79 cnh 1.5 CALL PRINT_MAPRS(
80 cnh 1.1 I fld, fldTitle, PRINT_MAP_XY,
81     I 1-OLx,sNx+OLx,1-OLy,sNy+OLy,1,1, nSx, nSy,
82     I iStart, iEnd, iStride,
83     I jStart, jEnd, jStride,
84     I kStart, kEnd, kStride,
85     I biStart, biEnd, biStride,
86     I bjStart, bjEnd, bjStride )
87     ENDIF
88    
89     RETURN
90     END
91 cnh 1.5 SUBROUTINE PLOT_FIELD_XYRL(
92 cnh 1.1 I fld, fldNam , myIter, myThid )
93    
94     C /==========================================================\
95 cnh 1.5 C | SUBROUTINE PLOT_FIELD_XYRL |
96     C | Print out an XY _RL field using text map. |
97 cnh 1.1 C |==========================================================|
98     C | This routine references "numerical model" parameters like|
99     C | like the integration time. It uses these to create a |
100     C | title for the field before calling a generic execution |
101     C | environment support routine. |
102     C | This routine can also be edited to cause only some region|
103     C | of a field to be printed by default, or every other |
104     C | point etc.. |
105     C | Other plot formats can also be substituted here. |
106 cnh 1.5 C | _RL is usually REAL*8 |
107 cnh 1.1 C \==========================================================/
108     #include "SIZE.h"
109     #include "EEPARAMS.h"
110     #include "PARAMS.h"
111     #include "CG2D.h"
112    
113     C == Routine arguments ==
114     C fld - Field to plot
115     C fldNam - Name of field
116     C myIter - Iteration number for plot
117     C myThid - Thread id of thread instance calling plot_field
118 cnh 1.5 _RL fld(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
119 cnh 1.1 CHARACTER*(*) fldNam
120     INTEGER myThid
121     INTEGER myIter
122    
123     C == Local variables ==
124     CHARACTER*(MAX_LEN_MBUF) fldTitle
125     INTEGER iStart, iEnd, iStride
126     INTEGER jStart, jEnd, jStride
127     INTEGER kStart, kEnd, kStride
128     INTEGER biStart, biEnd, biStride
129     INTEGER bjStart, bjEnd, bjStride
130    
131     C-- To get around synchronisation and multi-threaded I/O issues
132     C-- thread 1 will do all the writes.
133     IF ( myThid .EQ. 1 ) THEN
134     C-- Form name for identifying "plot"
135     IF ( myIter .GE. 0 ) THEN
136 cnh 1.3 WRITE(fldTitle,'(A,A,A,I10)') '// Field ', fldNam, ' at iteration ',
137 cnh 1.1 & myIter
138     ELSE
139     WRITE(fldTitle,'(A,A)') '// Field ', fldNam
140     ENDIF
141     C-- Do "plot" using textual contour map "execution environment" routine
142     C Substitute other plotting utilities here!
143     iStart = 1-OLx
144     iEnd = sNx+OLx
145     iStride = 1
146     jStart = sNy+OLy
147     jEnd = 1-OLy
148     jStride = -1
149     kStart = 1
150     kEnd = 1
151     kStride = 1
152     biStart = 1
153     biEnd = nSx
154     biStride = 1
155     bjStart = nSy
156     bjEnd = 1
157     bjStride = -1
158 cnh 1.5 CALL PRINT_MAPRL(
159 cnh 1.1 I fld, fldTitle, PRINT_MAP_XY,
160     I 1-OLx,sNx+OLx,1-OLy,sNy+OLy,1,1, nSx, nSy,
161     I iStart, iEnd, iStride,
162     I jStart, jEnd, jStride,
163     I kStart, kEnd, kStride,
164     I biStart, biEnd, biStride,
165     I bjStart, bjEnd, bjStride )
166     ENDIF
167    
168     RETURN
169     END
170 cnh 1.5 SUBROUTINE PLOT_FIELD_XYZRS(
171 cnh 1.1 I fld, fldNam , fldNz, myIter, myThid )
172    
173     C /==========================================================\
174     C | SUBROUTINE PLOT_FIELD_XYZR4 |
175 cnh 1.5 C | Print out an XYZ _RS field using text map. |
176 cnh 1.1 C |==========================================================|
177     C | This routine references "numerical model" parameters like|
178     C | like the integration time. It uses these to create a |
179     C | title for the field before calling a generic execution |
180     C | environment support routine. |
181     C | This routine can also be edited to cause only some region|
182     C | of a field to be printed by default, or every other |
183     C | point etc.. |
184     C | Other plot formats can also be substituted here. |
185 cnh 1.5 C | _RS is usually a REAL*4 field |
186 cnh 1.1 C \==========================================================/
187     #include "SIZE.h"
188     #include "EEPARAMS.h"
189     #include "PARAMS.h"
190     #include "CG2D.h"
191    
192     C == Routine arguments ==
193     C fld - Field to plot
194     C fldNam - Name of field
195     C fldNz - No. of layers in the vertical
196     C (Different fields may have different vertical extents)
197     C (Under the present implementation all fields have the)
198     C (same lateral extents. )
199     C myIter - Iteration number for plot
200     C myThid - Thread id of thread instance calling plot_field
201     INTEGER fldNz
202 cnh 1.5 _RS fld(1-OLx:sNx+OLx,1-OLy:sNy+OLy,1:fldNz,nSx,nSy)
203 cnh 1.1 CHARACTER*(*) fldNam
204     INTEGER myThid
205     INTEGER myIter
206    
207     C == Local variables ==
208     CHARACTER*(MAX_LEN_MBUF) fldTitle
209     INTEGER iStart, iEnd, iStride
210     INTEGER jStart, jEnd, jStride
211     INTEGER kStart, kEnd, kStride
212     INTEGER biStart, biEnd, biStride
213     INTEGER bjStart, bjEnd, bjStride
214    
215     C-- To get around synchronisation and multi-threaded I/O issues
216     C-- thread 1 will do all the writes.
217     IF ( myThid .EQ. 1 ) THEN
218     C-- Form name for identifying "plot"
219     IF ( myIter .GE. 0 ) THEN
220 cnh 1.3 WRITE(fldTitle,'(A,A,A,I10)') '// Field ', fldNam, ' at iteration ',
221 cnh 1.1 & myIter
222     ELSE
223     WRITE(fldTitle,'(A,A)') '// Field ', fldNam
224     ENDIF
225     C-- Do "plot" using textual contour map "execution environment" routine
226     C Substitute other plotting utilities here!
227     iStart = 1-OLx
228     iEnd = sNx+OLx
229     C iStart = 1
230     C iEnd = sNx
231     iStride = 1
232     jStart = sNy+OLy
233     jEnd = 1-OLy
234     C jStart = sNy
235     C jEnd = 1
236     jStride = -1
237     kStart = 1
238     kEnd = fldNz
239 cnh 1.5 kEnd = 1
240 cnh 1.1 kStride = 1
241     biStart = 1
242     biEnd = nSx
243     biStride = 1
244     bjStart = nSy
245     bjEnd = 1
246     bjStride = -1
247 cnh 1.5 CALL PRINT_MAPRS(
248 cnh 1.1 I fld, fldTitle, PRINT_MAP_XY,
249     I 1-OLx,sNx+OLx,1-OLy,sNy+OLy,1,fldNz, nSx, nSy,
250     I iStart, iEnd, iStride,
251     I jStart, jEnd, jStride,
252     I kStart, kEnd, kStride,
253     I biStart, biEnd, biStride,
254     I bjStart, bjEnd, bjStride )
255     ENDIF
256    
257     RETURN
258     END
259 cnh 1.5 SUBROUTINE PLOT_FIELD_XYZRL(
260 cnh 1.1 I fld, fldNam , fldNz, myIter, myThid )
261    
262     C /==========================================================\
263 cnh 1.5 C | SUBROUTINE PLOT_FIELD_XYZRL |
264     C | Print out an XYZ _RL field using text map. |
265 cnh 1.1 C |==========================================================|
266     C | This routine references "numerical model" parameters like|
267     C | like the integration time. It uses these to create a |
268     C | title for the field before calling a generic execution |
269     C | environment support routine. |
270     C | This routine can also be edited to cause only some region|
271     C | of a field to be printed by default, or every other |
272     C | point etc.. |
273     C | Other plot formats can also be substituted here. |
274 cnh 1.5 C | _RL is usually a REAL*8 field |
275 cnh 1.1 C \==========================================================/
276     #include "SIZE.h"
277     #include "EEPARAMS.h"
278     #include "PARAMS.h"
279     #include "CG2D.h"
280    
281     C == Routine arguments ==
282     C fld - Field to plot
283     C fldNam - Name of field
284     C fldNz - No. of layers in the vertical
285     C (Different fields may have different vertical extents)
286     C (Under the present implementation all fields have the)
287     C (same lateral extents. )
288     C myIter - Iteration number for plot
289     C myThid - Thread id of thread instance calling plot_field
290     INTEGER fldNz
291 cnh 1.5 _RL fld(1-OLx:sNx+OLx,1-OLy:sNy+OLy,1:fldNz,nSx,nSy)
292 cnh 1.1 CHARACTER*(*) fldNam
293     INTEGER myThid
294     INTEGER myIter
295    
296     C == Local variables ==
297     CHARACTER*(MAX_LEN_MBUF) fldTitle
298     INTEGER iStart, iEnd, iStride
299     INTEGER jStart, jEnd, jStride
300     INTEGER kStart, kEnd, kStride
301     INTEGER biStart, biEnd, biStride
302     INTEGER bjStart, bjEnd, bjStride
303    
304     C-- To get around synchronisation and multi-threaded I/O issues
305     C-- thread 1 will do all the writes.
306     IF ( myThid .EQ. 1 ) THEN
307     C-- Form name for identifying "plot"
308     IF ( myIter .GE. 0 ) THEN
309 cnh 1.3 WRITE(fldTitle,'(A,A,A,I10)') '// Field ', fldNam, ' at iteration ',
310 cnh 1.1 & myIter
311     ELSE
312     WRITE(fldTitle,'(A,A)') '// Field ', fldNam
313     ENDIF
314     C-- Do "plot" using textual contour map "execution environment" routine
315     C Substitute other plotting utilities here!
316     iStart = 1-OLx
317     iEnd = sNx+OLx
318 cnh 1.4 iStart = 1
319     iEnd = sNx
320 cnh 1.1 iStride = 1
321     jStart = sNy+OLy
322     jEnd = 1-OLy
323 cnh 1.4 jStart = sNy
324     jEnd = 1
325 cnh 1.1 jStride = -1
326     kStart = 1
327     kEnd = fldNz
328     kEnd = 1
329     kStride = 1
330     biStart = 1
331     biEnd = nSx
332     biStride = 1
333     bjStart = nSy
334     bjEnd = 1
335     bjStride = -1
336 cnh 1.5 CALL PRINT_MAPRL(
337 cnh 1.1 I fld, fldTitle, PRINT_MAP_XY,
338     I 1-OLx,sNx+OLx,1-OLy,sNy+OLy,1,fldNz, nSx, nSy,
339     I iStart, iEnd, iStride,
340     I jStart, jEnd, jStride,
341     I kStart, kEnd, kStride,
342     I biStart, biEnd, biStride,
343     I bjStart, bjEnd, bjStride )
344     ENDIF
345    
346     RETURN
347     END
348    

  ViewVC Help
Powered by ViewVC 1.1.22