1 |
C $Header: /u/gcmpack/MITgcm/pkg/exf/exf_interp_read.F,v 1.14 2011/06/07 22:19:48 jmc Exp $ |
2 |
C $Name: $ |
3 |
|
4 |
#include "EXF_OPTIONS.h" |
5 |
|
6 |
CBOP |
7 |
C !ROUTINE: EXF_INTERP_READ |
8 |
C !INTERFACE: |
9 |
SUBROUTINE EXF_INTERP_READ( |
10 |
I infile, filePrec, |
11 |
O arrayin, |
12 |
I irecord, nx_in, ny_in, myThid ) |
13 |
|
14 |
C !DESCRIPTION: |
15 |
|
16 |
C !USES: |
17 |
IMPLICIT NONE |
18 |
|
19 |
C Global variables / common blocks |
20 |
#include "SIZE.h" |
21 |
#include "EEPARAMS.h" |
22 |
#include "EXF_PARAM.h" |
23 |
#ifdef ALLOW_USE_MPI |
24 |
# include "EESUPPORT.h" |
25 |
#endif /* ALLOW_USE_MPI */ |
26 |
#include "PARAMS.h" |
27 |
|
28 |
|
29 |
C !INPUT/OUTPUT PARAMETERS: |
30 |
C infile (string) :: name of the binary input file (direct access) |
31 |
C filePrec (integer) :: number of bits per word in file (32 or 64) |
32 |
C arrayin ( _RL ) :: array to read file into |
33 |
C irecord (integer) :: record number to read |
34 |
C nx_in,ny_in (integer) :: size in x & y direction of input file to read |
35 |
C myThid (integer) :: My Thread Id number |
36 |
|
37 |
CHARACTER*(*) infile |
38 |
INTEGER filePrec, irecord, nx_in, ny_in |
39 |
_RL arrayin( -1:nx_in+2 , -1:ny_in+2 ) |
40 |
INTEGER myThid |
41 |
CEOP |
42 |
|
43 |
C !FUNCTIONS |
44 |
INTEGER ILNBLNK |
45 |
INTEGER MDS_RECLEN |
46 |
LOGICAL MASTER_CPU_IO |
47 |
EXTERNAL ILNBLNK |
48 |
EXTERNAL MDS_RECLEN |
49 |
EXTERNAL MASTER_CPU_IO |
50 |
|
51 |
C !LOCAL VARIABLES |
52 |
INTEGER i, j |
53 |
INTEGER ioUnit, length_of_rec, IL |
54 |
CHARACTER*(MAX_LEN_MBUF) msgBuf |
55 |
LOGICAL exst |
56 |
#ifdef EXF_INTERP_USE_DYNALLOC |
57 |
#ifdef EXF_IREAD_USE_GLOBAL_POINTER |
58 |
C When using threads the address of the local automatic array |
59 |
C "buffer" is not visible to the other threads. So we create |
60 |
C a pointer to share that address here. This is presently |
61 |
C in an ifdef because it won't go through g77 and I'm not |
62 |
C currently sure what TAF would do with this. |
63 |
COMMON /EXF_IOPTR8/ glPtr8 |
64 |
REAL*8, POINTER :: glPtr8(:,:) |
65 |
COMMON /EXF_IOPTR4/ glPtr4 |
66 |
REAL*4, POINTER :: glPtr4(:,:) |
67 |
|
68 |
Real*8, target :: buffer_r8(nx_in,ny_in) |
69 |
Real*4, target :: buffer_r4(nx_in,ny_in) |
70 |
#else /* ndef EXF_IREAD_USE_GLOBAL_POINTER */ |
71 |
Real*8 buffer_r8(nx_in,ny_in) |
72 |
Real*4 buffer_r4(nx_in,ny_in) |
73 |
#endif /* ndef EXF_IREAD_USE_GLOBAL_POINTER */ |
74 |
#else /* ndef EXF_INTERP_USE_DYNALLOC */ |
75 |
Real*8 buffer_r8(exf_interp_bufferSize) |
76 |
Real*4 buffer_r4(exf_interp_bufferSize) |
77 |
COMMON /EXF_INTERP_BUFFER/ buffer_r8, buffer_r4 |
78 |
INTEGER ijs |
79 |
#endif /* ndef EXF_INTERP_USE_DYNALLOC */ |
80 |
#ifdef ALLOW_USE_MPI |
81 |
INTEGER ierr |
82 |
#endif |
83 |
|
84 |
C-- Check for consistency: |
85 |
#ifdef EXF_INTERP_USE_DYNALLOC |
86 |
#ifndef EXF_IREAD_USE_GLOBAL_POINTER |
87 |
C The CPP symbol EXF_IREAD_USE_GLOBAL_POINTER must be defined for the |
88 |
C case of nThreads > 1. Stop IF it isnt. |
89 |
IF ( nThreads .GT. 1 ) THEN |
90 |
STOP |
91 |
&'EXF_INTERP_READ: nThreads > 1 needs EXF_IREAD_USE_GLOBAL_POINTER' |
92 |
ENDIF |
93 |
#endif |
94 |
#else /* ndef EXF_INTERP_USE_DYNALLOC */ |
95 |
#ifdef EXF_IREAD_USE_GLOBAL_POINTER |
96 |
STOP |
97 |
&'EXF_INTERP_READ: USE_GLOBAL_POINTER needs INTERP_USE_DYNALLOC' |
98 |
#endif |
99 |
IF ( nx_in*ny_in .GT. exf_interp_bufferSize ) THEN |
100 |
STOP 'EXF_INTERP_READ: exf_interp_bufferSize too small' |
101 |
ENDIF |
102 |
#endif /* ndef EXF_INTERP_USE_DYNALLOC */ |
103 |
|
104 |
C-- before starting to read, wait for everyone to finish |
105 |
_BARRIER |
106 |
|
107 |
C--- read in input data |
108 |
|
109 |
IF ( MASTER_CPU_IO(myThid) ) THEN |
110 |
C-- master thread of process 0, only, opens a global file |
111 |
|
112 |
IL = ILNBLNK( infile ) |
113 |
INQUIRE( file=infile, exist=exst ) |
114 |
IF (exst) THEN |
115 |
IF ( debugLevel.GE.debLevB ) THEN |
116 |
WRITE(msgBuf,'(A,A)') |
117 |
& ' EXF_INTERP_READ: opening file: ',infile(1:IL) |
118 |
CALL PRINT_MESSAGE( msgBuf, standardMessageUnit, |
119 |
& SQUEEZE_RIGHT , myThid) |
120 |
ENDIF |
121 |
ELSE |
122 |
WRITE(msgBuf,'(2A)') |
123 |
& ' EXF_INTERP_READ: filename: ', infile(1:IL) |
124 |
CALL PRINT_MESSAGE( msgBuf, standardMessageUnit, |
125 |
& SQUEEZE_RIGHT , myThid) |
126 |
CALL PRINT_ERROR( msgBuf, myThid ) |
127 |
WRITE(msgBuf,'(A)') |
128 |
& ' EXF_INTERP_READ: File does not exist' |
129 |
CALL PRINT_MESSAGE( msgBuf, standardMessageUnit, |
130 |
& SQUEEZE_RIGHT , myThid) |
131 |
CALL PRINT_ERROR( msgBuf, myThid ) |
132 |
STOP 'ABNORMAL END: S/R EXF_INTERP_READ' |
133 |
ENDIF |
134 |
|
135 |
CALL MDSFINDUNIT( ioUnit, myThid ) |
136 |
length_of_rec=MDS_RECLEN( filePrec, nx_in*ny_in, myThid ) |
137 |
OPEN( ioUnit, file=infile, status='old', access='direct', |
138 |
& recl=length_of_rec ) |
139 |
IF ( filePrec .EQ. 32 ) THEN |
140 |
#ifdef EXF_INTERP_USE_DYNALLOC |
141 |
READ(ioUnit,rec=irecord) buffer_r4 |
142 |
#else |
143 |
READ(ioUnit,rec=irecord) (buffer_r4(i),i=1,nx_in*ny_in) |
144 |
#endif |
145 |
#ifdef _BYTESWAPIO |
146 |
CALL MDS_BYTESWAPR4(nx_in*ny_in,buffer_r4) |
147 |
#endif /* _BYTESWAPIO */ |
148 |
ELSE |
149 |
#ifdef EXF_INTERP_USE_DYNALLOC |
150 |
READ(ioUnit,rec=irecord) buffer_r8 |
151 |
#else |
152 |
READ(ioUnit,rec=irecord) (buffer_r8(i),i=1,nx_in*ny_in) |
153 |
#endif |
154 |
#ifdef _BYTESWAPIO |
155 |
CALL MDS_BYTESWAPR8(nx_in*ny_in,buffer_r8) |
156 |
#endif /* _BYTESWAPIO */ |
157 |
ENDIF |
158 |
CLOSE( ioUnit ) |
159 |
C-- end if MASTER_CPU_IO |
160 |
ENDIF |
161 |
|
162 |
_BEGIN_MASTER( myThid ) |
163 |
#ifdef ALLOW_USE_MPI |
164 |
C-- broadcast to all processes |
165 |
IF ( useSingleCpuInput ) THEN |
166 |
IF ( filePrec .EQ. 32 ) THEN |
167 |
CALL MPI_BCAST(buffer_r4,nx_in*ny_in,MPI_REAL, |
168 |
& 0,MPI_COMM_MODEL,ierr) |
169 |
ELSE |
170 |
CALL MPI_BCAST(buffer_r8,nx_in*ny_in,MPI_DOUBLE_PRECISION, |
171 |
& 0,MPI_COMM_MODEL,ierr) |
172 |
ENDIF |
173 |
ENDIF |
174 |
#endif /* ALLOW_USE_MPI */ |
175 |
|
176 |
#ifdef EXF_IREAD_USE_GLOBAL_POINTER |
177 |
IF ( filePrec .EQ. 32 ) THEN |
178 |
glPtr4 => buffer_r4 |
179 |
ELSE |
180 |
glPtr8 => buffer_r8 |
181 |
ENDIF |
182 |
#endif |
183 |
_END_MASTER( myThid ) |
184 |
_BARRIER |
185 |
|
186 |
C--- Transfer buffer to "arrayin" array: |
187 |
#ifdef EXF_INTERP_USE_DYNALLOC |
188 |
#ifdef EXF_IREAD_USE_GLOBAL_POINTER |
189 |
IF ( filePrec .EQ. 32 ) THEN |
190 |
DO j=1,ny_in |
191 |
DO i=1,nx_in |
192 |
arrayin(i,j)=glPtr4(i,j) |
193 |
ENDDO |
194 |
ENDDO |
195 |
ELSE |
196 |
DO j=1,ny_in |
197 |
DO i=1,nx_in |
198 |
arrayin(i,j)=glPtr8(i,j) |
199 |
ENDDO |
200 |
ENDDO |
201 |
ENDIF |
202 |
#else /* ndef EXF_IREAD_USE_GLOBAL_POINTER */ |
203 |
IF ( filePrec .EQ. 32 ) THEN |
204 |
DO j=1,ny_in |
205 |
DO i=1,nx_in |
206 |
arrayin(i,j)=buffer_r4(i,j) |
207 |
ENDDO |
208 |
ENDDO |
209 |
ELSE |
210 |
DO j=1,ny_in |
211 |
DO i=1,nx_in |
212 |
arrayin(i,j)=buffer_r8(i,j) |
213 |
ENDDO |
214 |
ENDDO |
215 |
ENDIF |
216 |
#endif /* ndef EXF_IREAD_USE_GLOBAL_POINTER */ |
217 |
#else /* ndef EXF_INTERP_USE_DYNALLOC */ |
218 |
IF ( filePrec .EQ. 32 ) THEN |
219 |
DO j=1,ny_in |
220 |
ijs = (j-1)*nx_in |
221 |
DO i=1,nx_in |
222 |
arrayin(i,j)=buffer_r4(i+ijs) |
223 |
ENDDO |
224 |
ENDDO |
225 |
ELSE |
226 |
DO j=1,ny_in |
227 |
ijs = (j-1)*nx_in |
228 |
DO i=1,nx_in |
229 |
arrayin(i,j)=buffer_r8(i+ijs) |
230 |
ENDDO |
231 |
ENDDO |
232 |
ENDIF |
233 |
#endif /* ndef EXF_INTERP_USE_DYNALLOC */ |
234 |
|
235 |
RETURN |
236 |
END |