/[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.6 - (hide annotations) (download)
Tue Sep 29 18:50:57 1998 UTC (25 years, 8 months ago) by cnh
Branch: MAIN
CVS Tags: checkpoint15
Changes since 1.5: +9 -1 lines
Changes for new exchange routines which do general tile <-> tile
connectivity, variable width overlap regions and provide
hooks for shared memory  and DMA protocols like Arctic, Memory Channel
etc..

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

  ViewVC Help
Powered by ViewVC 1.1.22