/[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.13 - (show annotations) (download)
Mon Jun 29 21:31:09 2009 UTC (14 years, 10 months ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint62, checkpoint62c, checkpoint62b, checkpoint62a, checkpoint62g, checkpoint62f, checkpoint62e, checkpoint62d, checkpoint62k, checkpoint62j, checkpoint62i, checkpoint62h, checkpoint62o, checkpoint62n, checkpoint62m, checkpoint62l, checkpoint62s, checkpoint62r, checkpoint62q, checkpoint62p, checkpoint62w, checkpoint62v, checkpoint62u, checkpoint62t, checkpoint62y, checkpoint62x, checkpoint61v, checkpoint61w, checkpoint61t, checkpoint61u, checkpoint61s, checkpoint61z, checkpoint61x, checkpoint61y
Changes since 1.12: +2 -2 lines
Reduce output for "standard" debug level (=1).

1 C $Header: /u/gcmpack/MITgcm/pkg/exf/exf_interp_read.F,v 1.12 2008/01/23 16:38:58 mlosch 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 #ifndef ALLOW_ECCO
113 IL = ILNBLNK( infile )
114 INQUIRE( file=infile, exist=exst )
115 IF (exst) THEN
116 IF ( debugLevel .GT. debLevA ) THEN
117 WRITE(msgBuf,'(A,A)')
118 & ' EXF_INTERP_READ: opening file: ',infile(1:IL)
119 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
120 & SQUEEZE_RIGHT , myThid)
121 ENDIF
122 ELSE
123 WRITE(msgBuf,'(2A)')
124 & ' EXF_INTERP_READ: filename: ', infile(1:IL)
125 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
126 & SQUEEZE_RIGHT , myThid)
127 CALL PRINT_ERROR( msgBuf, myThid )
128 WRITE(msgBuf,'(A)')
129 & ' EXF_INTERP_READ: File does not exist'
130 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
131 & SQUEEZE_RIGHT , myThid)
132 CALL PRINT_ERROR( msgBuf, myThid )
133 STOP 'ABNORMAL END: S/R EXF_INTERP_READ'
134 ENDIF
135 #endif /* ALLOW_ECCO */
136
137 CALL MDSFINDUNIT( ioUnit, myThid )
138 length_of_rec=MDS_RECLEN( filePrec, nx_in*ny_in, myThid )
139 OPEN( ioUnit, file=infile, status='old', access='direct',
140 & recl=length_of_rec )
141 IF ( filePrec .EQ. 32 ) THEN
142 #ifdef EXF_INTERP_USE_DYNALLOC
143 READ(ioUnit,rec=irecord) buffer_r4
144 #else
145 READ(ioUnit,rec=irecord) (buffer_r4(i),i=1,nx_in*ny_in)
146 #endif
147 #ifdef _BYTESWAPIO
148 CALL MDS_BYTESWAPR4(nx_in*ny_in,buffer_r4)
149 #endif /* _BYTESWAPIO */
150 ELSE
151 #ifdef EXF_INTERP_USE_DYNALLOC
152 READ(ioUnit,rec=irecord) buffer_r8
153 #else
154 READ(ioUnit,rec=irecord) (buffer_r8(i),i=1,nx_in*ny_in)
155 #endif
156 #ifdef _BYTESWAPIO
157 CALL MDS_BYTESWAPR8(nx_in*ny_in,buffer_r8)
158 #endif /* _BYTESWAPIO */
159 ENDIF
160 CLOSE( ioUnit )
161 C-- end if MASTER_CPU_IO
162 ENDIF
163
164 _BEGIN_MASTER( myThid )
165 #ifdef ALLOW_USE_MPI
166 C-- broadcast to all processes
167 IF ( useSingleCPUIO ) THEN
168 IF ( filePrec .EQ. 32 ) THEN
169 CALL MPI_BCAST(buffer_r4,nx_in*ny_in,MPI_REAL,
170 & 0,MPI_COMM_MODEL,ierr)
171 ELSE
172 CALL MPI_BCAST(buffer_r8,nx_in*ny_in,MPI_DOUBLE_PRECISION,
173 & 0,MPI_COMM_MODEL,ierr)
174 ENDIF
175 ENDIF
176 #endif /* ALLOW_USE_MPI */
177
178 #ifdef EXF_IREAD_USE_GLOBAL_POINTER
179 IF ( filePrec .EQ. 32 ) THEN
180 glPtr4 => buffer_r4
181 ELSE
182 glPtr8 => buffer_r8
183 ENDIF
184 #endif
185 _END_MASTER( myThid )
186 _BARRIER
187
188 C--- Transfer buffer to "arrayin" array:
189 #ifdef EXF_INTERP_USE_DYNALLOC
190 #ifdef EXF_IREAD_USE_GLOBAL_POINTER
191 IF ( filePrec .EQ. 32 ) THEN
192 DO j=1,ny_in
193 DO i=1,nx_in
194 arrayin(i,j)=glPtr4(i,j)
195 ENDDO
196 ENDDO
197 ELSE
198 DO j=1,ny_in
199 DO i=1,nx_in
200 arrayin(i,j)=glPtr8(i,j)
201 ENDDO
202 ENDDO
203 ENDIF
204 #else /* ndef EXF_IREAD_USE_GLOBAL_POINTER */
205 IF ( filePrec .EQ. 32 ) THEN
206 DO j=1,ny_in
207 DO i=1,nx_in
208 arrayin(i,j)=buffer_r4(i,j)
209 ENDDO
210 ENDDO
211 ELSE
212 DO j=1,ny_in
213 DO i=1,nx_in
214 arrayin(i,j)=buffer_r8(i,j)
215 ENDDO
216 ENDDO
217 ENDIF
218 #endif /* ndef EXF_IREAD_USE_GLOBAL_POINTER */
219 #else /* ndef EXF_INTERP_USE_DYNALLOC */
220 IF ( filePrec .EQ. 32 ) THEN
221 DO j=1,ny_in
222 ijs = (j-1)*nx_in
223 DO i=1,nx_in
224 arrayin(i,j)=buffer_r4(i+ijs)
225 ENDDO
226 ENDDO
227 ELSE
228 DO j=1,ny_in
229 ijs = (j-1)*nx_in
230 DO i=1,nx_in
231 arrayin(i,j)=buffer_r8(i+ijs)
232 ENDDO
233 ENDDO
234 ENDIF
235 #endif /* ndef EXF_INTERP_USE_DYNALLOC */
236
237 RETURN
238 END

  ViewVC Help
Powered by ViewVC 1.1.22