/[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.11 - (hide annotations) (download)
Sun Feb 4 14:38:48 2001 UTC (23 years, 3 months ago) by cnh
Branch: MAIN
CVS Tags: checkpoint36, checkpoint35
Changes since 1.10: +2 -1 lines
Made sure each .F and .h file had
the CVS keywords Header and Name at its start.
Most had header but very few currently have Name, so
lots of changes!

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

  ViewVC Help
Powered by ViewVC 1.1.22