/[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.2 - (show annotations) (download)
Fri Mar 7 04:30:08 2003 UTC (21 years, 3 months ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint50c_post, checkpoint50g_post, checkpoint50d_pre, checkpoint51, checkpoint50d_post, checkpoint50b_pre, checkpoint51b_pre, checkpoint50f_post, checkpoint50a_post, checkpoint50f_pre, checkpoint51b_post, checkpoint50c_pre, checkpoint50h_post, checkpoint50e_pre, checkpoint50i_post, checkpoint50e_post, checkpoint50, checkpoint50b_post, checkpoint51a_post
Changes since 1.1: +6 -2 lines
merging.

1 C $Header: /u/gcmpack/MITgcm/pkg/mdsio/mdsio_readvector.F,v 1.1 2001/03/06 15:28:54 adcroft 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*(80) dataFName
58 integer iG,jG,irec,dUnit,IL
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
85 C Assign a free unit number as the I/O channel for this routine
86 call MDSFINDUNIT( dUnit, mythid )
87
88 C Check first for global file with simple name (ie. fName)
89 dataFName = fName
90 inquire( file=dataFname, exist=exst )
91 if (exst) then
92 write(msgbuf,'(a,a)')
93 & ' MDSREADVECTOR: opening global file: ',dataFName
94 call print_message( msgbuf, standardmessageunit,
95 & SQUEEZE_RIGHT , mythid)
96 globalFile = .TRUE.
97 endif
98
99 C If negative check for global file with MDS name (ie. fName.data)
100 if (.NOT. globalFile) then
101 write(dataFname(1:80),'(2a)') fName(1:IL),'.data'
102 inquire( file=dataFname, exist=exst )
103 if (exst) then
104 write(msgbuf,'(a,a)')
105 & ' MDSREADVECTOR: opening global file: ',dataFName
106 call print_message( msgbuf, standardmessageunit,
107 & SQUEEZE_RIGHT , mythid)
108 globalFile = .TRUE.
109 endif
110 endif
111
112 C If we are reading from a global file then we open it here
113 if (globalFile) then
114 length_of_rec=MDS_RECLEN( filePrec, narr, mythid )
115 open( dUnit, file=dataFName, status='old',
116 & access='direct', recl=length_of_rec )
117 fileIsOpen=.TRUE.
118 endif
119
120 C Loop over all tiles
121 ce do bj=1,nSy
122 ce do bi=1,nSx
123 C If we are reading from a tiled MDS file then we open each one here
124 if (.NOT. globalFile) then
125 iG=bi+(myXGlobalLo-1)/sNx ! Kludge until unstructered tiles
126 jG=bj+(myYGlobalLo-1)/sNy ! Kludge until unstructered tiles
127 write(dataFname(1:80),'(2a,i3.3,a,i3.3,a)')
128 & fName(1:IL),'.',iG,'.',jG,'.data'
129 inquire( file=dataFname, exist=exst )
130 C Of course, we only open the file if the tile is "active"
131 C (This is a place-holder for the active/passive mechanism)
132 if (exst) then
133 write(msgbuf,'(a,a)')
134 & ' MDSREADVECTOR: opening file: ',dataFName
135 call print_message( msgbuf, standardmessageunit,
136 & SQUEEZE_RIGHT , mythid)
137 length_of_rec=MDS_RECLEN( filePrec, narr, mythid )
138 open( dUnit, file=dataFName, status='old',
139 & access='direct', recl=length_of_rec )
140 fileIsOpen=.TRUE.
141 else
142 fileIsOpen=.FALSE.
143 write(msgbuf,'(a,a)')
144 & ' MDSREADVECTOR: opening file: ',dataFName
145 call print_message( msgbuf, standardmessageunit,
146 & SQUEEZE_RIGHT , mythid)
147 write(msgbuf,'(a)')
148 & ' MDSREADVECTOR: un-active tiles not implemented yet'
149 call print_error( msgbuf, mythid )
150 stop 'ABNORMAL END: S/R MDSREADVECTOR'
151 endif
152 endif
153 if (fileIsOpen) then
154 if (globalFile) then
155 iG = myXGlobalLo-1+(bi-1)*sNx
156 jG = myYGlobalLo-1+(bj-1)*sNy
157 irec = 1 + int(iG/sNx) + (jG/sNy)*nSx*nPx +
158 & (irecord-1)*nSx*nPx*nSy*nPy
159 else
160 iG = 0
161 jG = 0
162 irec = irecord
163 endif
164 if (filePrec .eq. precFloat32) then
165 call MDS_READ_RS_VEC( dUnit, irec, narr, arr, myThid )
166 elseif (filePrec .eq. precFloat64) then
167 call MDS_READ_RL_VEC( dUnit, irec, narr, arr, myThid )
168 else
169 write(msgbuf,'(a)')
170 & ' MDSREADVECTOR: illegal value for filePrec'
171 call print_error( msgbuf, mythid )
172 stop 'ABNORMAL END: S/R MDSREADVECTOR'
173 endif
174 if (.NOT. globalFile) then
175 close( dUnit )
176 fileIsOpen = .FALSE.
177 endif
178 endif
179 C End of bi,bj loops
180 ce enddo
181 ce enddo
182
183 C If global file was opened then close it
184 if (fileIsOpen .AND. globalFile) then
185 close( dUnit )
186 fileIsOpen = .FALSE.
187 endif
188
189 _END_MASTER( myThid )
190
191 C ------------------------------------------------------------------
192 return
193 end

  ViewVC Help
Powered by ViewVC 1.1.22