/[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.7 - (hide annotations) (download)
Wed Oct 28 03:11:38 1998 UTC (25 years, 7 months ago) by cnh
Branch: MAIN
CVS Tags: checkpoint17, checkpoint16
Changes since 1.6: +9 -5 lines
Changes to support
 - g77 compilation under Linux
 - LR(1) form of 64-bit is D or E for constants
 - Modified adjoint of exch with adjoint variables
   acuumulated.

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

  ViewVC Help
Powered by ViewVC 1.1.22