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

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

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


Revision 1.20 - (show annotations) (download)
Thu Dec 23 02:41:47 2010 UTC (13 years, 4 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint62v, checkpoint62u, checkpoint62t, checkpoint62s, checkpoint62r, checkpoint62q, checkpoint62w, checkpoint62z, checkpoint62y, checkpoint62x, checkpoint63g, checkpoint63, checkpoint63h, checkpoint63i, checkpoint63j, checkpoint63k, checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63a, checkpoint63b, checkpoint63c
Changes since 1.19: +12 -7 lines
- change arg. list of S/R MDSIO_PASS_R4/8toRL/S ;
- change barrier call for safe multi-threads access to 3-D shared buffer.

1 C $Header: /u/gcmpack/MITgcm/pkg/mdsio/mdsio_writelocal.F,v 1.19 2010/08/24 14:56:24 jmc Exp $
2 C $Name: $
3
4 #include "MDSIO_OPTIONS.h"
5
6 CBOP
7 C !ROUTINE: MDS_WRITE_FIELD
8 C !INTERFACE:
9 SUBROUTINE MDS_WRITELOCAL(
10 I fName,
11 I filePrec,
12 I globFile,
13 I arrType,
14 I nNz,
15 I fldRL, fldRS,
16 I biArg, bjArg,
17 I irecord,
18 I myIter,
19 I myThArg )
20
21 C !DESCRIPTION:
22 C Arguments:
23 C
24 C fName (string) :: base name for file to write
25 C filePrec (integer) :: number of bits per word in file (32 or 64)
26 C globalFile (logical):: selects between writing a global or tiled file
27 C arrType (char(2)) :: which array (fldRL/RS) to write, either "RL" or "RS"
28 C nNz (integer) :: size of third dimension: normally either 1 or Nr
29 C fldRL ( RL ) :: array to write if arrType="RL", fldRL(:,:,nNz)
30 C fldRS ( RS ) :: array to write if arrType="RS", fldRS(:,:,nNz)
31 C biArg (integer) :: tile X-index argument
32 C bjArg (integer) :: tile Y-index argument
33 C irecord (integer) :: record number to write
34 C myIter (integer) :: time step number
35 C myThArg (integer) :: thread argument (= my Thread Id or = 0 to simply
36 C write 1 tile without thread synchronisation)
37 C
38 C MDS_WRITELOCAL write a local-tile array corresponding to tile biArg,bjArg
39 C of this Process. Threading: with myThArg=0 or when LOCBIN_IO_THREAD_SAFE
40 C is defined, go for a strait writing of this tile ; otherwise, use the
41 C shared buffer IO to store data from all threads, then synchronise and
42 C let the master thread write nThreads tiles. If multiple tiles per thread,
43 C will repeat this sequence each time this S/R is called by the master thread
44 C with a different biArg,biArg. IMPORTANT: 2nd case requires that all threads
45 C call this S/R and assumes symmetry in tiles per thread treatment.
46 C Convention regarding thread synchronisation (BARRIER): see mdsio_write_field.F
47 C MDS_WRITELOCAL creates either a file of the form "fName.data" and
48 C "fName.meta" if the logical flag "globalFile" is set true. Otherwise
49 C it creates MDS tiled files of the form "fName.xxx.yyy.data" and
50 C "fName.xxx.yyy.meta". A meta-file is always created.
51 C Currently, the meta-files are not read because it is difficult
52 C to parse files in fortran. We should read meta information before
53 C adding records to an existing multi-record file.
54 C The precision of the file is decsribed by filePrec, set either
55 C to floatPrec32 or floatPrec64. The char*(2) string arrType, either
56 C "RL" or "RS", selects which array is written, either fldRL or fldRS.
57 C nNz allows for both 2-D and 3-D arrays to be handled. nNz=1 implies
58 C a 2-D model field and nNz=Nr implies a 3-D model field.
59 C irecord is the record number to be written and must be >= 1.
60 C NOTE: It is currently assumed that the highest record number in the file
61 C was the last record written. Nor is there a consistency check between the
62 C routine arguments and file, i.e., if you write record 2 after record 4
63 C the meta information will record the number of records to be 2. This,
64 C again, is because we have read the meta information. To be fixed.
65 C
66 C Created: 03/16/99 adcroft@mit.edu
67 C Changed: 05/31/00 heimbach@mit.edu
68 C open(dUnit, ..., status='old', ... -> status='unknown'
69 CEOP
70
71 C !USES:
72 IMPLICIT NONE
73 C Global variables / common blocks
74 #include "SIZE.h"
75 #include "EEPARAMS.h"
76 #include "PARAMS.h"
77 #ifdef ALLOW_EXCH2
78 #include "W2_EXCH2_SIZE.h"
79 #include "W2_EXCH2_TOPOLOGY.h"
80 #include "W2_EXCH2_PARAMS.h"
81 #endif /* ALLOW_EXCH2 */
82 #ifdef ALLOW_FIZHI
83 # include "fizhi_SIZE.h"
84 #endif /* ALLOW_FIZHI */
85 #include "MDSIO_BUFF_3D.h"
86
87 C !INPUT PARAMETERS:
88 CHARACTER*(*) fName
89 INTEGER filePrec
90 LOGICAL globFile
91 CHARACTER*(2) arrType
92 INTEGER nNz
93 _RL fldRL(*)
94 _RS fldRS(*)
95 INTEGER biArg, bjArg
96 INTEGER irecord
97 INTEGER myIter
98 INTEGER myThArg
99 C !OUTPUT PARAMETERS:
100
101 C !FUNCTIONS
102 INTEGER ILNBLNK
103 INTEGER MDS_RECLEN
104 EXTERNAL ILNBLNK, MDS_RECLEN
105
106 C !LOCAL VARIABLES:
107 C bBij :: base shift in Buffer index for tile bi,bj
108 CHARACTER*(MAX_LEN_FNAM) dataFName,metaFName
109 CHARACTER*(MAX_LEN_MBUF) msgBuf
110 LOGICAL fileIsOpen
111 LOGICAL globalFile
112 LOGICAL iAmDoingIO
113 INTEGER xSize, ySize
114 INTEGER iG,jG
115 INTEGER i1,i2,i,j,k
116 INTEGER irec,dUnit,IL
117 INTEGER dimList(3,3),nDims, map2gl(2)
118 INTEGER length_of_rec
119 INTEGER bBij
120 INTEGER bi, bj
121 INTEGER myThid, ith, nthLoop
122 INTEGER tNx, tNy, global_nTx
123 INTEGER tBx, tBy, iGjLoc, jGjLoc
124 #ifdef ALLOW_EXCH2
125 INTEGER tN
126 #endif /* ALLOW_EXCH2 */
127 _RL dummyRL(1)
128 CHARACTER*8 blank8c
129
130 DATA dummyRL(1) / 0. _d 0 /
131 DATA blank8c / ' ' /
132
133 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
134 C Set dimensions:
135 xSize = Nx
136 ySize = Ny
137 #ifdef ALLOW_EXCH2
138 IF ( W2_useE2ioLayOut ) THEN
139 xSize = exch2_global_Nx
140 ySize = exch2_global_Ny
141 ENDIF
142 #endif /* ALLOW_EXCH2 */
143
144 C- default:
145 iGjLoc = 0
146 jGjLoc = 1
147
148 IL = ILNBLNK( fName )
149 globalFile = globFile
150 myThid = MAX(myThArg,1)
151 #ifdef LOCBIN_IO_THREAD_SAFE
152 nthLoop = 1
153 iAmDoingIO = .TRUE.
154 #else /* LOCBIN_IO_THREAD_SAFE */
155 nthLoop = nThreads
156 IF ( myThArg.EQ.0 ) nthLoop = 1
157 iAmDoingIO = .FALSE.
158 IF ( myThid.EQ.1 ) iAmDoingIO = .TRUE.
159 #endif /* LOCBIN_IO_THREAD_SAFE */
160
161 IF ( nThreads.GT.1 .AND. globFile ) THEN
162 C- do not assume safe Muti-Threaded Binary IO to a single global file
163 C => switch to tiled file
164 globalFile = .FALSE.
165 IF ( debugLevel.GE.debLevA .AND. IL.GT.0 ) THEN
166 WRITE(msgBuf,'(A,I10,A,2I5,A)')
167 & 'MDS_WRITELOCAL (it=', myIter, ' ; bi,bj=', biArg,bjArg,
168 & ' ): No global-file multi-threaded IO'
169 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
170 & SQUEEZE_RIGHT , myThid )
171 WRITE(msgBuf,'(2A)')
172 & 'MDS_WRITELOCAL: => write tiled file: ', fName(1:IL)
173 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
174 & SQUEEZE_RIGHT , myThid )
175 ENDIF
176 ENDIF
177
178 C Record number must be >= 1
179 IF (irecord .LT. 1) THEN
180 WRITE(msgBuf,'(3A,I10)')
181 & ' MDS_WRITELOCAL: file="', fName(1:IL), '" , iter=', myIter
182 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
183 & SQUEEZE_RIGHT , myThid )
184 WRITE(msgBuf,'(A,I9.8)')
185 & ' MDS_WRITELOCAL: argument irecord = ',irecord
186 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
187 & SQUEEZE_RIGHT , myThid )
188 WRITE(msgBuf,'(A)')
189 & ' MDS_WRITELOCAL: invalid value for irecord'
190 CALL PRINT_ERROR( msgBuf, myThid )
191 STOP 'ABNORMAL END: S/R MDS_WRITELOCAL'
192 ENDIF
193 C check for 3-D Buffer size:
194 IF ( .NOT.useSingleCpuIO .AND. nNz.GT.size3dBuf ) THEN
195 WRITE(msgBuf,'(3A,I10)')
196 & ' MDS_WRITELOCAL: file="', fName(1:IL), '" , iter=', myIter
197 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
198 & SQUEEZE_RIGHT , myThid )
199 WRITE(msgBuf,'(3(A,I6))')
200 & ' MDS_WRITELOCAL: Nb Lev to write =', nNz,
201 & ' >', size3dBuf, ' = buffer 3rd Dim'
202 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
203 & SQUEEZE_RIGHT , myThid )
204 WRITE(msgBuf,'(A)')
205 & ' MDS_WRITELOCAL: buffer 3rd Dim. too small'
206 CALL PRINT_ERROR( msgBuf, myThid )
207 WRITE(msgBuf,'(A)')
208 & ' increase "size3dBuf" in "MDSIO_BUFF_3D.h" and recompile'
209 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
210 & SQUEEZE_RIGHT , myThid )
211 c CALL ALL_PROC_DIE( myThid )
212 STOP 'ABNORMAL END: S/R MDS_WRITELOCAL'
213 ENDIF
214
215 C Wait for all thread to finish. This prevents other threads (e.g., master)
216 C to continue to acces 3-D buffer while this thread is filling it.
217 IF ( nthLoop.GT.1 ) CALL BAR2( myThid )
218
219 C-------------------------------------------------
220 C--- Copy from fldRL/RS to 3-D buffer (multi-threads):
221 IF ( filePrec.EQ.precFloat32 ) THEN
222 IF ( arrType.EQ.'RS' ) THEN
223 CALL MDS_PASS_R4toRS( shared3dBuf_r4, fldRS,
224 I 0, 0, nNz, 1, nNz, biArg, bjArg, .FALSE., myThid )
225 ELSEIF ( arrType.EQ.'RL' ) THEN
226 CALL MDS_PASS_R4toRL( shared3dBuf_r4, fldRL,
227 I 0, 0, nNz, 1, nNz, biArg, bjArg, .FALSE., myThid )
228 ELSE
229 WRITE(msgBuf,'(A)')
230 & ' MDS_WRITELOCAL: illegal value for arrType'
231 CALL PRINT_ERROR( msgBuf, myThid )
232 STOP 'ABNORMAL END: S/R MDS_WRITELOCAL'
233 ENDIF
234 ELSEIF ( filePrec.EQ.precFloat64 ) THEN
235 IF ( arrType.EQ.'RS' ) THEN
236 CALL MDS_PASS_R8toRS( shared3dBuf_r8, fldRS,
237 I 0, 0, nNz, 1, nNz, biArg, bjArg, .FALSE., myThid )
238 ELSEIF ( arrType.EQ.'RL' ) THEN
239 CALL MDS_PASS_R8toRL( shared3dBuf_r8, fldRL,
240 I 0, 0, nNz, 1, nNz, biArg, bjArg, .FALSE., myThid )
241 ELSE
242 WRITE(msgBuf,'(A)')
243 & ' MDS_WRITELOCAL: illegal value for arrType'
244 CALL PRINT_ERROR( msgBuf, myThid )
245 STOP 'ABNORMAL END: S/R MDS_WRITELOCAL'
246 ENDIF
247 ELSE
248 WRITE(msgBuf,'(A)')
249 & ' MDS_WRITELOCAL: illegal value for filePrec'
250 CALL PRINT_ERROR( msgBuf, myThid )
251 STOP 'ABNORMAL END: S/R MDS_WRITELOCAL'
252 ENDIF
253 C-------------------------------------------------
254
255 C Wait for all threads to finish filling shared buffer
256 IF ( nthLoop.GT.1 ) CALL BAR2( myThid )
257
258 C Only do I/O if I am the master thread
259 IF ( iAmDoingIO ) THEN
260
261 C Assume nothing
262 fileIsOpen=.FALSE.
263
264 C Assign a free unit number as the I/O channel for this routine
265 CALL MDSFINDUNIT( dUnit, myThid )
266
267 C If we are writing to a global file then we open it here
268 IF (globalFile) THEN
269 WRITE(dataFName,'(2A)') fName(1:IL),'.data'
270 length_of_rec = MDS_RECLEN( filePrec, sNx, myThid )
271 IF (irecord .EQ. 1) THEN
272 OPEN( dUnit, file=dataFName, status='unknown',
273 & access='direct', recl=length_of_rec )
274 ELSE
275 OPEN( dUnit, file=dataFName, status=_OLD_STATUS,
276 & access='direct', recl=length_of_rec )
277 ENDIF
278 fileIsOpen=.TRUE.
279 ENDIF
280
281 C Loop over tiles
282 DO ith=1,nthLoop
283 bi = biArg + myBxLo(ith) - 1
284 bj = bjArg + myByLo(ith) - 1
285
286 bBij = sNx*sNy*nNz*( bi-1 + (bj-1)*nSx )
287 i1 = bBij + 1
288 #ifdef _BYTESWAPIO
289 IF ( filePrec.EQ.precFloat32 ) THEN
290 CALL MDS_BYTESWAPR4( sNx*sNy*nNz, shared3dBuf_r4(i1) )
291 ELSE
292 CALL MDS_BYTESWAPR8( sNx*sNy*nNz, shared3dBuf_r8(i1) )
293 ENDIF
294 #endif
295
296 tNx = sNx
297 tNy = sNy
298 global_nTx = xSize/sNx
299 tBx = myXGlobalLo-1 + (bi-1)*sNx
300 tBy = myYGlobalLo-1 + (bj-1)*sNy
301 #ifdef ALLOW_EXCH2
302 IF ( W2_useE2ioLayOut ) THEN
303 tN = W2_myTileList(bi,bj)
304 c global_nTx = exch2_global_Nx/sNx
305 tBx = exch2_txGlobalo(tN) - 1
306 tBy = exch2_tyGlobalo(tN) - 1
307 IF ( exch2_mydNx(tN) .GT. xSize ) THEN
308 C- face x-size larger than glob-size : fold it
309 iGjLoc = 0
310 jGjLoc = exch2_mydNx(tN) / xSize
311 ELSEIF ( exch2_tNy(tN) .GT. ySize ) THEN
312 C- tile y-size larger than glob-size : make a long line
313 iGjLoc = exch2_mydNx(tN)
314 jGjLoc = 0
315 ELSE
316 C- default (face fit into global-IO-array)
317 iGjLoc = 0
318 jGjLoc = 1
319 ENDIF
320 ENDIF
321 #endif /* ALLOW_EXCH2 */
322
323 IF (globalFile) THEN
324 C--- Case of 1 Global file:
325
326 DO k=1,nNz
327 DO j=1,sNy
328 C- compute record number:
329 irec = 1 + ( tBx + (j-1)*iGjLoc )/tNx
330 & + ( tBy + (j-1)*jGjLoc )*global_nTx
331 & + ( k-1 + (irecord-1)*nNz )*global_nTx*ySize
332 i1 = bBij + 1 + (j-1)*sNx + (k-1)*sNx*sNy
333 i2 = bBij + j*sNx + (k-1)*sNx*sNy
334 IF ( filePrec.EQ.precFloat32 ) THEN
335 WRITE(dUnit,rec=irec) (shared3dBuf_r4(i),i=i1,i2)
336 ELSE
337 WRITE(dUnit,rec=irec) (shared3dBuf_r8(i),i=i1,i2)
338 ENDIF
339 C End of j,k loops
340 ENDDO
341 ENDDO
342
343 ELSE
344 C--- Case of 1 file per tile (globalFile=F):
345
346 C If we are writing to a tiled MDS file then we open each one here
347 iG=bi+(myXGlobalLo-1)/sNx
348 jG=bj+(myYGlobalLo-1)/sNy
349 WRITE(dataFName,'(2A,I3.3,A,I3.3,A)')
350 & fName(1:IL),'.',iG,'.',jG,'.data'
351 length_of_rec = MDS_RECLEN( filePrec, sNx*sNy*nNz, myThid )
352 IF (irecord .EQ. 1) THEN
353 OPEN( dUnit, file=dataFName, status=_NEW_STATUS,
354 & access='direct', recl=length_of_rec )
355 ELSE
356 OPEN( dUnit, file=dataFName, status=_OLD_STATUS,
357 & access='direct', recl=length_of_rec )
358 ENDIF
359 fileIsOpen=.TRUE.
360
361 irec = irecord
362 i1 = bBij + 1
363 i2 = bBij + sNx*sNy*nNz
364 IF ( filePrec.EQ.precFloat32 ) THEN
365 WRITE(dUnit,rec=irec) (shared3dBuf_r4(i),i=i1,i2)
366 ELSE
367 WRITE(dUnit,rec=irec) (shared3dBuf_r8(i),i=i1,i2)
368 ENDIF
369
370 C If we were writing to a tiled MDS file then we close it here
371 IF ( fileIsOpen ) THEN
372 CLOSE( dUnit )
373 fileIsOpen = .FALSE.
374 ENDIF
375
376 C--- End Global File / tile-file cases
377 ENDIF
378
379 C Create meta-file for each tile if we are tiling
380 IF ( .NOT.globalFile ) THEN
381 iG=bi+(myXGlobalLo-1)/sNx
382 jG=bj+(myYGlobalLo-1)/sNy
383 WRITE(metaFname,'(2A,I3.3,A,I3.3,A)')
384 & fName(1:IL),'.',iG,'.',jG,'.meta'
385 dimList(1,1) = xSize
386 dimList(2,1) = tBx + 1
387 dimList(3,1) = tBx + tNx
388 dimList(1,2) = ySize
389 dimList(2,2) = tBy + 1
390 dimList(3,2) = tBy + tNy
391 dimList(1,3) = Nr
392 dimList(2,3) = 1
393 dimList(3,3) = Nr
394 nDims = 3
395 IF ( nNz.EQ.1 ) nDims = 2
396 map2gl(1) = iGjLoc
397 map2gl(2) = jGjLoc
398 CALL MDS_WRITE_META(
399 I metaFName, dataFName, the_run_name, ' ',
400 I filePrec, nDims, dimList, map2gl, 0, blank8c,
401 I 0, dummyRL, irecord, myIter, myThid )
402 ENDIF
403
404 C End of ith loop
405 ENDDO
406
407 C If global file was opened then close it
408 IF (fileIsOpen .AND. globalFile) THEN
409 CLOSE( dUnit )
410 fileIsOpen = .FALSE.
411 ENDIF
412
413 C Create meta-file for the global-file
414 IF (globalFile) THEN
415 WRITE(metaFName,'(2A)') fName(1:IL),'.meta'
416 dimList(1,1) = xSize
417 dimList(2,1) = 1
418 dimList(3,1) = xSize
419 dimList(1,2) = ySize
420 dimList(2,2) = 1
421 dimList(3,2) = ySize
422 dimList(1,3) = Nr
423 dimList(2,3) = 1
424 dimList(3,3) = Nr
425 nDims = 3
426 IF ( nNz.EQ.1 ) nDims = 2
427 map2gl(1) = 0
428 map2gl(2) = 1
429 CALL MDS_WRITE_META(
430 I metaFName, dataFName, the_run_name, ' ',
431 I filePrec, nDims, dimList, map2gl, 0, blank8c,
432 I 0, dummyRL, irecord, myIter, myThid )
433 ENDIF
434
435 C- end if iAmDoingIO
436 ENDIF
437
438 C Make other threads wait for I/O completion so that after this,
439 C 3-D buffer can again be modified by any thread
440 c IF ( nthLoop.GT.1 ) CALL BAR2( myThid )
441
442 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
443 RETURN
444 END

  ViewVC Help
Powered by ViewVC 1.1.22