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

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

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


Revision 1.3 - (hide annotations) (download)
Wed Sep 28 20:52:22 2005 UTC (19 years, 10 months ago) by edhill
Branch: MAIN
CVS Tags: HEAD
Changes since 1.2: +115 -81 lines
 o adding corner data

1 edhill 1.3 C $Header: /u/gcmpack/MITgcm_contrib/eh3_spgr/hs94.cs-32x32x5/code_v2/w2_write_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_WRITE_ATOPO
10    
11     C !INTERFACE:
12     SUBROUTINE W2_WRITE_ATOPO
13    
14     C !DESCRIPTION:
15     C Write in the EXCH2 tile topology information to a "flat" ascii
16     C text file compatible with the format used by W2_READ_ATOPO
17    
18     C !USES:
19     IMPLICIT NONE
20     #include "SIZE.h"
21     #include "EEPARAMS.h"
22     #include "EESUPPORT.h"
23     #include "W2_EXCH2_TOPOLOGY.h"
24     #include "W2_EXCH2_PARAMS.h"
25     INTEGER IFNBLNK
26     EXTERNAL IFNBLNK
27     INTEGER ILNBLNK
28     EXTERNAL ILNBLNK
29     CEOP
30    
31     C !LOCAL VARIABLES:
32     C iUnit :: Work variable for IO unit number
33     C errIO :: IO unit error flag
34     C IL :: Temp. for index strings
35     C msgBuf :: Temp. for textual I/O
36     C line :: Temp. for textual I/O
37     INTEGER IL, errIO, iUnit
38     CHARACTER*(MAX_LEN_MBUF) msgBuf
39 edhill 1.3 INTEGER ii, jj, k, ic, nneigh
40 edhill 1.1
41    
42     IL = ILNBLNK(W2_ATOPO_ONAME)
43     iUnit = eeDataUnit
44     OPEN(UNIT=iUnit,FILE=W2_ATOPO_ONAME(1:IL),
45     & status='unknown',err=100,IOSTAT=errIO)
46     IF ( errIO .GE. 0 ) GOTO 200
47     100 CONTINUE
48     WRITE(msgBuf,'(A)')
49     & 'S/R W2_WRITE_ATOPO'
50     CALL PRINT_ERROR( msgBuf , 1)
51     WRITE(msgBuf,'(3A)')
52     & 'Unable to open file "',W2_ATOPO_FNAME(1:IL),'"'
53     CALL PRINT_ERROR( msgBuf , 1)
54     STOP 'ABNORMAL END: S/R W2_WRITE_ATOPO'
55    
56     200 CONTINUE
57    
58 edhill 1.3 C ======== ASCII FORMAT ========
59 edhill 1.1 300 FORMAT(10i12)
60     C The above format is not an efficient way to pack the topology
61 edhill 1.3 C data. But it does NOT matter! Considering a hypothetical system
62     C with 10,000 tiles (one full order of magnitude larger than any
63     C MITgcm run performed through 2005), the file size would still be
64     C less than 10MB:
65     C
66     C (10000 tiles) * (~5500 bytes / 6 tiles) = 9.2 MB
67     C
68     C and this is orders of magnitude smaller than any binary data files
69     C that would be needed by such a run.
70 edhill 1.1 C
71     C Write the topo-file version string :
72     C = 0 0
73     C = 123456789 123456789
74     C = EXCH2TOPO ver 001
75     C = ===
76 edhill 1.3 C
77     C ======== ASCII FORMAT ========
78    
79     IF ( W2_atopo_o_ver(1:3) .EQ. '001'
80     & .OR. W2_atopo_o_ver(1:3) .EQ. '002' ) THEN
81    
82     WRITE(iUnit,'(a)') '#'
83     WRITE(iUnit,'(a)') '# MODEL GENERATED'
84     WRITE(iUnit,'(a)') '#'
85     WRITE(iUnit,'(a)') 'EXCH2TOPO ver 001'
86     WRITE(iUnit,300) NTILES
87     DO k = 1,NTILES
88    
89     WRITE(iUnit,300) k
90     C exch2_myFace = 1 ;
91     C exch2_isNedge = 1 ;
92     C exch2_isSedge = 1 ;
93     C exch2_isEedge = 1 ;
94     C exch2_isWedge = 1 ;
95     WRITE(iUnit,300) exch2_myFace(k),
96     & exch2_isNedge(k), exch2_isSedge(k),
97     & exch2_isEedge(k), exch2_isWedge(k)
98     C XXX exch2_tnx = 32 ;
99     C XXX exch2_tny = 32 ;
100     C XXX exch2_mydnx = 32 ;
101     C XXX exch2_mydny = 32 ;
102     WRITE(iUnit,300)
103     & exch2_tnx(k), exch2_tny(k),
104     & exch2_mydnx(k), exch2_mydny(k)
105     C exch2_txglobalo = 1 ;
106     C exch2_tyglobalo = 1 ;
107     C exch2_tbasex = 0 ;
108     C exch2_tbasey = 0 ;
109     C exch2_nNeighbours = 4 ;
110     WRITE(iUnit,300)
111     & exch2_txglobalo(k), exch2_tyglobalo(k),
112     & exch2_tbasex(k), exch2_tbasey(k),
113     & exch2_nNeighbours(k)
114     nneigh = exch2_nNeighbours(k)
115     C exch2_neighbourId = 3, 6, 2, 5 ;
116     WRITE(iUnit,300)
117     & (exch2_neighbourId(ii,k), ii=1,nneigh)
118     C exch2_pi = 0, -1, 1, 0, 1, 0, 0, 1 ;
119     WRITE(iUnit,300)
120     & ((exch2_pi(jj,ii,k), jj=1,2), ii=1,nneigh)
121     C exch2_pj = 1, 0, 0, 1, 0, 1, -1, 0 ;
122     WRITE(iUnit,300)
123     & ((exch2_pj(jj,ii,k), jj=1,2), ii=1,nneigh)
124     C exch2_oi = 33, 0, 32, -32 ;
125     WRITE(iUnit,300)
126     & (exch2_oi(ii,k), ii=1,nneigh)
127     C exch2_oj = 32, -32, 0, 33 ;
128     WRITE(iUnit,300)
129     & (exch2_oj(ii,k), ii=1,nneigh)
130     C exch2_oi_f = 34, 0, 32, -32 ;
131     WRITE(iUnit,300)
132     & (exch2_oi_f(ii,k), ii=1,nneigh)
133     C exch2_oj_f = 32, -32, 0, 34 ;
134     WRITE(iUnit,300)
135     & (exch2_oj_f(ii,k), ii=1,nneigh)
136     C XXX exch2_itlo_c = 0, 33 ;
137     WRITE(iUnit,300)
138     & (exch2_itlo_c(ii,k), ii=1,nneigh)
139     C XXX exch2_ithi_c = 0, 0 ;
140     WRITE(iUnit,300)
141     & (exch2_ithi_c(ii,k), ii=1,nneigh)
142     C XXX exch2_jtlo_c = 0, 33 ;
143     WRITE(iUnit,300)
144     & (exch2_jtlo_c(ii,k), ii=1,nneigh)
145     C XXX exch2_jthi_c = 0, 0 ;
146     WRITE(iUnit,300)
147     & (exch2_jthi_c(ii,k), ii=1,nneigh)
148     C XXX exch2_opposingSend_record = 4, 1, 4, 1 ;
149     WRITE(iUnit,300)
150     & (exch2_opposingSend_record(ii,k), ii=1,nneigh)
151    
152     C Add the corners, if necessary
153     IF ( W2_atopo_o_ver(1:3) .EQ. '002' ) THEN
154     WRITE(iUnit,300)
155     & (GEx_ncor(ii,k), ii=1,4)
156     DO ii = 1,4
157     DO jj = 1,2
158     WRITE(iUnit,300)
159     & (GEx_cInfo(ic,jj,ii,k), ic=1,GEx_ncor(ii,k))
160     ENDDO
161     ENDDO
162     ENDIF
163    
164     ENDDO
165    
166     ELSE
167    
168     WRITE(msgBuf,'(A)')
169     & 'S/R W2_WRITE_ATOPO'
170     CALL PRINT_ERROR( msgBuf , 1)
171     WRITE(msgBuf,'(3A)')
172     & 'Unknown topology version "',W2_atopo_o_ver(1:3),'"'
173     CALL PRINT_ERROR( msgBuf , 1)
174     WRITE(msgBuf,'(3A)')
175     & 'Currently, valid values are "001" or "002"'
176     CALL PRINT_ERROR( msgBuf , 1)
177     STOP 'ABNORMAL END: S/R W2_WRITE_ATOPO'
178 edhill 1.2
179 edhill 1.3 ENDIF
180 edhill 1.1
181     CLOSE(iUnit)
182    
183     RETURN
184     END

  ViewVC Help
Powered by ViewVC 1.1.22