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

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

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


Revision 1.1 - (hide annotations) (download)
Tue Mar 6 15:28:54 2001 UTC (23 years, 3 months ago) by adcroft
Branch: MAIN
CVS Tags: checkpoint46b_post, checkpoint48f_post, checkpoint46k_post, checkpoint47j_post, icebear2, checkpoint46c_pre, checkpoint48d_pre, branch-exfmods-tag, checkpoint47e_post, checkpoint44h_pre, release1_p12, checkpoint48i_post, release1_p10, release1_p16, release1_p15, release1_p11, pre38tag1, checkpoint47, checkpoint47f_post, ecco_c44_e16, checkpoint48d_post, checkpoint46j_post, checkpoint47c_post, checkpoint50e_post, checkpoint50c_post, checkpoint47d_post, ecco_c44_e21, ecco_c44_e26, ecco_c44_e27, ecco_c44_e24, checkpoint44f_pre, checkpoint45a_post, checkpoint47a_post, icebear3, checkpoint46f_post, ecco_c50_e33a, checkpoint46a_post, checkpoint48a_post, checkpoint46n_post, release1_p13_pre, checkpoint46d_pre, checkpoint48e_post, checkpoint46e_post, checkpoint45b_post, checkpoint48h_post, checkpoint50c_pre, release1-branch_tutorials, ecco_c50_e28, checkpoint40pre1, release1_p14, checkpoint44g_post, checkpoint46h_pre, checkpoint45c_post, checkpoint44h_post, release1_p12_pre, chkpt44c_post, checkpoint44e_post, checkpoint46e_pre, ecco-branch-mod4, checkpoint43a-release1mods, checkpoint50h_post, ecco_c44_e22, checkpoint50d_pre, checkpoint47i_post, release1_p13, checkpoint46l_pre, checkpoint46j_pre, checkpoint46b_pre, checkpoint45d_post, checkpoint47h_post, checkpoint48c_post, checkpoint46l_post, chkpt44a_pre, release1-branch-end, checkpoint50b_pre, c37_adj, release1_final_v1, ecco_c44_e19, checkpoint51b_post, checkpoint46, checkpoint44f_post, ecco_c44_e20, ecco_c50_e31, checkpoint44, ecco_c44_e18, checkpoint48, checkpoint49, checkpoint50i_post, checkpoint47b_post, checkpoint40pre2, checkpoint40pre5, checkpoint40pre6, checkpoint40pre8, checkpoint48g_post, ecco_c44_e17, release1_p17, release1_b1, checkpoint44b_post, ecco_c51_e34, chkpt44d_post, ecco_c50_e29, checkpoint42, release1_p9, checkpoint51, checkpoint50, release1_p8, checkpoint50d_post, checkpoint43, checkpoint46m_post, checkpoint46g_pre, release1_p2, release1_p3, release1_p4, checkpoint51b_pre, release1_p6, checkpoint47g_post, chkpt44a_post, checkpoint44b_pre, release1_p1, checkpoint40pre4, checkpoint46a_pre, ecco-branch-mod1, checkpoint40pre3, checkpoint50g_post, release1_p5, checkpoint44e_pre, chkpt44c_pre, checkpoint40pre9, ecco_ice2, ecco_ice1, pre38-close, checkpoint46d_post, ecco-branch-mod2, checkpoint48b_post, checkpoint50b_post, checkpoint46g_post, ecco_c51_e34a, ecco_c51_e34b, checkpoint50f_post, checkpoint50a_post, ecco_c50_e32, checkpoint50f_pre, ecco-branch-mod3, ecco_c50_e33, checkpoint47d_pre, checkpoint37, ecco_c50_e30, checkpoint48c_pre, ecco-branch-mod5, checkpoint46i_post, release1_beta1, ecco_c44_e23, release1-branch_branchpoint, checkpoint40pre7, checkpoint46c_post, checkpoint51a_post, checkpoint40, checkpoint45, checkpoint39, checkpoint46h_post, checkpoint50e_pre, checkpoint38, release1_chkpt44d_post, ecco_c44_e25, icebear5, icebear4, checkpoint41, release1_p7
Branch point for: c24_e25_ice, ecco-branch, pre38, release1_coupled, icebear, release1_final, release1-branch, release1, release1_50yr, branch-exfmods-curt
Packaged mdsio.

Note: using a "feature" of genmake to keep original mdsio.F and mdsio_gl.F
in place during testing of mdsio package. To use original code simply
use genmake -disable=mdsio.
                                             Enjoy.

1 adcroft 1.1 C $Header: $
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
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     write(msgbuf,'(a,a)')
98     & ' MDSREADFIELD: opening global file: ',dataFName
99     call print_message( msgbuf, standardmessageunit,
100     & SQUEEZE_RIGHT , mythid)
101     globalFile = .TRUE.
102     endif
103    
104     C If negative check for global file with MDS name (ie. fName.data)
105     if (.NOT. globalFile) then
106     write(dataFname(1:80),'(2a)') fName(1:IL),'.data'
107     inquire( file=dataFname, exist=exst )
108     if (exst) then
109     write(msgbuf,'(a,a)')
110     & ' MDSREADFIELD: opening global file: ',dataFName
111     call print_message( msgbuf, standardmessageunit,
112     & SQUEEZE_RIGHT , mythid)
113     globalFile = .TRUE.
114     endif
115     endif
116    
117     C If we are reading from a global file then we open it here
118     if (globalFile) then
119     length_of_rec=MDS_RECLEN( filePrec, sNx, mythid )
120     open( dUnit, file=dataFName, status='old',
121     & access='direct', recl=length_of_rec )
122     fileIsOpen=.TRUE.
123     endif
124    
125     C Loop over all tiles
126     do bj=1,nSy
127     do bi=1,nSx
128     C If we are reading from a tiled MDS file then we open each one here
129     if (.NOT. globalFile) then
130     iG=bi+(myXGlobalLo-1)/sNx ! Kludge until unstructered tiles
131     jG=bj+(myYGlobalLo-1)/sNy ! Kludge until unstructered tiles
132     write(dataFname(1:80),'(2a,i3.3,a,i3.3,a)')
133     & fName(1:IL),'.',iG,'.',jG,'.data'
134     inquire( file=dataFname, exist=exst )
135     C Of course, we only open the file if the tile is "active"
136     C (This is a place-holder for the active/passive mechanism
137     if (exst) then
138     write(msgbuf,'(a,a)')
139     & ' MDSREADFIELD: opening file: ',dataFName
140     call print_message( msgbuf, standardmessageunit,
141     & SQUEEZE_RIGHT , mythid)
142     length_of_rec=MDS_RECLEN( filePrec, sNx, mythid )
143     open( dUnit, file=dataFName, status='old',
144     & access='direct', recl=length_of_rec )
145     fileIsOpen=.TRUE.
146     else
147     fileIsOpen=.FALSE.
148     write(msgbuf,'(a,a)')
149     & ' MDSREADFIELD: filename: ',dataFName
150     call print_message( msgbuf, standardmessageunit,
151     & SQUEEZE_RIGHT , mythid)
152     write(msgbuf,'(a)')
153     & ' MDSREADFIELD: File does not exist'
154     call print_error( msgbuf, mythid )
155     stop 'ABNORMAL END: S/R MDSREADFIELD'
156     endif
157     endif
158    
159     if (fileIsOpen) then
160     do k=1,nNz
161     do j=1,sNy
162     if (globalFile) then
163     iG = myXGlobalLo-1 + (bi-1)*sNx
164     jG = myYGlobalLo-1 + (bj-1)*sNy
165     irec=1 + INT(iG/sNx) + nSx*nPx*(jG+j-1) + nSx*nPx*Ny*(k-1)
166     & + nSx*nPx*Ny*nNz*(irecord-1)
167     else
168     iG = 0
169     jG = 0
170     irec=j + sNy*(k-1) + sNy*nNz*(irecord-1)
171     endif
172     if (filePrec .eq. precFloat32) then
173     read(dUnit,rec=irec) r4seg
174     #ifdef _BYTESWAPIO
175     call MDS_BYTESWAPR4( sNx, r4seg )
176     #endif
177     if (arrType .eq. 'RS') then
178     call MDS_SEG4toRS( j,bi,bj,k,nNz, r4seg, .TRUE., arr )
179     elseif (arrType .eq. 'RL') then
180     call MDS_SEG4toRL( j,bi,bj,k,nNz, r4seg, .TRUE., arr )
181     else
182     write(msgbuf,'(a)')
183     & ' MDSREADFIELD: illegal value for arrType'
184     call print_error( msgbuf, mythid )
185     stop 'ABNORMAL END: S/R MDSREADFIELD'
186     endif
187     elseif (filePrec .eq. precFloat64) then
188     read(dUnit,rec=irec) r8seg
189     #ifdef _BYTESWAPIO
190     call MDS_BYTESWAPR8( sNx, r8seg )
191     #endif
192     if (arrType .eq. 'RS') then
193     call MDS_SEG8toRS( j,bi,bj,k,nNz, r8seg, .TRUE., arr )
194     elseif (arrType .eq. 'RL') then
195     call MDS_SEG8toRL( j,bi,bj,k,nNz, r8seg, .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     else
203     write(msgbuf,'(a)')
204     & ' MDSREADFIELD: illegal value for filePrec'
205     call print_error( msgbuf, mythid )
206     stop 'ABNORMAL END: S/R MDSREADFIELD'
207     endif
208     C End of j loop
209     enddo
210     C End of k loop
211     enddo
212     if (.NOT. globalFile) then
213     close( dUnit )
214     fileIsOpen = .FALSE.
215     endif
216     endif
217     C End of bi,bj loops
218     enddo
219     enddo
220    
221     C If global file was opened then close it
222     if (fileIsOpen .AND. globalFile) then
223     close( dUnit )
224     fileIsOpen = .FALSE.
225     endif
226    
227     _END_MASTER( myThid )
228    
229     C ------------------------------------------------------------------
230     return
231     end

  ViewVC Help
Powered by ViewVC 1.1.22