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

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

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


Revision 1.5 - (show annotations) (download)
Tue Nov 30 16:11:10 2004 UTC (19 years, 7 months ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint57g_pre, checkpoint57b_post, checkpoint57g_post, checkpoint56b_post, checkpoint57d_post, checkpoint57i_post, checkpoint57, checkpoint57l_post, checkpoint57h_post, checkpoint57f_post, checkpoint57a_post, checkpoint57h_pre, checkpoint57c_post, checkpoint57c_pre, checkpoint57e_post, eckpoint57e_pre, checkpoint57h_done, checkpoint57j_post, checkpoint57f_pre, checkpoint56c_post, checkpoint57a_pre, checkpoint57k_post
Changes since 1.4: +4 -4 lines
For I/O vector routines change debugLevel to debLevB
(they are only used for tapelev I/O)

1 C $Header: /u/gcmpack/MITgcm/pkg/mdsio/mdsio_readvector.F,v 1.4 2003/07/18 21:10:50 heimbach Exp $
2 C $Name: $
3
4 #include "MDSIO_OPTIONS.h"
5
6 SUBROUTINE MDSREADVECTOR(
7 I fName,
8 I filePrec,
9 I arrType,
10 I narr,
11 O arr,
12 I bi,
13 I bj,
14 I irecord,
15 I myThid )
16 C
17 C Arguments:
18 C
19 C fName string base name for file to read
20 C filePrec integer number of bits per word in file (32 or 64)
21 C arrType char(2) declaration of "arr": either "RS" or "RL"
22 C narr integer size of third dimension: normally either 1 or Nr
23 C arr RS/RL array to read into, arr(narr)
24 ce bi integer x tile index
25 ce bj integer y tile index
26 C irecord integer record number to read
27 C myThid integer thread identifier
28 C
29 C Created: 03/26/99 eckert@mit.edu
30 C Modified: 03/29/99 adcroft@mit.edu + eckert@mit.edu
31 C Fixed to work work with _RS and _RL declarations
32 C Modified: 07/27/99 eckert@mit.edu
33 C Customized for state estimation (--> active_file_control.F)
34
35 implicit none
36 C Global variables / common blocks
37 #include "SIZE.h"
38 #include "EEPARAMS.h"
39 #include "PARAMS.h"
40
41 C Routine arguments
42 character*(*) fName
43 integer filePrec
44 character*(2) arrType
45 integer narr
46 Real arr(narr)
47 integer irecord
48 integer myThid
49 ce
50 integer bi,bj
51 ce
52
53 C Functions
54 integer ILNBLNK
55 integer MDS_RECLEN
56 C Local variables
57 character*(128) dataFName,pfName
58 integer iG,jG,irec,dUnit,IL,pIL
59 logical exst
60 logical globalFile,fileIsOpen
61 integer length_of_rec
62 character*(max_len_mbuf) msgbuf
63 C ------------------------------------------------------------------
64
65 C Only do I/O if I am the master thread
66 _BEGIN_MASTER( myThid )
67
68 C Record number must be >= 1
69 if (irecord .LT. 1) then
70 write(msgbuf,'(a,i9.8)')
71 & ' MDSREADVECTOR: argument irecord = ',irecord
72 call print_message( msgbuf, standardmessageunit,
73 & SQUEEZE_RIGHT , mythid)
74 write(msgbuf,'(a)')
75 & ' MDSREADVECTOR: invalid value for irecord'
76 call print_error( msgbuf, mythid )
77 stop 'ABNORMAL END: S/R MDSREADVECTOR'
78 endif
79
80 C Assume nothing
81 globalFile = .FALSE.
82 fileIsOpen = .FALSE.
83 IL = ILNBLNK( fName )
84 pIL = ILNBLNK( mdsioLocalDir )
85
86 C Assign special directory
87 if ( mdsioLocalDir .NE. ' ' ) then
88 write(pFname(1:128),'(2a)')
89 & mdsioLocalDir(1:pIL), fName(1:IL)
90 else
91 pFname= fName
92 endif
93 pIL=ILNBLNK( pfName )
94
95 C Assign a free unit number as the I/O channel for this routine
96 call MDSFINDUNIT( dUnit, mythid )
97
98 C Check first for global file with simple name (ie. fName)
99 dataFName = fName
100 inquire( file=dataFname, exist=exst )
101 if (exst) then
102 if ( debugLevel .GE. debLevB ) then
103 write(msgbuf,'(a,a)')
104 & ' MDSREADVECTOR: opening global file: ',dataFName
105 call print_message( msgbuf, standardmessageunit,
106 & SQUEEZE_RIGHT , mythid)
107 endif
108 globalFile = .TRUE.
109 endif
110
111 C If negative check for global file with MDS name (ie. fName.data)
112 if (.NOT. globalFile) then
113 write(dataFname(1:128),'(2a)') fName(1:IL),'.data'
114 inquire( file=dataFname, exist=exst )
115 if (exst) then
116 if ( debugLevel .GE. debLevB ) then
117 write(msgbuf,'(a,a)')
118 & ' MDSREADVECTOR: opening global file: ',dataFName
119 call print_message( msgbuf, standardmessageunit,
120 & SQUEEZE_RIGHT , mythid)
121 endif
122 globalFile = .TRUE.
123 endif
124 endif
125
126 C If we are reading from a global file then we open it here
127 if (globalFile) then
128 length_of_rec=MDS_RECLEN( filePrec, narr, mythid )
129 open( dUnit, file=dataFName, status='old',
130 & access='direct', recl=length_of_rec )
131 fileIsOpen=.TRUE.
132 endif
133
134 C Loop over all tiles
135 ce do bj=1,nSy
136 ce do bi=1,nSx
137 C If we are reading from a tiled MDS file then we open each one here
138 if (.NOT. globalFile) then
139 iG=bi+(myXGlobalLo-1)/sNx ! Kludge until unstructered tiles
140 jG=bj+(myYGlobalLo-1)/sNy ! Kludge until unstructered tiles
141 write(dataFname(1:128),'(2a,i3.3,a,i3.3,a)')
142 & pfName(1:pIL),'.',iG,'.',jG,'.data'
143 inquire( file=dataFname, exist=exst )
144 C Of course, we only open the file if the tile is "active"
145 C (This is a place-holder for the active/passive mechanism)
146 if (exst) then
147 if ( debugLevel .GE. debLevB ) then
148 write(msgbuf,'(a,a)')
149 & ' MDSREADVECTOR: opening file: ',dataFName
150 call print_message( msgbuf, standardmessageunit,
151 & SQUEEZE_RIGHT , mythid)
152 endif
153 length_of_rec=MDS_RECLEN( filePrec, narr, mythid )
154 open( dUnit, file=dataFName, status='old',
155 & access='direct', recl=length_of_rec )
156 fileIsOpen=.TRUE.
157 else
158 fileIsOpen=.FALSE.
159 write(msgbuf,'(3a)')
160 & ' MDSREADVECTOR: opening file: ',dataFName,pfName
161 call print_message( msgbuf, standardmessageunit,
162 & SQUEEZE_RIGHT , mythid)
163 write(msgbuf,'(a)')
164 & ' MDSREADVECTOR: un-active tiles not implemented yet'
165 call print_error( msgbuf, mythid )
166 stop 'ABNORMAL END: S/R MDSREADVECTOR'
167 endif
168 endif
169 if (fileIsOpen) then
170 if (globalFile) then
171 iG = myXGlobalLo-1+(bi-1)*sNx
172 jG = myYGlobalLo-1+(bj-1)*sNy
173 irec = 1 + int(iG/sNx) + (jG/sNy)*nSx*nPx +
174 & (irecord-1)*nSx*nPx*nSy*nPy
175 else
176 iG = 0
177 jG = 0
178 irec = irecord
179 endif
180 if (filePrec .eq. precFloat32) then
181 call MDS_READ_RS_VEC( dUnit, irec, narr, arr, myThid )
182 elseif (filePrec .eq. precFloat64) then
183 call MDS_READ_RL_VEC( dUnit, irec, narr, arr, myThid )
184 else
185 write(msgbuf,'(a)')
186 & ' MDSREADVECTOR: illegal value for filePrec'
187 call print_error( msgbuf, mythid )
188 stop 'ABNORMAL END: S/R MDSREADVECTOR'
189 endif
190 if (.NOT. globalFile) then
191 close( dUnit )
192 fileIsOpen = .FALSE.
193 endif
194 endif
195 C End of bi,bj loops
196 ce enddo
197 ce enddo
198
199 C If global file was opened then close it
200 if (fileIsOpen .AND. globalFile) then
201 close( dUnit )
202 fileIsOpen = .FALSE.
203 endif
204
205 _END_MASTER( myThid )
206
207 C ------------------------------------------------------------------
208 return
209 end

  ViewVC Help
Powered by ViewVC 1.1.22