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

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

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


Revision 1.2 - (show annotations) (download)
Tue Jul 8 15:00:27 2003 UTC (20 years, 11 months ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint51k_post, checkpoint51l_post, checkpoint51j_post, checkpoint51o_pre, checkpoint51n_pre, checkpoint52d_pre, checkpoint51f_pre, branchpoint-genmake2, branch-netcdf, checkpoint51r_post, checkpoint52b_pre, checkpoint51i_post, checkpoint51e_post, checkpoint51l_pre, checkpoint51c_post, checkpoint51o_post, checkpoint51q_post, checkpoint52, checkpoint52a_post, checkpoint52b_post, checkpoint52c_post, checkpoint51h_pre, checkpoint51g_post, ecco_c52_e35, checkpoint51f_post, checkpoint52a_pre, checkpoint51d_post, checkpoint51m_post, checkpoint51t_post, checkpoint51p_post, checkpoint51n_post, checkpoint51i_pre, checkpoint51u_post, checkpoint51s_post
Branch point for: branch-genmake2, branch-nonh, tg2-branch, checkpoint51n_branch
Changes since 1.1: +29 -14 lines
o introducing integer flag debugLevel
o introducing pathname variable mdsioLocalDir for mdsio

1 C $Header: /u/gcmpack/MITgcm/pkg/mdsio/mdsio_readfield.F,v 1.1 2001/03/06 15:28:54 adcroft Exp $
2 C $Name: $
3
4 #include "MDSIO_OPTIONS.h"
5
6 SUBROUTINE MDSREADFIELD(
7 I fName,
8 I filePrec,
9 I arrType,
10 I nNz,
11 O arr,
12 I irecord,
13 I myThid )
14 C
15 C Arguments:
16 C
17 C fName string base name for file to read
18 C filePrec integer number of bits per word in file (32 or 64)
19 C arrType char(2) declaration of "arr": either "RS" or "RL"
20 C nNz integer size of third dimension: normally either 1 or Nr
21 C arr RS/RL array to read into, arr(:,:,nNz,:,:)
22 C irecord integer record number to read
23 C myThid integer thread identifier
24 C
25 C MDSREADFIELD first checks to see if the file "fName" exists, then
26 C if the file "fName.data" exists and finally the tiled files of the
27 C form "fName.xxx.yyy.data" exist. Currently, the meta-files are not
28 C read because it is difficult to parse files in fortran.
29 C The precision of the file is decsribed by filePrec, set either
30 C to floatPrec32 or floatPrec64. The precision or declaration of
31 C the array argument must be consistently described by the char*(2)
32 C string arrType, either "RS" or "RL". nNz allows for both 2-D and
33 C 3-D arrays to be handled. nNz=1 implies a 2-D model field and
34 C nNz=Nr implies a 3-D model field. irecord is the record number
35 C to be read and must be >= 1. The file data is stored in
36 C arr *but* the overlaps are *not* updated. ie. An exchange must
37 C be called. This is because the routine is sometimes called from
38 C within a MASTER_THID region.
39 C
40 C Created: 03/16/99 adcroft@mit.edu
41
42 implicit none
43 C Global variables / common blocks
44 #include "SIZE.h"
45 #include "EEPARAMS.h"
46 #include "PARAMS.h"
47
48 C Routine arguments
49 character*(*) fName
50 integer filePrec
51 character*(2) arrType
52 integer nNz
53 Real arr(*)
54 integer irecord
55 integer myThid
56 C Functions
57 integer ILNBLNK
58 integer MDS_RECLEN
59 C Local variables
60 character*(80) dataFName,pfName
61 integer iG,jG,irec,bi,bj,j,k,dUnit,IL,pIL
62 logical exst
63 Real*4 r4seg(sNx)
64 Real*8 r8seg(sNx)
65 logical globalFile,fileIsOpen
66 integer length_of_rec
67 character*(max_len_mbuf) msgbuf
68 C ------------------------------------------------------------------
69
70 C Only do I/O if I am the master thread
71 _BEGIN_MASTER( myThid )
72
73 C Record number must be >= 1
74 if (irecord .LT. 1) then
75 write(msgbuf,'(a,i9.8)')
76 & ' MDSREADFIELD: argument irecord = ',irecord
77 call print_message( msgbuf, standardmessageunit,
78 & SQUEEZE_RIGHT , mythid)
79 write(msgbuf,'(a)')
80 & ' MDSREADFIELD: Invalid value for irecord'
81 call print_error( msgbuf, mythid )
82 stop 'ABNORMAL END: S/R MDSREADFIELD'
83 endif
84
85 C Assume nothing
86 globalFile = .FALSE.
87 fileIsOpen = .FALSE.
88 IL = ILNBLNK( fName )
89 pIL = ILNBLNK( mdsioLocalDir )
90
91 C Assign special directory
92 if ( mdsioLocalDir .NE. ' ' ) then
93 write(pFname(1:80),'(2a)') mdsioLocalDir(1:pIL), fName(1:IL)
94 else
95 pFname= fName
96 endif
97 pIL=ILNBLNK( pfName )
98
99 C Assign a free unit number as the I/O channel for this routine
100 call MDSFINDUNIT( dUnit, mythid )
101
102 C Check first for global file with simple name (ie. fName)
103 dataFName = fName
104 inquire( file=dataFname, exist=exst )
105 if (exst) then
106 if ( debugLevel .GE. debLevA ) then
107 write(msgbuf,'(a,a)')
108 & ' MDSREADFIELD: opening global file: ',dataFName
109 call print_message( msgbuf, standardmessageunit,
110 & SQUEEZE_RIGHT , mythid)
111 endif
112 globalFile = .TRUE.
113 endif
114
115 C If negative check for global file with MDS name (ie. fName.data)
116 if (.NOT. globalFile) then
117 write(dataFname(1:80),'(2a)') fName(1:IL),'.data'
118 inquire( file=dataFname, exist=exst )
119 if (exst) then
120 if ( debugLevel .GE. debLevA ) then
121 write(msgbuf,'(a,a)')
122 & ' MDSREADFIELD: opening global file: ',dataFName
123 call print_message( msgbuf, standardmessageunit,
124 & SQUEEZE_RIGHT , mythid)
125 endif
126 globalFile = .TRUE.
127 endif
128 endif
129
130 C If we are reading from a global file then we open it here
131 if (globalFile) then
132 length_of_rec=MDS_RECLEN( filePrec, sNx, mythid )
133 open( dUnit, file=dataFName, status='old',
134 & access='direct', recl=length_of_rec )
135 fileIsOpen=.TRUE.
136 endif
137
138 C Loop over all tiles
139 do bj=1,nSy
140 do bi=1,nSx
141 C If we are reading from a tiled MDS file then we open each one here
142 if (.NOT. globalFile) then
143 iG=bi+(myXGlobalLo-1)/sNx ! Kludge until unstructered tiles
144 jG=bj+(myYGlobalLo-1)/sNy ! Kludge until unstructered tiles
145 write(dataFname(1:80),'(2a,i3.3,a,i3.3,a)')
146 & pfName(1:pIL),'.',iG,'.',jG,'.data'
147 inquire( file=dataFname, exist=exst )
148 C Of course, we only open the file if the tile is "active"
149 C (This is a place-holder for the active/passive mechanism
150 if (exst) then
151 if ( debugLevel .GE. debLevA ) then
152 write(msgbuf,'(a,a)')
153 & ' MDSREADFIELD: opening file: ',dataFName
154 call print_message( msgbuf, standardmessageunit,
155 & SQUEEZE_RIGHT , mythid)
156 endif
157 length_of_rec=MDS_RECLEN( filePrec, sNx, mythid )
158 open( dUnit, file=dataFName, status='old',
159 & access='direct', recl=length_of_rec )
160 fileIsOpen=.TRUE.
161 else
162 fileIsOpen=.FALSE.
163 write(msgbuf,'(3a)')
164 & ' MDSREADFIELD: filename: ',dataFName, pfName
165 call print_message( msgbuf, standardmessageunit,
166 & SQUEEZE_RIGHT , mythid)
167 write(msgbuf,'(a)')
168 & ' MDSREADFIELD: File does not exist'
169 call print_error( msgbuf, mythid )
170 stop 'ABNORMAL END: S/R MDSREADFIELD'
171 endif
172 endif
173
174 if (fileIsOpen) then
175 do k=1,nNz
176 do j=1,sNy
177 if (globalFile) then
178 iG = myXGlobalLo-1 + (bi-1)*sNx
179 jG = myYGlobalLo-1 + (bj-1)*sNy
180 irec=1 + INT(iG/sNx) + nSx*nPx*(jG+j-1) + nSx*nPx*Ny*(k-1)
181 & + nSx*nPx*Ny*nNz*(irecord-1)
182 else
183 iG = 0
184 jG = 0
185 irec=j + sNy*(k-1) + sNy*nNz*(irecord-1)
186 endif
187 if (filePrec .eq. precFloat32) then
188 read(dUnit,rec=irec) r4seg
189 #ifdef _BYTESWAPIO
190 call MDS_BYTESWAPR4( sNx, r4seg )
191 #endif
192 if (arrType .eq. 'RS') then
193 call MDS_SEG4toRS( j,bi,bj,k,nNz, r4seg, .TRUE., arr )
194 elseif (arrType .eq. 'RL') then
195 call MDS_SEG4toRL( j,bi,bj,k,nNz, r4seg, .TRUE., arr )
196 else
197 write(msgbuf,'(a)')
198 & ' MDSREADFIELD: illegal value for arrType'
199 call print_error( msgbuf, mythid )
200 stop 'ABNORMAL END: S/R MDSREADFIELD'
201 endif
202 elseif (filePrec .eq. precFloat64) then
203 read(dUnit,rec=irec) r8seg
204 #ifdef _BYTESWAPIO
205 call MDS_BYTESWAPR8( sNx, r8seg )
206 #endif
207 if (arrType .eq. 'RS') then
208 call MDS_SEG8toRS( j,bi,bj,k,nNz, r8seg, .TRUE., arr )
209 elseif (arrType .eq. 'RL') then
210 call MDS_SEG8toRL( j,bi,bj,k,nNz, r8seg, .TRUE., arr )
211 else
212 write(msgbuf,'(a)')
213 & ' MDSREADFIELD: illegal value for arrType'
214 call print_error( msgbuf, mythid )
215 stop 'ABNORMAL END: S/R MDSREADFIELD'
216 endif
217 else
218 write(msgbuf,'(a)')
219 & ' MDSREADFIELD: illegal value for filePrec'
220 call print_error( msgbuf, mythid )
221 stop 'ABNORMAL END: S/R MDSREADFIELD'
222 endif
223 C End of j loop
224 enddo
225 C End of k loop
226 enddo
227 if (.NOT. globalFile) then
228 close( dUnit )
229 fileIsOpen = .FALSE.
230 endif
231 endif
232 C End of bi,bj loops
233 enddo
234 enddo
235
236 C If global file was opened then close it
237 if (fileIsOpen .AND. globalFile) then
238 close( dUnit )
239 fileIsOpen = .FALSE.
240 endif
241
242 _END_MASTER( myThid )
243
244 C ------------------------------------------------------------------
245 return
246 end

  ViewVC Help
Powered by ViewVC 1.1.22