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

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

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


Revision 1.5 - (show annotations) (download)
Sun Oct 5 16:22:22 2003 UTC (20 years, 8 months ago) by dimitri
Branch: MAIN
CVS Tags: checkpoint51k_post, checkpoint51l_post, checkpoint51j_post, checkpoint52e_pre, checkpoint51o_pre, checkpoint52e_post, checkpoint51n_pre, checkpoint52d_pre, branch-netcdf, checkpoint51r_post, checkpoint52b_pre, checkpoint51i_post, checkpoint51l_pre, checkpoint51o_post, checkpoint51q_post, checkpoint52, checkpoint52d_post, checkpoint52a_post, checkpoint52b_post, checkpoint52f_post, checkpoint52c_post, checkpoint51h_pre, ecco_c52_e35, checkpoint52a_pre, checkpoint51m_post, checkpoint51t_post, checkpoint52i_post, checkpoint51p_post, checkpoint51n_post, checkpoint51i_pre, checkpoint52i_pre, checkpoint51u_post, checkpoint52h_pre, checkpoint52f_pre, hrcube_1, checkpoint51s_post
Branch point for: netcdf-sm0, branch-nonh, tg2-branch, checkpoint51n_branch
Changes since 1.4: +7 -1 lines
added BYTESWAPIO support for useSingleCpuIO option

1 C $Header: /usr/local/gcmpack/MITgcm/pkg/mdsio/mdsio_writefield.F,v 1.4 2003/07/08 15:00:27 heimbach Exp $
2 C $Name: $
3
4 #include "MDSIO_OPTIONS.h"
5
6 SUBROUTINE MDSWRITEFIELD(
7 I fName,
8 I filePrec,
9 I globalFile,
10 I arrType,
11 I nNz,
12 I arr,
13 I irecord,
14 I myIter,
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 globalFile logical selects between writing a global or tiled file
22 C arrType char(2) declaration of "arr": either "RS" or "RL"
23 C nNz integer size of third dimension: normally either 1 or Nr
24 C arr RS/RL array to write, arr(:,:,nNz,:,:)
25 C irecord integer record number to read
26 C myIter integer time step number
27 C myThid integer thread identifier
28 C
29 C MDSWRITEFIELD creates either a file of the form "fName.data" and
30 C "fName.meta" if the logical flag "globalFile" is set true. Otherwise
31 C it creates MDS tiled files of the form "fName.xxx.yyy.data" and
32 C "fName.xxx.yyy.meta". A meta-file is always created.
33 C Currently, the meta-files are not read because it is difficult
34 C to parse files in fortran. We should read meta information before
35 C adding records to an existing multi-record file.
36 C The precision of the file is decsribed by filePrec, set either
37 C to floatPrec32 or floatPrec64. The precision or declaration of
38 C the array argument must be consistently described by the char*(2)
39 C string arrType, either "RS" or "RL". nNz allows for both 2-D and
40 C 3-D arrays to be handled. nNz=1 implies a 2-D model field and
41 C nNz=Nr implies a 3-D model field. irecord is the record number
42 C to be read and must be >= 1. NOTE: It is currently assumed that
43 C the highest record number in the file was the last record written.
44 C Nor is there a consistency check between the routine arguments and file.
45 C ie. if your write record 2 after record 4 the meta information
46 C will record the number of records to be 2. This, again, is because
47 C we have read the meta information. To be fixed.
48 C
49 C Created: 03/16/99 adcroft@mit.edu
50 C
51 C Changed: 05/31/00 heimbach@mit.edu
52 C open(dUnit, ..., status='old', ... -> status='unknown'
53 C
54 C Changed: 01/06/02 menemenlis@jpl.nasa.gov
55 C added useSingleCpuIO hack
56
57 implicit none
58 C Global variables / common blocks
59 #include "SIZE.h"
60 #include "EEPARAMS.h"
61 #include "EESUPPORT.h"
62 #include "PARAMS.h"
63
64 C Routine arguments
65 character*(*) fName
66 integer filePrec
67 logical globalFile
68 character*(2) arrType
69 integer nNz
70 cph(
71 cph Real arr(*)
72 _RL arr(1-oLx:sNx+oLx,1-oLy:sNy+oLy,nNz,nSx,nSy)
73 cph)
74 integer irecord
75 integer myIter
76 integer myThid
77 C Functions
78 integer ILNBLNK
79 integer MDS_RECLEN
80 C Local variables
81 character*(80) dataFName,metaFName,pfName
82 integer iG,jG,irec,bi,bj,j,k,dUnit,IL,pIL
83 Real*4 r4seg(sNx)
84 Real*8 r8seg(sNx)
85 integer dimList(3,3),ndims
86 integer length_of_rec
87 logical fileIsOpen
88 character*(max_len_mbuf) msgbuf
89 #ifdef ALLOW_USE_MPI
90 integer i
91 Real*8 global(Nx,Ny)
92 Real*4 global_r4(Nx,Ny)
93 _RL local(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
94 #endif /* ALLOW_USE_MPI */
95
96 C ------------------------------------------------------------------
97
98 C Only do I/O if I am the master thread
99 _BEGIN_MASTER( myThid )
100
101 C Record number must be >= 1
102 if (irecord .LT. 1) then
103 write(msgbuf,'(a,i9.8)')
104 & ' MDSWRITEFIELD: argument irecord = ',irecord
105 call print_message( msgbuf, standardmessageunit,
106 & SQUEEZE_RIGHT , mythid)
107 write(msgbuf,'(a)')
108 & ' MDSWRITEFIELD: invalid value for irecord'
109 call print_error( msgbuf, mythid )
110 stop 'ABNORMAL END: S/R MDSWRITEFIELD'
111 endif
112
113 C Assume nothing
114 fileIsOpen=.FALSE.
115 IL = ILNBLNK( fName )
116 pIL = ILNBLNK( mdsioLocalDir )
117
118 C Assign special directory
119 if ( mdsioLocalDir .NE. ' ' ) then
120 write(pFname(1:80),'(2a)') mdsioLocalDir(1:pIL), fName(1:IL)
121 else
122 pFname= fName
123 endif
124 pIL=ILNBLNK( pfName )
125
126 C Assign a free unit number as the I/O channel for this routine
127 call MDSFINDUNIT( dUnit, mythid )
128
129 #ifdef ALLOW_USE_MPI
130 _END_MASTER( myThid )
131 C If option globalFile is desired but does not work or if
132 C globalFile is too slow, then try using single-CPU I/O.
133 if (useSingleCpuIO) then
134
135 C Master thread of process 0, only, opens a global file
136 _BEGIN_MASTER( myThid )
137 IF( mpiMyId .EQ. 0 ) THEN
138 write(dataFname(1:80),'(2a)') fName(1:IL),'.data'
139 length_of_rec=MDS_RECLEN( filePrec, Nx*Ny, mythid )
140 if (irecord .EQ. 1) then
141 open( dUnit, file=dataFName, status=_NEW_STATUS,
142 & access='direct', recl=length_of_rec )
143 else
144 open( dUnit, file=dataFName, status=_OLD_STATUS,
145 & access='direct', recl=length_of_rec )
146 endif
147 ENDIF
148 _END_MASTER( myThid )
149
150 C Gather array and write it to file, one vertical level at a time
151 DO k=1,nNz
152 DO bj = myByLo(myThid), myByHi(myThid)
153 DO bi = myBxLo(myThid), myBxHi(myThid)
154 DO J=1-Oly,sNy+Oly
155 DO I=1-Olx,sNx+Olx
156 local(I,J,bi,bj) = arr(I,J,k,bi,bj)
157 ENDDO
158 ENDDO
159 ENDDO
160 ENDDO
161 CALL GATHER_2D( global, local, myThid )
162 _BEGIN_MASTER( myThid )
163 IF( mpiMyId .EQ. 0 ) THEN
164 irec=k+nNz*(irecord-1)
165 if (filePrec .eq. precFloat32) then
166 DO J=1,Ny
167 DO I=1,Nx
168 global_r4(I,J) = global(I,J)
169 ENDDO
170 ENDDO
171 #ifdef _BYTESWAPIO
172 call MDS_BYTESWAPR4( Nx*Ny, global_r4 )
173 #endif
174 write(dUnit,rec=irec) global_r4
175 elseif (filePrec .eq. precFloat64) then
176 #ifdef _BYTESWAPIO
177 call MDS_BYTESWAPR8( Nx*Ny, global )
178 #endif
179 write(dUnit,rec=irec) global
180 else
181 write(msgbuf,'(a)')
182 & ' MDSWRITEFIELD: illegal value for filePrec'
183 call print_error( msgbuf, mythid )
184 stop 'ABNORMAL END: S/R MDSWRITEFIELD'
185 endif
186 ENDIF
187 _END_MASTER( myThid )
188 ENDDO
189
190 C Close data-file and create meta-file
191 _BEGIN_MASTER( myThid )
192 IF( mpiMyId .EQ. 0 ) THEN
193 close( dUnit )
194 write(metaFName(1:80),'(2a)') fName(1:IL),'.meta'
195 dimList(1,1)=Nx
196 dimList(2,1)=1
197 dimList(3,1)=Nx
198 dimList(1,2)=Ny
199 dimList(2,2)=1
200 dimList(3,2)=Ny
201 dimList(1,3)=nNz
202 dimList(2,3)=1
203 dimList(3,3)=nNz
204 ndims=3
205 if (nNz .EQ. 1) ndims=2
206 call MDSWRITEMETA( metaFName, dataFName,
207 & filePrec, ndims, dimList, irecord, myIter, mythid )
208 ENDIF
209 _END_MASTER( myThid )
210 C To be safe, make other processes wait for I/O completion
211 _BARRIER
212
213 elseif ( .NOT. useSingleCpuIO ) then
214 _BEGIN_MASTER( myThid )
215 #endif /* ALLOW_USE_MPI */
216
217 C If we are writing to a global file then we open it here
218 if (globalFile) then
219 write(dataFname(1:80),'(2a)') fName(1:IL),'.data'
220 if (irecord .EQ. 1) then
221 length_of_rec=MDS_RECLEN( filePrec, sNx, mythid )
222 open( dUnit, file=dataFName, status=_NEW_STATUS,
223 & access='direct', recl=length_of_rec )
224 fileIsOpen=.TRUE.
225 else
226 length_of_rec=MDS_RECLEN( filePrec, sNx, mythid )
227 open( dUnit, file=dataFName, status=_OLD_STATUS,
228 & access='direct', recl=length_of_rec )
229 fileIsOpen=.TRUE.
230 endif
231 endif
232
233 C Loop over all tiles
234 do bj=1,nSy
235 do bi=1,nSx
236 C If we are writing to a tiled MDS file then we open each one here
237 if (.NOT. globalFile) then
238 iG=bi+(myXGlobalLo-1)/sNx ! Kludge until unstructered tiles
239 jG=bj+(myYGlobalLo-1)/sNy ! Kludge until unstructered tiles
240 write(dataFname(1:80),'(2a,i3.3,a,i3.3,a)')
241 & pfName(1:pIL),'.',iG,'.',jG,'.data'
242 if (irecord .EQ. 1) then
243 length_of_rec=MDS_RECLEN( filePrec, sNx, mythid )
244 open( dUnit, file=dataFName, status=_NEW_STATUS,
245 & access='direct', recl=length_of_rec )
246 fileIsOpen=.TRUE.
247 else
248 length_of_rec=MDS_RECLEN( filePrec, sNx, mythid )
249 open( dUnit, file=dataFName, status=_OLD_STATUS,
250 & access='direct', recl=length_of_rec )
251 fileIsOpen=.TRUE.
252 endif
253 endif
254 if (fileIsOpen) then
255 do k=1,nNz
256 do j=1,sNy
257 if (globalFile) then
258 iG = myXGlobalLo-1+(bi-1)*sNx
259 jG = myYGlobalLo-1+(bj-1)*sNy
260 irec=1+INT(iG/sNx)+nSx*nPx*(jG+j-1)+nSx*nPx*Ny*(k-1)
261 & +nSx*nPx*Ny*nNz*(irecord-1)
262 else
263 iG = 0
264 jG = 0
265 irec=j + sNy*(k-1) + sNy*nNz*(irecord-1)
266 endif
267 if (filePrec .eq. precFloat32) then
268 if (arrType .eq. 'RS') then
269 call MDS_SEG4toRS( j,bi,bj,k,nNz, r4seg, .FALSE., arr )
270 elseif (arrType .eq. 'RL') then
271 call MDS_SEG4toRL( j,bi,bj,k,nNz, r4seg, .FALSE., arr )
272 else
273 write(msgbuf,'(a)')
274 & ' MDSWRITEFIELD: illegal value for arrType'
275 call print_error( msgbuf, mythid )
276 stop 'ABNORMAL END: S/R MDSWRITEFIELD'
277 endif
278 #ifdef _BYTESWAPIO
279 call MDS_BYTESWAPR4( sNx, r4seg )
280 #endif
281 write(dUnit,rec=irec) r4seg
282 elseif (filePrec .eq. precFloat64) then
283 if (arrType .eq. 'RS') then
284 call MDS_SEG8toRS( j,bi,bj,k,nNz, r8seg, .FALSE., arr )
285 elseif (arrType .eq. 'RL') then
286 call MDS_SEG8toRL( j,bi,bj,k,nNz, r8seg, .FALSE., arr )
287 else
288 write(msgbuf,'(a)')
289 & ' MDSWRITEFIELD: illegal value for arrType'
290 call print_error( msgbuf, mythid )
291 stop 'ABNORMAL END: S/R MDSWRITEFIELD'
292 endif
293 #ifdef _BYTESWAPIO
294 call MDS_BYTESWAPR8( sNx, r8seg )
295 #endif
296 write(dUnit,rec=irec) r8seg
297 else
298 write(msgbuf,'(a)')
299 & ' MDSWRITEFIELD: illegal value for filePrec'
300 call print_error( msgbuf, mythid )
301 stop 'ABNORMAL END: S/R MDSWRITEFIELD'
302 endif
303 C End of j loop
304 enddo
305 C End of k loop
306 enddo
307 else
308 write(msgbuf,'(a)')
309 & ' MDSWRITEFIELD: I should never get to this point'
310 call print_error( msgbuf, mythid )
311 stop 'ABNORMAL END: S/R MDSWRITEFIELD'
312 endif
313 C If we were writing to a tiled MDS file then we close it here
314 if (fileIsOpen .AND. (.NOT. globalFile)) then
315 close( dUnit )
316 fileIsOpen = .FALSE.
317 endif
318 C Create meta-file for each tile if we are tiling
319 if (.NOT. globalFile) then
320 iG=bi+(myXGlobalLo-1)/sNx ! Kludge until unstructered tiles
321 jG=bj+(myYGlobalLo-1)/sNy ! Kludge until unstructered tiles
322 write(metaFname(1:80),'(2a,i3.3,a,i3.3,a)')
323 & pfName(1:pIL),'.',iG,'.',jG,'.meta'
324 dimList(1,1)=Nx
325 dimList(2,1)=myXGlobalLo+(bi-1)*sNx
326 dimList(3,1)=myXGlobalLo+bi*sNx-1
327 dimList(1,2)=Ny
328 dimList(2,2)=myYGlobalLo+(bj-1)*sNy
329 dimList(3,2)=myYGlobalLo+bj*sNy-1
330 dimList(1,3)=nNz
331 dimList(2,3)=1
332 dimList(3,3)=nNz
333 ndims=3
334 if (nNz .EQ. 1) ndims=2
335 call MDSWRITEMETA( metaFName, dataFName,
336 & filePrec, ndims, dimList, irecord, myIter, mythid )
337 endif
338 C End of bi,bj loops
339 enddo
340 enddo
341
342 C If global file was opened then close it
343 if (fileIsOpen .AND. globalFile) then
344 close( dUnit )
345 fileIsOpen = .FALSE.
346 endif
347
348 C Create meta-file for the global-file
349 if (globalFile) then
350 C We can not do this operation using threads (yet) because of the
351 C "barrier" at the next step. The barrier could be removed but
352 C at the cost of "safe" distributed I/O.
353 if (nThreads.NE.1) then
354 write(msgbuf,'(a,a)')
355 & ' MDSWRITEFIELD: A threads version of this routine',
356 & ' does not exist.'
357 call print_message( msgbuf, standardmessageunit,
358 & SQUEEZE_RIGHT , mythid)
359 write(msgbuf,'(a)')
360 & ' MDSWRITEFIELD: This needs to be fixed...'
361 call print_message( msgbuf, standardmessageunit,
362 & SQUEEZE_RIGHT , mythid)
363 write(msgbuf,'(a,i3.2)')
364 & ' MDSWRITEFIELD: nThreads = ',nThreads
365 call print_message( msgbuf, standardmessageunit,
366 & SQUEEZE_RIGHT , mythid)
367 write(msgbuf,'(a)')
368 & ' MDSWRITEFIELD: Stopping because you are using threads'
369 call print_error( msgbuf, mythid )
370 stop 'ABNORMAL END: S/R MDSWRITEFIELD'
371 endif
372 C We put a barrier here to ensure that all processes have finished
373 C writing their data before we update the meta-file
374 _BARRIER
375 write(metaFName(1:80),'(2a)') fName(1:IL),'.meta'
376 dimList(1,1)=Nx
377 dimList(2,1)=1
378 dimList(3,1)=Nx
379 dimList(1,2)=Ny
380 dimList(2,2)=1
381 dimList(3,2)=Ny
382 dimList(1,3)=nNz
383 dimList(2,3)=1
384 dimList(3,3)=nNz
385 ndims=3
386 if (nNz .EQ. 1) ndims=2
387 call MDSWRITEMETA( metaFName, dataFName,
388 & filePrec, ndims, dimList, irecord, myIter, mythid )
389 fileIsOpen=.TRUE.
390 endif
391
392 _END_MASTER( myThid )
393
394 #ifdef ALLOW_USE_MPI
395 C endif useSingleCpuIO
396 endif
397 #endif /* ALLOW_USE_MPI */
398
399 C ------------------------------------------------------------------
400 return
401 end

  ViewVC Help
Powered by ViewVC 1.1.22