/[MITgcm]/MITgcm_contrib/dgoldberg/streamice/streamice_driving_stress.F
ViewVC logotype

Annotation of /MITgcm_contrib/dgoldberg/streamice/streamice_driving_stress.F

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


Revision 1.5 - (hide annotations) (download)
Mon Dec 10 02:34:45 2012 UTC (12 years, 7 months ago) by dgoldberg
Branch: MAIN
Changes since 1.4: +9 -9 lines
various updates, mostly adding ifdefs to include statements

1 dgoldberg 1.5 C $Header: /u/gcmpack/MITgcm_contrib/dgoldberg/streamice/streamice_driving_stress.F,v 1.4 2012/09/28 02:55:40 heimbach Exp $
2 heimbach 1.1 C $Name: $
3    
4     #include "STREAMICE_OPTIONS.h"
5    
6     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
7    
8     CBOP
9     SUBROUTINE STREAMICE_DRIVING_STRESS( myThid )
10     ! O taudx,
11     ! O taudy )
12    
13     C /============================================================\
14     C | SUBROUTINE |
15     C | o |
16     C |============================================================|
17     C | |
18     C \============================================================/
19     IMPLICIT NONE
20    
21     C === Global variables ===
22     #include "SIZE.h"
23     #include "EEPARAMS.h"
24     #include "PARAMS.h"
25     #include "GRID.h"
26     #include "STREAMICE.h"
27     #include "STREAMICE_CG.h"
28    
29     C !INPUT/OUTPUT ARGUMENTS
30     INTEGER myThid
31     ! _RL taudx (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
32     ! _RL taudx (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
33    
34     #ifdef ALLOW_STREAMICE
35    
36    
37     C LOCAL VARIABLES
38     INTEGER i, j, bi, bj, k, l,
39     & Gi, Gj
40     LOGICAL at_west_bdry, at_east_bdry,
41     & at_north_bdry, at_south_bdry
42     _RL sx, sy, diffx, diffy, neu_val
43    
44     IF (myXGlobalLo.eq.1) at_west_bdry = .true.
45     IF (myYGlobalLo.eq.1) at_south_bdry = .true.
46     IF (myXGlobalLo-1+sNx*nSx.eq.Nx)
47     & at_east_bdry = .false.
48     IF (myYGlobalLo-1+sNy*nSy.eq.Ny)
49     & at_north_bdry = .false.
50    
51     DO bj = myByLo(myThid), myByHi(myThid)
52     DO bi = myBxLo(myThid), myBxHi(myThid)
53     DO j=1-OLy,sNy+OLy
54     DO i=1-OLx,sNx+OLx
55     taudx_SI(i,j,bi,bj) = 0. _d 0
56     taudy_SI(i,j,bi,bj) = 0. _d 0
57     ENDDO
58     ENDDO
59     ENDDO
60     ENDDO
61    
62     DO bj = myByLo(myThid), myByHi(myThid)
63     DO bi = myBxLo(myThid), myBxHi(myThid)
64    
65     DO i=0,sNx+1
66     DO j=0,sNy+1
67    
68     diffx = 0. _d 0
69     diffy = 0. _d 0
70     sx = 0. _d 0
71     sy = 0. _d 0
72    
73     Gi = (myXGlobalLo-1)+(bi-1)*sNx+i
74     Gj = (myYGlobalLo-1)+(bj-1)*sNy+j
75    
76     IF (STREAMICE_hmask(i,j,bi,bj).eq.1.0) THEN
77 dgoldberg 1.3
78     ! we are in an "active" cell
79    
80 dgoldberg 1.2 IF (Gi.eq.1.AND..NOT.STREAMICE_EW_periodic) THEN
81 dgoldberg 1.3
82     ! western boundary - only one sided possible
83    
84 heimbach 1.1 IF (STREAMICE_hmask(i+1,j,bi,bj).eq.1.0) THEN
85 dgoldberg 1.3
86     ! cell to east is active
87    
88 heimbach 1.1 sx = (surf_el_streamice(i+1,j,bi,bj)-
89     & surf_el_streamice(i,j,bi,bj))/dxC(i+1,j,bi,bj)
90     ELSE
91 dgoldberg 1.3
92     ! cell to east is empty
93    
94 heimbach 1.1 sx = 0. _d 0
95     ENDIF
96 dgoldberg 1.3
97 dgoldberg 1.2 ELSEIF (Gi.eq.Nx.AND..NOT.STREAMICE_EW_periodic) THEN
98 dgoldberg 1.3
99     ! eastern boundary - only one sided possible
100    
101 heimbach 1.1 IF (STREAMICE_hmask(i-1,j,bi,bj).eq.1.0) THEN
102 dgoldberg 1.3
103     ! cell to west is active
104    
105 heimbach 1.1 sx = (surf_el_streamice(i,j,bi,bj)-
106     & surf_el_streamice(i-1,j,bi,bj))/dxC(i,j,bi,bj)
107     ELSE
108 dgoldberg 1.3
109     ! cell to west is inactive
110    
111 heimbach 1.1 sx = 0. _d 0
112     ENDIF
113 dgoldberg 1.3
114 heimbach 1.1 ELSE
115 dgoldberg 1.3
116     ! interior (west-east) cell
117    
118 heimbach 1.1 IF (STREAMICE_hmask(i+1,j,bi,bj).eq.1.0) THEN
119 dgoldberg 1.3
120     ! cell to east is active
121    
122 heimbach 1.1 diffx = diffx + dxC(i+1,j,bi,bj)
123     sx = surf_el_streamice(i+1,j,bi,bj)
124     ELSE
125     sx = surf_el_streamice(i,j,bi,bj)
126     ENDIF
127     IF (STREAMICE_hmask(i-1,j,bi,bj).eq.1.0) THEN
128 dgoldberg 1.3
129     ! cell to west is active
130    
131 heimbach 1.1 diffx = diffx + dxC(i,j,bi,bj)
132     sx = sx - surf_el_streamice(i-1,j,bi,bj)
133     ELSE
134     sx = sx - surf_el_streamice(i,j,bi,bj)
135     ENDIF
136     IF (diffx .gt. 0. _d 0) THEN
137     sx = sx / diffx
138     ELSE
139     sx = 0. _d 0
140     ENDIF
141 dgoldberg 1.3
142 heimbach 1.1 ENDIF
143    
144    
145    
146 dgoldberg 1.2 IF (Gj.eq.1.AND..NOT.STREAMICE_NS_periodic) THEN
147 heimbach 1.1 IF (STREAMICE_hmask(i,j+1,bi,bj).eq.1.0) THEN
148     sy = (surf_el_streamice(i,j+1,bi,bj)-
149     & surf_el_streamice(i,j,bi,bj))/dyC(i,j+1,bi,bj)
150     ELSE
151     sy = 0. _d 0
152     ENDIF
153 dgoldberg 1.2 ELSEIF (Gj.eq.Ny.AND..NOT.STREAMICE_NS_periodic) THEN
154 heimbach 1.1 IF (STREAMICE_hmask(i,j-1,bi,bj).eq.1.0) THEN
155     sy = (surf_el_streamice(i,j,bi,bj)-
156     & surf_el_streamice(i,j-1,bi,bj))/dyC(i,j,bi,bj)
157     ELSE
158     sy = 0. _d 0
159     ENDIF
160     ELSE
161     IF (STREAMICE_hmask(i,j+1,bi,bj).eq.1.0) THEN
162    
163     diffy = diffy + dyC(i,j+1,bi,bj)
164     sy = surf_el_streamice(i,j+1,bi,bj)
165     ELSE
166     sy = surf_el_streamice(i,j,bi,bj)
167     ENDIF
168     IF (STREAMICE_hmask(i,j-1,bi,bj).eq.1.0) THEN
169     diffy = diffy + dyC(i,j,bi,bj)
170     sy = sy - surf_el_streamice(i,j-1,bi,bj)
171     ELSE
172     sy = sy - surf_el_streamice(i,j,bi,bj)
173     ENDIF
174     IF (diffy .gt. 0. _d 0) THEN
175     sy = sy / diffy
176     ELSE
177     sy = 0. _d 0
178     ENDIF
179     ENDIF
180    
181     DO k=0,1
182     DO l=0,1
183     IF (STREAMICE_umask(i+k,j+l,bi,bj).eq.1.0) THEN
184     taudx_SI(i+k,j+l,bi,bj) = taudx_SI(i+k,j+l,bi,bj) -
185 dgoldberg 1.2 & 0.25 * streamice_density * gravity *
186     & (streamice_bg_surf_slope_x+sx) *
187 heimbach 1.1 & H_streamice(i,j,bi,bj) * rA(i,j,bi,bj)
188 dgoldberg 1.2 ! & (streamice_bg_surf_slope_x) *
189     ! & 1000. * rA(i,j,bi,bj)
190 heimbach 1.1 taudy_SI(i+k,j+l,bi,bj) = taudy_SI(i+k,j+l,bi,bj) -
191 dgoldberg 1.2 & 0.25 * streamice_density * gravity *
192     & (streamice_bg_surf_slope_y+sy) *
193 heimbach 1.1 & H_streamice(i,j,bi,bj) * rA(i,j,bi,bj)
194    
195     ENDIF
196     ENDDO
197     ENDDO
198    
199     IF (float_frac_streamice(i,j,bi,bj) .eq. 1.0) then
200 dgoldberg 1.3 #ifdef USE_ALT_RLOW
201 heimbach 1.1 neu_val = .5 * gravity *
202     & (streamice_density * H_streamice (i,j,bi,bj) ** 2 -
203 dgoldberg 1.3 & streamice_density_ocean_avg * R_low_si(i,j,bi,bj) ** 2)
204     #else
205     neu_val = .5 * gravity *
206     & (streamice_density * H_streamice (i,j,bi,bj) ** 2 -
207 heimbach 1.4 & streamice_density_ocean_avg * R_low(i,j,bi,bj) ** 2)
208 dgoldberg 1.3 #endif
209 heimbach 1.1 ELSE
210     neu_val = .5 * gravity *
211     & (1-streamice_density/streamice_density_ocean_avg) *
212     & streamice_density * H_streamice(i,j,bi,bj) ** 2
213     ENDIF
214    
215     IF ((STREAMICE_ufacemask(i,j,bi,bj) .eq. 2)
216     & .OR. (STREAMICE_hmask(i-1,j,bi,bj) .eq. 0)
217     & .OR. (STREAMICE_hmask(i-1,j,bi,bj) .eq. 2) ) THEN ! left face of the cell is at a stress boundary
218     ! the depth-integrated longitudinal stress is equal to the difference of depth-integrated pressure on either side of the face
219     ! on the ice side, it is rho g h^2 / 2
220     ! on the ocean side, it is rhow g (delta OD)^2 / 2
221     ! OD can be zero under the ice; but it is ASSUMED on the ice-free side of the face, topography elevation is not above the base of the
222     ! ice in the current cell
223    
224     taudx_SI(i,j,bi,bj) = taudx_SI(i,j,bi,bj) -
225 dgoldberg 1.5 & .5 * dyG(i,j,bi,bj)*(neu_val+streamice_addl_backstress) ! note negative sign is due to direction of normal vector
226 heimbach 1.1 taudx_SI(i,j+1,bi,bj) = taudx_SI(i,j+1,bi,bj) -
227 dgoldberg 1.5 & .5 * dyG(i,j,bi,bj)*(neu_val+streamice_addl_backstress)
228 heimbach 1.1 ENDIF
229    
230     IF ((STREAMICE_ufacemask(i+1,j,bi,bj) .eq. 2)
231     & .OR. (STREAMICE_hmask(i+1,j,bi,bj) .eq. 0)
232     & .OR. (STREAMICE_hmask(i+1,j,bi,bj) .eq. 2) ) THEN
233    
234     taudx_SI(i+1,j,bi,bj) = taudx_SI(i+1,j,bi,bj) +
235 dgoldberg 1.5 & .5 * dyG(i+1,j,bi,bj)*(neu_val+streamice_addl_backstress) ! note negative sign is due to direction of normal vector
236 heimbach 1.1 taudx_SI(i+1,j+1,bi,bj) = taudx_SI(i+1,j+1,bi,bj) +
237 dgoldberg 1.5 & .5 * dyG(i+1,j,bi,bj)*(neu_val+streamice_addl_backstress)
238 heimbach 1.1 ENDIF
239    
240     IF ((STREAMICE_vfacemask(i,j,bi,bj) .eq. 2)
241     & .OR. (STREAMICE_hmask(i,j-1,bi,bj) .eq. 0)
242     & .OR. (STREAMICE_hmask(i,j-1,bi,bj) .eq. 2) ) THEN
243    
244     taudy_SI(i,j,bi,bj) = taudy_SI(i,j,bi,bj) -
245 dgoldberg 1.5 & .5 * dxG(i,j,bi,bj)*(neu_val+streamice_addl_backstress) ! note negative sign is due to direction of normal vector
246 heimbach 1.1 taudy_SI(i+1,j,bi,bj) = taudy_SI(i+1,j,bi,bj) -
247 dgoldberg 1.5 & .5 * dxG(i,j,bi,bj)*(neu_val+streamice_addl_backstress)
248 heimbach 1.1 ENDIF
249    
250     IF ((STREAMICE_vfacemask(i,j+1,bi,bj) .eq. 2)
251     & .OR. (STREAMICE_hmask(i,j+1,bi,bj) .eq. 0)
252     & .OR. (STREAMICE_hmask(i,j+1,bi,bj) .eq. 2) ) THEN
253    
254     taudy_SI(i,j+1,bi,bj) = taudy_SI(i,j+1,bi,bj) +
255 dgoldberg 1.5 & .5 * dxG(i,j+1,bi,bj)*(neu_val+streamice_addl_backstress) ! note negative sign is due to direction of normal vector
256 heimbach 1.1 taudy_SI(i+1,j+1,bi,bj) = taudy_SI(i+1,j+1,bi,bj) +
257 dgoldberg 1.5 & .5 * dxG(i,j+1,bi,bj)*(neu_val+streamice_addl_backstress)
258 heimbach 1.1 ENDIF
259    
260     ENDIF
261     ENDDO
262     ENDDO
263     ENDDO
264     ENDDO
265    
266    
267    
268     #endif
269     RETURN
270     END
271    
272    

  ViewVC Help
Powered by ViewVC 1.1.22