/[MITgcm]/MITgcm/model/src/read_write.F
ViewVC logotype

Contents of /MITgcm/model/src/read_write.F

Parent Directory Parent Directory | Revision Log Revision Log | View Revision Graph Revision Graph


Revision 1.20 - (show annotations) (download)
Sun Feb 4 16:46:44 2001 UTC (23 years, 4 months ago) by cnh
Branch: MAIN
CVS Tags: checkpoint40pre3, checkpoint40pre2, checkpoint40pre1, checkpoint40pre7, checkpoint40pre6, checkpoint40pre9, checkpoint40pre8, checkpoint38, checkpoint40pre4, pre38tag1, c37_adj, pre38-close, checkpoint39, checkpoint37, checkpoint36, checkpoint35, checkpoint40pre5, checkpoint40
Branch point for: pre38
Changes since 1.19: +149 -4 lines
o Added printing of key grid variables in config_summary.F
  and removed write(0,*) output of these variables in ini_spherical_polar_grid.F
o Added two new routines to do consistently formatted output of
  lines of constant X or Y for an XY variable. New routines are in
  read_write.F

1 C $Header: /u/gcmpack/models/MITgcmUV/model/src/read_write.F,v 1.19 2001/02/04 14:38:48 cnh Exp $
2 C $Name: $
3 #include "CPP_OPTIONS.h"
4
5 CStartofinterface
6 SUBROUTINE WRITE_1D_I( fld, lFld, index_type, head, comment )
7 C /==========================================================
8 C | o SUBROUTINE WRITE_1D_I |
9 C | Controls formatted, tabular I/O for a one-dimensional |
10 C | INTEGER field. |
11 C |==========================================================|
12 C | This routine produces a standard format for list |
13 C | one-dimensional INTEGER data in textual form. The format |
14 C | is designed to be readily parsed by a post-processing |
15 C | utility. |
16 C \==========================================================/
17 IMPLICIT NONE
18
19 C == Global data ==
20 #include "SIZE.h"
21 #include "EEPARAMS.h"
22
23 C == Routine arguments ==
24 C fld - Field to be printed
25 C lFld - Number of elements in field fld.
26 C index_type - Type of index labelling (I=,J=,...) to use
27 C head - Statement start e.g. phi =
28 C comment - Descriptive comment for field
29 INTEGER lFld
30 INTEGER fld(lFld)
31 INTEGER index_type
32 CHARACTER*(*) head
33 CHARACTER*(*) comment
34 CEndofinterface
35
36 C == Local variables ==
37 CHARACTER*(MAX_LEN_MBUF) msgBuf
38
39 WRITE(msgBuf,'(A,A)') head, comment
40 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
41 & SQUEEZE_RIGHT , 1)
42 CALL PRINT_LIST_I( fld, lFld, index_type, .FALSE.,
43 & .TRUE., standardMessageUnit )
44 WRITE(msgBuf,'(A)') ' ; '
45 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
46 & SQUEEZE_RIGHT , 1)
47
48 END
49
50
51 CStartofinterface
52 SUBROUTINE WRITE_1D_L( fld, lFld, index_type, head, comment )
53 C /==========================================================
54 C | o SUBROUTINE WRITE_1D_L |
55 C | Controls formatted, tabular I/O for a one-dimensional |
56 C | LOGICAL field. |
57 C |==========================================================|
58 C | This routine produces a standard format for list |
59 C | one-dimensional LOGICAL data in textual form. The format |
60 C | is designed to be readily parsed by a post-processing |
61 C | utility. |
62 C \==========================================================/
63 IMPLICIT NONE
64
65 C == Global data ==
66 #include "SIZE.h"
67 #include "EEPARAMS.h"
68
69 C == Routine arguments ==
70 C fld - Field to be printed
71 C lFld - Number of elements in field fld.
72 C index_type - Type of index labelling (I=,J=,...) to use
73 C head - Statement start e.g. phi =
74 C comment - Descriptive comment for field
75 INTEGER lFld
76 LOGICAL fld(lFld)
77 INTEGER index_type
78 CHARACTER*(*) head
79 CHARACTER*(*) comment
80 CEndofinterface
81
82 C == Local variables ==
83 CHARACTER*(MAX_LEN_MBUF) msgBuf
84
85 WRITE(msgBuf,'(A,A)') head, comment
86 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
87 & SQUEEZE_RIGHT , 1)
88 CALL PRINT_LIST_L( fld, lFld, index_type, .FALSE.,
89 & .TRUE., standardMessageUnit )
90 WRITE(msgBuf,'(A)') ' ; '
91 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
92 & SQUEEZE_RIGHT , 1)
93
94 END
95
96
97 CStartofinterface
98 SUBROUTINE WRITE_1D_R8( fld, lFld, index_type, head, comment )
99 C /==========================================================
100 C | o SUBROUTINE WRITE_1D_R8 |
101 C | Controls formatted, tabular I/O for a one-dimensional |
102 C | real*8 field. |
103 C |==========================================================|
104 C | This routine produces a standard format for list |
105 C | one-dimensional real*8 data in textual form. The format |
106 C | is designed to be readilya parsed by a post-processing |
107 C | utility. |
108 C \==========================================================/
109 IMPLICIT NONE
110
111 C == Global data ==
112 #include "SIZE.h"
113 #include "EEPARAMS.h"
114 EXTERNAL ILNBLNK
115 INTEGER ILNBLNK
116
117 C == Routine arguments ==
118 C fld - Field to be printed
119 C lFld - Number of elements in field fld.
120 C index_type - Type of index labelling (I=,J=,...) to use
121 C head - Statement start e.g. phi =
122 C comment - Descriptive comment for field
123 INTEGER lFld
124 Real*8 fld(lFld)
125 INTEGER index_type
126 CHARACTER*(*) head
127 CHARACTER*(*) comment
128 CEndofinterface
129
130 C == Local variables ==
131 C ILH, ILC - Index of last balnk in head and comment
132 CHARACTER*(MAX_LEN_MBUF) msgBuf
133 INTEGER ILH, ILC
134
135 ILH=ILNBLNK(head)
136 ILC=ILNBLNK(comment)
137 WRITE(msgBuf,'(A,A)') head(1:ILH), comment(1:ILC)
138 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
139 & SQUEEZE_RIGHT , 1)
140 CALL PRINT_LIST_R8( fld, lFld, index_type, .FALSE.,
141 & .TRUE., standardMessageUnit )
142 WRITE(msgBuf,'(A)') ' ; '
143 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
144 & SQUEEZE_RIGHT , 1)
145
146 END
147
148
149 CStartofinterface
150 SUBROUTINE WRITE_0D_I( fld, index_type, head, comment )
151 C /==========================================================
152 C | o SUBROUTINE WRITE_1D_I |
153 C | Controls formatted, tabular I/O for a one-dimensional |
154 C | INTEGER field. |
155 C |==========================================================|
156 C | This routine produces a standard format for list |
157 C | one-dimensional INTEGER data in textual form. The format |
158 C | is designed to be readily parsed by a post-processing |
159 C | utility. |
160 C \==========================================================/
161 IMPLICIT NONE
162
163 C == Global data ==
164 #include "SIZE.h"
165 #include "EEPARAMS.h"
166
167 C == Routine arguments ==
168 C fld - Field to be printed
169 C lFld - Number of elements in field fld.
170 C index_type - Type of index labelling (I=,J=,...) to use
171 C head - Statement start e.g. phi =
172 C comment - Descriptive comment for field
173 INTEGER fld
174 INTEGER index_type
175 CHARACTER*(*) head
176 CHARACTER*(*) comment
177 CEndofinterface
178
179 C == Local variables ==
180 CHARACTER*(MAX_LEN_MBUF) msgBuf
181 INTEGER idummy(1)
182
183 idummy(1) = fld
184
185 WRITE(msgBuf,'(A,A)') head, comment
186 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
187 & SQUEEZE_RIGHT , 1)
188 CALL PRINT_LIST_I( idummy, 1, index_type, .FALSE.,
189 & .TRUE., standardMessageUnit )
190 WRITE(msgBuf,'(A)') ' ; '
191 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
192 & SQUEEZE_RIGHT , 1)
193
194 END
195
196
197 CStartofinterface
198 SUBROUTINE WRITE_0D_L( fld, index_type, head, comment )
199 C /==========================================================
200 C | o SUBROUTINE WRITE_1D_L |
201 C | Controls formatted, tabular I/O for a one-dimensional |
202 C | LOGICAL field. |
203 C |==========================================================|
204 C | This routine produces a standard format for list |
205 C | one-dimensional LOGICAL data in textual form. The format |
206 C | is designed to be readily parsed by a post-processing |
207 C | utility. |
208 C \==========================================================/
209 IMPLICIT NONE
210
211 C == Global data ==
212 #include "SIZE.h"
213 #include "EEPARAMS.h"
214
215 C == Routine arguments ==
216 C fld - Field to be printed
217 C lFld - Number of elements in field fld.
218 C index_type - Type of index labelling (I=,J=,...) to use
219 C head - Statement start e.g. phi =
220 C comment - Descriptive comment for field
221 LOGICAL fld
222 INTEGER index_type
223 CHARACTER*(*) head
224 CHARACTER*(*) comment
225 CEndofinterface
226
227 C == Local variables ==
228 CHARACTER*(MAX_LEN_MBUF) msgBuf
229 LOGICAL ldummy(1)
230
231 ldummy(1) = fld
232 WRITE(msgBuf,'(A,A)') head, comment
233 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
234 & SQUEEZE_RIGHT , 1)
235 CALL PRINT_LIST_L( ldummy, 1, index_type, .FALSE.,
236 & .TRUE., standardMessageUnit )
237 WRITE(msgBuf,'(A)') ' ; '
238 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
239 & SQUEEZE_RIGHT , 1)
240
241 END
242
243
244 CStartofinterface
245 SUBROUTINE WRITE_0D_R8( fld, index_type, head, comment )
246 C /==========================================================
247 C | o SUBROUTINE WRITE_1D_R8 |
248 C | Controls formatted, tabular I/O for a one-dimensional |
249 C | real*8 field. |
250 C |==========================================================|
251 C | This routine produces a standard format for list |
252 C | one-dimensional real*8 data in textual form. The format |
253 C | is designed to be readilya parsed by a post-processing |
254 C | utility. |
255 C \==========================================================/
256 IMPLICIT NONE
257
258 C == Global data ==
259 #include "SIZE.h"
260 #include "EEPARAMS.h"
261
262 C == Routine arguments ==
263 C fld - Field to be printed
264 C lFld - Number of elements in field fld.
265 C index_type - Type of index labelling (I=,J=,...) to use
266 C head - Statement start e.g. phi =
267 C comment - Descriptive comment for field
268 Real*8 fld
269 INTEGER index_type
270 CHARACTER*(*) head
271 CHARACTER*(*) comment
272 CEndofinterface
273
274 C == Local variables ==
275 CHARACTER*(MAX_LEN_MBUF) msgBuf
276 Real*8 r8dummy(1)
277
278 r8dummy(1) = fld
279
280 WRITE(msgBuf,'(A,A)') head, comment
281 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
282 & SQUEEZE_RIGHT , 1)
283 CALL PRINT_LIST_R8( r8dummy, 1, index_type, .FALSE.,
284 & .TRUE., standardMessageUnit )
285 WRITE(msgBuf,'(A)') ' ; '
286 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
287 & SQUEEZE_RIGHT , 1)
288
289 END
290
291
292 CStartofinterface
293 SUBROUTINE WRITE_XY_XLINE_RS(
294 I fld, sCoord, tCoord,
295 I head, comment )
296 C /==========================================================
297 C | o SUBROUTINE WRITE_XY_XLINE_RS |
298 C | Prints out X row of an XY RS field e.g. phi(:,n,:,m) |
299 C |==========================================================|
300 C | This routine produces a standard format for list |
301 C | one-dimensional RS data in textual form. The format |
302 C | is designed to be readily parsed by a post-processing |
303 C | utility. |
304 C \==========================================================/
305 IMPLICIT NONE
306
307 C == Global data ==
308 #include "SIZE.h"
309 #include "EEPARAMS.h"
310 EXTERNAL IFNBLNK
311 INTEGER IFNBLNK
312 EXTERNAL ILNBLNK
313 INTEGER ILNBLNK
314
315 C == Routine arguments ==
316 C fld - Field to be printed
317 C sCoord - subgrid coordinate
318 C tCoord - tile coordinate
319 C head - Statement start e.g. phi =
320 C comment - Descriptive comment for field
321 _RS fld(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
322 INTEGER sCoord
323 INTEGER tCoord
324 CHARACTER*(*) head
325 CHARACTER*(*) comment
326 CEndofinterface
327
328 C == Local variables ==
329 CHARACTER*(MAX_LEN_MBUF) msgBuf1
330 CHARACTER*(MAX_LEN_MBUF) msgBuf2
331 CHARACTER*10 num1, num2
332 REAL*8 xcoord(sNx*nSx)
333 INTEGER bi, bj, i, j
334 INTEGER IFN1, ILN1, IFN2, ILN2
335
336 WRITE(msgBuf1,'(A,A)') head,' = '
337 bj = tCoord
338 J = sCoord
339 WRITE(num1,'(I10)') J
340 WRITE(num2,'(I10)') bj
341 IFN1 = IFNBLNK(num1)
342 ILN1 = ILNBLNK(num1)
343 IFN2 = IFNBLNK(num2)
344 ILN2 = ILNBLNK(num2)
345 C fld(:,J,:,bj)
346 WRITE(msgBuf2,'(A,A,A,A,A,A,A,A,A)')
347 & ' /* ', head,'(:,',
348 & num1(IFN1:ILN1),',:,',
349 & num2(IFN2:ILN2),') ',
350 & comment,' */'
351 DO bi=1,nSx
352 DO I=1,sNx
353 xcoord(sNx*(bi-1)+I)=fld(I,J,bi,bj)
354 ENDDO
355 ENDDO
356 CALL WRITE_1D_R8( xcoord, sNx*nSx, INDEX_I,msgBuf1,msgBuf2)
357
358 RETURN
359 END
360
361 CStartofinterface
362 SUBROUTINE WRITE_XY_YLINE_RS(
363 I fld, sCoord, tCoord,
364 I head, comment )
365 C /==========================================================
366 C | o SUBROUTINE WRITE_XY_YLINE_RS |
367 C | Prints out Y row of an XY RS field e.g. phi(n,:,m,:) |
368 C |==========================================================|
369 C | This routine produces a standard format for list |
370 C | one-dimensional RS data in textual form. The format |
371 C | is designed to be readily parsed by a post-processing |
372 C | utility. |
373 C \==========================================================/
374 IMPLICIT NONE
375
376 C == Global data ==
377 #include "SIZE.h"
378 #include "EEPARAMS.h"
379 EXTERNAL IFNBLNK
380 INTEGER IFNBLNK
381 EXTERNAL ILNBLNK
382 INTEGER ILNBLNK
383
384 C == Routine arguments ==
385 C fld - Field to be printed
386 C sCoord - subgrid coordinate
387 C tCoord - tile coordinate
388 C head - Statement start e.g. phi =
389 C comment - Descriptive comment for field
390 _RS fld(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
391 INTEGER sCoord
392 INTEGER tCoord
393 CHARACTER*(*) head
394 CHARACTER*(*) comment
395 CEndofinterface
396
397 C == Local variables ==
398 CHARACTER*(MAX_LEN_MBUF) msgBuf1
399 CHARACTER*(MAX_LEN_MBUF) msgBuf2
400 REAL*8 ycoord(sNy*nSy)
401 INTEGER bi, bj, i, j
402 CHARACTER*10 num1, num2
403 INTEGER IFN1, ILN1, IFN2, ILN2
404
405 WRITE(msgBuf1,'(A,A)') head,' = '
406 bi = tCoord
407 I = sCoord
408 WRITE(num1,'(I10)') I
409 WRITE(num2,'(I10)') bi
410 IFN1 = IFNBLNK(num1)
411 ILN1 = ILNBLNK(num1)
412 IFN2 = IFNBLNK(num2)
413 ILN2 = ILNBLNK(num2)
414 C fld(I,:,bi,:)
415 WRITE(msgBuf2,'(A,A,A,A,A,A,A,A,A)')
416 & ' /* ',head,'(',
417 & num1(IFN1:ILN1),',:,',
418 & num2(IFN2:ILN2),',:) ',
419 & comment,' */'
420 DO bj=1,nSy
421 DO J=1,sNy
422 ycoord(sNy*(bj-1)+J)=fld(I,J,bi,bj)
423 ENDDO
424 ENDDO
425 CALL WRITE_1D_R8( ycoord, sNy*nSy, INDEX_J,msgBuf1,msgBuf2)
426
427 RETURN
428 END

  ViewVC Help
Powered by ViewVC 1.1.22