/[MITgcm]/MITgcm_contrib/shelfice_remeshing/CLEAN/code/shelfice_update_masks_JJ.F
ViewVC logotype

Annotation of /MITgcm_contrib/shelfice_remeshing/CLEAN/code/shelfice_update_masks_JJ.F

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


Revision 1.1 - (hide annotations) (download)
Mon Dec 7 17:08:44 2015 UTC (9 years, 7 months ago) by dgoldberg
Branch: MAIN
*** empty log message ***

1 dgoldberg 1.1 C $Header: /u/gcmpack/MITgcm_contrib/shelfice_remeshing/AUTO/code/shelfice_update_masks_JJ.F,v 1.3 2015/10/12 11:34:28 dgoldberg Exp $
2     C $Name: $
3    
4     #include "SHELFICE_OPTIONS.h"
5     #ifdef ALLOW_CTRL
6     # include "CTRL_OPTIONS.h"
7     #endif
8    
9     CBOP
10     C !ROUTINE: SHELFICE_UPDATE_MASKS
11     C !INTERFACE:
12     SUBROUTINE SHELFICE_UPDATE_MASKS_JJ(
13     I rF, recip_drF,
14     U hFacC,
15     I myThid )
16     C !DESCRIPTION: \bv
17     C *==========================================================*
18     C | SUBROUTINE SHELFICE_UPDATE_MASKS
19     C | o modify topography factor hFacC according to ice shelf
20     C | topography
21     C *==========================================================*
22     C \ev
23    
24     C !USES:
25     IMPLICIT NONE
26     C === Global variables ===
27     #include "SIZE.h"
28     #include "EEPARAMS.h"
29     #include "PARAMS.h"
30     #include "DYNVARS.h"
31     #include "SURFACE.h"
32     #ifdef ALLOW_SHELFICE
33     # include "SHELFICE.h"
34     #endif /* ALLOW_SHELFICE */
35    
36     C !INPUT/OUTPUT PARAMETERS:
37     C == Routine arguments ==
38     C rF :: R-coordinate of face of cell (units of r).
39     C recip_drF :: Recipricol of cell face separation along Z axis ( units of r ).
40     C hFacC :: Fraction of cell in vertical which is open (see GRID.h)
41     C myThid :: Number of this instance of SHELFICE_UPDATE_MASKS
42     _RS rF (1:Nr+1)
43     _RS recip_drF (1:Nr)
44     _RS hFacC (1-OLx:sNx+OLx,1-OLy:sNy+OLy,1:Nr,nSx,nSy)
45    
46     INTEGER myThid
47    
48     #ifdef ALLOW_SHELFICE
49     C !LOCAL VARIABLES:
50     C == Local variables ==
51     C bi,bj :: tile indices
52     C I,J,K :: Loop counters
53     INTEGER bi, bj
54     INTEGER I, J, K
55     _RL hFacCtmp
56     _RL hFacMnSz
57    
58     C- Update etaN
59     DO bj = myByLo(myThid), myByHi(myThid)
60     DO bi = myBxLo(myThid), myBxHi(myThid)
61     DO J = 1-OLy,sNy+OLy
62     DO I = 1-OLx,sNx+OLx
63     IF ( R_shelfice(I,J,bi,bj) .LT. 0.0) THEN
64     IF (etah(I,J,bi,bj) .GT. SHELFICESplitThreshold ) THEN
65     K = MAX(1,kTopC(I,J,bi,bj))
66     etaN(I,J,bi,bj) = etaN(I,J,bi,bj) - 1/recip_drF(K)
67     etaH(I,J,bi,bj) = etaH(I,J,bi,bj) - 1/recip_drF(K)
68     R_shelfIce(I,J,bi,bj) = R_shelfIce(I,J,bi,bj)+1/recip_drF(K)
69     uVel(I,J,K-1,bi,bj)=uVel(I,J,K,bi,bj)
70     uVel(I+1,J,K-1,bi,bj)=uVel(I+1,J,K,bi,bj)
71     vVel(I,J,K-1,bi,bj)=vVel(I,J,K,bi,bj)
72     vVel(I,J+1,K-1,bi,bj)=vVel(I,J+1,K,bi,bj)
73    
74     gvnm1(I,J,K-1,bi,bj)=gvnm1(I,J,K,bi,bj)
75     gvnm1(I,J+1,K-1,bi,bj)=gvnm1(I,J+1,K,bi,bj)
76     gunm1(I,J,K-1,bi,bj)=gunm1(I,J,K,bi,bj)
77     gunm1(I+1,J,K-1,bi,bj)=gunm1(I,J,K,bi,bj)
78    
79     salt(I,J,K-1,bi,bj)=salt(I,J,K,bi,bj)
80     theta(I,J,K-1,bi,bj)=theta(I,J,K,bi,bj)
81     hfacC(I,J,K,bi,bj)=1.0
82    
83     ENDIF
84     IF (R_shelfice(i,j,bi,bj) .NE. R_grounding(i,j,bi,bj))THEN
85     IF (etah(I,J,bi,bj) .LT. SHELFICEMergeThreshold ) THEN
86     K = MAX(1,kTopC(I,J,bi,bj))
87    
88     salt(I,J,K+1,bi,bj)=((salt(I,J,K,bi,bj)*(1/recip_drF(K)+
89     & etaN(I,J,bi,bj)))+(salt(I,J,K+1,bi,bj)*1/recip_drF(K+1)))/(
90     & 1/recip_drF(K)+1/recip_drF(K+1)+etaN(I,J,bi,bj))
91    
92     theta(I,J,K+1,bi,bj)=((theta(I,J,K,bi,bj)*(1/recip_drF(K)+
93     & etaN(I,J,bi,bj)))+(theta(I,J,K+1,bi,bj)*1/recip_drF(K+1)))/(
94     & 1/recip_drF(K)+1/recip_drF(K+1)+etaN(I,J,bi,bj))
95    
96     vVel(I,J,K+1,bi,bj)=((vVel(I,J,K,bi,bj)*(1/recip_drF(K)+
97     & etaN(I,J,bi,bj)))+(vVel(I,J,K+1,bi,bj)*1/recip_drF(K+1)))/(
98     & 1/recip_drF(K)+1/recip_drF(K+1)+etaN(I,J,bi,bj))
99    
100     vVel(I,J+1,K+1,bi,bj)=((vVel(I,J+1,K,bi,bj)*(1/recip_drF(K)+
101     & etaN(I,J,bi,bj)))+(vVel(I,J+1,K+1,bi,bj)*1/recip_drF(K+1)))/
102     & (1/recip_drF(K)+1/recip_drF(K+1)+etaN(I,J,bi,bj))
103    
104     uVel(I,J,K+1,bi,bj)=((uVel(I,J,K,bi,bj)*(1/recip_drF(K)+
105     & etaN(I,J,bi,bj)))+(uVel(I,J,K+1,bi,bj)*1/recip_drF(K+1)))/(
106     & 1/recip_ drF(K)+1/recip_drF(K+1)+etaN(I,J,bi,bj))
107    
108     uVel(I+1,J,K+1,bi,bj)=((uVel(I+1,J,K,bi,bj)*(1/recip_drF(K)+
109     & etaN(I,J,bi,bj)))+(uVel(I+1,J,K+1,bi,bj)*1/recip_drF(K+1)))/
110     & (1/recip_drF(K)+1/recip_drF(K+1)+etaN(I,J,bi,bj))
111    
112     etaN(I,J,bi,bj) = etaN(I,J,bi,bj) +1/recip_drF(K)
113     etaH(I,J,bi,bj) = etaH(I,J,bi,bj) +1/recip_drF(K)
114     R_shelfice(I,J,bi,bj) = R_shelfice(I,J,bi,bj) -1/recip_drF(K)
115    
116     gunm1(I+1,J,K+1,bi,bj)=((gunm1(I+1,J,K,bi,bj)*(1/recip_drF(K)+
117     & etaN(I,J,bi,bj)))+(gunm1(I+1,J,K+1,bi,bj)*1/recip_drF(K+1)))/
118     & (1/recip_drF(K)+1/recip_drF(K+1)+etaN(I,J,bi,bj))
119    
120     gunm1(I,J,K+1,bi,bj)=((gunm1(I,J,K,bi,bj)*(1/recip_drF(K)+
121     & etaN(I,J,bi,bj)))+(gunm1(I,J,K+1,bi,bj)*1/recip_drF(K+1)))/
122     & (1/recip_drF(K)+1/recip_drF(K+1)+etaN(I,J,bi,bj))
123    
124     gvnm1(I,J+1,K+1,bi,bj)=((gvnm1(I,J+1,K,bi,bj)*(1/recip_drF(K)+
125     & etaN(I,J,bi,bj)))+(gvnm1(I,J+1,K+1,bi,bj)*1/recip_drF(K+1)))/
126     & (1/recip_drF(K)+1/recip_drF(K+1)+etaN(I,J,bi,bj))
127    
128    
129     gvnm1(I,J,K+1,bi,bj)=((gvnm1(I,J,K,bi,bj)*(1/recip_drF(K)+
130     & etaN(I,J,bi,bj)))+(gvnm1(I,J,K+1,bi,bj)*1/recip_drF(K+1)))/
131     & (1/recip_drF(K)+1/recip_drF(K+1)+etaN(I,J,bi,bj))
132    
133    
134    
135    
136    
137     hfacC(I,J,K,bi,bj)=1.0
138     ENDIF
139     ENDIF
140     ENDIF
141     ENDDO
142     ENDDO
143     ENDDO
144     ENDDO
145    
146    
147     DO bj = myByLo(myThid), myByHi(myThid)
148     DO bi = myBxLo(myThid), myBxHi(myThid)
149     DO J = 1-OLy,sNy+OLy
150     DO I = 1-OLx,sNx+OLx
151     etaH(I,J,bi,bj)=etaN(I,J,bi,bj)
152     etaHnm1(I,J,bi,bj)=etaH(I,J,bi,bj)
153     ENDDO
154     ENDDO
155     ENDDO
156     ENDDO
157    
158    
159    
160     DO bj = myByLo(myThid), myByHi(myThid)
161     DO bi = myBxLo(myThid), myBxHi(myThid)
162     DO J = 1-OLy,sNy+OLy
163     DO I = 1-OLx,sNx+OLx
164     K = MAX(1,kTopC(I,J,bi,bj))
165    
166     hfac_surfc(I,J,bi,bj)= ((etaH(I,J,bi,bJ) +(1/recip_drF(K)))
167     & *recip_drF(K))
168    
169    
170    
171     ENDDO
172     ENDDO
173     ENDDO
174     ENDDO
175    
176    
177    
178    
179    
180     C- fill in the overlap (+ BARRIER):
181     _EXCH_XY_RS(R_shelfIce, myThid )
182    
183     C-- Calculate lopping factor hFacC : Remove part outside of the domain
184     C taking into account the Reference (=at rest) Surface Position Ro_shelfIce
185     DO bj=myByLo(myThid), myByHi(myThid)
186     DO bi=myBxLo(myThid), myBxHi(myThid)
187    
188     C-- compute contributions of shelf ice to looping factors
189     DO K=1, Nr
190     hFacMnSz=max( hFacMin, min(hFacMinDr*recip_drF(k),1. _d 0) )
191     DO J=1-OLy,sNy+OLy
192     DO I=1-OLx,sNx+OLx
193     C o Non-dimensional distance between grid boundary and model surface
194     hFacCtmp = (rF(k)-R_shelfIce(I,J,bi,bj))*recip_drF(K)
195     C o Reduce the previous fraction : substract the outside part.
196     hFacCtmp = hFacC(I,J,K,bi,bj) - max( hFacCtmp, 0. _d 0)
197     C o set to zero if empty Column :
198     hFacCtmp = max( hFacCtmp, 0. _d 0)
199     C o Impose minimum fraction and/or size (dimensional)
200     IF (hFacCtmp.LT.hFacMnSz) THEN
201     IF (hFacCtmp.LT.hFacMnSz*0.5) THEN
202     hFacC(I,J,K,bi,bj)=0.
203     ELSE
204     hFacC(I,J,K,bi,bj)=hFacMnSz
205     ENDIF
206     ELSE
207     hFacC(I,J,K,bi,bj)=hFacCtmp
208     ENDIF
209     ENDDO
210     ENDDO
211     ENDDO
212    
213     #ifdef ALLOW_SHIFWFLX_CONTROL
214     C maskSHI is a hack to play along with the general ctrl-package
215     C infrastructure, where only the k=1 layer of a 3D mask is used
216     C for 2D fields. We cannot use maskInC instead, because routines
217     C like ctrl_get_gen and ctrl_set_unpack_xy require 3D masks.
218     DO K=1,Nr
219     DO J=1-OLy,sNy+OLy
220     DO I=1-OLx,sNx+OLx
221     maskSHI(I,J,K,bi,bj) = 0. _d 0
222     ENDDO
223     ENDDO
224     ENDDO
225     DO K=1,Nr
226     DO J=1-OLy,sNy+OLy
227     DO I=1-OLx,sNx+OLx
228     IF ( ABS(R_shelfice(I,J,bi,bj)) .GT. 0. _d 0
229     & .AND. hFacC(I,J,K,bi,bj) .NE. 0. _d 0 ) THEN
230     maskSHI(I,J,K,bi,bj) = 1. _d 0
231     maskSHI(I,J,1,bi,bj) = 1. _d 0
232     ENDIF
233     ENDDO
234     ENDDO
235     ENDDO
236     #endif /* ALLOW_SHIFWFLX_CONTROL */
237    
238     C - end bi,bj loops.
239     ENDDO
240     ENDDO
241     #endif /* ALLOW_SHELFICE */
242     RETURN
243     END

  ViewVC Help
Powered by ViewVC 1.1.22