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

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

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


Revision 1.4 - (show annotations) (download)
Sun Aug 2 20:42:43 2009 UTC (14 years, 10 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint61u
Changes since 1.3: +8 -4 lines
changed to pass when compiling with strick checking of arguments across S/R

1 C $Header: /u/gcmpack/MITgcm/pkg/mdsio/mdsio_writevec_loc.F,v 1.3 2009/02/03 22:57:01 jmc Exp $
2 C $Name: $
3
4 #include "MDSIO_OPTIONS.h"
5
6 CBOP
7 C !ROUTINE: MDS_WRITEVEC_LOC
8 C !INTERFACE:
9 SUBROUTINE MDS_WRITEVEC_LOC(
10 I fName,
11 I filePrec,
12 U ioUnit,
13 I arrType,
14 I nArr,
15 I arr,
16 I bi, bj,
17 I irecord,
18 I myIter,
19 I myThid )
20
21 C !DESCRIPTION:
22 C Arguments:
23 C
24 C fName string :: base name for file to written
25 C filePrec integer :: number of bits per word in file (32 or 64)
26 C ioUnit integer :: fortran file IO unit
27 C nArr integer :: number of elements from input array "arr" to be written
28 C arrType char(2) :: declaration type of "arr": either "RS" or "RL"
29 C arr RS/RL :: array to WRITE, arr(nArr)
30 C bi,bj integer :: tile indices (if tiled array) or 0,0 if not a tiled array
31 C irecord integer :: record number to WRITE =|irecord|
32 C myIter integer :: time step number
33 C myThid integer :: my Thread Id number
34 C
35 C MDS_WRITEVEC_LOC according to ioUnit:
36 C ioUnit = 0 : open file, write and close the file (return ioUnit=0).
37 C ioUnit =-1 : open file, write and leave it open (return IO unit in ioUnit)
38 C ioUnit > 0 : assume file "ioUnit" is open, and write to it.
39 C MDS_WRITEVEC_LOC writes either to a file of the form "fName.data" and
40 C "fName.meta" IF bi=bj=0. Otherwise it writes to MDS tiled files of the
41 C form "fName.xxx.yyy.data" and "fName.xxx.yyy.meta".
42 C If irecord>0, a meta-file is created (skipped if irecord<0).
43 C The precision of the file is decsribed by filePrec, set either
44 C to floatPrec32 or floatPrec64.
45 C |irecord|=iRec is the record number to be written and must be >=1.
46
47 C !USES:
48 IMPLICIT NONE
49
50 C Global variables / common blocks
51 #include "SIZE.h"
52 #include "EEPARAMS.h"
53 #include "PARAMS.h"
54
55 C !INPUT/OUTPUT PARAMETERS:
56 CHARACTER*(*) fName
57 INTEGER ioUnit
58 INTEGER filePrec
59 CHARACTER*(2) arrType
60 INTEGER nArr
61 _RL arr(*)
62 INTEGER bi,bj
63 INTEGER irecord
64 INTEGER myIter
65 INTEGER myThid
66
67 C !FUNCTIONS:
68 INTEGER ILNBLNK
69 INTEGER MDS_RECLEN
70 EXTERNAL ILNBLNK
71 EXTERNAL MDS_RECLEN
72
73 C !LOCAL VARIABLES:
74 CHARACTER*(MAX_LEN_FNAM) dataFName, metaFName, pfName
75 CHARACTER*(MAX_LEN_MBUF) msgBuf
76 LOGICAL fileIsOpen
77 INTEGER iG,jG,iRec,k,dUnit,IL,pIL
78 INTEGER dimList(3,3), nDims, map2gl(2)
79 INTEGER length_of_rec
80 INTEGER loc_size
81 PARAMETER( loc_size = Nx+Ny+Nr )
82 real*4 r4seg(loc_size)
83 real*8 r8seg(loc_size)
84 _RL dummyRL(1)
85 CHARACTER*8 blank8c
86 CEOP
87
88 DATA dummyRL(1) / 0. _d 0 /
89 DATA blank8c / ' ' /
90 DATA map2gl / 0, 1 /
91
92 C We write a non-tiled array (bi=bj=0) only 1 time (if ProcId=0):
93 IF ( myProcId.EQ.0 .OR. bi.NE.0 .OR. bj.NE.0 ) THEN
94
95 C Only DO I/O IF I am the master thread
96 _BEGIN_MASTER( myThid )
97
98 C Assume nothing
99 fileIsOpen = .FALSE.
100 IL = ILNBLNK( fName )
101 iRec = ABS(irecord)
102
103 C Record number must be >= 1
104 IF ( iRec.LT.1 ) THEN
105 WRITE(msgBuf,'(A,I9)')
106 & ' MDS_WRITEVEC_LOC: argument irecord = ',irecord
107 CALL PRINT_ERROR( msgBuf, myThid )
108 WRITE(msgBuf,'(A)')
109 & ' MDS_WRITEVEC_LOC: invalid value for irecord'
110 CALL PRINT_ERROR( msgBuf, myThid )
111 STOP 'ABNORMAL END: S/R MDS_WRITEVEC_LOC'
112 ENDIF
113
114 C Check buffer size
115 IF ( nArr.GT.loc_size ) THEN
116 WRITE(msgBuf,'(3A)')
117 & ' MDS_WRITEVEC_LOC: writing to file "', fName(1:IL), '":'
118 CALL PRINT_ERROR( msgBuf, myThid )
119 WRITE(msgBuf,'(A,I9)')
120 & ' MDS_WRITEVEC_LOC: dim of arr to write=', nArr
121 CALL PRINT_ERROR( msgBuf, myThid )
122 WRITE(msgBuf,'(A,I9)')
123 & ' MDS_WRITEVEC_LOC: exceeds buffer size=', loc_size
124 CALL PRINT_ERROR( msgBuf, myThid )
125 STOP 'ABNORMAL END: S/R MDS_WRITEVEC_LOC'
126 ENDIF
127
128 C Assign special directory
129 IF ( mdsioLocalDir .NE. ' ' ) THEN
130 pIL = ILNBLNK( mdsioLocalDir )
131 WRITE(pFname,'(2A)') mdsioLocalDir(1:pIL), fName(1:IL)
132 pIL = IL + pIL
133 ELSE
134 WRITE(pFname,'(A)') fName(1:IL)
135 pIL = IL
136 ENDIF
137
138 IF ( ioUnit.GT.0 ) THEN
139 C- Assume file Unit is already open with correct Rec-Length & Precision
140 fileIsOpen = .TRUE.
141 dUnit = ioUnit
142 ELSE
143 C- Need to open file IO unit with File-name, Rec-Length & Precision
144
145 C Assign a free unit number as the I/O channel for this routine
146 CALL MDSFINDUNIT( dUnit, myThid )
147
148 C-- Set the file Name:
149 IF ( bi.EQ.0 .AND. bj.EQ.0 ) THEN
150 C- we are writing a non-tiled array (bi=bj=0):
151 WRITE(dataFname,'(2A)') fName(1:IL),'.data'
152 ELSE
153 C- we are writing a tiled array (bi>0,bj>0):
154 iG=bi+(myXGlobalLo-1)/sNx
155 jG=bj+(myYGlobalLo-1)/sNy
156 WRITE(dataFname,'(2A,I3.3,A,I3.3,A)')
157 & pfName(1:pIL),'.',iG,'.',jG,'.data'
158 ENDIF
159
160 C-- Open the file:
161 length_of_rec=MDS_RECLEN( filePrec, nArr, myThid )
162 IF (iRec .EQ. 1) THEN
163 OPEN( dUnit, file=dataFName, status=_NEW_STATUS,
164 & access='direct', recl=length_of_rec )
165 fileIsOpen=.TRUE.
166 ELSE
167 OPEN( dUnit, file=dataFName, status=_OLD_STATUS,
168 & access='direct', recl=length_of_rec )
169 fileIsOpen=.TRUE.
170 ENDIF
171 IF ( debugLevel.GE.debLevB ) THEN
172 WRITE(msgBuf,'(2A)')
173 & ' MDS_WRITEVEC_LOC: open file: ',dataFname(1:pIL+13)
174 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
175 & SQUEEZE_RIGHT , 1)
176 ENDIF
177 C- End if block: File Unit is already open / Need to open it
178 ENDIF
179
180 IF (fileIsOpen) THEN
181 IF ( arrType.EQ.'RS' ) THEN
182 CALL MDS_WR_REC_RS( arr, r4seg, r8seg,
183 I filePrec, dUnit, iRec, nArr, myThid )
184 ELSEIF ( arrType.EQ.'RL' ) THEN
185 CALL MDS_WR_REC_RL( arr, r4seg, r8seg,
186 I filePrec, dUnit, iRec, nArr, myThid )
187 ELSE
188 WRITE(msgBuf,'(A)')
189 & ' MDS_WRITEVEC_LOC: illegal value for arrType'
190 CALL PRINT_ERROR( msgBuf, myThid )
191 STOP 'ABNORMAL END: S/R MDS_WRITEVEC_LOC'
192 ENDIF
193 ELSE
194 WRITE(msgBuf,'(A)')
195 & ' MDS_WRITEVEC_LOC: should never reach this point'
196 CALL PRINT_ERROR( msgBuf, myThid )
197 STOP 'ABNORMAL END: S/R MDS_WRITEVEC_LOC'
198 ENDIF
199
200 C If we were writing to a tiled MDS file then we close it here
201 IF ( fileIsOpen .AND. ioUnit.EQ.0 ) THEN
202 CLOSE( dUnit )
203 fileIsOpen = .FALSE.
204 ENDIF
205 IF ( ioUnit.EQ.-1 ) ioUnit = dUnit
206
207 IF ( irecord.GT.0 ) THEN
208 C Create meta-file for each tile IF we are tiling
209 IF ( bi.EQ.0 .AND. bj.EQ.0 ) THEN
210 C-- we are writing a non-tiled array (bi=bj=0):
211 WRITE(metaFname,'(2A)') fName(1:IL),'.meta'
212 dimList(1,1)=1
213 dimList(2,1)=1
214 dimList(3,1)=1
215 dimList(1,2)=1
216 dimList(2,2)=1
217 dimList(3,2)=1
218 ELSE
219 C-- we are writing a tiled array (bi>0,bj>0):
220 iG=bi+(myXGlobalLo-1)/sNx
221 jG=bj+(myYGlobalLo-1)/sNy
222 WRITE(metaFname,'(2A,I3.3,A,I3.3,A)')
223 & pfName(1:pIL),'.',iG,'.',jG,'.meta'
224 dimList(1,1)=nSx*nPx
225 dimList(2,1)=iG
226 dimList(3,1)=iG
227 dimList(1,2)=nSy*nPy
228 dimList(2,2)=jG
229 dimList(3,2)=jG
230 ENDIF
231 dimList(1,3)=nArr
232 dimList(2,3)=1
233 dimList(3,3)=nArr
234 nDims=3
235 IF ( nArr.EQ.1 ) nDims=2
236 CALL MDS_WRITE_META(
237 I metaFName, dataFName, the_run_name, ' ',
238 I filePrec, nDims, dimList, map2gl, 0, blank8c,
239 I 0, dummyRL, iRec, myIter, myThid )
240 ENDIF
241
242 _END_MASTER( myThid )
243 ENDIF
244
245 RETURN
246 END

  ViewVC Help
Powered by ViewVC 1.1.22