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

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

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


Revision 1.3 - (show annotations) (download)
Mon Aug 7 20:30:28 2006 UTC (17 years, 8 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint59, checkpoint58y_post, checkpoint58t_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, checkpoint58v_post, checkpoint58x_post, checkpoint59j, checkpoint58u_post, checkpoint58s_post
Changes since 1.2: +3 -1 lines
never called ; not maintained ; put a stop at the beginning.

1 C $Header: /u/gcmpack/MITgcm/pkg/mdsio/mdsio_writetile.F,v 1.2 2005/11/02 14:49:12 jmc Exp $
2 C $Name: $
3
4 #include "MDSIO_OPTIONS.h"
5
6 SUBROUTINE MDS_WRITETILE(
7 I fName,
8 I filePrec,
9 I globalFile,
10 I arrType,
11 I nNz,
12 I arr,
13 I bi, bj,
14 I irecord,
15 I myIter,
16 I myThid )
17 C
18 C Arguments:
19 C
20 C fName string base name for file to written
21 C filePrec integer number of bits per word in file (32 or 64)
22 C globalFile logical selects between writing a global or tiled file
23 C arrType char(2) declaration of "arr": either "RS" or "RL"
24 C nNz integer size of third dimension: normally either 1 or Nr
25 C arr RS/RL array to write, arr(:,:,nNz,:,:)
26 C irecord integer record number to read
27 C myIter integer time step number
28 C myThid integer thread identifier
29 C
30 C MDS_WRITETILE creates either a file of the form "fName.data" and
31 C "fName.meta" if the logical flag "globalFile" is set true. Otherwise
32 C it creates MDS tiled files of the form "fName.xxx.yyy.data" and
33 C "fName.xxx.yyy.meta". A meta-file is always created.
34 C Currently, the meta-files are not read because it is difficult
35 C to parse files in fortran. We should read meta information before
36 C adding records to an existing multi-record file.
37 C The precision of the file is decsribed by filePrec, set either
38 C to floatPrec32 or floatPrec64. The precision or declaration of
39 C the array argument must be consistently described by the char*(2)
40 C string arrType, either "RS" or "RL". nNz allows for both 2-D and
41 C 3-D arrays to be handled. nNz=1 implies a 2-D model field and
42 C nNz=Nr implies a 3-D model field. irecord is the record number
43 C to be read and must be >= 1. NOTE: It is currently assumed that
44 C the highest record number in the file was the last record written.
45 C Nor is there a consistency check between the routine arguments and file.
46 C ie. if your write record 2 after record 4 the meta information
47 C will record the number of records to be 2. This, again, is because
48 C we have read the meta information. To be fixed.
49 C
50 C Created: 03/16/99 adcroft@mit.edu
51 C
52 C Changed: 05/31/00 heimbach@mit.edu
53 C open(dUnit, ..., status='old', ... -> status='unknown'
54
55 implicit none
56 C Global variables / common blocks
57 #include "SIZE.h"
58 #include "EEPARAMS.h"
59 #include "PARAMS.h"
60
61 C Routine arguments
62 character*(*) fName
63 integer filePrec
64 logical globalFile
65 character*(2) arrType
66 integer nNz
67 _RL arr(1-oLx:sNx+oLx,1-oLy:sNy+oLy,nNz,nSx,nSy)
68 integer bi, bj
69 integer irecord
70 integer myIter
71 integer myThid
72 C Functions
73 integer ILNBLNK
74 integer MDS_RECLEN
75 C Local variables
76 character*(MAX_LEN_FNAM) dataFName,metaFName
77 integer iG,jG,irec,j,k,dUnit,IL
78 Real*4 r4seg(sNx)
79 Real*8 r8seg(sNx)
80 integer dimList(3,3),ndims
81 integer length_of_rec
82 logical fileIsOpen
83 character*(max_len_mbuf) msgbuf
84 C ------------------------------------------------------------------
85
86 STOP 'S/R MDS_WRITETILE: not maintained'
87
88 C Only do I/O if I am the master thread
89 _BEGIN_MASTER( myThid )
90
91 C Record number must be >= 1
92 if (irecord .LT. 1) then
93 write(msgbuf,'(a,i9.8)')
94 & ' MDS_WRITETILE: argument irecord = ',irecord
95 call print_message( msgbuf, standardmessageunit,
96 & SQUEEZE_RIGHT , mythid)
97 write(msgbuf,'(a)')
98 & ' MDS_WRITETILE: invalid value for irecord'
99 call print_error( msgbuf, mythid )
100 stop 'ABNORMAL END: S/R MDS_WRITETILE'
101 endif
102
103 C Assume nothing
104 fileIsOpen=.FALSE.
105 IL=ILNBLNK( fName )
106
107 C Assign a free unit number as the I/O channel for this routine
108 call MDSFINDUNIT( dUnit, mythid )
109
110 C If we are writing to a global file then we open it here
111 if (globalFile) then
112 write(dataFname,'(2a)') fName(1:IL),'.data'
113 if (irecord .EQ. 1) then
114 length_of_rec=MDS_RECLEN( filePrec, sNx, mythid )
115 open( dUnit, file=dataFName, status='unknown',
116 & access='direct', recl=length_of_rec )
117 fileIsOpen=.TRUE.
118 else
119 length_of_rec=MDS_RECLEN( filePrec, sNx, mythid )
120 open( dUnit, file=dataFName, status=_OLD_STATUS,
121 & access='direct', recl=length_of_rec )
122 fileIsOpen=.TRUE.
123 endif
124 endif
125
126 C Loop over all tiles
127 c do bj=1,nSy
128 c do bi=1,nSx
129 C If we are writing to a tiled MDS file then we open each one here
130 if (.NOT. globalFile) then
131 iG=bi+(myXGlobalLo-1)/sNx ! Kludge until unstructered tiles
132 jG=bj+(myYGlobalLo-1)/sNy ! Kludge until unstructered tiles
133 write(dataFname,'(2a,i3.3,a,i3.3,a)')
134 & fName(1:IL),'.',iG,'.',jG,'.data'
135 if (irecord .EQ. 1) then
136 length_of_rec=MDS_RECLEN( filePrec, sNx, mythid )
137 open( dUnit, file=dataFName, status=_NEW_STATUS,
138 & access='direct', recl=length_of_rec )
139 fileIsOpen=.TRUE.
140 else
141 length_of_rec=MDS_RECLEN( filePrec, sNx, mythid )
142 open( dUnit, file=dataFName, status=_OLD_STATUS,
143 & access='direct', recl=length_of_rec )
144 fileIsOpen=.TRUE.
145 endif
146 endif
147 if (fileIsOpen) then
148 do k=1,nNz
149 do j=1,sNy
150 if (globalFile) then
151 iG = myXGlobalLo-1+(bi-1)*sNx
152 jG = myYGlobalLo-1+(bj-1)*sNy
153 irec=1+INT(iG/sNx)+nSx*nPx*(jG+j-1)+nSx*nPx*Ny*(k-1)
154 & +nSx*nPx*Ny*nNz*(irecord-1)
155 else
156 iG = 0
157 jG = 0
158 irec=j + sNy*(k-1) + sNy*nNz*(irecord-1)
159 endif
160 if (filePrec .eq. precFloat32) then
161 if (arrType .eq. 'RS') then
162 call MDS_SEG4toRS( j,bi,bj,k,nNz, r4seg, .FALSE., arr )
163 elseif (arrType .eq. 'RL') then
164 call MDS_SEG4toRL( j,bi,bj,k,nNz, r4seg, .FALSE., arr )
165 else
166 write(msgbuf,'(a)')
167 & ' MDS_WRITETILE: illegal value for arrType'
168 call print_error( msgbuf, mythid )
169 stop 'ABNORMAL END: S/R MDS_WRITETILE'
170 endif
171 #ifdef _BYTESWAPIO
172 call MDS_BYTESWAPR4( sNx, r4seg )
173 #endif
174 write(dUnit,rec=irec) r4seg
175 elseif (filePrec .eq. precFloat64) then
176 if (arrType .eq. 'RS') then
177 call MDS_SEG8toRS( j,bi,bj,k,nNz, r8seg, .FALSE., arr )
178 elseif (arrType .eq. 'RL') then
179 call MDS_SEG8toRL( j,bi,bj,k,nNz, r8seg, .FALSE., arr )
180 else
181 write(msgbuf,'(a)')
182 & ' MDS_WRITETILE: illegal value for arrType'
183 call print_error( msgbuf, mythid )
184 stop 'ABNORMAL END: S/R MDS_WRITETILE'
185 endif
186 #ifdef _BYTESWAPIO
187 call MDS_BYTESWAPR8( sNx, r8seg )
188 #endif
189 write(dUnit,rec=irec) r8seg
190 else
191 write(msgbuf,'(a)')
192 & ' MDS_WRITETILE: illegal value for filePrec'
193 call print_error( msgbuf, mythid )
194 stop 'ABNORMAL END: S/R MDS_WRITETILE'
195 endif
196 C End of j loop
197 enddo
198 C End of k loop
199 enddo
200 else
201 write(msgbuf,'(a)')
202 & ' MDS_WRITETILE: I should never get to this point'
203 call print_error( msgbuf, mythid )
204 stop 'ABNORMAL END: S/R MDS_WRITETILE'
205 endif
206 C If we were writing to a tiled MDS file then we close it here
207 if (fileIsOpen .AND. (.NOT. globalFile)) then
208 close( dUnit )
209 fileIsOpen = .FALSE.
210 endif
211 C Create meta-file for each tile if we are tiling
212 if (.NOT. globalFile) then
213 iG=bi+(myXGlobalLo-1)/sNx ! Kludge until unstructered tiles
214 jG=bj+(myYGlobalLo-1)/sNy ! Kludge until unstructered tiles
215 write(metaFname,'(2a,i3.3,a,i3.3,a)')
216 & fName(1:IL),'.',iG,'.',jG,'.meta'
217 dimList(1,1)=Nx
218 dimList(2,1)=myXGlobalLo+(bi-1)*sNx
219 dimList(3,1)=myXGlobalLo+bi*sNx-1
220 dimList(1,2)=Ny
221 dimList(2,2)=myYGlobalLo+(bj-1)*sNy
222 dimList(3,2)=myYGlobalLo+bj*sNy-1
223 dimList(1,3)=Nr
224 dimList(2,3)=1
225 dimList(3,3)=Nr
226 ndims=3
227 if (nNz .EQ. 1) ndims=2
228 call MDSWRITEMETA( metaFName, dataFName,
229 & filePrec, ndims, dimList, irecord, myIter, mythid )
230 endif
231 C End of bi,bj loops
232 c enddo
233 c enddo
234
235 C If global file was opened then close it
236 if (fileIsOpen .AND. globalFile) then
237 close( dUnit )
238 fileIsOpen = .FALSE.
239 endif
240
241 C Create meta-file for the global-file
242 if (globalFile) then
243 C We can not do this operation using threads (yet) because of the
244 C "barrier" at the next step. The barrier could be removed but
245 C at the cost of "safe" distributed I/O.
246 if (nThreads.NE.1) then
247 write(msgbuf,'(a,a)')
248 & ' MDS_WRITETILE: A threads version of this routine',
249 & ' does not exist.'
250 call print_message( msgbuf, standardmessageunit,
251 & SQUEEZE_RIGHT , mythid)
252 write(msgbuf,'(a)')
253 & ' MDS_WRITETILE: This needs to be fixed...'
254 call print_message( msgbuf, standardmessageunit,
255 & SQUEEZE_RIGHT , mythid)
256 write(msgbuf,'(a,i3.2)')
257 & ' MDS_WRITETILE: nThreads = ',nThreads
258 call print_message( msgbuf, standardmessageunit,
259 & SQUEEZE_RIGHT , mythid)
260 write(msgbuf,'(a)')
261 & ' MDS_WRITETILE: Stopping because you are using threads'
262 call print_error( msgbuf, mythid )
263 stop 'ABNORMAL END: S/R MDS_WRITETILE'
264 endif
265 C We put a barrier here to ensure that all processes have finished
266 C writing their data before we update the meta-file
267 _BARRIER
268 write(metaFName,'(2a)') fName(1:IL),'.meta'
269 dimList(1,1)=Nx
270 dimList(2,1)=1
271 dimList(3,1)=Nx
272 dimList(1,2)=Ny
273 dimList(2,2)=1
274 dimList(3,2)=Ny
275 dimList(1,3)=Nr
276 dimList(2,3)=1
277 dimList(3,3)=Nr
278 ndims=3
279 if (nNz .EQ. 1) ndims=2
280 call MDSWRITEMETA( metaFName, dataFName,
281 & filePrec, ndims, dimList, irecord, myIter, mythid )
282 fileIsOpen=.TRUE.
283 endif
284
285 _END_MASTER( myThid )
286
287 C ------------------------------------------------------------------
288 return
289 end

  ViewVC Help
Powered by ViewVC 1.1.22