/[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.2 - (hide annotations) (download)
Sat Sep 24 22:40:16 2005 UTC (19 years, 10 months ago) by edhill
Branch: MAIN
Changes since 1.1: +41 -14 lines
 o first working ASCII topology version

1 edhill 1.2 C $Header: /u/gcmpack/MITgcm_contrib/eh3_spgr/hs94.cs-32x32x5/code_v2/w2_read_atopo.F,v 1.1 2005/09/23 20:52:00 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     C Make scratch copies of input data file with and without comments
44     #ifdef TARGET_BGL
45     OPEN(UNIT=scrUnit1,FILE='scratch1',STATUS='UNKNOWN')
46     #else
47     OPEN(UNIT=scrUnit1,STATUS='SCRATCH')
48     #endif
49     IL = ILNBLNK(W2_ATOPO_FNAME)
50     OPEN(UNIT=eeDataUnit,FILE=W2_ATOPO_FNAME(1:IL),
51     & STATUS='OLD',err=100,IOSTAT=errIO)
52     IF ( errIO .GE. 0 ) GOTO 200
53     100 CONTINUE
54     WRITE(msgBuf,'(A)')
55     & 'S/R W2_READ_ATOPO'
56     CALL PRINT_ERROR( msgBuf , 1)
57     WRITE(msgBuf,'(A)')
58     & 'Unable to open execution environment ASCII topology'
59     CALL PRINT_ERROR( msgBuf , 1)
60     WRITE(msgBuf,'(3A)')
61     & 'file "',W2_ATOPO_FNAME(1:IL),'"'
62     CALL PRINT_ERROR( msgBuf , 1)
63     STOP 'ABNORMAL END: S/R W2_READ_ATOPO'
64     200 CONTINUE
65     300 CONTINUE
66     READ(eeDataUnit,FMT='(A)',END=400) LINE
67     IL = MAX(ILNBLNK(LINE),1)
68     IF ( LINE(1:1) .NE. commentCharacter ) THEN
69     WRITE(UNIT=scrUnit1,FMT='(A)') LINE(:IL)
70     ENDIF
71     GOTO 300
72     400 CONTINUE
73     CLOSE(eeDataUnit)
74    
75     iUnit = scrUnit1
76     REWIND(iUnit)
77     450 READ(UNIT=iUnit,FMT='(A)',END=500) LINE
78     IF ( LINE(1:9) .EQ. 'EXCH2TOPO' ) GOTO 600
79     GOTO 450
80     500 CONTINUE
81     #ifndef TARGET_PWR3
82     WRITE(msgBuf,'(A)')
83     & 'S/R W2_READ_ATOPO'
84     CALL PRINT_ERROR( msgBuf , 1)
85     WRITE(msgBuf,'(A)')
86     & 'Error reading execution environment ASCII topology'
87     CALL PRINT_ERROR( msgBuf , 1)
88     WRITE(msgBuf,'(3A)')
89     & 'file "',W2_ATOPO_FNAME(1:IL),'"'
90     CALL PRINT_ERROR( msgBuf , 1)
91     WRITE(msgBuf,'(A)')
92     & 'Cannot locate the topology header string'
93     CALL PRINT_ERROR( msgBuf , 1)
94     STOP 'ABNORMAL END: S/R W2_READ_ATOPO'
95     #endif
96    
97     600 CONTINUE
98     C Parse the topo-file version string :
99     C = 0 0
100     C = 123456789 123456789
101     C = EXCH2TOPO ver 001
102     C = ===
103    
104 edhill 1.2 650 FORMAT(10i12)
105    
106     IF ( LINE(15:17) .EQ. '001' ) GOTO 700
107 edhill 1.1 C Other versions go here...
108    
109     GOTO 900
110    
111     700 CONTINUE
112     C VERSION : "001"
113 edhill 1.2 READ(iUnit,650) ntile
114 edhill 1.1 DO k = 1,ntile
115    
116 edhill 1.2 READ(iUnit,650) it
117 edhill 1.1 C exch2_myFace = 1 ;
118     C exch2_isNedge = 1 ;
119     C exch2_isSedge = 1 ;
120     C exch2_isEedge = 1 ;
121     C exch2_isWedge = 1 ;
122 edhill 1.2 READ(iUnit,650) exch2_myFace(it),
123 edhill 1.1 & exch2_isNedge(it), exch2_isSedge(it),
124     & exch2_isEedge(it), exch2_isWedge(it)
125 edhill 1.2 C XXX exch2_tnx = 32 ;
126     C XXX exch2_tny = 32 ;
127     C XXX exch2_mydnx = 32 ;
128     C XXX exch2_mydny = 32 ;
129     READ(iUnit,650)
130     & exch2_tnx(it), exch2_tny(it),
131     & exch2_mydnx(it), exch2_mydny(it)
132 edhill 1.1 C exch2_txglobalo = 1 ;
133     C exch2_tyglobalo = 1 ;
134     C exch2_tbasex = 0 ;
135     C exch2_tbasey = 0 ;
136     C exch2_nNeighbours = 4 ;
137 edhill 1.2 READ(iUnit,650)
138 edhill 1.1 & exch2_txglobalo(it), exch2_tyglobalo(it),
139     & exch2_tbasex(it), exch2_tbasey(it),
140     & exch2_nNeighbours(it)
141     nneigh = exch2_nNeighbours(it)
142     C exch2_neighbourId = 3, 6, 2, 5 ;
143 edhill 1.2 READ(iUnit,650)
144 edhill 1.1 & (exch2_neighbourId(ii,it), ii=1,nneigh)
145     C exch2_pi = 0, -1, 1, 0, 1, 0, 0, 1 ;
146 edhill 1.2 READ(iUnit,650)
147 edhill 1.1 & ((exch2_pi(jj,ii,it), jj=1,2), ii=1,nneigh)
148     C exch2_pj = 1, 0, 0, 1, 0, 1, -1, 0 ;
149 edhill 1.2 READ(iUnit,650)
150 edhill 1.1 & ((exch2_pj(jj,ii,it), jj=1,2), ii=1,nneigh)
151     C exch2_oi = 33, 0, 32, -32 ;
152 edhill 1.2 READ(iUnit,650)
153 edhill 1.1 & (exch2_oi(ii,it), ii=1,nneigh)
154     C exch2_oj = 32, -32, 0, 33 ;
155 edhill 1.2 READ(iUnit,650)
156 edhill 1.1 & (exch2_oj(ii,it), ii=1,nneigh)
157     C exch2_oi_f = 34, 0, 32, -32 ;
158 edhill 1.2 READ(iUnit,650)
159 edhill 1.1 & (exch2_oi_f(ii,it), ii=1,nneigh)
160     C exch2_oj_f = 32, -32, 0, 34 ;
161 edhill 1.2 READ(iUnit,650)
162 edhill 1.1 & (exch2_oj_f(ii,it), ii=1,nneigh)
163 edhill 1.2 C XXX exch2_itlo_c = 0, 33 ;
164     READ(iUnit,650)
165     & (exch2_itlo_c(ii,it), ii=1,nneigh)
166     C XXX exch2_ithi_c = 0, 0 ;
167     READ(iUnit,650)
168     & (exch2_ithi_c(ii,it), ii=1,nneigh)
169     C XXX exch2_jtlo_c = 0, 33 ;
170     READ(iUnit,650)
171     & (exch2_jtlo_c(ii,it), ii=1,nneigh)
172     C XXX exch2_jthi_c = 0, 0 ;
173     READ(iUnit,650)
174     & (exch2_jthi_c(ii,it), ii=1,nneigh)
175     C XXX exch2_opposingSend_record = 4, 1, 4, 1 ;
176     READ(iUnit,650)
177     & (exch2_opposingSend_record(ii,it), ii=1,nneigh)
178    
179 edhill 1.1 ENDDO
180 edhill 1.2
181     C CALL W2_WRITE_ATOPO
182    
183 edhill 1.1 GOTO 999
184    
185     900 CONTINUE
186     C Unknown version string
187     WRITE(msgBuf,'(A)')
188     & 'S/R W2_READ_ATOPO'
189     CALL PRINT_ERROR( msgBuf , 1)
190     WRITE(msgBuf,'(3A)')
191     & ' Error: EXCH2TOPO version string "', LINE(1:9), '"'
192     CALL PRINT_ERROR( msgBuf , 1)
193     WRITE(msgBuf,'(A)')
194     & ' is not understood'
195     CALL PRINT_ERROR( msgBuf , 1)
196     STOP 'ABNORMAL END: S/R W2_READ_ATOPO'
197    
198     999 CONTINUE
199     CLOSE(iUnit)
200    
201     RETURN
202     END

  ViewVC Help
Powered by ViewVC 1.1.22