/[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.12 - (hide annotations) (download)
Tue Mar 6 17:10:29 2001 UTC (23 years, 2 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint40pre3, checkpoint40pre1, checkpoint40pre7, checkpoint40pre6, checkpoint40pre9, checkpoint40pre8, checkpoint38, checkpoint40pre2, checkpoint40pre4, pre38tag1, c37_adj, pre38-close, checkpoint39, checkpoint37, checkpoint40pre5, checkpoint40
Branch point for: pre38
Changes since 1.11: +2 -6 lines
remove "include CG2D.h"

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

  ViewVC Help
Powered by ViewVC 1.1.22