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

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

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


Revision 1.7 - (show annotations) (download)
Fri Aug 19 18:01:29 2005 UTC (18 years, 10 months ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint57s_post, checkpoint57r_post, checkpoint57t_post, checkpoint57v_post, checkpint57u_post, checkpoint57q_post, checkpoint57w_post
Changes since 1.6: +2 -2 lines
Fixed [data,meta]FName initialization.

1 C $Header: /u/gcmpack/MITgcm/pkg/mdsio/mdsio_readvector.F,v 1.6 2005/07/20 20:01:46 heimbach Exp $
2 C $Name: $
3
4 #include "MDSIO_OPTIONS.h"
5
6 SUBROUTINE MDSREADVECTOR(
7 I fName,
8 I filePrec,
9 I arrType,
10 I narr,
11 O arr,
12 I bi,
13 I bj,
14 I irecord,
15 I myThid )
16 C
17 C Arguments:
18 C
19 C fName string base name for file to read
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 narr integer size of third dimension: normally either 1 or Nr
23 C arr RS/RL array to read into, arr(narr)
24 ce bi integer x tile index
25 ce bj integer y tile index
26 C irecord integer record number to read
27 C myThid integer thread identifier
28 C
29 C Created: 03/26/99 eckert@mit.edu
30 C Modified: 03/29/99 adcroft@mit.edu + eckert@mit.edu
31 C Fixed to work work with _RS and _RL declarations
32 C Modified: 07/27/99 eckert@mit.edu
33 C Customized for state estimation (--> active_file_control.F)
34
35 implicit none
36 C Global variables / common blocks
37 #include "SIZE.h"
38 #include "EEPARAMS.h"
39 #include "PARAMS.h"
40 #include "EESUPPORT.h"
41
42 C Routine arguments
43 character*(*) fName
44 integer filePrec
45 character*(2) arrType
46 integer narr
47 Real arr(narr)
48 integer irecord
49 integer myThid
50 ce
51 integer bi,bj
52 ce
53
54 C Functions
55 integer ILNBLNK
56 integer MDS_RECLEN
57 C Local variables
58 character*(128) dataFName,pfName
59 integer iG,jG,irec,dUnit,IL,pIL
60 logical exst
61 logical globalFile,fileIsOpen
62 integer length_of_rec
63 character*(max_len_mbuf) msgbuf
64
65 cph(
66 cph Deal with useSingleCpuIO
67 cph Not extended here for EXCH2
68 integer k,l
69 integer nNz
70 integer vec_size
71 Real*4 xy_buffer_r4(narr*nPx*nPy)
72 Real*8 xy_buffer_r8(narr*nPx*nPy)
73 Real*8 global (narr*nPx*nPy)
74 _RL local(narr)
75 cph)
76 C ------------------------------------------------------------------
77
78 vec_size = narr*nPx*nPy
79 nNz = 1
80
81 C Only do I/O if I am the master thread
82 _BEGIN_MASTER( myThid )
83
84 C Record number must be >= 1
85 if (irecord .LT. 1) then
86 write(msgbuf,'(a,i9.8)')
87 & ' MDSREADVECTOR: argument irecord = ',irecord
88 call print_message( msgbuf, standardmessageunit,
89 & SQUEEZE_RIGHT , mythid)
90 write(msgbuf,'(a)')
91 & ' MDSREADVECTOR: invalid value for irecord'
92 call print_error( msgbuf, mythid )
93 stop 'ABNORMAL END: S/R MDSREADVECTOR'
94 endif
95
96 C Assume nothing
97 globalFile = .FALSE.
98 fileIsOpen = .FALSE.
99 IL = ILNBLNK( fName )
100 pIL = ILNBLNK( mdsioLocalDir )
101
102 C Assign special directory
103 if ( mdsioLocalDir .NE. ' ' ) then
104 write(pFname(1:128),'(2a)')
105 & mdsioLocalDir(1:pIL), fName(1:IL)
106 else
107 pFname= fName
108 endif
109 pIL=ILNBLNK( pfName )
110
111 C Assign a free unit number as the I/O channel for this routine
112 call MDSFINDUNIT( dUnit, mythid )
113
114 if ( .not. useSingleCPUIO ) then
115
116 C Check first for global file with simple name (ie. fName)
117 dataFName = fName
118 inquire( file=dataFname, exist=exst )
119 if (exst) then
120 if ( debugLevel .GE. debLevB ) then
121 write(msgbuf,'(a,a)')
122 & ' MDSREADVECTOR: opening global file: ',dataFName
123 call print_message( msgbuf, standardmessageunit,
124 & SQUEEZE_RIGHT , mythid)
125 endif
126 globalFile = .TRUE.
127 endif
128
129 C If negative check for global file with MDS name (ie. fName.data)
130 if (.NOT. globalFile) then
131 write(dataFname(1:128),'(2a)') fName(1:IL),'.data'
132 inquire( file=dataFname, exist=exst )
133 if (exst) then
134 if ( debugLevel .GE. debLevB ) then
135 write(msgbuf,'(a,a)')
136 & ' MDSREADVECTOR: opening global file: ',dataFName
137 call print_message( msgbuf, standardmessageunit,
138 & SQUEEZE_RIGHT , mythid)
139 endif
140 globalFile = .TRUE.
141 endif
142 endif
143
144 C If we are reading from a global file then we open it here
145 if (globalFile) then
146 length_of_rec=MDS_RECLEN( filePrec, narr, mythid )
147 open( dUnit, file=dataFName, status='old',
148 & access='direct', recl=length_of_rec )
149 fileIsOpen=.TRUE.
150 endif
151
152 C Loop over all tiles
153 ce do bj=1,nSy
154 ce do bi=1,nSx
155 C If we are reading from a tiled MDS file then we open each one here
156 if (.NOT. globalFile) then
157 iG=bi+(myXGlobalLo-1)/sNx ! Kludge until unstructered tiles
158 jG=bj+(myYGlobalLo-1)/sNy ! Kludge until unstructered tiles
159 write(dataFname(1:128),'(2a,i3.3,a,i3.3,a)')
160 & pfName(1:pIL),'.',iG,'.',jG,'.data'
161 inquire( file=dataFname, exist=exst )
162 C Of course, we only open the file if the tile is "active"
163 C (This is a place-holder for the active/passive mechanism)
164 if (exst) then
165 if ( debugLevel .GE. debLevB ) then
166 write(msgbuf,'(a,a)')
167 & ' MDSREADVECTOR: opening file: ',dataFName
168 call print_message( msgbuf, standardmessageunit,
169 & SQUEEZE_RIGHT , mythid)
170 endif
171 length_of_rec=MDS_RECLEN( filePrec, narr, mythid )
172 open( dUnit, file=dataFName, status='old',
173 & access='direct', recl=length_of_rec )
174 fileIsOpen=.TRUE.
175 else
176 fileIsOpen=.FALSE.
177 write(msgbuf,'(3a)')
178 & ' MDSREADVECTOR: opening file: ',dataFName,pfName
179 call print_message( msgbuf, standardmessageunit,
180 & SQUEEZE_RIGHT , mythid)
181 write(msgbuf,'(a)')
182 & ' MDSREADVECTOR: un-active tiles not implemented yet'
183 call print_error( msgbuf, mythid )
184 stop 'ABNORMAL END: S/R MDSREADVECTOR'
185 endif
186 endif
187 if (fileIsOpen) then
188 if (globalFile) then
189 iG = myXGlobalLo-1+(bi-1)*sNx
190 jG = myYGlobalLo-1+(bj-1)*sNy
191 irec = 1 + int(iG/sNx) + (jG/sNy)*nSx*nPx +
192 & (irecord-1)*nSx*nPx*nSy*nPy
193 else
194 iG = 0
195 jG = 0
196 irec = irecord
197 endif
198 if (filePrec .eq. precFloat32) then
199 call MDS_READ_RS_VEC( dUnit, irec, narr, arr, myThid )
200 elseif (filePrec .eq. precFloat64) then
201 call MDS_READ_RL_VEC( dUnit, irec, narr, arr, myThid )
202 else
203 write(msgbuf,'(a)')
204 & ' MDSREADVECTOR: illegal value for filePrec'
205 call print_error( msgbuf, mythid )
206 stop 'ABNORMAL END: S/R MDSREADVECTOR'
207 endif
208 if (.NOT. globalFile) then
209 close( dUnit )
210 fileIsOpen = .FALSE.
211 endif
212 endif
213 C End of bi,bj loops
214 ce enddo
215 ce enddo
216
217 C If global file was opened then close it
218 if (fileIsOpen .AND. globalFile) then
219 close( dUnit )
220 fileIsOpen = .FALSE.
221 endif
222
223 _END_MASTER( myThid )
224
225 endif
226 c endif ( .not. useSingleCPUIO )
227
228
229 C ------------------------------------------------------------------
230
231
232 if ( useSingleCPUIO ) then
233
234 C master thread of process 0, only, opens a global file
235 _BEGIN_MASTER( myThid )
236 #ifdef ALLOW_USE_MPI
237 IF( mpiMyId .EQ. 0 ) THEN
238 #else
239 IF ( .TRUE. ) THEN
240 #endif /* ALLOW_USE_MPI */
241
242 C Check first for global file with simple name (ie. fName)
243 dataFName = fName
244 inquire( file=dataFname, exist=exst )
245 if (exst) globalFile = .TRUE.
246
247 C If negative check for global file with MDS name (ie. fName.data)
248 if (.NOT. globalFile) then
249 write(dataFname(1:128),'(2a)') fName(1:IL),'.data'
250 inquire( file=dataFname, exist=exst )
251 if (exst) globalFile = .TRUE.
252 endif
253
254 C If global file is visible to process 0, then open it here.
255 C Otherwise stop program.
256 if ( globalFile) then
257 length_of_rec=MDS_RECLEN( filePrec, vec_size, mythid )
258 open( dUnit, file=dataFName, status='old',
259 & access='direct', recl=length_of_rec )
260 else
261 write(msgbuf,'(2a)') ' MDSREADFIELD: filename: ',dataFName
262 call print_message( msgbuf, standardmessageunit,
263 & SQUEEZE_RIGHT , mythid)
264 call print_error( msgbuf, mythid )
265 write(msgbuf,'(a)')
266 & ' MDSREADFIELD: File does not exist'
267 call print_message( msgbuf, standardmessageunit,
268 & SQUEEZE_RIGHT , mythid)
269 call print_error( msgbuf, mythid )
270 stop 'ABNORMAL END: S/R MDSREADFIELD'
271 endif
272
273 ENDIF
274 _END_MASTER( myThid )
275
276 DO k=1,1
277
278 _BEGIN_MASTER( myThid )
279 #ifdef ALLOW_USE_MPI
280 IF( mpiMyId .EQ. 0 ) THEN
281 #else
282 IF ( .TRUE. ) THEN
283 #endif /* ALLOW_USE_MPI */
284 irec = irecord
285 if (filePrec .eq. precFloat32) then
286 read(dUnit,rec=irec) xy_buffer_r4
287 #ifdef _BYTESWAPIO
288 call MDS_BYTESWAPR4( vec_size, xy_buffer_r4 )
289 #endif
290 #if defined(ALLOW_EXCH2) && !defined(MISSING_TILE_IO)
291 c
292 #else /* defined(ALLOW_EXCH2) && !defined(MISSING_TILE_IO) */
293 DO L=1,narr*nPx*nPy
294 global(L) = xy_buffer_r4(L)
295 ENDDO
296 #endif /* defined(ALLOW_EXCH2) && !defined(MISSING_TILE_IO) */
297 elseif (filePrec .eq. precFloat64) then
298 read(dUnit,rec=irec) xy_buffer_r8
299 #ifdef _BYTESWAPIO
300 call MDS_BYTESWAPR8( vec_size, xy_buffer_r8 )
301 #endif
302 #if defined(ALLOW_EXCH2) && !defined(MISSING_TILE_IO)
303 c
304 #else /* defined(ALLOW_EXCH2) && !defined(MISSING_TILE_IO) */
305 DO L=1,narr*nPx*nPy
306 global(L) = xy_buffer_r8(L)
307 ENDDO
308 #endif /* defined(ALLOW_EXCH2) && !defined(MISSING_TILE_IO) */
309 else
310 write(msgbuf,'(a)')
311 & ' MDSREADFIELD: illegal value for filePrec'
312 call print_error( msgbuf, mythid )
313 stop 'ABNORMAL END: S/R MDSREADFIELD'
314 endif
315 ENDIF
316 _END_MASTER( myThid )
317 CALL SCATTER_VECTOR( narr,global,local,mythid )
318 if (arrType .eq. 'RS') then
319 call PASStoRSvector( local,arr,narr,k,nNz,mythid )
320 elseif (arrType .eq. 'RL') then
321 call PASStoRLvector( local,arr,narr,k,nNz,mythid )
322 else
323 write(msgbuf,'(a)')
324 & ' MDSREADFIELD: illegal value for arrType'
325 call print_error( msgbuf, mythid )
326 stop 'ABNORMAL END: S/R MDSREADFIELD'
327 endif
328
329 ENDDO
330 c ENDDO k=1,nNz
331
332 _BEGIN_MASTER( myThid )
333 close( dUnit )
334 _END_MASTER( myThid )
335
336 endif
337 c endif ( useSingleCPUIO )
338
339 return
340 end
341
342
343 C ==================================================================
344
345 subroutine passToRSvector(local,arr,narr,k,nNz,mythid)
346 implicit none
347 #include "EEPARAMS.h"
348 #include "SIZE.h"
349
350 integer narr
351 _RL local(narr)
352 integer i,j,k,l,bi,bj,nNz
353 _RS arr(narr)
354 integer mythid
355
356 DO L=1,narr
357 arr(L) = local(L)
358 ENDDO
359
360 return
361 end
362
363 subroutine passToRLvector(local,arr,narr,k,nNz,mythid)
364 implicit none
365 #include "EEPARAMS.h"
366 #include "SIZE.h"
367
368 integer narr
369 _RL local(narr)
370 integer i,j,k,l,bi,bj,nNz
371 _RL arr(narr)
372 integer mythid
373
374 DO L=1,narr
375 arr(L) = local(L)
376 ENDDO
377
378 return
379 end

  ViewVC Help
Powered by ViewVC 1.1.22