/[MITgcm]/MITgcm/pkg/regrid/regrid_init_varia.F
ViewVC logotype

Annotation of /MITgcm/pkg/regrid/regrid_init_varia.F

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


Revision 1.1 - (hide annotations) (download)
Tue Aug 15 04:05:48 2006 UTC (17 years, 10 months ago) by edhill
Branch: MAIN
CVS Tags: checkpoint58u_post, checkpoint58w_post, checkpoint60, checkpoint61, checkpoint58r_post, checkpoint58x_post, checkpoint58t_post, checkpoint58q_post, checkpoint59q, checkpoint59p, checkpoint59r, checkpoint59e, checkpoint59d, checkpoint59g, checkpoint59f, checkpoint59a, checkpoint59c, checkpoint59b, checkpoint59m, checkpoint59l, checkpoint59o, checkpoint59n, checkpoint59i, checkpoint59h, checkpoint59k, checkpoint59j, checkpoint59, checkpoint58o_post, checkpoint58y_post, checkpoint58v_post, checkpoint58s_post, checkpoint61f, checkpoint61g, checkpoint61d, checkpoint61e, checkpoint61b, checkpoint61c, checkpoint58p_post, checkpoint61a, checkpoint61n, checkpoint61l, checkpoint61m, checkpoint61j, checkpoint61k, checkpoint61h, checkpoint61i
initial check-in

1 edhill 1.1 C $Header: /u/gcmpack/MITgcm_contrib/eh3/regrid/regrid/regrid_init_varia.F,v 1.3 2006/08/12 03:19:59 edhill Exp $
2     C $Name: $
3    
4     #include "REGRID_OPTIONS.h"
5    
6     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
7     CBOP 0
8     C !ROUTINE: REGRID_INIT_VARIA
9    
10     C !INTERFACE:
11     SUBROUTINE REGRID_INIT_VARIA( myThid )
12    
13     C !DESCRIPTION:
14     C Initialize REGRID variables
15    
16     C !USES:
17     IMPLICIT NONE
18     #include "SIZE.h"
19     #include "EEPARAMS.h"
20     #include "PARAMS.h"
21     #include "GRID.h"
22     #include "REGRID_SIZE.h"
23     #include "REGRID.h"
24     #ifdef ALLOW_EXCH2
25     #include "W2_EXCH2_TOPOLOGY.h"
26     #include "W2_EXCH2_PARAMS.h"
27     #endif
28     INTEGER ILNBLNK
29     EXTERNAL ILNBLNK
30    
31     C !INPUT/OUTPUT PARAMETERS:
32     C myThid :: my Thread Id number
33     INTEGER myThid
34     CEOP
35    
36     C !LOCAL VARIABLES:
37     INTEGER i,k, iface, uniq_tnum, bi,bj
38     INTEGER irx, isrc, idst, nFx,nFy, init_nlpts,nlpts
39     INTEGER iUnit, errIO, nnb
40     INTEGER iminx,iminy, imaxx,imaxy
41     _RL wt
42     CHARACTER*(MAX_LEN_FNAM) fname
43     CHARACTER*(MAX_LEN_MBUF) msgbuf
44     LOGICAL exst
45    
46     C Regrid files contain information on a per-face basis. This is
47     C convenient in two respects: (1) the domain can be re-tiled without
48     C changing any of the files [since the ordering with respect to
49     C tiles is performed here in the model] and (2) when faces are
50     C removed or added only the corresponding per-face files will need
51     C to be removed or added [and all the other per-face files remain
52     C unchanged provided the face numbers do not change].
53     C
54     C The convention is: "points cycle most quickly in X and then Y"
55     C
56     C +-------------------+
57     C | Face |
58     C | |
59     C | +-----+ |
60     C Y | |Tile | |
61     C | +-----+ |
62     C | |
63     C |123... |
64     C +-------------------+
65     C X
66    
67     _BEGIN_MASTER( myThid )
68    
69     WRITE(msgBuf,'(a)')
70     & '// ======================================================='
71     CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,
72     & SQUEEZE_RIGHT,myThid)
73     WRITE(msgBuf,'(a)')
74     & '// Begin reading the per-face REGRID information'
75     CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,
76     & SQUEEZE_RIGHT,myThid)
77     WRITE(msgBuf,'(a)')
78     & '// ======================================================='
79     CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,
80     & SQUEEZE_RIGHT,myThid)
81    
82     nlpts = 0
83    
84     CALL MDSFINDUNIT(iUnit, myThid)
85    
86     DO bj = myByLo(myThid), myByHi(myThid)
87     DO bi = myBxLo(myThid), myBxHi(myThid)
88    
89     #ifdef ALLOW_EXCH2
90     C EXCH2 domains
91     uniq_tnum = W2_myTileList(bi)
92     iface = exch2_myFace(uniq_tnum)
93     nFx = exch2_mydnx(uniq_tnum)
94     nFy = exch2_mydny(uniq_tnum)
95     iminx = exch2_tbasex(uniq_tnum) + 1
96     imaxx = iminx + exch2_tnx(uniq_tnum) - 1
97     iminy = exch2_tbasey(uniq_tnum) + 1
98     imaxy = iminy + exch2_tny(uniq_tnum) - 1
99     #else
100     C Global tile number for simple single-face "EXCH1" domains
101     iG = bi + (myXGlobalLo-1)/sNx
102     jG = bj + (myYGlobalLo-1)/sNy
103     uniq_tnum = (jG - 1)*(nPx*nSx) + iG
104     iface = 1
105     nFx = nSx * sNx
106     nFy = sSy * sNy
107     iminx = myXGlobalLo
108     imaxx = myXGlobalLo + sNx - 1
109     iminy = myYGlobalLo
110     imaxy = myYGlobalLo + sNy - 1
111     #endif
112    
113     C WRITE(*,*) 'iminx, imaxx, nFx, nFy = ',
114     C & iminx, imaxx, nFx, nFy
115    
116     C Read through all the weights files for this tile (face) and
117     C locate the points that belong to this tile
118     DO i = 1,regrid_ngrids
119    
120     IF (i .EQ. 1) THEN
121     nlpts = 0
122     ELSE
123     nlpts = REGRID_iend(i,bi,bj)
124     ENDIF
125     init_nlpts = nlpts
126    
127     DO k = 1,MAX_LEN_FNAM
128     fname(k:k) = ' '
129     ENDDO
130     nnb = ILNBLNK(REGRID_fbname_in(i))
131     write(fname,'(a,i3.3,a)')
132     & REGRID_fbname_in(i)(1:nnb),iface,'.regrid.ascii'
133     nnb = ILNBLNK(fname)
134     INQUIRE( FILE=fname, EXIST=exst )
135     IF (.NOT. exst) THEN
136     WRITE(msgBuf,'(A)') 'S/R REGRID_INIT_VARIA()'
137     CALL PRINT_ERROR( msgBuf , 1)
138     WRITE(msgBuf,'(3A)') ' File "',
139     & fname(1:nnb), '" does not exist'
140     CALL PRINT_ERROR( msgBuf , 1)
141     CLOSE(iUnit)
142     STOP ' stopped in REGRID_INIT_VARIA()'
143     ENDIF
144    
145     open(unit=iUnit, file=fname, status='old', iostat=errIO)
146    
147     IF (errIO .LT. 0) THEN
148     WRITE(msgBuf,'(A)') 'S/R REGRID_INIT_VARIA()'
149     CALL PRINT_ERROR( msgBuf , 1)
150     WRITE(msgBuf,'(3A)') 'Unable to open file="',
151     & fname(1:nnb), '"'
152     CALL PRINT_ERROR( msgBuf , 1)
153     CLOSE(iUnit)
154     STOP ' stopped in REGRID_INIT_VARIA()'
155     ELSE
156     WRITE(msgBuf,'(3a)') 'Reading file "', fname(1:nnb),'"'
157     call PRINT_MESSAGE(msgBuf,standardMessageUnit,
158     & SQUEEZE_RIGHT,myThid)
159     ENDIF
160    
161     DO WHILE ( .TRUE. )
162     C READ(iUnit,fmt='(2(I10,1X),1P1E23.13E3)',iostat=errIO)
163     READ(iUnit,fmt='(2(1X,I10),1X,E28.22)',iostat=errIO)
164     & isrc, idst, wt
165     IF ( errIO .NE. 0 ) THEN
166     GOTO 100
167     ENDIF
168     irx = MOD(isrc,nFx)
169     IF (irx .EQ. 0) irx = nFx
170     IF ((iminx .LE. irx) .AND. (irx .LE. imaxx)) THEN
171     nlpts = nlpts + 1
172     REGRID_i_loc(nlpts,bi,bj) = irx
173     REGRID_j_loc(nlpts,bi,bj) = isrc/nFx + 1
174     REGRID_i_out(nlpts,bi,bj) = idst
175     REGRID_amat(nlpts,bi,bj) = wt
176     ENDIF
177    
178     ENDDO
179     100 CONTINUE
180     close(iUnit)
181     WRITE(msgBuf,'(a,i10)') ' num weights read = ',
182     & (nlpts - init_nlpts)
183     call PRINT_MESSAGE(msgBuf,standardMessageUnit,
184     & SQUEEZE_RIGHT,myThid)
185    
186     REGRID_ibeg(i,bi,bj) = init_nlpts + 1
187     REGRID_iend(i,bi,bj) = nlpts
188     ENDDO
189    
190     ENDDO
191     ENDDO
192    
193     WRITE(msgBuf,'(a)') ' '
194     CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,
195     & SQUEEZE_RIGHT,myThid)
196    
197     _END_MASTER( myThid )
198    
199     RETURN
200     END

  ViewVC Help
Powered by ViewVC 1.1.22