/[MITgcm]/MITgcm/pkg/exf/exf_interp_read.F
ViewVC logotype

Contents of /MITgcm/pkg/exf/exf_interp_read.F

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


Revision 1.16 - (show annotations) (download)
Fri Mar 10 00:14:27 2017 UTC (7 years, 2 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint66g, checkpoint66f, checkpoint66e, checkpoint66o, checkpoint66n, checkpoint66m, checkpoint66l, checkpoint66k, checkpoint66j, checkpoint66i, checkpoint66h, HEAD
Changes since 1.15: +3 -4 lines
- interpolation with #undef EXF_INTERP_USE_DYNALLOC: move buffer size
  definition outside EXF_PARAM.h in new header file: EXF_INTERP_SIZE.h;

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

  ViewVC Help
Powered by ViewVC 1.1.22