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

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

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


Revision 1.10 - (hide annotations) (download)
Tue Dec 30 00:14:05 2008 UTC (15 years, 5 months ago) by jahn
Branch: MAIN
Changes since 1.9: +5 -1 lines
comment out subroutines if not used to save memory

1 jahn 1.10 C $Header: /u/gcmpack/MITgcm/pkg/mdsio/mdsio_writevector.F,v 1.9 2008/09/30 22:39:25 heimbach Exp $
2 heimbach 1.2 C $Name: $
3 adcroft 1.1
4     #include "MDSIO_OPTIONS.h"
5    
6     SUBROUTINE MDSWRITEVECTOR(
7     I fName,
8     I filePrec,
9     I globalfile,
10     I arrType,
11     I narr,
12     I arr,
13     I bi,
14     I bj,
15     I irecord,
16     I myIter,
17     I myThid )
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 narr integer size of third dimension: normally either 1 or Nr
25     C arr RS/RL array to write, arr(narr)
26     ce bi integer x tile index
27     ce bj integer y tile index
28     C irecord integer record number to read
29     C myIter integer time step number
30     C myThid integer thread identifier
31     C
32     C Created: 03/26/99 eckert@mit.edu
33     C Modified: 03/29/99 adcroft@mit.edu + eckert@mit.edu
34     C Fixed to work work with _RS and _RL declarations
35     C Modified: 07/27/99 eckert@mit.edu
36     C Customized for state estimation (--> active_file_control.F)
37     C Changed: 05/31/00 heimbach@mit.edu
38     C open(dUnit, ..., status='old', ... -> status='unknown'
39    
40     implicit none
41     C Global variables / common blocks
42     #include "SIZE.h"
43     #include "EEPARAMS.h"
44     #include "PARAMS.h"
45 heimbach 1.4 #include "EESUPPORT.h"
46 adcroft 1.1
47     C Routine arguments
48     character*(*) fName
49     integer filePrec
50     logical globalfile
51     character*(2) arrType
52     integer narr
53 heimbach 1.8 _RL arr(narr)
54 adcroft 1.1 integer irecord
55     integer myIter
56     integer myThid
57     ce
58     integer bi,bj
59     ce
60    
61 jahn 1.10 #if defined(ALLOW_AUTODIFF) || defined(ALLOW_FLT)
62    
63 adcroft 1.1 C Functions
64     integer ILNBLNK
65     integer MDS_RECLEN
66     C Local variables
67 jmc 1.6 character*(MAX_LEN_FNAM) dataFName,metaFName,pfName
68 heimbach 1.2 integer iG,jG,irec,dUnit,IL,pIL
69 adcroft 1.1 logical fileIsOpen
70     integer dimList(3,3),ndims
71     integer length_of_rec
72     character*(max_len_mbuf) msgbuf
73 heimbach 1.4
74     cph(
75     cph Deal with useSingleCpuIO
76     cph Not implemented here for EXCH2
77     INTEGER nNz
78     INTEGER vec_size
79     #ifdef ALLOW_USE_MPI
80 jmc 1.6 logical lprint
81     INTEGER K,L
82 jmc 1.7 c INTEGER iG_IO,jG_IO,npe
83 heimbach 1.4 Real*4 xy_buffer_r4(narr*nPx*nPy)
84     Real*8 xy_buffer_r8(narr*nPx*nPy)
85     Real*8 global(narr*nPx*nPy)
86     _RL local(narr)
87     #endif
88     cph)
89    
90 adcroft 1.1 C ------------------------------------------------------------------
91    
92 heimbach 1.4 vec_size = narr*nPx*nPy
93     nNz = 1
94    
95 adcroft 1.1 C Only do I/O if I am the master thread
96     _BEGIN_MASTER( myThid )
97    
98     C Record number must be >= 1
99     if (irecord .LT. 1) then
100     write(msgbuf,'(a,i9.8)')
101     & ' MDSWRITEVECTOR: argument irecord = ',irecord
102     call print_message( msgbuf, standardmessageunit,
103     & SQUEEZE_RIGHT , mythid)
104     write(msgbuf,'(a)')
105     & ' MDSWRITEVECTOR: invalid value for irecord'
106     call print_error( msgbuf, mythid )
107     stop 'ABNORMAL END: S/R MDSWRITEVECTOR'
108     endif
109    
110     C Assume nothing
111     fileIsOpen = .FALSE.
112 heimbach 1.2 IL = ILNBLNK( fName )
113     pIL = ILNBLNK( mdsioLocalDir )
114    
115     C Assign special directory
116     if ( mdsioLocalDir .NE. ' ' ) then
117 jmc 1.6 write(pFname,'(2a)')
118 heimbach 1.3 & mdsioLocalDir(1:pIL), fName(1:IL)
119 heimbach 1.2 else
120     pFname= fName
121     endif
122     pIL=ILNBLNK( pfName )
123 adcroft 1.1
124     C Assign a free unit number as the I/O channel for this routine
125     call MDSFINDUNIT( dUnit, mythid )
126    
127 heimbach 1.4 #ifdef ALLOW_USE_MPI
128     _END_MASTER( myThid )
129     C If option globalFile is desired but does not work or if
130     C globalFile is too slow, then try using single-CPU I/O.
131     if (useSingleCpuIO) then
132    
133     C Master thread of process 0, only, opens a global file
134     _BEGIN_MASTER( myThid )
135     IF( mpiMyId .EQ. 0 ) THEN
136 jmc 1.6 write(dataFname,'(2a)') fName(1:IL),'.data'
137 heimbach 1.4 length_of_rec=MDS_RECLEN(filePrec,vec_size,mythid)
138     if (irecord .EQ. 1) then
139     open( dUnit, file=dataFName, status=_NEW_STATUS,
140     & access='direct', recl=length_of_rec )
141     else
142     open( dUnit, file=dataFName, status=_OLD_STATUS,
143     & access='direct', recl=length_of_rec )
144     endif
145     ENDIF
146     _END_MASTER( myThid )
147    
148     C Gather array and write it to file, one vertical level at a time
149     DO k=1,1
150     DO L=1,narr
151     local(L) = arr(L)
152     ENDDO
153     cph(
154     cph if ( irecord .EQ. 1 .AND. fName(1:IL) .EQ.
155     cph & 'tapelev2_7_the_main_loop_theta.it0000' ) then
156     cph lprint = .TRUE.
157     cph else
158     lprint = .FALSE.
159     cph endif
160     cph)
161     CALL GATHER_VECTOR( lprint, narr, global, local, myThid )
162     _BEGIN_MASTER( myThid )
163     IF( mpiMyId .EQ. 0 ) THEN
164     irec=irecord
165     if (filePrec .eq. precFloat32) then
166 heimbach 1.9 cph#if defined(ALLOW_EXCH2) && !defined(MISSING_TILE_IO)
167 heimbach 1.4 c
168 heimbach 1.9 cph#else /* defined(ALLOW_EXCH2) && !defined(MISSING_TILE_IO) */
169 heimbach 1.4 DO L=1,narr*nPx*nPy
170     xy_buffer_r4(L) = global(L)
171     ENDDO
172 heimbach 1.9 cph#endif /* defined(ALLOW_EXCH2) && !defined(MISSING_TILE_IO) */
173 heimbach 1.4 #ifdef _BYTESWAPIO
174     call MDS_BYTESWAPR4( vec_size, xy_buffer_r4 )
175     #endif
176     write(dUnit,rec=irec) xy_buffer_r4
177     elseif (filePrec .eq. precFloat64) then
178 heimbach 1.9 cph#if defined(ALLOW_EXCH2) && !defined(MISSING_TILE_IO)
179 heimbach 1.4 c
180 heimbach 1.9 cph#else /* defined(ALLOW_EXCH2) && !defined(MISSING_TILE_IO) */
181 heimbach 1.4 DO L=1,narr*nPx*nPy
182     xy_buffer_r8(L) = global(L)
183     ENDDO
184 heimbach 1.9 cph#endif /* defined(ALLOW_EXCH2) && !defined(MISSING_TILE_IO) */
185 heimbach 1.4 #ifdef _BYTESWAPIO
186     call MDS_BYTESWAPR8( vec_size, xy_buffer_r8 )
187     #endif
188     write(dUnit,rec=irec) xy_buffer_r8
189     else
190     write(msgbuf,'(a)')
191     & ' MDSWRITEFIELD: illegal value for filePrec'
192     call print_error( msgbuf, mythid )
193     stop 'ABNORMAL END: S/R MDSWRITEFIELD'
194     endif
195     ENDIF
196     _END_MASTER( myThid )
197     ENDDO
198    
199     C Close data-file and create meta-file
200     _BEGIN_MASTER( myThid )
201     IF( mpiMyId .EQ. 0 ) THEN
202     close( dUnit )
203 jmc 1.6 write(metaFName,'(2a)') fName(1:IL),'.meta'
204 heimbach 1.4 dimList(1,1)=vec_size
205     dimList(2,1)=1
206     dimList(3,1)=vec_size
207     dimList(1,2)=vec_size
208     dimList(2,2)=1
209     dimList(3,2)=vec_size
210     dimList(1,3)=1
211     dimList(2,3)=1
212     dimList(3,3)=1
213     ndims=1
214     cph if (nNz .EQ. 1) ndims=2
215     call MDSWRITEMETA( metaFName, dataFName,
216     & filePrec, ndims, dimList, irecord, myIter, mythid )
217     ENDIF
218     _END_MASTER( myThid )
219     C To be safe, make other processes wait for I/O completion
220     _BARRIER
221    
222     elseif ( .NOT. useSingleCpuIO ) then
223     _BEGIN_MASTER( myThid )
224     #endif /* ALLOW_USE_MPI */
225    
226 adcroft 1.1 C If we are writing to a global file then we open it here
227     if (globalFile) then
228 jmc 1.6 write(dataFname,'(2a)') fName(1:IL),'.data'
229 adcroft 1.1 if (irecord .EQ. 1) then
230     length_of_rec = MDS_RECLEN( filePrec, narr, mythid )
231     open( dUnit, file=dataFName, status=_NEW_STATUS,
232     & access='direct', recl=length_of_rec )
233     fileIsOpen=.TRUE.
234     else
235     length_of_rec = MDS_RECLEN( filePrec, narr, mythid )
236     open( dUnit, file=dataFName, status=_OLD_STATUS,
237     & access='direct', recl=length_of_rec )
238     fileIsOpen=.TRUE.
239     endif
240     endif
241    
242     C Loop over all tiles
243     ce do bj=1,nSy
244     ce do bi=1,nSx
245     C If we are writing to a tiled MDS file then we open each one here
246     if (.NOT. globalFile) then
247     iG=bi+(myXGlobalLo-1)/sNx ! Kludge until unstructered tiles
248     jG=bj+(myYGlobalLo-1)/sNy ! Kludge until unstructered tiles
249 jmc 1.6 write(dataFname,'(2a,i3.3,a,i3.3,a)')
250 heimbach 1.3 & pfName(1:pIL),'.',iG,'.',jG,'.data'
251 adcroft 1.1 if (irecord .EQ. 1) then
252     length_of_rec = MDS_RECLEN( filePrec, narr, mythid )
253     open( dUnit, file=dataFName, status=_NEW_STATUS,
254     & access='direct', recl=length_of_rec )
255     fileIsOpen=.TRUE.
256     else
257     length_of_rec = MDS_RECLEN( filePrec, narr, mythid )
258     open( dUnit, file=dataFName, status=_OLD_STATUS,
259     & access='direct', recl=length_of_rec )
260     fileIsOpen=.TRUE.
261     endif
262     endif
263     if (fileIsOpen) then
264     if (globalFile) then
265     iG = myXGlobalLo-1+(bi-1)*sNx
266     jG = myYGlobalLo-1+(bj-1)*sNy
267     irec = 1 + int(iG/sNx) + (jG/sNy)*nSx*nPx +
268     & (irecord-1)*nSx*nPx*nSy*nPy
269     else
270     iG = 0
271     jG = 0
272     irec = irecord
273     endif
274     if (filePrec .eq. precFloat32) then
275     call MDS_WRITE_RS_VEC( dUnit, irec, narr, arr, myThid )
276     elseif (filePrec .eq. precFloat64) then
277     call MDS_WRITE_RL_VEC( dUnit, irec, narr, arr, myThid )
278     else
279     write(msgbuf,'(a)')
280     & ' MDSWRITEVECTOR: illegal value for filePrec'
281     call print_error( msgbuf, mythid )
282     stop 'ABNORMAL END: S/R MDSWRITEVECTOR'
283     endif
284     else
285     write(msgbuf,'(a)')
286     & ' MDSWRITEVECTOR: I should never get to this point'
287     call print_error( msgbuf, mythid )
288     stop 'ABNORMAL END: S/R MDSWRITEVECTOR'
289     endif
290     C If we were writing to a tiled MDS file then we close it here
291     if (fileIsOpen .AND. (.NOT. globalFile)) then
292     close( dUnit )
293     fileIsOpen = .FALSE.
294     endif
295     C Create meta-file for each tile file
296     if (.NOT. globalFile) then
297     iG=bi+(myXGlobalLo-1)/sNx ! Kludge until unstructered tiles
298     jG=bj+(myYGlobalLo-1)/sNy ! Kludge until unstructered tiles
299 jmc 1.6 write(metaFname,'(2a,i3.3,a,i3.3,a)')
300 heimbach 1.3 & pfName(1:pIL),'.',iG,'.',jG,'.meta'
301 adcroft 1.1 dimList(1,1) = nPx*nSx*narr
302     dimList(2,1) = ((myXGlobalLo-1)/sNx + (bi-1))*narr + 1
303     dimList(3,1) = ((myXGlobalLo-1)/sNx + bi )*narr
304     dimList(1,2) = nPy*nSy
305     dimList(2,2) = (myYGlobalLo-1)/sNy + bj
306     dimList(3,2) = (myYGlobalLo-1)/sNy + bj
307     dimList(1,3) = 1
308     dimList(2,3) = 1
309     dimList(3,3) = 1
310     ndims=1
311     call MDSWRITEMETA( metaFName, dataFName,
312     & filePrec, ndims, dimList, irecord, myIter, mythid )
313     endif
314     C End of bi,bj loops
315     ce enddo
316     ce enddo
317    
318     C If global file was opened then close it
319     if (fileIsOpen .AND. globalFile) then
320     close( dUnit )
321     fileIsOpen = .FALSE.
322     endif
323    
324     C Create meta-file for global file
325     if (globalFile) then
326 jmc 1.6 write(metaFName,'(2a)') fName(1:IL),'.meta'
327 adcroft 1.1 dimList(1,1) = nPx*nSx*narr
328     dimList(2,1) = 1
329     dimList(3,1) = nPx*nSx*narr
330     dimList(1,2) = nPy*nSy
331     dimList(2,2) = 1
332     dimList(3,2) = nPy*nSy
333     dimList(1,3) = 1
334     dimList(2,3) = 1
335     dimList(3,3) = 1
336     ndims=1
337     call MDSWRITEMETA( metaFName, dataFName,
338     & filePrec, ndims, dimList, irecord, myIter, mythid )
339     endif
340    
341     _END_MASTER( myThid )
342 heimbach 1.4
343     #ifdef ALLOW_USE_MPI
344     C endif useSingleCpuIO
345     endif
346     #endif /* ALLOW_USE_MPI */
347    
348 jahn 1.10 #endif /* defined(ALLOW_AUTODIFF) || defined(ALLOW_FLT) */
349    
350 adcroft 1.1 C ------------------------------------------------------------------
351     return
352     end

  ViewVC Help
Powered by ViewVC 1.1.22