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

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

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


Revision 1.4 - (hide annotations) (download)
Sun Jul 20 12:26:10 2008 UTC (15 years, 11 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint61f, checkpoint61n, checkpoint61q, checkpoint61g, checkpoint61d, checkpoint61e, checkpoint61b, checkpoint61c, checkpoint61a, checkpoint61o, checkpoint61l, checkpoint61m, checkpoint61j, checkpoint61k, checkpoint61h, checkpoint61i, checkpoint61t, checkpoint61u, checkpoint61r, checkpoint61s, checkpoint61p
Changes since 1.3: +1 -2 lines
PARAMS.h no longer needed

1 jmc 1.4 C $Header: /u/gcmpack/MITgcm/pkg/mdsio/mdsio_writetile.F,v 1.3 2006/08/07 20:30:28 jmc Exp $
2 jmc 1.2 C $Name: $
3 adcroft 1.1
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    
60     C Routine arguments
61     character*(*) fName
62     integer filePrec
63     logical globalFile
64     character*(2) arrType
65     integer nNz
66     _RL arr(1-oLx:sNx+oLx,1-oLy:sNy+oLy,nNz,nSx,nSy)
67     integer bi, bj
68     integer irecord
69     integer myIter
70     integer myThid
71     C Functions
72     integer ILNBLNK
73     integer MDS_RECLEN
74     C Local variables
75 jmc 1.2 character*(MAX_LEN_FNAM) dataFName,metaFName
76 adcroft 1.1 integer iG,jG,irec,j,k,dUnit,IL
77     Real*4 r4seg(sNx)
78     Real*8 r8seg(sNx)
79     integer dimList(3,3),ndims
80     integer length_of_rec
81     logical fileIsOpen
82     character*(max_len_mbuf) msgbuf
83     C ------------------------------------------------------------------
84    
85 jmc 1.3 STOP 'S/R MDS_WRITETILE: not maintained'
86    
87 adcroft 1.1 C Only do I/O if I am the master thread
88     _BEGIN_MASTER( myThid )
89    
90     C Record number must be >= 1
91     if (irecord .LT. 1) then
92     write(msgbuf,'(a,i9.8)')
93     & ' MDS_WRITETILE: argument irecord = ',irecord
94     call print_message( msgbuf, standardmessageunit,
95     & SQUEEZE_RIGHT , mythid)
96     write(msgbuf,'(a)')
97     & ' MDS_WRITETILE: invalid value for irecord'
98     call print_error( msgbuf, mythid )
99     stop 'ABNORMAL END: S/R MDS_WRITETILE'
100     endif
101    
102     C Assume nothing
103     fileIsOpen=.FALSE.
104     IL=ILNBLNK( fName )
105    
106     C Assign a free unit number as the I/O channel for this routine
107     call MDSFINDUNIT( dUnit, mythid )
108    
109     C If we are writing to a global file then we open it here
110     if (globalFile) then
111 jmc 1.2 write(dataFname,'(2a)') fName(1:IL),'.data'
112 adcroft 1.1 if (irecord .EQ. 1) then
113     length_of_rec=MDS_RECLEN( filePrec, sNx, mythid )
114     open( dUnit, file=dataFName, status='unknown',
115     & access='direct', recl=length_of_rec )
116     fileIsOpen=.TRUE.
117     else
118     length_of_rec=MDS_RECLEN( filePrec, sNx, mythid )
119     open( dUnit, file=dataFName, status=_OLD_STATUS,
120     & access='direct', recl=length_of_rec )
121     fileIsOpen=.TRUE.
122     endif
123     endif
124    
125     C Loop over all tiles
126     c do bj=1,nSy
127     c do bi=1,nSx
128     C If we are writing to a tiled MDS file then we open each one here
129     if (.NOT. globalFile) then
130     iG=bi+(myXGlobalLo-1)/sNx ! Kludge until unstructered tiles
131     jG=bj+(myYGlobalLo-1)/sNy ! Kludge until unstructered tiles
132 jmc 1.2 write(dataFname,'(2a,i3.3,a,i3.3,a)')
133 adcroft 1.1 & fName(1:IL),'.',iG,'.',jG,'.data'
134     if (irecord .EQ. 1) then
135     length_of_rec=MDS_RECLEN( filePrec, sNx, mythid )
136     open( dUnit, file=dataFName, status=_NEW_STATUS,
137     & access='direct', recl=length_of_rec )
138     fileIsOpen=.TRUE.
139     else
140     length_of_rec=MDS_RECLEN( filePrec, sNx, mythid )
141     open( dUnit, file=dataFName, status=_OLD_STATUS,
142     & access='direct', recl=length_of_rec )
143     fileIsOpen=.TRUE.
144     endif
145     endif
146     if (fileIsOpen) then
147     do k=1,nNz
148     do j=1,sNy
149     if (globalFile) then
150     iG = myXGlobalLo-1+(bi-1)*sNx
151     jG = myYGlobalLo-1+(bj-1)*sNy
152     irec=1+INT(iG/sNx)+nSx*nPx*(jG+j-1)+nSx*nPx*Ny*(k-1)
153     & +nSx*nPx*Ny*nNz*(irecord-1)
154     else
155     iG = 0
156     jG = 0
157     irec=j + sNy*(k-1) + sNy*nNz*(irecord-1)
158     endif
159     if (filePrec .eq. precFloat32) then
160     if (arrType .eq. 'RS') then
161     call MDS_SEG4toRS( j,bi,bj,k,nNz, r4seg, .FALSE., arr )
162     elseif (arrType .eq. 'RL') then
163     call MDS_SEG4toRL( j,bi,bj,k,nNz, r4seg, .FALSE., arr )
164     else
165     write(msgbuf,'(a)')
166     & ' MDS_WRITETILE: illegal value for arrType'
167     call print_error( msgbuf, mythid )
168     stop 'ABNORMAL END: S/R MDS_WRITETILE'
169     endif
170     #ifdef _BYTESWAPIO
171     call MDS_BYTESWAPR4( sNx, r4seg )
172     #endif
173     write(dUnit,rec=irec) r4seg
174     elseif (filePrec .eq. precFloat64) then
175     if (arrType .eq. 'RS') then
176     call MDS_SEG8toRS( j,bi,bj,k,nNz, r8seg, .FALSE., arr )
177     elseif (arrType .eq. 'RL') then
178     call MDS_SEG8toRL( j,bi,bj,k,nNz, r8seg, .FALSE., arr )
179     else
180     write(msgbuf,'(a)')
181     & ' MDS_WRITETILE: illegal value for arrType'
182     call print_error( msgbuf, mythid )
183     stop 'ABNORMAL END: S/R MDS_WRITETILE'
184     endif
185     #ifdef _BYTESWAPIO
186     call MDS_BYTESWAPR8( sNx, r8seg )
187     #endif
188     write(dUnit,rec=irec) r8seg
189     else
190     write(msgbuf,'(a)')
191     & ' MDS_WRITETILE: illegal value for filePrec'
192     call print_error( msgbuf, mythid )
193     stop 'ABNORMAL END: S/R MDS_WRITETILE'
194     endif
195     C End of j loop
196     enddo
197     C End of k loop
198     enddo
199     else
200     write(msgbuf,'(a)')
201     & ' MDS_WRITETILE: I should never get to this point'
202     call print_error( msgbuf, mythid )
203     stop 'ABNORMAL END: S/R MDS_WRITETILE'
204     endif
205     C If we were writing to a tiled MDS file then we close it here
206     if (fileIsOpen .AND. (.NOT. globalFile)) then
207     close( dUnit )
208     fileIsOpen = .FALSE.
209     endif
210     C Create meta-file for each tile if we are tiling
211     if (.NOT. globalFile) then
212     iG=bi+(myXGlobalLo-1)/sNx ! Kludge until unstructered tiles
213     jG=bj+(myYGlobalLo-1)/sNy ! Kludge until unstructered tiles
214 jmc 1.2 write(metaFname,'(2a,i3.3,a,i3.3,a)')
215 adcroft 1.1 & fName(1:IL),'.',iG,'.',jG,'.meta'
216     dimList(1,1)=Nx
217     dimList(2,1)=myXGlobalLo+(bi-1)*sNx
218     dimList(3,1)=myXGlobalLo+bi*sNx-1
219     dimList(1,2)=Ny
220     dimList(2,2)=myYGlobalLo+(bj-1)*sNy
221     dimList(3,2)=myYGlobalLo+bj*sNy-1
222     dimList(1,3)=Nr
223     dimList(2,3)=1
224     dimList(3,3)=Nr
225     ndims=3
226     if (nNz .EQ. 1) ndims=2
227     call MDSWRITEMETA( metaFName, dataFName,
228     & filePrec, ndims, dimList, irecord, myIter, mythid )
229     endif
230     C End of bi,bj loops
231     c enddo
232     c enddo
233    
234     C If global file was opened then close it
235     if (fileIsOpen .AND. globalFile) then
236     close( dUnit )
237     fileIsOpen = .FALSE.
238     endif
239    
240     C Create meta-file for the global-file
241     if (globalFile) then
242     C We can not do this operation using threads (yet) because of the
243     C "barrier" at the next step. The barrier could be removed but
244     C at the cost of "safe" distributed I/O.
245     if (nThreads.NE.1) then
246     write(msgbuf,'(a,a)')
247     & ' MDS_WRITETILE: A threads version of this routine',
248     & ' does not exist.'
249     call print_message( msgbuf, standardmessageunit,
250     & SQUEEZE_RIGHT , mythid)
251     write(msgbuf,'(a)')
252     & ' MDS_WRITETILE: This needs to be fixed...'
253     call print_message( msgbuf, standardmessageunit,
254     & SQUEEZE_RIGHT , mythid)
255     write(msgbuf,'(a,i3.2)')
256     & ' MDS_WRITETILE: nThreads = ',nThreads
257     call print_message( msgbuf, standardmessageunit,
258     & SQUEEZE_RIGHT , mythid)
259     write(msgbuf,'(a)')
260     & ' MDS_WRITETILE: Stopping because you are using threads'
261     call print_error( msgbuf, mythid )
262     stop 'ABNORMAL END: S/R MDS_WRITETILE'
263     endif
264     C We put a barrier here to ensure that all processes have finished
265     C writing their data before we update the meta-file
266     _BARRIER
267 jmc 1.2 write(metaFName,'(2a)') fName(1:IL),'.meta'
268 adcroft 1.1 dimList(1,1)=Nx
269     dimList(2,1)=1
270     dimList(3,1)=Nx
271     dimList(1,2)=Ny
272     dimList(2,2)=1
273     dimList(3,2)=Ny
274     dimList(1,3)=Nr
275     dimList(2,3)=1
276     dimList(3,3)=Nr
277     ndims=3
278     if (nNz .EQ. 1) ndims=2
279     call MDSWRITEMETA( metaFName, dataFName,
280     & filePrec, ndims, dimList, irecord, myIter, mythid )
281     fileIsOpen=.TRUE.
282     endif
283    
284     _END_MASTER( myThid )
285    
286     C ------------------------------------------------------------------
287     return
288     end

  ViewVC Help
Powered by ViewVC 1.1.22