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

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

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


Revision 1.4 - (show annotations) (download)
Wed Nov 2 14:49:12 2005 UTC (18 years, 6 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint58l_post, checkpoint58e_post, checkpoint58b_post, checkpoint58m_post, checkpoint58r_post, checkpoint57y_post, checkpoint58g_post, checkpoint57x_post, checkpoint58n_post, checkpoint58h_post, checkpoint58j_post, checkpoint57y_pre, checkpoint58, checkpoint58f_post, checkpoint58d_post, checkpoint57w_post, checkpoint58a_post, checkpoint58i_post, mitgcm_mapl_00, checkpoint58o_post, checkpoint57z_post, checkpoint58c_post, checkpoint58k_post, checkpoint58s_post, checkpoint58p_post, checkpoint58q_post
Changes since 1.3: +11 -11 lines
- use MAX_LEN_FNAM (instead of hard coded 80) in file-name declaration

1 C $Header: /u/gcmpack/MITgcm/pkg/mdsio/mdsio_readfield_loc.F,v 1.3 2004/11/17 03:04:36 heimbach Exp $
2 C $Name: $
3
4 #include "MDSIO_OPTIONS.h"
5
6 SUBROUTINE MDSREADFIELD_LOC(
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*(MAX_LEN_FNAM) dataFName
61 integer iG,jG,irec,bi,bj,j,k,dUnit,IL
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
90 C Assign a free unit number as the I/O channel for this routine
91 call MDSFINDUNIT( dUnit, mythid )
92
93 C Check first for global file with simple name (ie. fName)
94 dataFName = fName
95 inquire( file=dataFName, exist=exst )
96 if (exst) then
97 if ( debugLevel .GE. debLevA ) then
98 write(msgbuf,'(a,a)')
99 & ' MDSREADFIELD: opening global file: ',dataFName(1:IL)
100 call print_message( msgbuf, standardmessageunit,
101 & SQUEEZE_RIGHT , mythid)
102 endif
103 globalFile = .TRUE.
104 endif
105
106 C If negative check for global file with MDS name (ie. fName.data)
107 if (.NOT. globalFile) then
108 write(dataFName,'(2a)') fName(1:IL),'.data'
109 inquire( file=dataFName, exist=exst )
110 if (exst) then
111 if ( debugLevel .GE. debLevA ) then
112 write(msgbuf,'(a,a)')
113 & ' MDSREADFIELD: opening global file: ',dataFName(1:IL+5)
114 call print_message( msgbuf, standardmessageunit,
115 & SQUEEZE_RIGHT , mythid)
116 endif
117 globalFile = .TRUE.
118 endif
119 endif
120
121 C If we are reading from a global file then we open it here
122 if (globalFile) then
123 length_of_rec=MDS_RECLEN( filePrec, sNx, mythid )
124 open( dUnit, file=dataFName, status='old',
125 & access='direct', recl=length_of_rec )
126 fileIsOpen=.TRUE.
127 endif
128
129 C Loop over all tiles
130 do bj=1,nSy
131 do bi=1,nSx
132 C If we are reading from a tiled MDS file then we open each one here
133 if (.NOT. globalFile) then
134 iG=bi+(myXGlobalLo-1)/sNx ! Kludge until unstructered tiles
135 jG=bj+(myYGlobalLo-1)/sNy ! Kludge until unstructered tiles
136 write(dataFName,'(2a,i3.3,a,i3.3,a)')
137 & fName(1:IL),'.',iG,'.',jG,'.data'
138 inquire( file=dataFName, exist=exst )
139 C Of course, we only open the file if the tile is "active"
140 C (This is a place-holder for the active/passive mechanism
141 if (exst) then
142 if ( debugLevel .GE. debLevA ) then
143 write(msgbuf,'(a,a)')
144 & ' MDSREADFIELD: opening file: ',dataFName(1:IL+13)
145 call print_message( msgbuf, standardmessageunit,
146 & SQUEEZE_RIGHT , mythid)
147 endif
148 length_of_rec=MDS_RECLEN( filePrec, sNx, mythid )
149 open( dUnit, file=dataFName, status='old',
150 & access='direct', recl=length_of_rec )
151 fileIsOpen=.TRUE.
152 else
153 fileIsOpen=.FALSE.
154 write(msgbuf,'(a,a)')
155 & ' MDSREADFIELD: filename: ',dataFName(1:IL+13)
156 call print_message( msgbuf, standardmessageunit,
157 & SQUEEZE_RIGHT , mythid)
158 call print_error( msgbuf, mythid )
159 write(msgbuf,'(a)')
160 & ' MDSREADFIELD: File does not exist'
161 call print_message( msgbuf, standardmessageunit,
162 & SQUEEZE_RIGHT , mythid)
163 call print_error( msgbuf, mythid )
164 stop 'ABNORMAL END: S/R MDSREADFIELD'
165 endif
166 endif
167
168 if (fileIsOpen) then
169 do k=1,nNz
170 do j=1,sNy
171 if (globalFile) then
172 iG = myXGlobalLo-1 + (bi-1)*sNx
173 jG = myYGlobalLo-1 + (bj-1)*sNy
174 irec=1 + INT(iG/sNx) + nSx*nPx*(jG+j-1) + nSx*nPx*Ny*(k-1)
175 & + nSx*nPx*Ny*nNz*(irecord-1)
176 else
177 iG = 0
178 jG = 0
179 irec=j + sNy*(k-1) + sNy*nNz*(irecord-1)
180 endif
181 if (filePrec .eq. precFloat32) then
182 read(dUnit,rec=irec) r4seg
183 #ifdef _BYTESWAPIO
184 call MDS_BYTESWAPR4( sNx, r4seg )
185 #endif
186 if (arrType .eq. 'RS') then
187 call MDS_SEG4toRS( j,bi,bj,k,nNz, r4seg, .TRUE., arr )
188 elseif (arrType .eq. 'RL') then
189 call MDS_SEG4toRL( j,bi,bj,k,nNz, r4seg, .TRUE., arr )
190 else
191 write(msgbuf,'(a)')
192 & ' MDSREADFIELD: illegal value for arrType'
193 call print_error( msgbuf, mythid )
194 stop 'ABNORMAL END: S/R MDSREADFIELD'
195 endif
196 elseif (filePrec .eq. precFloat64) then
197 read(dUnit,rec=irec) r8seg
198 #ifdef _BYTESWAPIO
199 call MDS_BYTESWAPR8( sNx, r8seg )
200 #endif
201 if (arrType .eq. 'RS') then
202 call MDS_SEG8toRS( j,bi,bj,k,nNz, r8seg, .TRUE., arr )
203 elseif (arrType .eq. 'RL') then
204 call MDS_SEG8toRL( j,bi,bj,k,nNz, r8seg, .TRUE., arr )
205 else
206 write(msgbuf,'(a)')
207 & ' MDSREADFIELD: illegal value for arrType'
208 call print_error( msgbuf, mythid )
209 stop 'ABNORMAL END: S/R MDSREADFIELD'
210 endif
211 else
212 write(msgbuf,'(a)')
213 & ' MDSREADFIELD: illegal value for filePrec'
214 call print_error( msgbuf, mythid )
215 stop 'ABNORMAL END: S/R MDSREADFIELD'
216 endif
217 C End of j loop
218 enddo
219 C End of k loop
220 enddo
221 if (.NOT. globalFile) then
222 close( dUnit )
223 fileIsOpen = .FALSE.
224 endif
225 endif
226 C End of bi,bj loops
227 enddo
228 enddo
229
230 C If global file was opened then close it
231 if (fileIsOpen .AND. globalFile) then
232 close( dUnit )
233 fileIsOpen = .FALSE.
234 endif
235
236 _END_MASTER( myThid )
237
238 C ------------------------------------------------------------------
239 return
240 end

  ViewVC Help
Powered by ViewVC 1.1.22