/[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.12 - (show annotations) (download)
Tue Dec 30 00:14:05 2008 UTC (15 years, 6 months ago) by jahn
Branch: MAIN
Changes since 1.11: +5 -1 lines
comment out subroutines if not used to save memory

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

  ViewVC Help
Powered by ViewVC 1.1.22