/[MITgcm]/MITgcm/pkg/mdsio/mdsio_rw_field.F
ViewVC logotype

Contents of /MITgcm/pkg/mdsio/mdsio_rw_field.F

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


Revision 1.1 - (show annotations) (download)
Fri Dec 29 05:50:48 2006 UTC (17 years, 4 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint58u_post, checkpoint58w_post, checkpoint58x_post, checkpoint58t_post, checkpoint59e, checkpoint59d, checkpoint59g, checkpoint59f, checkpoint59a, checkpoint59c, checkpoint59b, checkpoint59i, checkpoint59h, checkpoint59j, checkpoint59, checkpoint58y_post, checkpoint58v_post
collect in one file: mdsio_rw_field.F the 4 S/R:
  MDSREADFIELD  & MDSREADFIELD_LOC  (just a call to MDS_READ_FIELD)
  MDSWRITEFIELD & MDSWRITEFIELD_LOC (just a call to MDS_WRITE_FIELD)
and remove MDSWRITEFIELD_NEW (replaced by MDS_WRITE_FIELD)

1 C $Header: /u/gcmpack/MITgcm/pkg/mdsio/mdsio_writefield.F,v 1.9 2005/11/02 14:39:46 jmc Exp $
2 C $Name: $
3
4 #include "MDSIO_OPTIONS.h"
5
6 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
7
8 SUBROUTINE MDSREADFIELD(
9 I fName,
10 I filePrec,
11 I arrType,
12 I nNz,
13 O arr,
14 I irecord,
15 I myThid )
16 C
17 C Arguments:
18 C
19 C fName (string) :: base name for file to written
20 C filePrec (integer) :: number of bits per word in file (32 or 64)
21 C arrType (char(2)) :: declaration of "arr": either "RS" or "RL"
22 C nNz (integer) :: size of third dimension: normally either 1 or Nr
23 C arr ( RS/RL ) :: array to write, arr(:,:,nNz,:,:)
24 C irecord (integer) :: record number to read
25 C myThid (integer) :: thread identifier
26 C
27 C Routine now calls MDS_READ_FIELD, just a way to add 2 extra arguments
28 C to the argument list. The 1rst new argument is to make the difference between
29 C the vertical dimension (3rd dimension) of the output array and the number
30 C of levels to read in. This routine assumes they are the same.
31 C The 2nd new argument (useCurrentDir=.FALSE.) allows to read files from
32 C the "mdsioLocalDir" directory (if it is set).
33
34 IMPLICIT NONE
35 C Global variables / COMMON blocks
36 #include "SIZE.h"
37 c #include "EEPARAMS.h"
38
39 C Routine arguments
40 CHARACTER*(*) fName
41 INTEGER filePrec
42 CHARACTER*(2) arrType
43 INTEGER nNz
44 Real arr(*)
45 INTEGER irecord
46 INTEGER myThid
47 C ------------------------------------------------------------------
48 CALL MDS_READ_FIELD(
49 I fName, filePrec, .FALSE., arrType, nNz, nNz,
50 O arr,
51 I irecord, myThid )
52 C ------------------------------------------------------------------
53 RETURN
54 END
55
56 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
57
58 SUBROUTINE MDSREADFIELD_LOC(
59 I fName,
60 I filePrec,
61 I arrType,
62 I nNz,
63 O arr,
64 I irecord,
65 I myThid )
66 C
67 C Arguments:
68 C
69 C fName (string) :: base name for file to write
70 C filePrec (integer) :: number of bits per word in file (32 or 64)
71 C arrType (char(2)) :: declaration of "arr": either "RS" or "RL"
72 C nNz (integer) :: size of third dimension: normally either 1 or Nr
73 C arr ( RS/RL ) :: array to write, arr(:,:,nNz,:,:)
74 C irecord (integer) :: record number to read
75 C myThid (integer) :: thread identifier
76 C
77 C Routine now calls MDS_READ_FIELD, just a way to add 2 extra arguments
78 C to the argument list. The 1rst new argument is to make the difference between
79 C the vertical dimension (3rd dimension) of the output array and the number
80 C of levels to read in. This routine assumes they are the same.
81 C The 2nd new argument (useCurrentDir=.FALSE.) forces to ignore the
82 C "mdsioLocalDir" parameter and to always read from the current directory.
83
84 IMPLICIT NONE
85 C Global variables / COMMON blocks
86 #include "SIZE.h"
87 c #include "EEPARAMS.h"
88
89 C Routine arguments
90 CHARACTER*(*) fName
91 INTEGER filePrec
92 CHARACTER*(2) arrType
93 INTEGER nNz
94 Real arr(*)
95 INTEGER irecord
96 INTEGER myThid
97 C ------------------------------------------------------------------
98 CALL MDS_READ_FIELD(
99 I fName, filePrec, .TRUE., arrType, nNz, nNz,
100 O arr,
101 I irecord, myThid )
102 C ------------------------------------------------------------------
103 RETURN
104 END
105 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
106
107 SUBROUTINE MDSWRITEFIELD(
108 I fName,
109 I filePrec,
110 I globalFile,
111 I arrType,
112 I nNz,
113 I arr,
114 I irecord,
115 I myIter,
116 I myThid )
117 C
118 C Arguments:
119 C
120 C fName (string) :: base name for file to write
121 C filePrec (integer) :: number of bits per word in file (32 or 64)
122 C globalFile (logical):: selects between writing a global or tiled file
123 C arrType (char(2)) :: declaration of "arr": either "RS" or "RL"
124 C nNz (integer) :: size of third dimension: normally either 1 or Nr
125 C arr ( RS/RL ) :: array to write, arr(:,:,nNzdim,:,:)
126 C irecord (integer) :: record number to write
127 C myIter (integer) :: time step number
128 C myThid (integer) :: thread identifier
129 C
130 C Routine now calls MDS_WRITE_FIELD, just a way to add 2 extra arguments
131 C to the argument list. The 1rst new argument is to make the difference between
132 C the vertical dimension (3rd dimension) of an array and the number of levels
133 C the output routine should process. This routine assumes they are the same.
134 C The 2nd new argument (useCurrentDir=.FALSE.) allows to write files to
135 C the "mdsioLocalDir" directory (if it is set).
136
137 IMPLICIT NONE
138 C Global variables / common blocks
139 #include "SIZE.h"
140 c #include "EEPARAMS.h"
141
142 C Routine arguments
143 CHARACTER*(*) fName
144 INTEGER filePrec
145 LOGICAL globalFile
146 CHARACTER*(2) arrType
147 INTEGER nNz
148 _RL arr(1-oLx:sNx+oLx,1-oLy:sNy+oLy,nNz,nSx,nSy)
149 INTEGER irecord
150 INTEGER myIter
151 INTEGER myThid
152 C ------------------------------------------------------------------
153 CALL MDS_WRITE_FIELD(
154 I fName, filePrec, globalFile, .FALSE.,
155 I arrType, nNz, nNz, arr, irecord,
156 I myIter, myThid )
157 C ------------------------------------------------------------------
158 RETURN
159 END
160
161 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
162
163 SUBROUTINE MDSWRITEFIELD_LOC(
164 I fName,
165 I filePrec,
166 I globalFile,
167 I arrType,
168 I nNz,
169 I arr,
170 I irecord,
171 I myIter,
172 I myThid )
173 C
174 C Arguments:
175 C
176 C fName (string) :: base name for file to write
177 C filePrec (integer) :: number of bits per word in file (32 or 64)
178 C globalFile (logical):: selects between writing a global or tiled file
179 C arrType (char(2)) :: declaration of "arr": either "RS" or "RL"
180 C nNz (integer) :: size of third dimension: normally either 1 or Nr
181 C arr ( RS/RL ) :: array to write, arr(:,:,nNzdim,:,:)
182 C irecord (integer) :: record number to write
183 C myIter (integer) :: time step number
184 C myThid (integer) :: thread identifier
185 C
186 C Routine now calls mdswritefield_new, just a way to add 2 extra arguments
187 C to the argument list. The 1rst new argument is to make the difference between
188 C the vertical dimension (3rd dimension) of an array and the number of levels
189 C the output routine should process. This routine assumes they are the same.
190 C The 2nd new argument (useCurrentDir=.TRUE.) forces to ignore the
191 C "mdsioLocalDir" parameter and to always write to the current directory.
192
193 implicit none
194 C Global variables / common blocks
195 #include "SIZE.h"
196 c #include "EEPARAMS.h"
197
198 C Routine arguments
199 CHARACTER*(*) fName
200 INTEGER filePrec
201 LOGICAL globalFile
202 CHARACTER*(2) arrType
203 INTEGER nNz
204 _RL arr(1-oLx:sNx+oLx,1-oLy:sNy+oLy,nNz,nSx,nSy)
205 INTEGER irecord
206 INTEGER myIter
207 INTEGER myThid
208 C ------------------------------------------------------------------
209 CALL MDS_WRITE_FIELD(
210 I fName, filePrec, globalFile, .TRUE.,
211 I arrType, nNz, nNz, arr, irecord,
212 I myIter, myThid )
213 C ------------------------------------------------------------------
214 RETURN
215 END

  ViewVC Help
Powered by ViewVC 1.1.22