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

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

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


Revision 1.19 - (hide annotations) (download)
Sun Feb 4 14:38:48 2001 UTC (23 years, 5 months ago) by cnh
Branch: MAIN
Changes since 1.18: +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.19 C $Header: /u/gcmpack/models/MITgcmUV/model/src/read_write.F,v 1.18 2000/06/09 02:45:04 heimbach Exp $
2     C $Name: $
3 cnh 1.10 #include "CPP_OPTIONS.h"
4 cnh 1.1
5     CStartofinterface
6     SUBROUTINE WRITE_1D_I( fld, lFld, index_type, head, comment )
7 heimbach 1.18 C /==========================================================
8 cnh 1.1 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 adcroft 1.17 C | uFIELD. |
16 cnh 1.1 C \==========================================================/
17 adcroft 1.14 IMPLICIT NONE
18 cnh 1.1
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 cnh 1.12 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
41     & SQUEEZE_RIGHT , 1)
42     CALL PRINT_LIST_I( fld, lFld, index_type, .FALSE.,
43     & .TRUE., standardMessageUnit )
44 cnh 1.1 WRITE(msgBuf,'(A)') ' ; '
45 cnh 1.12 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
46     & SQUEEZE_RIGHT , 1)
47 heimbach 1.18
48 cnh 1.1 END
49    
50 heimbach 1.18
51 cnh 1.1 CStartofinterface
52     SUBROUTINE WRITE_1D_L( fld, lFld, index_type, head, comment )
53 heimbach 1.18 C /==========================================================
54 cnh 1.1 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 adcroft 1.14 IMPLICIT NONE
64 cnh 1.1
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 cnh 1.12 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
87     & SQUEEZE_RIGHT , 1)
88     CALL PRINT_LIST_L( fld, lFld, index_type, .FALSE.,
89     & .TRUE., standardMessageUnit )
90 cnh 1.1 WRITE(msgBuf,'(A)') ' ; '
91 cnh 1.12 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
92     & SQUEEZE_RIGHT , 1)
93 heimbach 1.18
94 cnh 1.1 END
95    
96 heimbach 1.18
97 cnh 1.1 CStartofinterface
98     SUBROUTINE WRITE_1D_R8( fld, lFld, index_type, head, comment )
99 heimbach 1.18 C /==========================================================
100 cnh 1.1 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 adcroft 1.14 IMPLICIT NONE
110 cnh 1.1
111     C == Global data ==
112     #include "SIZE.h"
113     #include "EEPARAMS.h"
114    
115     C == Routine arguments ==
116     C fld - Field to be printed
117     C lFld - Number of elements in field fld.
118     C index_type - Type of index labelling (I=,J=,...) to use
119     C head - Statement start e.g. phi =
120     C comment - Descriptive comment for field
121     INTEGER lFld
122     Real*8 fld(lFld)
123     INTEGER index_type
124     CHARACTER*(*) head
125     CHARACTER*(*) comment
126     CEndofinterface
127    
128     C == Local variables ==
129     CHARACTER*(MAX_LEN_MBUF) msgBuf
130    
131     WRITE(msgBuf,'(A,A)') head, comment
132 cnh 1.12 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
133     & SQUEEZE_RIGHT , 1)
134     CALL PRINT_LIST_R8( fld, lFld, index_type, .FALSE.,
135     & .TRUE., standardMessageUnit )
136 cnh 1.1 WRITE(msgBuf,'(A)') ' ; '
137 cnh 1.12 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
138     & SQUEEZE_RIGHT , 1)
139 heimbach 1.18
140     END
141    
142    
143     CStartofinterface
144     SUBROUTINE WRITE_0D_I( fld, index_type, head, comment )
145     C /==========================================================
146     C | o SUBROUTINE WRITE_1D_I |
147     C | Controls formatted, tabular I/O for a one-dimensional |
148     C | INTEGER field. |
149     C |==========================================================|
150     C | This routine produces a standard format for list |
151     C | one-dimensional INTEGER data in textual form. The format |
152     C | is designed to be readily parsed by a post-processing |
153     C | utility. |
154     C \==========================================================/
155     IMPLICIT NONE
156    
157     C == Global data ==
158     #include "SIZE.h"
159     #include "EEPARAMS.h"
160    
161     C == Routine arguments ==
162     C fld - Field to be printed
163     C lFld - Number of elements in field fld.
164     C index_type - Type of index labelling (I=,J=,...) to use
165     C head - Statement start e.g. phi =
166     C comment - Descriptive comment for field
167     INTEGER fld
168     INTEGER index_type
169     CHARACTER*(*) head
170     CHARACTER*(*) comment
171     CEndofinterface
172    
173     C == Local variables ==
174     CHARACTER*(MAX_LEN_MBUF) msgBuf
175     INTEGER idummy(1)
176    
177     idummy(1) = fld
178    
179     WRITE(msgBuf,'(A,A)') head, comment
180     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
181     & SQUEEZE_RIGHT , 1)
182     CALL PRINT_LIST_I( idummy, 1, index_type, .FALSE.,
183     & .TRUE., standardMessageUnit )
184     WRITE(msgBuf,'(A)') ' ; '
185     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
186     & SQUEEZE_RIGHT , 1)
187    
188     END
189    
190    
191     CStartofinterface
192     SUBROUTINE WRITE_0D_L( fld, index_type, head, comment )
193     C /==========================================================
194     C | o SUBROUTINE WRITE_1D_L |
195     C | Controls formatted, tabular I/O for a one-dimensional |
196     C | LOGICAL field. |
197     C |==========================================================|
198     C | This routine produces a standard format for list |
199     C | one-dimensional LOGICAL data in textual form. The format |
200     C | is designed to be readily parsed by a post-processing |
201     C | utility. |
202     C \==========================================================/
203     IMPLICIT NONE
204    
205     C == Global data ==
206     #include "SIZE.h"
207     #include "EEPARAMS.h"
208    
209     C == Routine arguments ==
210     C fld - Field to be printed
211     C lFld - Number of elements in field fld.
212     C index_type - Type of index labelling (I=,J=,...) to use
213     C head - Statement start e.g. phi =
214     C comment - Descriptive comment for field
215     LOGICAL fld
216     INTEGER index_type
217     CHARACTER*(*) head
218     CHARACTER*(*) comment
219     CEndofinterface
220    
221     C == Local variables ==
222     CHARACTER*(MAX_LEN_MBUF) msgBuf
223     LOGICAL ldummy(1)
224    
225     ldummy(1) = fld
226     WRITE(msgBuf,'(A,A)') head, comment
227     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
228     & SQUEEZE_RIGHT , 1)
229     CALL PRINT_LIST_L( ldummy, 1, index_type, .FALSE.,
230     & .TRUE., standardMessageUnit )
231     WRITE(msgBuf,'(A)') ' ; '
232     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
233     & SQUEEZE_RIGHT , 1)
234    
235     END
236    
237    
238     CStartofinterface
239     SUBROUTINE WRITE_0D_R8( fld, index_type, head, comment )
240     C /==========================================================
241     C | o SUBROUTINE WRITE_1D_R8 |
242     C | Controls formatted, tabular I/O for a one-dimensional |
243     C | real*8 field. |
244     C |==========================================================|
245     C | This routine produces a standard format for list |
246     C | one-dimensional real*8 data in textual form. The format |
247     C | is designed to be readilya parsed by a post-processing |
248     C | utility. |
249     C \==========================================================/
250     IMPLICIT NONE
251    
252     C == Global data ==
253     #include "SIZE.h"
254     #include "EEPARAMS.h"
255    
256     C == Routine arguments ==
257     C fld - Field to be printed
258     C lFld - Number of elements in field fld.
259     C index_type - Type of index labelling (I=,J=,...) to use
260     C head - Statement start e.g. phi =
261     C comment - Descriptive comment for field
262     Real*8 fld
263     INTEGER index_type
264     CHARACTER*(*) head
265     CHARACTER*(*) comment
266     CEndofinterface
267    
268     C == Local variables ==
269     CHARACTER*(MAX_LEN_MBUF) msgBuf
270     Real*8 r8dummy(1)
271    
272     r8dummy(1) = fld
273    
274     WRITE(msgBuf,'(A,A)') head, comment
275     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
276     & SQUEEZE_RIGHT , 1)
277     CALL PRINT_LIST_R8( r8dummy, 1, index_type, .FALSE.,
278     & .TRUE., standardMessageUnit )
279     WRITE(msgBuf,'(A)') ' ; '
280     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
281     & SQUEEZE_RIGHT , 1)
282    
283 cnh 1.1 END

  ViewVC Help
Powered by ViewVC 1.1.22