/[MITgcm]/MITgcm_contrib/verification_other/shelfice_remeshing/code/ini_masks_remesh.F
ViewVC logotype

Annotation of /MITgcm_contrib/verification_other/shelfice_remeshing/code/ini_masks_remesh.F

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


Revision 1.4 - (hide annotations) (download)
Sun May 20 13:04:08 2018 UTC (7 years, 1 month ago) by dgoldberg
Branch: MAIN
CVS Tags: checkpoint67d, HEAD
Changes since 1.3: +6 -14 lines
adding remeshing files to verification_otherw

1 dgoldberg 1.4 C $Header: /u/gcmpack/MITgcm_contrib/dgoldberg/remeshing/code/ini_masks_remesh.F,v 1.2 2017/04/04 23:36:06 jmc Exp $
2 dgoldberg 1.1 C $Name: $
3    
4     #include "PACKAGES_CONFIG.h"
5     #include "CPP_OPTIONS.h"
6     #include "SHELFICE_OPTIONS.h"
7    
8     CBOP
9     C !ROUTINE: INI_MASKS_ETC
10     C !INTERFACE:
11     SUBROUTINE INI_MASKS_REMESH( myThid )
12     C !DESCRIPTION: \bv
13     C *==========================================================*
14     C | SUBROUTINE INI_MASKS_ETC
15     C | o Initialise masks and topography factors
16     C *==========================================================*
17     C | These arrays are used throughout the code and describe
18     C | the topography of the domain through masks (0s and 1s)
19     C | and fractional height factors (0<hFac<1). The latter
20     C | distinguish between the lopped-cell and full-step
21     C | topographic representations.
22     C *==========================================================*
23     C \ev
24    
25     C !USES:
26     IMPLICIT NONE
27     C === Global variables ===
28     #include "SIZE.h"
29     #include "EEPARAMS.h"
30     #include "PARAMS.h"
31     #include "GRID.h"
32     #include "DYNVARS.h"
33     #ifdef NONLIN_FRSURF
34     # include "SURFACE.h"
35     #endif /* NONLIN_FRSURF */
36    
37     C !INPUT/OUTPUT PARAMETERS:
38     C == Routine arguments ==
39     C myThid :: Number of this instance of INI_MASKS_ETC
40     INTEGER myThid
41    
42     #ifdef ALLOW_SHELFICE
43     #ifdef ALLOW_SHELFICE_REMESHING
44    
45     C !LOCAL VARIABLES:
46     C == Local variables ==
47     C bi,bj :: tile indices
48     C i,j,k :: Loop counters
49     C tmpfld :: Temporary array used to compute & write Total Depth
50     _RS tmpfld(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
51 dgoldberg 1.4
52 dgoldberg 1.1 _RS rsurftmp(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
53    
54     INTEGER bi, bj
55     INTEGER i, j, k, ks
56     _RL hFacCtmp
57     _RL hFacMnSz
58     _RS hhm, hhp
59 dgoldberg 1.2 _RL Rmin_tmp
60 dgoldberg 1.1 CEOP
61    
62     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
63    
64     IF ( selectSigmaCoord.EQ.0 ) THEN
65     C--- r-coordinate with partial-cell or full cell mask
66    
67     C-- Calculate lopping factor hFacC : over-estimate the part inside of the domain
68     C taking into account the lower_R Boundary (Bathymetrie / Top of Atmos)
69     DO bj=myByLo(myThid), myByHi(myThid)
70     DO bi=myBxLo(myThid), myBxHi(myThid)
71     DO k=1, Nr
72     hFacMnSz=max( hFacMin, min(hFacMinDr*recip_drF(k),1. _d 0) )
73     DO j=1-OLy,sNy+OLy
74     DO i=1-OLx,sNx+OLx
75     C o Non-dimensional distance between grid bound. and domain lower_R bound.
76     hFacCtmp = (rF(k)-R_low(i,j,bi,bj))*recip_drF(k)
77     C o Select between, closed, open or partial (0,1,0-1)
78     hFacCtmp=min( max( hFacCtmp, 0. _d 0) , 1. _d 0)
79     C o Impose minimum fraction and/or size (dimensional)
80     IF (hFacCtmp.LT.hFacMnSz) THEN
81     IF (hFacCtmp.LT.hFacMnSz*0.5) THEN
82     hFacC(i,j,k,bi,bj)=0.
83     ELSE
84     hFacC(i,j,k,bi,bj)=hFacMnSz
85     ENDIF
86     ELSE
87     hFacC(i,j,k,bi,bj)=hFacCtmp
88     ENDIF
89     ENDDO
90     ENDDO
91     ENDDO
92    
93     C- Re-calculate lower-R Boundary position, taking into account hFacC
94     DO j=1-OLy,sNy+OLy
95     DO i=1-OLx,sNx+OLx
96     R_low(i,j,bi,bj) = rF(1)
97     ENDDO
98     ENDDO
99     DO k=Nr,1,-1
100     DO j=1-OLy,sNy+OLy
101     DO i=1-OLx,sNx+OLx
102     R_low(i,j,bi,bj) = R_low(i,j,bi,bj)
103     & - drF(k)*hFacC(i,j,k,bi,bj)
104     ENDDO
105     ENDDO
106     ENDDO
107     C- end bi,bj loops.
108     ENDDO
109     ENDDO
110    
111     C-- Calculate lopping factor hFacC : Remove part outside of the domain
112     C taking into account the Reference (=at rest) Surface Position Ro_surf
113     DO bj=myByLo(myThid), myByHi(myThid)
114     DO bi=myBxLo(myThid), myBxHi(myThid)
115     DO k=1, Nr
116     hFacMnSz=max( hFacMin, min(hFacMinDr*recip_drF(k),1. _d 0) )
117     DO j=1-OLy,sNy+OLy
118     DO i=1-OLx,sNx+OLx
119     C JJ HACK
120     Ro_surf(i,j,bi,bj)=0.0
121     C o Non-dimensional distance between grid boundary and model surface
122     hFacCtmp = (rF(k)-Ro_surf(i,j,bi,bj))*recip_drF(k)
123     C o Reduce the previous fraction : substract the outside part.
124     hFacCtmp = hFacC(i,j,k,bi,bj) - max( hFacCtmp, 0. _d 0)
125     C o set to zero if empty Column :
126     hFacCtmp = max( hFacCtmp, 0. _d 0)
127     C o Impose minimum fraction and/or size (dimensional)
128     IF (hFacCtmp.LT.hFacMnSz) THEN
129     IF (hFacCtmp.LT.hFacMnSz*0.5) THEN
130     hFacC(i,j,k,bi,bj)=0.
131     ELSE
132     hFacC(i,j,k,bi,bj)=hFacMnSz
133     ENDIF
134     ELSE
135     hFacC(i,j,k,bi,bj)=hFacCtmp
136     ENDIF
137     ENDDO
138     ENDDO
139     ENDDO
140     ENDDO
141     ENDDO
142    
143     #ifdef ALLOW_SHELFICE
144    
145     IF ( useShelfIce ) THEN
146     C-- Modify lopping factor hFacC : Remove part outside of the domain
147     C taking into account the Reference (=at rest) Surface Position Ro_shelfIce
148     CALL SHELFICE_UPDATE_MASKS_REMESH(
149     I rF, recip_drF, drF, kLowc,
150     U hFacC,
151     I myThid )
152     ENDIF
153     #endif /* ALLOW_SHELFICE */
154    
155     C- Re-calculate Reference surface position, taking into account hFacC
156     C initialize Total column fluid thickness and surface k index
157     C Note: if no fluid (continent) ==> kSurf = Nr+1
158     DO bj=myByLo(myThid), myByHi(myThid)
159     DO bi=myBxLo(myThid), myBxHi(myThid)
160     DO j=1-OLy,sNy+OLy
161     DO i=1-OLx,sNx+OLx
162     tmpfld(i,j,bi,bj) = 0.
163     kSurfC(i,j,bi,bj) = Nr+1
164     c maskH(i,j,bi,bj) = 0.
165     Ro_surf(i,j,bi,bj) = R_low(i,j,bi,bj)
166     DO k=Nr,1,-1
167     Ro_surf(i,j,bi,bj) = Ro_surf(i,j,bi,bj)
168     & + drF(k)*hFacC(i,j,k,bi,bj)
169     IF (hFacC(i,j,k,bi,bj).NE.0.) THEN
170     kSurfC(i,j,bi,bj) = k
171     c maskH(i,j,bi,bj) = 1.
172     tmpfld(i,j,bi,bj) = tmpfld(i,j,bi,bj) + 1.
173     ENDIF
174     ENDDO
175     kLowC(i,j,bi,bj) = 0
176     DO k= 1, Nr
177     IF (hFacC(i,j,k,bi,bj).NE.0) THEN
178     kLowC(i,j,bi,bj) = k
179     ENDIF
180     ENDDO
181     maskInC(i,j,bi,bj)= 0.
182     IF ( kSurfC(i,j,bi,bj).LE.Nr ) maskInC(i,j,bi,bj)= 1.
183     ENDDO
184     ENDDO
185     C- end bi,bj loops.
186     ENDDO
187     ENDDO
188    
189 dgoldberg 1.4 IF ( plotLevel.GE.debLevB ) THEN
190 dgoldberg 1.1 c CALL PLOT_FIELD_XYRS( tmpfld,
191     c & 'Model Depths K Index' , -1, myThid )
192     CALL PLOT_FIELD_XYRS(R_low,
193     & 'Model R_low (ini_masks_etc)', -1, myThid )
194     CALL PLOT_FIELD_XYRS(Ro_surf,
195     & 'Model Ro_surf (ini_masks_etc)', -1, myThid )
196     ENDIF
197    
198     C-- Calculate quantities derived from XY depth map
199     DO bj = myByLo(myThid), myByHi(myThid)
200     DO bi = myBxLo(myThid), myBxHi(myThid)
201     DO j=1-OLy,sNy+OLy
202     DO i=1-OLx,sNx+OLx
203     C Total fluid column thickness (r_unit) :
204     c Rcolumn(i,j,bi,bj)= Ro_surf(i,j,bi,bj) - R_low(i,j,bi,bj)
205     tmpfld(i,j,bi,bj) = Ro_surf(i,j,bi,bj) - R_low(i,j,bi,bj)
206     C Inverse of fluid column thickness (1/r_unit)
207     IF ( tmpfld(i,j,bi,bj) .LE. 0. ) THEN
208     recip_Rcol(i,j,bi,bj) = 0.
209     ELSE
210     recip_Rcol(i,j,bi,bj) = 1. _d 0 / tmpfld(i,j,bi,bj)
211     ENDIF
212     ENDDO
213     ENDDO
214     ENDDO
215     ENDDO
216    
217     C-- hFacW and hFacS (at U and V points)
218     DO bj=myByLo(myThid), myByHi(myThid)
219     DO bi=myBxLo(myThid), myBxHi(myThid)
220     DO k=1, Nr
221     DO j=1-OLy,sNy+OLy
222     hFacW(1-OLx,j,k,bi,bj)= 0.
223     DO i=2-OLx,sNx+OLx
224     hFacW(i,j,k,bi,bj)=
225     & MIN(hFacC(i,j,k,bi,bj),hFacC(i-1,j,k,bi,bj))
226     ENDDO
227     ENDDO
228     DO i=1-OLx,sNx+OLx
229     hFacS(i,1-OLy,k,bi,bj)= 0.
230     ENDDO
231 dgoldberg 1.4 DO j=2-OLy,sNy+OLy
232 dgoldberg 1.1 DO i=1-OLx,sNx+OLx
233     hFacS(i,j,k,bi,bj)=
234     & MIN(hFacC(i,j,k,bi,bj),hFacC(i,j-1,k,bi,bj))
235     ENDDO
236     ENDDO
237     ENDDO
238     C rLow & reference rSurf at Western & Southern edges (U and V points)
239     i = 1-OLx
240     DO j=1-OLy,sNy+OLy
241     rLowW (i,j,bi,bj) = 0.
242     rSurfW(i,j,bi,bj) = 0.
243     ENDDO
244     j = 1-OLy
245     DO i=1-OLx,sNx+OLx
246     rLowS (i,j,bi,bj) = 0.
247     rSurfS(i,j,bi,bj) = 0.
248     ENDDO
249     DO j=1-OLy,sNy+OLy
250     DO i=2-OLx,sNx+OLx
251     rLowW(i,j,bi,bj) =
252     & MAX( R_low(i-1,j,bi,bj), R_low(i,j,bi,bj) )
253     rSurfW(i,j,bi,bj) =
254     & MIN( Ro_surf(i-1,j,bi,bj), Ro_surf(i,j,bi,bj) )
255     rSurfW(i,j,bi,bj) =
256     & MAX( rSurfW(i,j,bi,bj), rLowW(i,j,bi,bj) )
257     ENDDO
258     ENDDO
259     DO j=2-OLy,sNy+OLy
260     DO i=1-OLx,sNx+OLx
261     rLowS(i,j,bi,bj) =
262     & MAX( R_low(i,j-1,bi,bj), R_low(i,j,bi,bj) )
263     rSurfS(i,j,bi,bj) =
264     & MIN( Ro_surf(i,j-1,bi,bj), Ro_surf(i,j,bi,bj) )
265     rSurfS(i,j,bi,bj) =
266     & MAX( rSurfS(i,j,bi,bj), rLowS(i,j,bi,bj) )
267     ENDDO
268     ENDDO
269     C- end bi,bj loops.
270     ENDDO
271     ENDDO
272     CALL EXCH_UV_XYZ_RS(hFacW,hFacS,.FALSE.,myThid)
273     CALL EXCH_UV_XY_RS( rSurfW, rSurfS, .FALSE., myThid )
274     CALL EXCH_UV_XY_RS( rLowW, rLowS, .FALSE., myThid )
275    
276     C-- Addtional closing of Western and Southern grid-cell edges: for example,
277     C a) might add some "thin walls" in specific location
278     C-- b) close non-periodic N & S boundaries of lat-lon grid at the N/S poles.
279     CALL ADD_WALLS2MASKS( myThid )
280    
281     C-- Calculate surface k index for interface W & S (U & V points)
282     DO bj=myByLo(myThid), myByHi(myThid)
283     DO bi=myBxLo(myThid), myBxHi(myThid)
284     DO j=1-OLy,sNy+OLy
285     DO i=1-OLx,sNx+OLx
286     kSurfW(i,j,bi,bj) = Nr+1
287     kSurfS(i,j,bi,bj) = Nr+1
288     DO k=Nr,1,-1
289     IF (hFacW(i,j,k,bi,bj).NE.0.) kSurfW(i,j,bi,bj) = k
290     IF (hFacS(i,j,k,bi,bj).NE.0.) kSurfS(i,j,bi,bj) = k
291     ENDDO
292     maskInW(i,j,bi,bj)= 0.
293     IF ( kSurfW(i,j,bi,bj).LE.Nr ) maskInW(i,j,bi,bj)= 1.
294     maskInS(i,j,bi,bj)= 0.
295     IF ( kSurfS(i,j,bi,bj).LE.Nr ) maskInS(i,j,bi,bj)= 1.
296     ENDDO
297     ENDDO
298     ENDDO
299     ENDDO
300    
301     ELSE
302     #ifndef DISABLE_SIGMA_CODE
303     C--- Sigma and Hybrid-Sigma set-up:
304     CALL INI_SIGMA_HFAC( myThid )
305     #endif /* DISABLE_SIGMA_CODE */
306     ENDIF
307    
308     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
309    
310     C-- Write to disk: Total Column Thickness & hFac(C,W,S):
311     C This I/O is now done in write_grid.F
312     c CALL WRITE_FLD_XY_RS( 'Depth',' ',tmpfld,0,myThid)
313     c CALL WRITE_FLD_XYZ_RS( 'hFacC',' ',hFacC,0,myThid)
314     c CALL WRITE_FLD_XYZ_RS( 'hFacW',' ',hFacW,0,myThid)
315     c CALL WRITE_FLD_XYZ_RS( 'hFacS',' ',hFacS,0,myThid)
316    
317 dgoldberg 1.4 IF ( plotLevel.GE.debLevB ) THEN
318 dgoldberg 1.1 CALL PLOT_FIELD_XYZRS( hFacC, 'hFacC' , Nr, 0, myThid )
319     CALL PLOT_FIELD_XYZRS( hFacW, 'hFacW' , Nr, 0, myThid )
320     CALL PLOT_FIELD_XYZRS( hFacS, 'hFacS' , Nr, 0, myThid )
321     ENDIF
322    
323     C-- Masks and reciprocals of hFac[CWS]
324     DO bj = myByLo(myThid), myByHi(myThid)
325     DO bi = myBxLo(myThid), myBxHi(myThid)
326     DO k=1,Nr
327     DO j=1-OLy,sNy+OLy
328     DO i=1-OLx,sNx+OLx
329     IF (hFacC(i,j,k,bi,bj) .NE. 0. ) THEN
330     recip_hFacC(i,j,k,bi,bj) = 1. _d 0 / hFacC(i,j,k,bi,bj)
331     maskC(i,j,k,bi,bj) = 1.
332     ELSE
333     recip_hFacC(i,j,k,bi,bj) = 0.
334     maskC(i,j,k,bi,bj) = 0.
335     ENDIF
336     IF (hFacW(i,j,k,bi,bj) .NE. 0. ) THEN
337     recip_hFacW(i,j,k,bi,bj) = 1. _d 0 / hFacW(i,j,k,bi,bj)
338     maskW(i,j,k,bi,bj) = 1.
339     ELSE
340     recip_hFacW(i,j,k,bi,bj) = 0.
341     maskW(i,j,k,bi,bj) = 0.
342     ENDIF
343     IF (hFacS(i,j,k,bi,bj) .NE. 0. ) THEN
344     recip_hFacS(i,j,k,bi,bj) = 1. _d 0 / hFacS(i,j,k,bi,bj)
345     maskS(i,j,k,bi,bj) = 1.
346     ELSE
347     recip_hFacS(i,j,k,bi,bj) = 0.
348     maskS(i,j,k,bi,bj) = 0.
349     ENDIF
350     ENDDO
351     ENDDO
352     ENDDO
353     #ifdef NONLIN_FRSURF
354     C-- Save initial geometrical hFac factor into h0Fac (fixed in time):
355     C Note: In case 1 pkg modifies hFac (from packages_init_fixed, called
356     C later in sequence of calls) this pkg would need also to update h0Fac.
357     DO k=1,Nr
358     DO j=1-OLy,sNy+OLy
359     DO i=1-OLx,sNx+OLx
360     h0FacC(i,j,k,bi,bj) = _hFacC(i,j,k,bi,bj)
361     h0FacW(i,j,k,bi,bj) = _hFacW(i,j,k,bi,bj)
362     h0FacS(i,j,k,bi,bj) = _hFacS(i,j,k,bi,bj)
363     ENDDO
364     ENDDO
365     ENDDO
366     #endif /* NONLIN_FRSURF */
367     C- end bi,bj loops.
368     ENDDO
369     ENDDO
370    
371     DO bj = myByLo(myThid), myByHi(myThid)
372     DO bi = myBxLo(myThid), myBxHi(myThid)
373     DO k=1,Nr
374     DO j=1-OLy,sNy+OLy
375     DO i=1-OLx,sNx+OLx
376     uVel(i,j,k,bi,bj)=uVel(i,j,k,bi,bj)*maskW(i,j,k,bi,bj)
377     vVel(i,j,k,bi,bj)=vVel(i,j,k,bi,bj)*maskS(i,j,k,bi,bj)
378     wVel(i,j,k,bi,bj)=0.0
379     salt(i,j,k,bi,bj)=salt(i,j,k,bi,bj)*maskC(i,j,k,bi,bj)
380     theta(i,j,k,bi,bj)=theta(i,j,k,bi,bj)*maskC(i,j,k,bi,bj)
381    
382     ENDDO
383     ENDDO
384     ENDDO
385     ENDDO
386     ENDDO
387    
388     DO bj = myByLo(myThid), myByHi(myThid)
389     DO bi = myBxLo(myThid), myBxHi(myThid)
390     DO j=1,sNy
391     DO i=1,sNx+1
392     ks = kSurfW(i,j,bi,bj)
393     IF (ks.LE.Nr) THEN
394     c- allows hFacW to be larger than surrounding hFacC=1 @ edge of a step with
395     C different kSurfC on either side (topo in p-coords, ice-shelf in z-coords)
396     hhm = Ro_surf(i-1,j,bi,bj)+etaN(i-1,j,bi,bj)
397    
398     hhp = Ro_surf(i,j,bi,bj)+etaN(i,j,bi,bj)
399    
400     C- make sure hFacW is not larger than the 2 surrounding hFacC
401     c hhm = rF(ks)
402     c IF(ks.EQ.kSurfC(i-1,j,bi,bj)) hhm = rSurftmp(i-1,j)
403     c hhp = rF(ks)
404     c IF(ks.EQ.kSurfC(i,j,bi,bj)) hhp = rSurftmp(i,j)
405     hFac_surfW(i,j,bi,bj) = h0FacW(i,j,ks,bi,bj)
406     & + ( MIN(hhm,hhp)
407     & - MIN( Ro_surf(i-1,j,bi,bj), Ro_surf(i,j,bi,bj) )
408     & )*recip_drF(ks)*maskW(i,j,ks,bi,bj)
409     ENDIF
410     ENDDO
411     ENDDO
412    
413     DO j=1,sNy+1
414     DO i=1,sNx
415     ks = kSurfS(i,j,bi,bj)
416     IF (ks.LE.Nr) THEN
417     C- allows hFacS to be larger than surrounding hFacC=1 @ edge of a step with
418     C different kSurfC on either side (topo in p-coords, ice-shelf in z-coords)
419     hhm = Ro_surf(i,j-1,bi,bj)+etaN(i,j-1,bi,bj)
420    
421     hhp = Ro_surf(i,j,bi,bj)+etaN(i,j,bi,bj)
422    
423     C- make sure hFacS is not larger than the 2 surrounding hFacC
424     c hhm = rF(ks)
425     c IF(ks.EQ.kSurfC(i,j-1,bi,bj)) hhm = rSurftmp(i,j-1)
426     c hhp = rF(ks)
427     c IF(ks.EQ.kSurfC(i,j,bi,bj)) hhp = rSurftmp(i,j)
428     hFac_surfS(i,j,bi,bj) = h0FacS(i,j,ks,bi,bj)
429     & + ( MIN(hhm,hhp)
430     & - MIN( Ro_surf(i,j-1,bi,bj), Ro_surf(i,j,bi,bj) )
431     & )*recip_drF(ks)*maskS(i,j,ks,bi,bj)
432     ENDIF
433     ENDDO
434     ENDDO
435     ENDDO
436     ENDDO
437    
438 dgoldberg 1.2 #ifdef NONLIN_FRSURF
439    
440     DO bj=myByLo(myThid), myByHi(myThid)
441     DO bi=myBxLo(myThid), myBxHi(myThid)
442    
443     C-- Compute the mimimum value of r_surf (used for computing hFac_surfC)
444     DO j=1,sNy
445     DO i=1,sNx
446     ks = kSurfC(i,j,bi,bj)
447     IF (ks.LE.Nr) THEN
448     Rmin_tmp = rF(ks+1)
449     IF ( ks.EQ.kSurfW(i,j,bi,bj))
450     & Rmin_tmp = MAX(Rmin_tmp, R_low(i-1,j,bi,bj))
451     IF ( ks.EQ.kSurfW(i+1,j,bi,bj))
452     & Rmin_tmp = MAX(Rmin_tmp, R_low(i+1,j,bi,bj))
453     IF ( ks.EQ.kSurfS(i,j,bi,bj))
454     & Rmin_tmp = MAX(Rmin_tmp, R_low(i,j-1,bi,bj))
455     IF ( ks.EQ.kSurfS(i,j+1,bi,bj))
456     & Rmin_tmp = MAX(Rmin_tmp, R_low(i,j+1,bi,bj))
457    
458     Rmin_surf(i,j,bi,bj) =
459     & MAX( MAX(rF(ks+1),R_low(i,j,bi,bj)) + hFacInf*drF(ks),
460     & Rmin_tmp + hFacInf*drF(ks)
461     & )
462 dgoldberg 1.4
463 dgoldberg 1.2 ENDIF
464     ENDDO
465     ENDDO
466    
467     C- end bi,bj loop.
468     ENDDO
469     ENDDO
470    
471     CALL EXCH_XY_RL( Rmin_surf, myThid )
472    
473     #endif /* NONLIN_FRSURF */
474    
475 dgoldberg 1.1 c #if
476     C-- Calculate "recip_hFacU" = reciprocal hfac distance/volume for W cells
477     C NOTE: not used ; computed locally in CALC_GW
478     c #endif
479    
480     #endif
481     #endif
482    
483     RETURN
484     END

  ViewVC Help
Powered by ViewVC 1.1.22