/[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.9 - (hide annotations) (download)
Wed Dec 9 16:11:53 1998 UTC (25 years, 5 months ago) by adcroft
Branch: MAIN
CVS Tags: checkpoint19
Changes since 1.8: +9 -1 lines
Added IMPLICIT NONE in a lot of subroutines.
Also corrected the recip_Rhonil bug: we didn't set it in ini_parms.F

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

  ViewVC Help
Powered by ViewVC 1.1.22