/[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.3 - (hide annotations) (download)
Sun Jun 28 01:05:41 2009 UTC (15 years ago) by jmc
Branch: MAIN
CVS Tags: checkpoint64y, checkpoint64x, checkpoint64z, checkpoint64q, checkpoint64p, checkpoint64s, checkpoint64r, checkpoint64u, checkpoint64t, checkpoint64w, checkpoint64v, checkpoint64i, checkpoint64h, checkpoint64k, checkpoint64j, checkpoint64m, checkpoint64l, checkpoint64o, checkpoint64n, checkpoint64a, checkpoint64c, checkpoint64b, checkpoint64e, checkpoint64d, checkpoint64g, checkpoint64f, checkpoint63p, checkpoint63q, checkpoint63r, checkpoint63s, checkpoint63l, checkpoint63m, checkpoint63n, checkpoint63o, checkpoint63h, checkpoint63i, checkpoint63j, checkpoint63k, checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63g, checkpoint63a, checkpoint63b, checkpoint63c, checkpoint64, checkpoint65, checkpoint62, checkpoint63, checkpoint66g, checkpoint66f, checkpoint66e, checkpoint66d, checkpoint66c, checkpoint66b, checkpoint66a, checkpoint66o, checkpoint66n, checkpoint66m, checkpoint66l, checkpoint66k, checkpoint66j, checkpoint66i, checkpoint66h, checkpoint65z, checkpoint65x, checkpoint65y, checkpoint65r, checkpoint65s, checkpoint65p, checkpoint65q, checkpoint65v, checkpoint65w, checkpoint65t, checkpoint65u, checkpoint65j, checkpoint65k, checkpoint65h, checkpoint65i, checkpoint65n, checkpoint65o, checkpoint65l, checkpoint65m, checkpoint65b, checkpoint65c, checkpoint65a, checkpoint65f, checkpoint65g, checkpoint65d, checkpoint65e, checkpoint62c, checkpoint62b, checkpoint62a, checkpoint62g, checkpoint62f, checkpoint62e, checkpoint62d, checkpoint62k, checkpoint62j, checkpoint62i, checkpoint62h, checkpoint62o, checkpoint62n, checkpoint62m, checkpoint62l, checkpoint62s, checkpoint62r, checkpoint62q, checkpoint62p, checkpoint62w, checkpoint62v, checkpoint62u, checkpoint62t, checkpoint62z, checkpoint62y, checkpoint62x, checkpoint61v, checkpoint61w, checkpoint61t, checkpoint61u, checkpoint61s, checkpoint61z, checkpoint61x, checkpoint61y, HEAD
Changes since 1.2: +12 -12 lines
add bj in exch2 arrays and S/R

1 jmc 1.3 C $Header: /u/gcmpack/MITgcm/pkg/regrid/regrid_init_varia.F,v 1.2 2009/05/12 19:56:36 jmc Exp $
2 edhill 1.1 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 jmc 1.2 #include "W2_EXCH2_SIZE.h"
26 edhill 1.1 #include "W2_EXCH2_TOPOLOGY.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 jmc 1.3 C The convention is: "points cycle most quickly in X and then Y"
55 edhill 1.1 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 jmc 1.3 WRITE(msgBuf,'(a)')
70 edhill 1.1 & '// ======================================================='
71     CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,
72     & SQUEEZE_RIGHT,myThid)
73 jmc 1.3 WRITE(msgBuf,'(a)')
74 edhill 1.1 & '// Begin reading the per-face REGRID information'
75     CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,
76     & SQUEEZE_RIGHT,myThid)
77 jmc 1.3 WRITE(msgBuf,'(a)')
78 edhill 1.1 & '// ======================================================='
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 jmc 1.3
89 edhill 1.1 #ifdef ALLOW_EXCH2
90     C EXCH2 domains
91 jmc 1.3 uniq_tnum = W2_myTileList(bi,bj)
92 edhill 1.1 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 jmc 1.3 write(fname,'(a,i3.3,a)')
132 edhill 1.1 & 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 jmc 1.3 WRITE(msgBuf,'(3A)') ' File "',
139 edhill 1.1 & 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 jmc 1.3 WRITE(msgBuf,'(3A)') 'Unable to open file="',
151 edhill 1.1 & 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 jmc 1.3 READ(iUnit,fmt='(2(1X,I10),1X,E28.22)',iostat=errIO)
164 edhill 1.1 & 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 jmc 1.3
190 edhill 1.1 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