/[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.3 - (show annotations) (download)
Tue Feb 3 22:57:01 2009 UTC (15 years, 4 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint61n, checkpoint61o, checkpoint61l, checkpoint61m, checkpoint61j, checkpoint61k, checkpoint61i, checkpoint61t, checkpoint61r, checkpoint61s, checkpoint61p, checkpoint61q
Changes since 1.2: +104 -78 lines
- removed S/R mdsio_writevec_loc from mdsio_ad.flow list
- add argument to by-pass Open/Close of file ;
- add option to by-pass writing of meta file.

1 C $Header: /u/gcmpack/MITgcm/pkg/mdsio/mdsio_writevec_loc.F,v 1.2 2008/12/30 02:13: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 CEOP
85
86 DATA map2gl / 0, 1 /
87
88 C We write a non-tiled array (bi=bj=0) only 1 time (if ProcId=0):
89 IF ( myProcId.EQ.0 .OR. bi.NE.0 .OR. bj.NE.0 ) THEN
90
91 C Only DO I/O IF I am the master thread
92 _BEGIN_MASTER( myThid )
93
94 C Assume nothing
95 fileIsOpen = .FALSE.
96 IL = ILNBLNK( fName )
97 iRec = ABS(irecord)
98
99 C Record number must be >= 1
100 IF ( iRec.LT.1 ) THEN
101 WRITE(msgBuf,'(A,I9)')
102 & ' MDS_WRITEVEC_LOC: argument irecord = ',irecord
103 CALL PRINT_ERROR( msgBuf, myThid )
104 WRITE(msgBuf,'(A)')
105 & ' MDS_WRITEVEC_LOC: invalid value for irecord'
106 CALL PRINT_ERROR( msgBuf, myThid )
107 STOP 'ABNORMAL END: S/R MDS_WRITEVEC_LOC'
108 ENDIF
109
110 C Check buffer size
111 IF ( nArr.GT.loc_size ) THEN
112 WRITE(msgBuf,'(3A)')
113 & ' MDS_WRITEVEC_LOC: writing to file "', fName(1:IL), '":'
114 CALL PRINT_ERROR( msgBuf, myThid )
115 WRITE(msgBuf,'(A,I9)')
116 & ' MDS_WRITEVEC_LOC: dim of arr to write=', nArr
117 CALL PRINT_ERROR( msgBuf, myThid )
118 WRITE(msgBuf,'(A,I9)')
119 & ' MDS_WRITEVEC_LOC: exceeds buffer size=', loc_size
120 CALL PRINT_ERROR( msgBuf, myThid )
121 STOP 'ABNORMAL END: S/R MDS_WRITEVEC_LOC'
122 ENDIF
123
124 C Assign special directory
125 IF ( mdsioLocalDir .NE. ' ' ) THEN
126 pIL = ILNBLNK( mdsioLocalDir )
127 WRITE(pFname,'(2A)') mdsioLocalDir(1:pIL), fName(1:IL)
128 pIL = IL + pIL
129 ELSE
130 WRITE(pFname,'(A)') fName(1:IL)
131 pIL = IL
132 ENDIF
133
134 IF ( ioUnit.GT.0 ) THEN
135 C- Assume file Unit is already open with correct Rec-Length & Precision
136 fileIsOpen = .TRUE.
137 dUnit = ioUnit
138 ELSE
139 C- Need to open file IO unit with File-name, Rec-Length & Precision
140
141 C Assign a free unit number as the I/O channel for this routine
142 CALL MDSFINDUNIT( dUnit, myThid )
143
144 C-- Set the file Name:
145 IF ( bi.EQ.0 .AND. bj.EQ.0 ) THEN
146 C- we are writing a non-tiled array (bi=bj=0):
147 WRITE(dataFname,'(2A)') fName(1:IL),'.data'
148 ELSE
149 C- we are writing a tiled array (bi>0,bj>0):
150 iG=bi+(myXGlobalLo-1)/sNx
151 jG=bj+(myYGlobalLo-1)/sNy
152 WRITE(dataFname,'(2A,I3.3,A,I3.3,A)')
153 & pfName(1:pIL),'.',iG,'.',jG,'.data'
154 ENDIF
155
156 C-- Open the file:
157 length_of_rec=MDS_RECLEN( filePrec, nArr, myThid )
158 IF (iRec .EQ. 1) THEN
159 OPEN( dUnit, file=dataFName, status=_NEW_STATUS,
160 & access='direct', recl=length_of_rec )
161 fileIsOpen=.TRUE.
162 ELSE
163 OPEN( dUnit, file=dataFName, status=_OLD_STATUS,
164 & access='direct', recl=length_of_rec )
165 fileIsOpen=.TRUE.
166 ENDIF
167 IF ( debugLevel.GE.debLevB ) THEN
168 WRITE(msgBuf,'(2A)')
169 & ' MDS_WRITEVEC_LOC: open file: ',dataFname(1:pIL+13)
170 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
171 & SQUEEZE_RIGHT , 1)
172 ENDIF
173 C- End if block: File Unit is already open / Need to open it
174 ENDIF
175
176 IF (fileIsOpen) THEN
177 IF ( arrType.EQ.'RS' ) THEN
178 CALL MDS_WR_REC_RS( arr, r4seg, r8seg,
179 I filePrec, dUnit, iRec, nArr, myThid )
180 ELSEIF ( arrType.EQ.'RL' ) THEN
181 CALL MDS_WR_REC_RL( arr, r4seg, r8seg,
182 I filePrec, dUnit, iRec, nArr, myThid )
183 ELSE
184 WRITE(msgBuf,'(A)')
185 & ' MDS_WRITEVEC_LOC: illegal value for arrType'
186 CALL PRINT_ERROR( msgBuf, myThid )
187 STOP 'ABNORMAL END: S/R MDS_WRITEVEC_LOC'
188 ENDIF
189 ELSE
190 WRITE(msgBuf,'(A)')
191 & ' MDS_WRITEVEC_LOC: should never reach this point'
192 CALL PRINT_ERROR( msgBuf, myThid )
193 STOP 'ABNORMAL END: S/R MDS_WRITEVEC_LOC'
194 ENDIF
195
196 C If we were writing to a tiled MDS file then we close it here
197 IF ( fileIsOpen .AND. ioUnit.EQ.0 ) THEN
198 CLOSE( dUnit )
199 fileIsOpen = .FALSE.
200 ENDIF
201 IF ( ioUnit.EQ.-1 ) ioUnit = dUnit
202
203 IF ( irecord.GT.0 ) THEN
204 C Create meta-file for each tile IF we are tiling
205 IF ( bi.EQ.0 .AND. bj.EQ.0 ) THEN
206 C-- we are writing a non-tiled array (bi=bj=0):
207 WRITE(metaFname,'(2A)') fName(1:IL),'.meta'
208 dimList(1,1)=1
209 dimList(2,1)=1
210 dimList(3,1)=1
211 dimList(1,2)=1
212 dimList(2,2)=1
213 dimList(3,2)=1
214 ELSE
215 C-- we are writing a tiled array (bi>0,bj>0):
216 iG=bi+(myXGlobalLo-1)/sNx
217 jG=bj+(myYGlobalLo-1)/sNy
218 WRITE(metaFname,'(2A,I3.3,A,I3.3,A)')
219 & pfName(1:pIL),'.',iG,'.',jG,'.meta'
220 dimList(1,1)=nSx*nPx
221 dimList(2,1)=iG
222 dimList(3,1)=iG
223 dimList(1,2)=nSy*nPy
224 dimList(2,2)=jG
225 dimList(3,2)=jG
226 ENDIF
227 dimList(1,3)=nArr
228 dimList(2,3)=1
229 dimList(3,3)=nArr
230 nDims=3
231 IF ( nArr.EQ.1 ) nDims=2
232 CALL MDS_WRITE_META(
233 I metaFName, dataFName, the_run_name, ' ',
234 I filePrec, nDims, dimList, map2gl, 0, ' ',
235 I 0, UNSET_RL, iRec, myIter, myThid )
236 ENDIF
237
238 _END_MASTER( myThid )
239 ENDIF
240
241 RETURN
242 END

  ViewVC Help
Powered by ViewVC 1.1.22