/[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.2 - (hide annotations) (download)
Tue Jul 8 15:00:27 2003 UTC (20 years, 11 months ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint51c_post
Changes since 1.1: +14 -5 lines
o introducing integer flag debugLevel
o introducing pathname variable mdsioLocalDir for mdsio

1 heimbach 1.2 C $Header: /u/gcmpack/MITgcm/pkg/mdsio/mdsio_writevector.F,v 1.1 2001/03/06 15:28:54 adcroft Exp $
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    
46     C Routine arguments
47     character*(*) fName
48     integer filePrec
49     logical globalfile
50     character*(2) arrType
51     integer narr
52     Real arr(narr)
53     integer irecord
54     integer myIter
55     integer myThid
56     ce
57     integer bi,bj
58     ce
59    
60     C Functions
61     integer ILNBLNK
62     integer MDS_RECLEN
63     C Local variables
64 heimbach 1.2 character*(80) dataFName,metaFName,pfName
65     integer iG,jG,irec,dUnit,IL,pIL
66 adcroft 1.1 logical fileIsOpen
67     integer dimList(3,3),ndims
68     integer length_of_rec
69     character*(max_len_mbuf) msgbuf
70     C ------------------------------------------------------------------
71    
72     C Only do I/O if I am the master thread
73     _BEGIN_MASTER( myThid )
74    
75     C Record number must be >= 1
76     if (irecord .LT. 1) then
77     write(msgbuf,'(a,i9.8)')
78     & ' MDSWRITEVECTOR: argument irecord = ',irecord
79     call print_message( msgbuf, standardmessageunit,
80     & SQUEEZE_RIGHT , mythid)
81     write(msgbuf,'(a)')
82     & ' MDSWRITEVECTOR: invalid value for irecord'
83     call print_error( msgbuf, mythid )
84     stop 'ABNORMAL END: S/R MDSWRITEVECTOR'
85     endif
86    
87     C Assume nothing
88     fileIsOpen = .FALSE.
89 heimbach 1.2 IL = ILNBLNK( fName )
90     pIL = ILNBLNK( mdsioLocalDir )
91    
92     C Assign special directory
93     if ( mdsioLocalDir .NE. ' ' ) then
94     write(pFname(1:80),'(2a)') mdsioLocalDir(1:pIL), fName(1:IL)
95     else
96     pFname= fName
97     endif
98     pIL=ILNBLNK( pfName )
99 adcroft 1.1
100     C Assign a free unit number as the I/O channel for this routine
101     call MDSFINDUNIT( dUnit, mythid )
102    
103     C If we are writing to a global file then we open it here
104     if (globalFile) then
105     write(dataFname(1:80),'(2a)') fName(1:IL),'.data'
106     if (irecord .EQ. 1) then
107     length_of_rec = MDS_RECLEN( filePrec, narr, mythid )
108     open( dUnit, file=dataFName, status=_NEW_STATUS,
109     & access='direct', recl=length_of_rec )
110     fileIsOpen=.TRUE.
111     else
112     length_of_rec = MDS_RECLEN( filePrec, narr, mythid )
113     open( dUnit, file=dataFName, status=_OLD_STATUS,
114     & access='direct', recl=length_of_rec )
115     fileIsOpen=.TRUE.
116     endif
117     endif
118    
119     C Loop over all tiles
120     ce do bj=1,nSy
121     ce do bi=1,nSx
122     C If we are writing to a tiled MDS file then we open each one here
123     if (.NOT. globalFile) then
124     iG=bi+(myXGlobalLo-1)/sNx ! Kludge until unstructered tiles
125     jG=bj+(myYGlobalLo-1)/sNy ! Kludge until unstructered tiles
126     write(dataFname(1:80),'(2a,i3.3,a,i3.3,a)')
127     & fName(1:IL),'.',iG,'.',jG,'.data'
128     if (irecord .EQ. 1) then
129     length_of_rec = MDS_RECLEN( filePrec, narr, mythid )
130     open( dUnit, file=dataFName, status=_NEW_STATUS,
131     & access='direct', recl=length_of_rec )
132     fileIsOpen=.TRUE.
133     else
134     length_of_rec = MDS_RECLEN( filePrec, narr, mythid )
135     open( dUnit, file=dataFName, status=_OLD_STATUS,
136     & access='direct', recl=length_of_rec )
137     fileIsOpen=.TRUE.
138     endif
139     endif
140     if (fileIsOpen) then
141     if (globalFile) then
142     iG = myXGlobalLo-1+(bi-1)*sNx
143     jG = myYGlobalLo-1+(bj-1)*sNy
144     irec = 1 + int(iG/sNx) + (jG/sNy)*nSx*nPx +
145     & (irecord-1)*nSx*nPx*nSy*nPy
146     else
147     iG = 0
148     jG = 0
149     irec = irecord
150     endif
151     if (filePrec .eq. precFloat32) then
152     call MDS_WRITE_RS_VEC( dUnit, irec, narr, arr, myThid )
153     elseif (filePrec .eq. precFloat64) then
154     call MDS_WRITE_RL_VEC( dUnit, irec, narr, arr, myThid )
155     else
156     write(msgbuf,'(a)')
157     & ' MDSWRITEVECTOR: illegal value for filePrec'
158     call print_error( msgbuf, mythid )
159     stop 'ABNORMAL END: S/R MDSWRITEVECTOR'
160     endif
161     else
162     write(msgbuf,'(a)')
163     & ' MDSWRITEVECTOR: I should never get to this point'
164     call print_error( msgbuf, mythid )
165     stop 'ABNORMAL END: S/R MDSWRITEVECTOR'
166     endif
167     C If we were writing to a tiled MDS file then we close it here
168     if (fileIsOpen .AND. (.NOT. globalFile)) then
169     close( dUnit )
170     fileIsOpen = .FALSE.
171     endif
172     C Create meta-file for each tile file
173     if (.NOT. globalFile) then
174     iG=bi+(myXGlobalLo-1)/sNx ! Kludge until unstructered tiles
175     jG=bj+(myYGlobalLo-1)/sNy ! Kludge until unstructered tiles
176     write(metaFname(1:80),'(2a,i3.3,a,i3.3,a)')
177     & fName(1:IL),'.',iG,'.',jG,'.meta'
178     dimList(1,1) = nPx*nSx*narr
179     dimList(2,1) = ((myXGlobalLo-1)/sNx + (bi-1))*narr + 1
180     dimList(3,1) = ((myXGlobalLo-1)/sNx + bi )*narr
181     dimList(1,2) = nPy*nSy
182     dimList(2,2) = (myYGlobalLo-1)/sNy + bj
183     dimList(3,2) = (myYGlobalLo-1)/sNy + bj
184     dimList(1,3) = 1
185     dimList(2,3) = 1
186     dimList(3,3) = 1
187     ndims=1
188     call MDSWRITEMETA( metaFName, dataFName,
189     & filePrec, ndims, dimList, irecord, myIter, mythid )
190     endif
191     C End of bi,bj loops
192     ce enddo
193     ce enddo
194    
195     C If global file was opened then close it
196     if (fileIsOpen .AND. globalFile) then
197     close( dUnit )
198     fileIsOpen = .FALSE.
199     endif
200    
201     C Create meta-file for global file
202     if (globalFile) then
203     write(metaFName(1:80),'(2a)') fName(1:IL),'.meta'
204     dimList(1,1) = nPx*nSx*narr
205     dimList(2,1) = 1
206     dimList(3,1) = nPx*nSx*narr
207     dimList(1,2) = nPy*nSy
208     dimList(2,2) = 1
209     dimList(3,2) = nPy*nSy
210     dimList(1,3) = 1
211     dimList(2,3) = 1
212     dimList(3,3) = 1
213     ndims=1
214     call MDSWRITEMETA( metaFName, dataFName,
215     & filePrec, ndims, dimList, irecord, myIter, mythid )
216     endif
217    
218     _END_MASTER( myThid )
219     C ------------------------------------------------------------------
220     return
221     end

  ViewVC Help
Powered by ViewVC 1.1.22