/[MITgcm]/MITgcm_contrib/eh3_spgr/hs94.cs-32x32x5/code_v2/w2_read_atopo.F
ViewVC logotype

Annotation of /MITgcm_contrib/eh3_spgr/hs94.cs-32x32x5/code_v2/w2_read_atopo.F

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


Revision 1.3 - (hide annotations) (download)
Sun Oct 2 15:06:02 2005 UTC (19 years, 10 months ago) by edhill
Branch: MAIN
CVS Tags: HEAD
Changes since 1.2: +32 -1 lines
 o save notes

1 edhill 1.3 C $Header: /u/gcmpack/MITgcm_contrib/eh3_spgr/hs94.cs-32x32x5/code_v2/w2_read_atopo.F,v 1.2 2005/09/24 22:40:16 edhill Exp $
2 edhill 1.1 C $Name: $
3    
4     #include "PACKAGES_CONFIG.h"
5     #include "CPP_EEOPTIONS.h"
6    
7     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
8     CBOP
9     C !ROUTINE: W2_READ_ATOPO
10    
11     C !INTERFACE:
12     SUBROUTINE W2_READ_ATOPO
13    
14     C !DESCRIPTION:
15     C Read in the EXCH2 tile topology information from a "flat" ascii
16     C text file that contains a version string to make the addition of
17     C topology data much easier and more flexible.
18    
19     C !USES:
20     IMPLICIT NONE
21     #include "SIZE.h"
22     #include "EEPARAMS.h"
23     #include "EESUPPORT.h"
24     #include "W2_EXCH2_TOPOLOGY.h"
25     #include "W2_EXCH2_PARAMS.h"
26     INTEGER IFNBLNK
27     EXTERNAL IFNBLNK
28     INTEGER ILNBLNK
29     EXTERNAL ILNBLNK
30     CEOP
31    
32     C !LOCAL VARIABLES:
33     C iUnit :: Work variable for IO unit number
34     C errIO :: IO unit error flag
35     C IL :: Temp. for index strings
36     C msgBuf :: Temp. for textual I/O
37     C line :: Temp. for textual I/O
38     INTEGER IL, errIO, iUnit
39     CHARACTER*(MAX_LEN_MBUF) msgBuf
40     CHARACTER*(MAX_LEN_PREC) line
41     INTEGER ii, jj, k, it, ntile, nneigh
42    
43 edhill 1.3 C Intialize GEx affine transformation matrix
44     DO ii = 1,8
45     DO jj = 1,4
46     GEx_affm(jj,ii) = 0
47     ENDDO
48     ENDDO
49     C ------------------- 1 : I
50     GEx_affm(1,1) = 1
51     GEx_affm(4,1) = 1
52     C ------------------- 2 : Iu-
53     GEx_affm(1,2) = -1
54     GEx_affm(4,2) = 1
55     C ------------------- 3 : Iv-
56     GEx_affm(1,3) = 1
57     GEx_affm(4,3) = -1
58     C ------------------- 4 : -I
59     GEx_affm(1,4) = -1
60     GEx_affm(4,4) = -1
61     C ------------------- 5 : P
62     GEx_affm(2,5) = 1
63     GEx_affm(3,5) = 1
64     C ------------------- 6 : Pu-
65     GEx_affm(2,6) = -1
66     GEx_affm(3,6) = 1
67     C ------------------- 7 : Pv-
68     GEx_affm(2,7) = 1
69     GEx_affm(3,7) = -1
70     C ------------------- 8 : -P
71     GEx_affm(2,8) = -1
72     GEx_affm(3,8) = -1
73    
74 edhill 1.1 C Make scratch copies of input data file with and without comments
75     #ifdef TARGET_BGL
76     OPEN(UNIT=scrUnit1,FILE='scratch1',STATUS='UNKNOWN')
77     #else
78     OPEN(UNIT=scrUnit1,STATUS='SCRATCH')
79     #endif
80     IL = ILNBLNK(W2_ATOPO_FNAME)
81     OPEN(UNIT=eeDataUnit,FILE=W2_ATOPO_FNAME(1:IL),
82     & STATUS='OLD',err=100,IOSTAT=errIO)
83     IF ( errIO .GE. 0 ) GOTO 200
84     100 CONTINUE
85     WRITE(msgBuf,'(A)')
86     & 'S/R W2_READ_ATOPO'
87     CALL PRINT_ERROR( msgBuf , 1)
88     WRITE(msgBuf,'(A)')
89     & 'Unable to open execution environment ASCII topology'
90     CALL PRINT_ERROR( msgBuf , 1)
91     WRITE(msgBuf,'(3A)')
92     & 'file "',W2_ATOPO_FNAME(1:IL),'"'
93     CALL PRINT_ERROR( msgBuf , 1)
94     STOP 'ABNORMAL END: S/R W2_READ_ATOPO'
95     200 CONTINUE
96     300 CONTINUE
97     READ(eeDataUnit,FMT='(A)',END=400) LINE
98     IL = MAX(ILNBLNK(LINE),1)
99     IF ( LINE(1:1) .NE. commentCharacter ) THEN
100     WRITE(UNIT=scrUnit1,FMT='(A)') LINE(:IL)
101     ENDIF
102     GOTO 300
103     400 CONTINUE
104     CLOSE(eeDataUnit)
105    
106     iUnit = scrUnit1
107     REWIND(iUnit)
108     450 READ(UNIT=iUnit,FMT='(A)',END=500) LINE
109     IF ( LINE(1:9) .EQ. 'EXCH2TOPO' ) GOTO 600
110     GOTO 450
111     500 CONTINUE
112     #ifndef TARGET_PWR3
113     WRITE(msgBuf,'(A)')
114     & 'S/R W2_READ_ATOPO'
115     CALL PRINT_ERROR( msgBuf , 1)
116     WRITE(msgBuf,'(A)')
117     & 'Error reading execution environment ASCII topology'
118     CALL PRINT_ERROR( msgBuf , 1)
119     WRITE(msgBuf,'(3A)')
120     & 'file "',W2_ATOPO_FNAME(1:IL),'"'
121     CALL PRINT_ERROR( msgBuf , 1)
122     WRITE(msgBuf,'(A)')
123     & 'Cannot locate the topology header string'
124     CALL PRINT_ERROR( msgBuf , 1)
125     STOP 'ABNORMAL END: S/R W2_READ_ATOPO'
126     #endif
127    
128     600 CONTINUE
129     C Parse the topo-file version string :
130     C = 0 0
131     C = 123456789 123456789
132     C = EXCH2TOPO ver 001
133     C = ===
134    
135 edhill 1.2 650 FORMAT(10i12)
136    
137     IF ( LINE(15:17) .EQ. '001' ) GOTO 700
138 edhill 1.1 C Other versions go here...
139    
140     GOTO 900
141    
142     700 CONTINUE
143     C VERSION : "001"
144 edhill 1.2 READ(iUnit,650) ntile
145 edhill 1.1 DO k = 1,ntile
146    
147 edhill 1.2 READ(iUnit,650) it
148 edhill 1.1 C exch2_myFace = 1 ;
149     C exch2_isNedge = 1 ;
150     C exch2_isSedge = 1 ;
151     C exch2_isEedge = 1 ;
152     C exch2_isWedge = 1 ;
153 edhill 1.2 READ(iUnit,650) exch2_myFace(it),
154 edhill 1.1 & exch2_isNedge(it), exch2_isSedge(it),
155     & exch2_isEedge(it), exch2_isWedge(it)
156 edhill 1.2 C XXX exch2_tnx = 32 ;
157     C XXX exch2_tny = 32 ;
158     C XXX exch2_mydnx = 32 ;
159     C XXX exch2_mydny = 32 ;
160     READ(iUnit,650)
161     & exch2_tnx(it), exch2_tny(it),
162     & exch2_mydnx(it), exch2_mydny(it)
163 edhill 1.1 C exch2_txglobalo = 1 ;
164     C exch2_tyglobalo = 1 ;
165     C exch2_tbasex = 0 ;
166     C exch2_tbasey = 0 ;
167     C exch2_nNeighbours = 4 ;
168 edhill 1.2 READ(iUnit,650)
169 edhill 1.1 & exch2_txglobalo(it), exch2_tyglobalo(it),
170     & exch2_tbasex(it), exch2_tbasey(it),
171     & exch2_nNeighbours(it)
172     nneigh = exch2_nNeighbours(it)
173     C exch2_neighbourId = 3, 6, 2, 5 ;
174 edhill 1.2 READ(iUnit,650)
175 edhill 1.1 & (exch2_neighbourId(ii,it), ii=1,nneigh)
176     C exch2_pi = 0, -1, 1, 0, 1, 0, 0, 1 ;
177 edhill 1.2 READ(iUnit,650)
178 edhill 1.1 & ((exch2_pi(jj,ii,it), jj=1,2), ii=1,nneigh)
179     C exch2_pj = 1, 0, 0, 1, 0, 1, -1, 0 ;
180 edhill 1.2 READ(iUnit,650)
181 edhill 1.1 & ((exch2_pj(jj,ii,it), jj=1,2), ii=1,nneigh)
182     C exch2_oi = 33, 0, 32, -32 ;
183 edhill 1.2 READ(iUnit,650)
184 edhill 1.1 & (exch2_oi(ii,it), ii=1,nneigh)
185     C exch2_oj = 32, -32, 0, 33 ;
186 edhill 1.2 READ(iUnit,650)
187 edhill 1.1 & (exch2_oj(ii,it), ii=1,nneigh)
188     C exch2_oi_f = 34, 0, 32, -32 ;
189 edhill 1.2 READ(iUnit,650)
190 edhill 1.1 & (exch2_oi_f(ii,it), ii=1,nneigh)
191     C exch2_oj_f = 32, -32, 0, 34 ;
192 edhill 1.2 READ(iUnit,650)
193 edhill 1.1 & (exch2_oj_f(ii,it), ii=1,nneigh)
194 edhill 1.2 C XXX exch2_itlo_c = 0, 33 ;
195     READ(iUnit,650)
196     & (exch2_itlo_c(ii,it), ii=1,nneigh)
197     C XXX exch2_ithi_c = 0, 0 ;
198     READ(iUnit,650)
199     & (exch2_ithi_c(ii,it), ii=1,nneigh)
200     C XXX exch2_jtlo_c = 0, 33 ;
201     READ(iUnit,650)
202     & (exch2_jtlo_c(ii,it), ii=1,nneigh)
203     C XXX exch2_jthi_c = 0, 0 ;
204     READ(iUnit,650)
205     & (exch2_jthi_c(ii,it), ii=1,nneigh)
206     C XXX exch2_opposingSend_record = 4, 1, 4, 1 ;
207     READ(iUnit,650)
208     & (exch2_opposingSend_record(ii,it), ii=1,nneigh)
209    
210 edhill 1.1 ENDDO
211 edhill 1.2
212     C CALL W2_WRITE_ATOPO
213    
214 edhill 1.1 GOTO 999
215    
216     900 CONTINUE
217     C Unknown version string
218     WRITE(msgBuf,'(A)')
219     & 'S/R W2_READ_ATOPO'
220     CALL PRINT_ERROR( msgBuf , 1)
221     WRITE(msgBuf,'(3A)')
222     & ' Error: EXCH2TOPO version string "', LINE(1:9), '"'
223     CALL PRINT_ERROR( msgBuf , 1)
224     WRITE(msgBuf,'(A)')
225     & ' is not understood'
226     CALL PRINT_ERROR( msgBuf , 1)
227     STOP 'ABNORMAL END: S/R W2_READ_ATOPO'
228    
229     999 CONTINUE
230     CLOSE(iUnit)
231    
232     RETURN
233     END

  ViewVC Help
Powered by ViewVC 1.1.22