/[MITgcm]/MITgcm/pkg/flt/flt_mdsreadvector.F
ViewVC logotype

Contents of /MITgcm/pkg/flt/flt_mdsreadvector.F

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


Revision 1.3 - (show annotations) (download)
Wed Dec 3 02:34:10 2008 UTC (15 years, 5 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint62c, checkpoint62a, checkpoint62g, checkpoint62f, checkpoint62e, checkpoint62d, checkpoint62i, checkpoint62h, checkpoint62, checkpoint62b, checkpoint61n, checkpoint61q, checkpoint61z, checkpoint61g, checkpoint61o, checkpoint61l, checkpoint61m, checkpoint61j, checkpoint61k, checkpoint61h, checkpoint61i, checkpoint61v, checkpoint61w, checkpoint61t, checkpoint61u, checkpoint61r, checkpoint61s, checkpoint61p, checkpoint61x, checkpoint61y
Changes since 1.2: +3 -3 lines
change condition for writing to STDOUT ( debLevB instead debLevA )

1 C $Header: /u/gcmpack/MITgcm/pkg/flt/flt_mdsreadvector.F,v 1.2 2008/12/03 01:43:07 jmc Exp $
2 C $Name: $
3
4 #include "FLT_OPTIONS.h"
5
6
7 #undef SAFE_IO
8
9 #ifdef SAFE_IO
10 #define _NEW_STATUS 'new'
11 #else
12 #define _NEW_STATUS 'unknown'
13 #endif
14
15 SUBROUTINE FLT_MDSREADVECTOR(
16 I fName,
17 O globalFile,
18 I filePrec,
19 I arrType,
20 I narr,
21 O arr,
22 I bi,
23 I bj,
24 I irecord,
25 I myThid )
26 C
27 C Arguments:
28 C
29 C fName string base name for file to read
30 C filePrec integer number of bits per word in file (32 or 64)
31 C arrType char(2) declaration of "arr": either "RS" or "RL"
32 C narr integer size of third dimension: normally either 1 or Nr
33 C arr RS/RL array to read into, arr(narr)
34 ce bi integer x tile index
35 ce bj integer y tile index
36 C irecord integer record number to read
37 C myThid integer thread identifier
38 C
39 C Created: 03/26/99 eckert@mit.edu
40 C Modified: 03/29/99 adcroft@mit.edu + eckert@mit.edu
41 C Fixed to work work with _RS and _RL declarations
42 C Modified: 07/27/99 eckert@mit.edu
43 C Customized for state estimation (--> active_file_control.F)
44 c Modified: 09/29/00 abiastoch@ucsd.edu
45 c based on mdsreadvector
46 c Checks first for local files and then for global
47
48 IMPLICIT NONE
49 C Global variables / COMMON blocks
50 #include "SIZE.h"
51 #include "EEPARAMS.h"
52 #include "PARAMS.h"
53
54 C Routine arguments
55 CHARACTER*(*) fName
56 INTEGER filePrec
57 CHARACTER*(2) arrType
58 INTEGER narr
59 c Real arr(narr)
60 _RL arr(narr)
61 INTEGER irecord
62 INTEGER myThid
63 INTEGER bi,bj
64
65 C Functions
66 INTEGER ILNBLNK
67 EXTERNAL ILNBLNK
68 INTEGER MDS_RECLEN
69 EXTERNAL MDS_RECLEN
70 C Local variables
71 CHARACTER*(MAX_LEN_FNAM) dataFName
72 INTEGER i,iG,jG,irec,dUnit,IL,iLfn
73 LOGICAL exst
74 LOGICAL globalFile,fileIsOpen
75 INTEGER length_of_rec
76 CHARACTER*(max_len_mbuf) msgbuf
77 C ------------------------------------------------------------------
78
79 C Only DO I/O IF I am the master thread
80 _BEGIN_MASTER( myThid )
81
82 C Record number must be >= 1
83 IF (irecord .LT. 1) THEN
84 WRITE(msgbuf,'(A,I9.8)')
85 & ' FLT_MDSREADVECTOR: argument irecord = ',irecord
86 CALL PRINT_MESSAGE( msgbuf, standardmessageunit,
87 & SQUEEZE_RIGHT , myThid)
88 WRITE(msgbuf,'(A)')
89 & ' FLT_MDSREADVECTOR: invalid value for irecord'
90 CALL PRINT_ERROR( msgbuf, myThid )
91 STOP 'ABNORMAL END: S/R FLT_MDSREADVECTOR'
92 ENDIF
93 IF ( arrType.NE.'RL' ) THEN
94 WRITE(msgbuf,'(3A)')
95 & ' FLT_MDSREADVECTOR: not yet coded for arrType="',arrType,'"'
96 CALL PRINT_ERROR( msgbuf, myThid )
97 STOP 'ABNORMAL END: S/R FLT_MDSREADVECTOR'
98 ENDIF
99
100 C Assume nothing
101 globalFile = .TRUE.
102 fileIsOpen = .FALSE.
103 IL=ILNBLNK( fName )
104
105 C Assign a free unit number as the I/O channel for this routine
106 CALL MDSFINDUNIT( dUnit, myThid )
107
108 C Check first for local file
109 iG=bi+(myXGlobalLo-1)/sNx ! Kludge until unstructered tiles
110 jG=bj+(myYGlobalLo-1)/sNy ! Kludge until unstructered tiles
111 WRITE(dataFname,'(2A,I3.3,A,I3.3,A)')
112 & fName(1:IL),'.',iG,'.',jG,'.data'
113 INQUIRE( file=dataFname, exist=exst )
114 C Of course, we only open the file IF the tile is "active"
115 C (This is a place-holder for the active/passive mechanism)
116 IF (exst) THEN
117 globalFile = .FALSE.
118 ENDIF
119
120 C If no local file is available check for global files
121 IF (globalFile) THEN
122 C Check first for global file with simple name (ie. fName)
123 WRITE(dataFname,'(2A)') fName(1:IL)
124 iLfn = IL
125 INQUIRE( file=dataFname, exist=exst )
126 c IF (exst) THEN
127 c write(0,*) 'found file: ',dataFname(1:iLfn)
128 c ENDIF
129 IF ( .NOT.exst) THEN
130 WRITE(dataFname,'(2A)') fName(1:IL),'.data'
131 iLfn = IL+5
132 INQUIRE( file=dataFname, exist=exst )
133 c IF (exst) THEN
134 c write(0,*) 'found file: ',dataFname(1:iLfn)
135 c ENDIF
136 ENDIF
137 ENDIF
138
139 C If we are reading from a global file then we open it here
140 IF (globalFile) THEN
141 IF ( debugLevel.GE.debLevB ) THEN
142 WRITE(msgbuf,'(A,A)')
143 & ' FLT_MDSREADVECTOR: opening global file: ',dataFName(1:iLfn)
144 CALL PRINT_MESSAGE( msgbuf, standardmessageunit,
145 & SQUEEZE_RIGHT , myThid)
146 ENDIF
147 length_of_rec=MDS_RECLEN( filePrec, narr, myThid )
148 OPEN( dUnit, file=dataFName, status='old',
149 & access='direct', recl=length_of_rec )
150 fileIsOpen=.TRUE.
151 ENDIF
152
153 C Loop over all tiles
154 ce DO bj=1,nSy
155 ce DO bi=1,nSx
156 C If we are reading from a tiled MDS file then we open each one here
157 IF (.NOT. globalFile) THEN
158 iG=bi+(myXGlobalLo-1)/sNx ! Kludge until unstructered tiles
159 jG=bj+(myYGlobalLo-1)/sNy ! Kludge until unstructered tiles
160 WRITE(dataFname,'(2A,I3.3,A,I3.3,A)')
161 & fName(1:IL),'.',iG,'.',jG,'.data'
162 iLfn= IL+8+5
163 INQUIRE( file=dataFname, exist=exst )
164 C Of course, we only open the file IF the tile is "active"
165 C (This is a place-holder for the active/passive mechanism)
166 IF (exst) THEN
167 IF ( debugLevel.GE.debLevB ) THEN
168 WRITE(msgbuf,'(A,A)')
169 & ' FLT_MDSREADVECTOR: opening file: ',dataFName(1:iLfn)
170 CALL PRINT_MESSAGE( msgbuf, standardmessageunit,
171 & SQUEEZE_RIGHT , myThid)
172 ENDIF
173 length_of_rec=MDS_RECLEN( filePrec, narr, myThid )
174 OPEN( dUnit, file=dataFName, status='old',
175 & access='direct', recl=length_of_rec )
176 fileIsOpen=.TRUE.
177 ELSE
178 fileIsOpen=.FALSE.
179 WRITE(msgbuf,'(A)')
180 & ' FLT_MDSREADVECTOR: un-active tiles not implemented yet'
181 CALL PRINT_ERROR( msgbuf, myThid )
182 STOP 'ABNORMAL END: S/R FLT_MDSREADVECTOR'
183 ENDIF
184 ENDIF
185
186 IF (fileIsOpen) THEN
187 irec = irecord
188 IF (filePrec .EQ. precFloat32) THEN
189 C- wrong S/R call: should be MDS_READ_R4_VEC_RL (if arrType=RL)
190 C- or MDS_READ_R4_VEC_RS (if arrType=RS)
191 c CALL MDS_READ_RS_VEC( dUnit, irec, narr, arr, myThid )
192 WRITE(msgbuf,'(A,I8)')
193 & ' FLT_MDSREADVECTOR: not yet coded for filePrec=',filePrec
194 CALL PRINT_ERROR( msgbuf, myThid )
195 STOP 'ABNORMAL END: S/R FLT_MDSREADVECTOR'
196 ELSEIF (filePrec .EQ. precFloat64) THEN
197 C- wrong S/R call: should be MDS_READ_R8_VEC_RL (if arrType=RL)
198 C- or MDS_READ_R8_VEC_RS (if arrType=RS)
199 C- + byte-swapp should be inside MDS_READ_RL_VEC
200 c CALL MDS_READ_RL_VEC( dUnit, irec, narr, arr, myThid )
201 READ( dUnit, rec=irec ) ( arr(i),i=1,narr )
202 #ifdef _BYTESWAPIO
203 CALL MDS_BYTESWAPR8( narr, arr )
204 #endif
205 ELSE
206 WRITE(msgbuf,'(A)')
207 & ' FLT_MDSREADVECTOR: illegal value for filePrec'
208 CALL PRINT_ERROR( msgbuf, myThid )
209 STOP 'ABNORMAL END: S/R FLT_MDSREADVECTOR'
210 ENDIF
211 IF (.NOT. globalFile) THEN
212 CLOSE( dUnit )
213 fileIsOpen = .FALSE.
214 ENDIF
215 ENDIF
216 C End of bi,bj loops
217 ce ENDDO
218 ce ENDDO
219
220 C If global file was opened then close it
221 IF (fileIsOpen .AND. globalFile) THEN
222 CLOSE( dUnit )
223 fileIsOpen = .FALSE.
224 ENDIF
225
226 _END_MASTER( myThid )
227
228 C ------------------------------------------------------------------
229 RETURN
230 END

  ViewVC Help
Powered by ViewVC 1.1.22