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

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

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

revision 1.4 by heimbach, Fri Sep 28 02:55:40 2012 UTC revision 1.6 by dgoldberg, Wed Aug 27 19:29:13 2014 UTC
# Line 39  C     LOCAL VARIABLES Line 39  C     LOCAL VARIABLES
39       &        Gi, Gj       &        Gi, Gj
40        LOGICAL at_west_bdry, at_east_bdry,        LOGICAL at_west_bdry, at_east_bdry,
41       &        at_north_bdry, at_south_bdry       &        at_north_bdry, at_south_bdry
42        _RL sx, sy, diffx, diffy, neu_val        _RL sx, sy, diffx, diffy, geom_fac
43                
44        IF (myXGlobalLo.eq.1) at_west_bdry = .true.        IF (myXGlobalLo.eq.1) at_west_bdry = .true.
45        IF (myYGlobalLo.eq.1) at_south_bdry = .true.        IF (myYGlobalLo.eq.1) at_south_bdry = .true.
# Line 50  C     LOCAL VARIABLES Line 50  C     LOCAL VARIABLES
50    
51        DO bj = myByLo(myThid), myByHi(myThid)        DO bj = myByLo(myThid), myByHi(myThid)
52         DO bi = myBxLo(myThid), myBxHi(myThid)         DO bi = myBxLo(myThid), myBxHi(myThid)
53          DO j=1-OLy,sNy+OLy          DO j=1-OLy+1,sNy+OLy-1
54           DO i=1-OLx,sNx+OLx           DO i=1-OLx+1,sNx+OLx-1
55            taudx_SI(i,j,bi,bj) = 0. _d 0            taudx_SI(i,j,bi,bj) = 0. _d 0
56            taudy_SI(i,j,bi,bj) = 0. _d 0            taudy_SI(i,j,bi,bj) = 0. _d 0
57           ENDDO           ENDDO
# Line 62  C     LOCAL VARIABLES Line 62  C     LOCAL VARIABLES
62        DO bj = myByLo(myThid), myByHi(myThid)        DO bj = myByLo(myThid), myByHi(myThid)
63         DO bi = myBxLo(myThid), myBxHi(myThid)         DO bi = myBxLo(myThid), myBxHi(myThid)
64                    
65          DO i=0,sNx+1          DO i=1,sNx
66           DO j=0,sNy+1           DO j=1,sNy
67    
68            diffx = 0. _d 0            diffx = 0. _d 0
69            diffy = 0. _d 0            diffy = 0. _d 0
# Line 73  C     LOCAL VARIABLES Line 73  C     LOCAL VARIABLES
73            Gi = (myXGlobalLo-1)+(bi-1)*sNx+i            Gi = (myXGlobalLo-1)+(bi-1)*sNx+i
74            Gj = (myYGlobalLo-1)+(bj-1)*sNy+j            Gj = (myYGlobalLo-1)+(bj-1)*sNy+j
75    
76            IF (STREAMICE_hmask(i,j,bi,bj).eq.1.0) THEN            IF (streamice_umask(i,j,bi,bj).eq.1.0) THEN
77    
78             ! we are in an "active" cell             IF (streamice_hmask(i-1,j,bi,bj).eq.1.0.AND.
79         &      streamice_hmask(i,j,bi,bj).eq.1.0) THEN
80            
81    !             geom_fac = sqrt(rA(i-1,j,bi,bj)*recip_rA(i,j,bi,bj)*
82    !      &        dxF(i,j,bi,bj)*recip_dxF(i-1,j,bi,bj))
83    
84                taudx_si(i,j,bi,bj) = taudx_si(i,j,bi,bj) -
85         &       0.25 * dyG(i,j,bi,bj) *
86         &       streamice_density * gravity *
87         &       (H_streamice(i,j,bi,bj)+
88         &        H_streamice(i-1,j,bi,bj)) *
89         &       (surf_el_streamice(i,j,bi,bj)-
90         &              surf_el_streamice(i-1,j,bi,bj))
91    
92                taudx_si(i,j,bi,bj) = taudx_si(i,j,bi,bj) -
93         &       streamice_density * gravity *
94         &       streamice_bg_surf_slope_x * .25 * rA(i,j,bi,bj) *
95         &       (H_streamice(i-1,j,bi,bj) + H_streamice(i,j,bi,bj))
96    
97               ELSE IF (streamice_hmask(i-1,j,bi,bj).eq.1.0) THEN
98    
99                IF (float_frac_streamice(i-1,j,bi,bj) .eq. 1.0) THEN
100    
101                 taudx_si(i,j,bi,bj) = taudx_si(i,j,bi,bj) +
102         &        0.25 * dyG(i,j,bi,bj) *
103         &        gravity *
104         &        (streamice_density * H_streamice(i-1,j,bi,bj)**2 -
105    #ifdef USE_ALT_RLOW
106         &         streamice_density_ocean_avg * R_low_si(i-1,j,bi,bj)**2)
107    #else          
108         &         streamice_density_ocean_avg * R_low(i-1,j,bi,bj)**2)
109    #endif
110    
111                ELSE
112    
113             IF (Gi.eq.1.AND..NOT.STREAMICE_EW_periodic) THEN               taudx_si(i,j,bi,bj) = taudx_si(i,j,bi,bj) +
114         &        0.25 * dyG(i,j,bi,bj) *
115         &        streamice_density * gravity *
116         &        (1-streamice_density/streamice_density_ocean_avg) *
117         &         H_streamice(i-1,j,bi,bj)**2
118    
119              ! western boundary - only one sided possible              ENDIF
120    
121              IF (STREAMICE_hmask(i+1,j,bi,bj).eq.1.0) THEN             ELSE IF (streamice_hmask(i,j,bi,bj).eq.1.0) THEN
122    
123               ! cell to east is active              IF (float_frac_streamice(i,j,bi,bj) .eq. 1.0) THEN
124    
125                 taudx_si(i,j,bi,bj) = taudx_si(i,j,bi,bj) -
126         &        0.25 * dyG(i,j,bi,bj) *
127         &        gravity *
128         &        (streamice_density * H_streamice(i,j,bi,bj)**2 -
129    #ifdef USE_ALT_RLOW
130         &         streamice_density_ocean_avg * R_low_si(i,j,bi,bj)**2)
131    #else          
132         &         streamice_density_ocean_avg * R_low(i,j,bi,bj)**2)
133    #endif
134    
              sx = (surf_el_streamice(i+1,j,bi,bj)-  
      &             surf_el_streamice(i,j,bi,bj))/dxC(i+1,j,bi,bj)  
135              ELSE              ELSE
136    
137               ! cell to east is empty               taudx_si(i,j,bi,bj) = taudx_si(i,j,bi,bj) -
138         &        0.25 * dyG(i,j,bi,bj) *
139         &        streamice_density * gravity *
140         &        (1-streamice_density/streamice_density_ocean_avg) *
141         &         H_streamice(i,j,bi,bj)**2
142    
143                END IF
144               END IF
145    
146    ! cells below
147    
148               IF (streamice_hmask(i-1,j-1,bi,bj).eq.1.0.AND.
149         &      streamice_hmask(i,j-1,bi,bj).eq.1.0) THEN
150            
151    !             geom_fac = sqrt(rA(i-1,j-1,bi,bj)*recip_rA(i,j-1,bi,bj)*
152    !      &             dxF(i,j-1,bi,bj)*recip_dxF(i-1,j-1,bi,bj))
153    
154                taudx_si(i,j,bi,bj) = taudx_si(i,j,bi,bj) -
155         &       0.25 * dyg(i,j-1,bi,bj) *
156         &       streamice_density * gravity *
157         &       (H_streamice(i,j-1,bi,bj)+
158         &        H_streamice(i-1,j-1,bi,bj)) *
159         &       (surf_el_streamice(i,j-1,bi,bj)-
160         &              surf_el_streamice(i-1,j-1,bi,bj))
161    
162                taudx_si(i,j,bi,bj) = taudx_si(i,j,bi,bj) -
163         &       streamice_density * gravity *
164         &       streamice_bg_surf_slope_x * .25 * rA(i,j-1,bi,bj) *
165         &       (H_streamice(i-1,j-1,bi,bj) + H_streamice(i,j-1,bi,bj))
166    
167               ELSE IF (streamice_hmask(i-1,j-1,bi,bj).eq.1.0) THEN
168    
169                IF (float_frac_streamice(i-1,j-1,bi,bj) .eq. 1.0) THEN
170    
171                 taudx_si(i,j,bi,bj) = taudx_si(i,j,bi,bj) +
172         &        0.25 * dyg(i,j-1,bi,bj) *
173         &        gravity *
174         &        (streamice_density * H_streamice(i-1,j-1,bi,bj)**2 -
175    #ifdef USE_ALT_RLOW
176         &         streamice_density_ocean_avg*R_low_si(i-1,j-1,bi,bj)**2)
177    #else          
178         &         streamice_density_ocean_avg * R_low(i-1,j-1,bi,bj)**2)
179    #endif
180    
181                ELSE
182    
183                 taudx_si(i,j,bi,bj) = taudx_si(i,j,bi,bj) +
184         &        0.25 * dyg(i,j-1,bi,bj) *
185         &        streamice_density * gravity *
186         &        (1-streamice_density/streamice_density_ocean_avg) *
187         &         H_streamice(i-1,j-1,bi,bj)**2
188    
              sx = 0. _d 0  
189              ENDIF              ENDIF
190    
191             ELSEIF (Gi.eq.Nx.AND..NOT.STREAMICE_EW_periodic) THEN             ELSE IF (streamice_hmask(i,j-1,bi,bj).eq.1.0) THEN
192    
193                IF (float_frac_streamice(i,j-1,bi,bj) .eq. 1.0) THEN
194    
195              ! eastern boundary - only one sided possible               taudx_si(i,j,bi,bj) = taudx_si(i,j,bi,bj) -
196         &        0.25 * dyg(i,j-1,bi,bj) *
197         &        gravity *
198         &        (streamice_density * H_streamice(i,j-1,bi,bj)**2 -
199    #ifdef USE_ALT_RLOW
200         &         streamice_density_ocean_avg * R_low_si(i,j-1,bi,bj)**2)
201    #else          
202         &         streamice_density_ocean_avg * R_low(i,j-1,bi,bj)**2)
203    #endif
204    
205              IF (STREAMICE_hmask(i-1,j,bi,bj).eq.1.0) THEN              ELSE
206    
207               ! cell to west is active               taudx_si(i,j,bi,bj) = taudx_si(i,j,bi,bj) -
208         &        0.25 * dyg(i,j-1,bi,bj) *
209         &        streamice_density * gravity *
210         &        (1-streamice_density/streamice_density_ocean_avg) *
211         &         H_streamice(i,j-1,bi,bj)**2
212    
213                END IF
214               END IF
215              END IF       ! if umask==1
216    
217    !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
218    
219              IF (streamice_vmask(i,j,bi,bj).eq.1.0) THEN
220    
221               IF (streamice_hmask(i,j-1,bi,bj).eq.1.0.AND.
222         &      streamice_hmask(i,j,bi,bj).eq.1.0) THEN
223            
224    !             geom_fac = sqrt(rA(i,j-1,bi,bj)*recip_rA(i,j,bi,bj)*
225    !      &        dxF(i,j,bi,bj)*recip_dyF(i,j-1,bi,bj))
226    
227                taudy_si(i,j,bi,bj) = taudy_si(i,j,bi,bj) -
228         &       0.25 * dxG(i,j,bi,bj) *
229         &       streamice_density * gravity *
230         &       (H_streamice(i,j,bi,bj)+
231         &        H_streamice(i,j-1,bi,bj)) *
232         &       (surf_el_streamice(i,j,bi,bj)-
233         &              surf_el_streamice(i,j-1,bi,bj))
234    
235                taudy_si(i,j,bi,bj) = taudy_si(i,j,bi,bj) -
236         &       streamice_density * gravity *
237         &       streamice_bg_surf_slope_y * .25 * rA(i,j,bi,bj) *
238         &       (H_streamice(i,j-1,bi,bj) + H_streamice(i,j,bi,bj))
239    
240               ELSE IF (streamice_hmask(i,j-1,bi,bj).eq.1.0) THEN
241    
242                IF (float_frac_streamice(i,j-1,bi,bj) .eq. 1.0) THEN
243    
244                 taudy_si(i,j,bi,bj) = taudy_si(i,j,bi,bj) +
245         &        0.25 * dxG(i,j,bi,bj) *
246         &        gravity *
247         &        (streamice_density * H_streamice(i,j-1,bi,bj)**2 -
248    #ifdef USE_ALT_RLOW
249         &         streamice_density_ocean_avg * R_low_si(i,j-1,bi,bj)**2)
250    #else          
251         &         streamice_density_ocean_avg * R_low(i,j-1,bi,bj)**2)
252    #endif
253    
              sx = (surf_el_streamice(i,j,bi,bj)-  
      &             surf_el_streamice(i-1,j,bi,bj))/dxC(i,j,bi,bj)  
254              ELSE              ELSE
255    
256               ! cell to west is inactive               taudy_si(i,j,bi,bj) = taudy_si(i,j,bi,bj) +
257         &        0.25 * dxG(i,j,bi,bj) *
258         &        streamice_density * gravity *
259         &        (1-streamice_density/streamice_density_ocean_avg) *
260         &         H_streamice(i,j-1,bi,bj)**2
261    
              sx = 0. _d 0  
262              ENDIF              ENDIF
263    
264             ELSE             ELSE IF (streamice_hmask(i,j,bi,bj).eq.1.0) THEN
265    
266              ! interior (west-east) cell              IF (float_frac_streamice(i,j,bi,bj) .eq. 1.0) THEN
267    
268              IF (STREAMICE_hmask(i+1,j,bi,bj).eq.1.0) THEN               taudy_si(i,j,bi,bj) = taudy_si(i,j,bi,bj) -
269         &        0.25 * dxG(i,j,bi,bj) *
270               ! cell to east is active       &        gravity *
271         &        (streamice_density * H_streamice(i,j,bi,bj)**2 -
272    #ifdef USE_ALT_RLOW
273         &         streamice_density_ocean_avg * R_low_si(i,j,bi,bj)**2)
274    #else          
275         &         streamice_density_ocean_avg * R_low(i,j,bi,bj)**2)
276    #endif
277    
              diffx = diffx + dxC(i+1,j,bi,bj)  
              sx = surf_el_streamice(i+1,j,bi,bj)  
278              ELSE              ELSE
              sx = surf_el_streamice(i,j,bi,bj)  
             ENDIF  
             IF (STREAMICE_hmask(i-1,j,bi,bj).eq.1.0) THEN  
279    
280               ! cell to west is active               taudy_si(i,j,bi,bj) = taudy_si(i,j,bi,bj) -
281         &        0.25 * dxG(i,j,bi,bj) *
282         &        streamice_density * gravity *
283         &        (1-streamice_density/streamice_density_ocean_avg) *
284         &         H_streamice(i,j,bi,bj)**2
285    
286                END IF
287               END IF
288    
289    ! cells to left
290    
291               IF (streamice_hmask(i-1,j-1,bi,bj).eq.1.0.AND.
292         &      streamice_hmask(i-1,j,bi,bj).eq.1.0) THEN
293            
294    !             geom_fac = sqrt(rA(i-1,j-1,bi,bj)*recip_rA(i-1,j,bi,bj)*
295    !      &        dxF(i-1,j,bi,bj)*recip_dxF(i-1,j-1,bi,bj))
296    
297                taudy_si(i,j,bi,bj) = taudy_si(i,j,bi,bj) -
298         &       0.25 * dxG(i-1,j,bi,bj) *
299         &       streamice_density * gravity *
300         &       (H_streamice(i-1,j,bi,bj)+
301         &        H_streamice(i-1,j-1,bi,bj)) *
302         &       (surf_el_streamice(i-1,j,bi,bj)-
303         &              surf_el_streamice(i-1,j-1,bi,bj))
304    
305                taudy_si(i,j,bi,bj) = taudy_si(i,j,bi,bj) -
306         &       streamice_density * gravity *
307         &       streamice_bg_surf_slope_y * .25 * rA(i-1,j,bi,bj) *
308         &       (H_streamice(i-1,j-1,bi,bj) + H_streamice(i-1,j,bi,bj))
309    
310    
311               ELSE IF (streamice_hmask(i-1,j-1,bi,bj).eq.1.0) THEN
312    
313                IF (float_frac_streamice(i-1,j-1,bi,bj) .eq. 1.0) THEN
314    
315                 taudy_si(i,j,bi,bj) = taudy_si(i,j,bi,bj) +
316         &        0.25 * dxG(i-1,j,bi,bj) *
317         &        gravity *
318         &        (streamice_density * H_streamice(i-1,j-1,bi,bj)**2 -
319    #ifdef USE_ALT_RLOW
320         &         streamice_density_ocean_avg*R_low_si(i-1,j-1,bi,bj)**2)
321    #else          
322         &         streamice_density_ocean_avg * R_low(i-1,j-1,bi,bj)**2)
323    #endif
324    
              diffx = diffx + dxC(i,j,bi,bj)  
              sx = sx - surf_el_streamice(i-1,j,bi,bj)  
             ELSE  
              sx = sx - surf_el_streamice(i,j,bi,bj)  
             ENDIF  
             IF (diffx .gt. 0. _d 0) THEN  
              sx = sx / diffx  
325              ELSE              ELSE
326               sx = 0. _d 0  
327                 taudy_si(i,j,bi,bj) = taudy_si(i,j,bi,bj) +
328         &        0.25 * dxG(i-1,j,bi,bj) *
329         &        streamice_density * gravity *
330         &        (1-streamice_density/streamice_density_ocean_avg) *
331         &         H_streamice(i-1,j-1,bi,bj)**2
332    
333              ENDIF              ENDIF
334    
335             ENDIF             ELSE IF (streamice_hmask(i-1,j,bi,bj).eq.1.0) THEN
336    
337                          IF (float_frac_streamice(i-1,j,bi,bj) .eq. 1.0) THEN
338    
339                 taudy_si(i,j,bi,bj) = taudy_si(i,j,bi,bj) -
340         &        0.25 * dxG(i-1,j,bi,bj) *
341         &        gravity *
342         &        (streamice_density * H_streamice(i-1,j,bi,bj)**2 -
343    #ifdef USE_ALT_RLOW
344         &         streamice_density_ocean_avg * R_low_si(i-1,j,bi,bj)**2)
345    #else          
346         &         streamice_density_ocean_avg * R_low(i-1,j,bi,bj)**2)
347    #endif
348    
            IF (Gj.eq.1.AND..NOT.STREAMICE_NS_periodic) THEN  
             IF (STREAMICE_hmask(i,j+1,bi,bj).eq.1.0) THEN  
              sy = (surf_el_streamice(i,j+1,bi,bj)-  
      &             surf_el_streamice(i,j,bi,bj))/dyC(i,j+1,bi,bj)  
             ELSE  
              sy = 0. _d 0  
             ENDIF  
            ELSEIF (Gj.eq.Ny.AND..NOT.STREAMICE_NS_periodic) THEN  
             IF (STREAMICE_hmask(i,j-1,bi,bj).eq.1.0) THEN  
              sy = (surf_el_streamice(i,j,bi,bj)-  
      &             surf_el_streamice(i,j-1,bi,bj))/dyC(i,j,bi,bj)  
             ELSE  
              sy = 0. _d 0  
             ENDIF  
            ELSE  
             IF (STREAMICE_hmask(i,j+1,bi,bj).eq.1.0) THEN  
               
              diffy = diffy + dyC(i,j+1,bi,bj)  
              sy = surf_el_streamice(i,j+1,bi,bj)  
             ELSE  
              sy = surf_el_streamice(i,j,bi,bj)  
             ENDIF  
             IF (STREAMICE_hmask(i,j-1,bi,bj).eq.1.0) THEN  
              diffy = diffy + dyC(i,j,bi,bj)  
              sy = sy - surf_el_streamice(i,j-1,bi,bj)  
             ELSE  
              sy = sy - surf_el_streamice(i,j,bi,bj)  
             ENDIF  
             IF (diffy .gt. 0. _d 0) THEN  
              sy = sy / diffy  
349              ELSE              ELSE
              sy = 0. _d 0  
             ENDIF  
            ENDIF  
350    
351             DO k=0,1               taudy_si(i,j,bi,bj) = taudy_si(i,j,bi,bj) -
352              DO l=0,1       &        0.25 * dxG(i-1,j,bi,bj) *
353               IF (STREAMICE_umask(i+k,j+l,bi,bj).eq.1.0) THEN       &        streamice_density * gravity *
354                taudx_SI(i+k,j+l,bi,bj) = taudx_SI(i+k,j+l,bi,bj) -       &        (1-streamice_density/streamice_density_ocean_avg) *
355       &         0.25 * streamice_density * gravity *       &         H_streamice(i-1,j,bi,bj)**2
356       &         (streamice_bg_surf_slope_x+sx) *  
357       &         H_streamice(i,j,bi,bj) * rA(i,j,bi,bj)              END IF
358  !     &          (streamice_bg_surf_slope_x) *             END IF
359  !     &         1000. * rA(i,j,bi,bj)            END IF      ! if vmask ==1
               taudy_SI(i+k,j+l,bi,bj) = taudy_SI(i+k,j+l,bi,bj) -  
      &         0.25 * streamice_density * gravity *  
      &         (streamice_bg_surf_slope_y+sy) *  
      &         H_streamice(i,j,bi,bj) * rA(i,j,bi,bj)  
                 
              ENDIF  
             ENDDO  
            ENDDO  
   
            IF (float_frac_streamice(i,j,bi,bj) .eq. 1.0) then  
 #ifdef USE_ALT_RLOW  
             neu_val = .5 * gravity *  
      &       (streamice_density * H_streamice (i,j,bi,bj) ** 2 -  
      &        streamice_density_ocean_avg * R_low_si(i,j,bi,bj) ** 2)  
 #else  
             neu_val = .5 * gravity *  
      &       (streamice_density * H_streamice (i,j,bi,bj) ** 2 -  
      &        streamice_density_ocean_avg * R_low(i,j,bi,bj) ** 2)  
 #endif  
            ELSE  
             neu_val = .5 * gravity *  
      &       (1-streamice_density/streamice_density_ocean_avg) *  
      &        streamice_density * H_streamice(i,j,bi,bj) ** 2  
            ENDIF  
   
            IF ((STREAMICE_ufacemask(i,j,bi,bj) .eq. 2)  
      &      .OR. (STREAMICE_hmask(i-1,j,bi,bj) .eq. 0)  
      &      .OR. (STREAMICE_hmask(i-1,j,bi,bj) .eq. 2) ) THEN ! left face of the cell is at a stress boundary  
           ! the depth-integrated longitudinal stress is equal to the difference of depth-integrated pressure on either side of the face  
           ! on the ice side, it is rho g h^2 / 2  
           ! on the ocean side, it is rhow g (delta OD)^2 / 2  
           ! 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  
           !     ice in the current cell  
               
              taudx_SI(i,j,bi,bj) = taudx_SI(i,j,bi,bj) -  
      &        .5 * dyG(i,j,bi,bj) * neu_val  ! note negative sign is due to direction of normal vector  
              taudx_SI(i,j+1,bi,bj) = taudx_SI(i,j+1,bi,bj) -  
      &        .5 * dyG(i,j,bi,bj) * neu_val  
            ENDIF  
   
            IF ((STREAMICE_ufacemask(i+1,j,bi,bj) .eq. 2)  
      &      .OR. (STREAMICE_hmask(i+1,j,bi,bj) .eq. 0)  
      &      .OR. (STREAMICE_hmask(i+1,j,bi,bj) .eq. 2) ) THEN  
               
              taudx_SI(i+1,j,bi,bj) = taudx_SI(i+1,j,bi,bj) +  
      &        .5 * dyG(i+1,j,bi,bj) * neu_val  ! note negative sign is due to direction of normal vector  
              taudx_SI(i+1,j+1,bi,bj) = taudx_SI(i+1,j+1,bi,bj) +  
      &        .5 * dyG(i+1,j,bi,bj) * neu_val  
            ENDIF  
   
            IF ((STREAMICE_vfacemask(i,j,bi,bj) .eq. 2)  
      &      .OR. (STREAMICE_hmask(i,j-1,bi,bj) .eq. 0)  
      &      .OR. (STREAMICE_hmask(i,j-1,bi,bj) .eq. 2) ) THEN  
               
              taudy_SI(i,j,bi,bj) = taudy_SI(i,j,bi,bj) -  
      &        .5 * dxG(i,j,bi,bj) * neu_val  ! note negative sign is due to direction of normal vector  
              taudy_SI(i+1,j,bi,bj) = taudy_SI(i+1,j,bi,bj) -  
      &        .5 * dxG(i,j,bi,bj) * neu_val  
            ENDIF  
   
            IF ((STREAMICE_vfacemask(i,j+1,bi,bj) .eq. 2)  
      &      .OR. (STREAMICE_hmask(i,j+1,bi,bj) .eq. 0)  
      &      .OR. (STREAMICE_hmask(i,j+1,bi,bj) .eq. 2) ) THEN  
               
              taudy_SI(i,j+1,bi,bj) = taudy_SI(i,j+1,bi,bj) +  
      &        .5 * dxG(i,j+1,bi,bj) * neu_val  ! note negative sign is due to direction of normal vector  
              taudy_SI(i+1,j+1,bi,bj) = taudy_SI(i+1,j+1,bi,bj) +  
      &        .5 * dxG(i,j+1,bi,bj) * neu_val  
            ENDIF  
360    
           ENDIF  
361           ENDDO           ENDDO
362          ENDDO          ENDDO
363         ENDDO         ENDDO
364        ENDDO        ENDDO
365    
366    !      taudx_SI (1,1,1,1) = taudx_SI (1,1,1,1) +
367    !     & streamice_v_normal_pert (1,1,1,1)
368    
369    
370    
371  #endif  #endif

Legend:
Removed from v.1.4  
changed lines
  Added in v.1.6

  ViewVC Help
Powered by ViewVC 1.1.22