/[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.13 - (hide annotations) (download)
Wed Sep 26 18:09:16 2001 UTC (22 years, 8 months ago) by cnh
Branch: MAIN
CVS Tags: checkpoint43a-release1mods, release1_b1, checkpoint43, release1-branch_tutorials, chkpt44a_post, release1-branch-end, chkpt44a_pre, ecco-branch-mod1, ecco-branch-mod2, ecco-branch-mod3, release1_beta1, checkpoint44b_pre, checkpoint42, checkpoint41, checkpoint44, release1-branch_branchpoint
Branch point for: release1-branch, release1, ecco-branch, release1_coupled
Changes since 1.12: +74 -46 lines
Bringing comments up to data and formatting for document extraction.

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

  ViewVC Help
Powered by ViewVC 1.1.22