/[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.10 - (show annotations) (download)
Wed Jun 7 21:13:46 2006 UTC (18 years ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint59, checkpoint58y_post, checkpoint58t_post, checkpoint58m_post, checkpoint60, checkpoint61, checkpoint58w_post, checkpoint58o_post, checkpoint58p_post, checkpoint58q_post, mitgcm_mapl_00, checkpoint58r_post, checkpoint58n_post, checkpoint59q, checkpoint59p, checkpoint59r, checkpoint59e, checkpoint59d, checkpoint59g, checkpoint59f, checkpoint59a, checkpoint59c, checkpoint59b, checkpoint59m, checkpoint59l, checkpoint59o, checkpoint59n, checkpoint59i, checkpoint59h, checkpoint59k, checkpoint58k_post, checkpoint58v_post, checkpoint58l_post, checkpoint58x_post, checkpoint59j, checkpoint58j_post, checkpoint58i_post, checkpoint58u_post, checkpoint58s_post, checkpoint61d, checkpoint61b, checkpoint61c, checkpoint61a
Changes since 1.9: +2 -2 lines
One more.

1 C $Header: /u/gcmpack/MITgcm/pkg/mdsio/mdsio_readvector.F,v 1.9 2006/06/07 20:45:48 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 _RL 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*(MAX_LEN_FNAM) 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,'(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(1:IL)
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,'(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(1:IL+5)
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,'(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(1:pIL+13)
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,'(4a)')
178 & ' MDSREADVECTOR: opening file: ',fName(1:IL),
179 & ' , ',dataFName(1:pIL+13)
180 call print_message( msgbuf, standardmessageunit,
181 & SQUEEZE_RIGHT , mythid)
182 write(msgbuf,'(a)')
183 & ' MDSREADVECTOR: un-active tiles not implemented yet'
184 call print_error( msgbuf, mythid )
185 stop 'ABNORMAL END: S/R MDSREADVECTOR'
186 endif
187 endif
188 if (fileIsOpen) then
189 if (globalFile) then
190 iG = myXGlobalLo-1+(bi-1)*sNx
191 jG = myYGlobalLo-1+(bj-1)*sNy
192 irec = 1 + int(iG/sNx) + (jG/sNy)*nSx*nPx +
193 & (irecord-1)*nSx*nPx*nSy*nPy
194 else
195 iG = 0
196 jG = 0
197 irec = irecord
198 endif
199 if (filePrec .eq. precFloat32) then
200 call MDS_READ_RS_VEC( dUnit, irec, narr, arr, myThid )
201 elseif (filePrec .eq. precFloat64) then
202 call MDS_READ_RL_VEC( dUnit, irec, narr, arr, myThid )
203 else
204 write(msgbuf,'(a)')
205 & ' MDSREADVECTOR: illegal value for filePrec'
206 call print_error( msgbuf, mythid )
207 stop 'ABNORMAL END: S/R MDSREADVECTOR'
208 endif
209 if (.NOT. globalFile) then
210 close( dUnit )
211 fileIsOpen = .FALSE.
212 endif
213 endif
214 C End of bi,bj loops
215 ce enddo
216 ce enddo
217
218 C If global file was opened then close it
219 if (fileIsOpen .AND. globalFile) then
220 close( dUnit )
221 fileIsOpen = .FALSE.
222 endif
223
224 _END_MASTER( myThid )
225
226 endif
227 c endif ( .not. useSingleCPUIO )
228
229
230 C ------------------------------------------------------------------
231
232
233 if ( useSingleCPUIO ) then
234
235 C master thread of process 0, only, opens a global file
236 _BEGIN_MASTER( myThid )
237 #ifdef ALLOW_USE_MPI
238 IF( mpiMyId .EQ. 0 ) THEN
239 #else
240 IF ( .TRUE. ) THEN
241 #endif /* ALLOW_USE_MPI */
242
243 C Check first for global file with simple name (ie. fName)
244 dataFName = fName
245 inquire( file=dataFname, exist=exst )
246 if (exst) globalFile = .TRUE.
247
248 C If negative check for global file with MDS name (ie. fName.data)
249 if (.NOT. globalFile) then
250 write(dataFname,'(2a)') fName(1:IL),'.data'
251 inquire( file=dataFname, exist=exst )
252 if (exst) globalFile = .TRUE.
253 endif
254
255 C If global file is visible to process 0, then open it here.
256 C Otherwise stop program.
257 if ( globalFile) then
258 length_of_rec=MDS_RECLEN( filePrec, vec_size, mythid )
259 open( dUnit, file=dataFName, status='old',
260 & access='direct', recl=length_of_rec )
261 else
262 write(msgbuf,'(2a)')
263 & ' MDSREADFIELD: filename: ',dataFName(1:IL)
264 call print_message( msgbuf, standardmessageunit,
265 & SQUEEZE_RIGHT , mythid)
266 call print_error( msgbuf, mythid )
267 write(msgbuf,'(a)')
268 & ' MDSREADFIELD: File does not exist'
269 call print_message( msgbuf, standardmessageunit,
270 & SQUEEZE_RIGHT , mythid)
271 call print_error( msgbuf, mythid )
272 stop 'ABNORMAL END: S/R MDSREADFIELD'
273 endif
274
275 ENDIF
276 _END_MASTER( myThid )
277
278 DO k=1,1
279
280 _BEGIN_MASTER( myThid )
281 #ifdef ALLOW_USE_MPI
282 IF( mpiMyId .EQ. 0 ) THEN
283 #else
284 IF ( .TRUE. ) THEN
285 #endif /* ALLOW_USE_MPI */
286 irec = irecord
287 if (filePrec .eq. precFloat32) then
288 read(dUnit,rec=irec) xy_buffer_r4
289 #ifdef _BYTESWAPIO
290 call MDS_BYTESWAPR4( vec_size, xy_buffer_r4 )
291 #endif
292 #if defined(ALLOW_EXCH2) && !defined(MISSING_TILE_IO)
293 c
294 #else /* defined(ALLOW_EXCH2) && !defined(MISSING_TILE_IO) */
295 DO L=1,narr*nPx*nPy
296 global(L) = xy_buffer_r4(L)
297 ENDDO
298 #endif /* defined(ALLOW_EXCH2) && !defined(MISSING_TILE_IO) */
299 elseif (filePrec .eq. precFloat64) then
300 read(dUnit,rec=irec) xy_buffer_r8
301 #ifdef _BYTESWAPIO
302 call MDS_BYTESWAPR8( vec_size, xy_buffer_r8 )
303 #endif
304 #if defined(ALLOW_EXCH2) && !defined(MISSING_TILE_IO)
305 c
306 #else /* defined(ALLOW_EXCH2) && !defined(MISSING_TILE_IO) */
307 DO L=1,narr*nPx*nPy
308 global(L) = xy_buffer_r8(L)
309 ENDDO
310 #endif /* defined(ALLOW_EXCH2) && !defined(MISSING_TILE_IO) */
311 else
312 write(msgbuf,'(a)')
313 & ' MDSREADFIELD: illegal value for filePrec'
314 call print_error( msgbuf, mythid )
315 stop 'ABNORMAL END: S/R MDSREADFIELD'
316 endif
317 ENDIF
318 _END_MASTER( myThid )
319 CALL SCATTER_VECTOR( narr,global,local,mythid )
320 if (arrType .eq. 'RS') then
321 call PASStoRSvector( local,arr,narr,k,nNz,mythid )
322 elseif (arrType .eq. 'RL') then
323 call PASStoRLvector( local,arr,narr,k,nNz,mythid )
324 else
325 write(msgbuf,'(a)')
326 & ' MDSREADFIELD: illegal value for arrType'
327 call print_error( msgbuf, mythid )
328 stop 'ABNORMAL END: S/R MDSREADFIELD'
329 endif
330
331 ENDDO
332 c ENDDO k=1,nNz
333
334 _BEGIN_MASTER( myThid )
335 close( dUnit )
336 _END_MASTER( myThid )
337
338 endif
339 c endif ( useSingleCPUIO )
340
341 return
342 end
343
344
345 C ==================================================================
346
347 subroutine passToRSvector(local,arr,narr,k,nNz,mythid)
348 implicit none
349 #include "EEPARAMS.h"
350 #include "SIZE.h"
351
352 integer narr
353 _RL local(narr)
354 _RS arr(narr)
355 integer k,nNz
356 integer mythid
357
358 integer L
359
360 DO L=1,narr
361 arr(L) = local(L)
362 ENDDO
363
364 return
365 end
366
367 subroutine passToRLvector(local,arr,narr,k,nNz,mythid)
368 implicit none
369 #include "EEPARAMS.h"
370 #include "SIZE.h"
371
372 integer narr
373 _RL local(narr)
374 _RL arr(narr)
375 integer k,nNz
376 integer mythid
377
378 integer L
379
380 DO L=1,narr
381 arr(L) = local(L)
382 ENDDO
383
384 return
385 end

  ViewVC Help
Powered by ViewVC 1.1.22