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

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

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

revision 1.1 by heimbach, Thu Mar 29 15:59:21 2012 UTC revision 1.8 by dgoldberg, Sat Jun 8 22:15:33 2013 UTC
# Line 7  C---+----1----+----2----+----3----+----4 Line 7  C---+----1----+----2----+----3----+----4
7    
8    
9  CBOP  CBOP
10        SUBROUTINE STREAMICE_ADVECT_THICKNESS ( myThid, time_step )        SUBROUTINE STREAMICE_ADVECT_THICKNESS ( myThid,myIter,time_step )
11    
12  C     /============================================================\  C     /============================================================\
13  C     | SUBROUTINE                                                 |    C     | SUBROUTINE                                                 |  
# Line 24  C     === Global variables === Line 24  C     === Global variables ===
24  #include "PARAMS.h"  #include "PARAMS.h"
25  #include "STREAMICE.h"  #include "STREAMICE.h"
26  #include "STREAMICE_ADV.h"  #include "STREAMICE_ADV.h"
27    #ifdef ALLOW_AUTODIFF_TAMC
28    # include "tamc.h"
29    #endif
30    
31        INTEGER myThid        INTEGER myThid, myIter
32        _RL time_step        _RL time_step
33    
34  #ifdef ALLOW_STREAMICE  #ifdef ALLOW_STREAMICE
35    
36        INTEGER i, j, bi, bj        INTEGER i, j, bi, bj
37        _RL thick_bd        _RL thick_bd, uflux, vflux
38        _RL SLOPE_LIMITER        _RL sec_per_year, time_step_loc, MR, SMB, TMB
39        _RL sec_per_year, time_step_loc        _RL BCVALX(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
40        external SLOPE_LIMITER        _RL BCVALY(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
41          _RS BCMASKX(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
42          _RS BCMASKY(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
43          _RL utrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
44          _RL vtrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
45          _RL h_after_uflux_SI(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
46          _RL h_after_vflux_SI(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
47          _RL hflux_x_SI(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
48          _RL hflux_y_SI(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
49          
50          CHARACTER*(MAX_LEN_MBUF) msgBuf
51    
52        sec_per_year = 365.*86400.        sec_per_year = 365.*86400.
53    
54        time_step_loc = time_step / sec_per_year        time_step_loc = time_step / sec_per_year
55    
56          PRINT *, "time_step_loc ", time_step_loc
57    
58    #ifdef ALLOW_AUTODIFF_TAMC
59    CADJ STORE streamice_hmask  = comlev1, key=ikey_dynamics
60    #endif
61    
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          DO j=1-OLy,sNy+OLy          DO j=1-3,sNy+3
65           DO i=1-OLx,sNx+OLx           DO i=1-3,sNx+3
66    
67              H_streamice_prev(i,j,bi,bj) =
68         &     H_streamice(i,j,bi,bj)
69    
70            hflux_x_SI (i,j,bi,bj) = 0. _d 0            hflux_x_SI (i,j,bi,bj) = 0. _d 0
71            hflux_y_SI (i,j,bi,bj) = 0. _d 0            hflux_y_SI (i,j,bi,bj) = 0. _d 0
72            hflux_x_SI2 (i,j,bi,bj) = 0. _d 0  
73            hflux_y_SI2 (i,j,bi,bj) = 0. _d 0  
74            IF (STREAMICE_hmask(i,j,bi,bj).eq.1.0) THEN            IF (STREAMICE_ufacemask(i,j,bi,bj).eq.3.0) THEN
75             h_after_uflux_SI (i,j,bi,bj) =             BCMASKX(i,j,bi,bj) = 3.0
76       &      H_streamice (i,j,bi,bj)             BCVALX(i,j,bi,bj) = h_ubdry_values_SI(i,j,bi,bj)
77               utrans(i,j,bi,bj) = .5 * (
78         &      u_streamice(i,j,bi,bj)+u_streamice(i,j+1,bi,bj))
79              ELSEIF (STREAMICE_ufacemask(i,j,bi,bj).eq.4.0) THEN
80               uflux = u_flux_bdry_SI(i,j,bi,bj)
81               BCMASKX(i,j,bi,bj) = 0.0
82               BCVALX(i,j,bi,bj) = uflux
83               utrans(i,j,bi,bj) = 1.0
84              ELSEIF (.not.(
85         &     STREAMICE_hmask(i,j,bi,bj).eq.1.0.OR.
86         &     STREAMICE_hmask(i-1,j,bi,bj).eq.1.0)) THEN
87               BCMASKX(i,j,bi,bj) = 0.0
88               BCVALX(i,j,bi,bj) = 0. _d 0
89               utrans(i,j,bi,bj) = 0. _d 0
90              ELSE
91               BCMASKX(i,j,bi,bj) = 0.0
92               BCVALX(i,j,bi,bj) = 0. _d 0
93               utrans(i,j,bi,bj) = .5 * (
94         &      u_streamice(i,j,bi,bj)+u_streamice(i,j+1,bi,bj))
95            ENDIF            ENDIF
96    
97            thick_bd = h_bdry_values_SI (i,j,bi,bj)            IF (STREAMICE_vfacemask(i,j,bi,bj).eq.3.0) THEN
98            IF (thick_bd .ne. 0. _d 0) THEN             BCMASKy(i,j,bi,bj) = 3.0
99              h_after_uflux_SI (i,j,bi,bj) = thick_bd             BCVALy(i,j,bi,bj) = h_vbdry_values_SI(i,j,bi,bj)
100               vtrans(i,j,bi,bj) = .5 * (
101         &      v_streamice(i,j,bi,bj)+v_streamice(i+1,j,bi,bj))
102              ELSEIF (STREAMICE_vfacemask(i,j,bi,bj).eq.4.0) THEN
103               vflux = v_flux_bdry_SI(i,j,bi,bj)
104               BCMASKy(i,j,bi,bj) = 0.0
105               BCVALy(i,j,bi,bj) = vflux
106               vtrans(i,j,bi,bj) = 1.0
107              ELSEIF (.not.(
108         &     STREAMICE_hmask(i,j,bi,bj).eq.1.0.OR.
109         &     STREAMICE_hmask(i,j-1,bi,bj).eq.1.0)) THEN
110               BCMASKY(i,j,bi,bj) = 0.0
111               BCVALY(i,j,bi,bj) = 0. _d 0
112               vtrans(i,j,bi,bj) = 0. _d 0
113              ELSE
114               BCMASKy(i,j,bi,bj) = 0.0
115               BCVALy(i,j,bi,bj) = 0. _d 0
116               vtrans(i,j,bi,bj) =  .5 * (
117         &      v_streamice(i,j,bi,bj)+v_streamice(i+1,j,bi,bj))
118            ENDIF            ENDIF
119    
120    
121           ENDDO           ENDDO
122          ENDDO          ENDDO
123         ENDDO         ENDDO
124        ENDDO        ENDDO
125    
126  !       PRINT *, "H in last row ", H_streamice(81,20,1,1)        _EXCH_XY_RL(utrans,myThid)
127          _EXCH_XY_RL(vtrans,myThid)
128          _EXCH_XY_RS(BCMASKx,myThid)
129          _EXCH_XY_RS(BCMASKy,myThid)
130          _EXCH_XY_RL(BCVALX,myThid)
131          _EXCH_XY_RL(BCVALY,myThid)
132    
133    #ifdef ALLOW_AUTODIFF_TAMC
134    CADJ STORE streamice_hmask  = comlev1, key=ikey_dynamics
135    CADJ STORE H_streamice  = comlev1, key=ikey_dynamics
136    #endif
137    
138    
139        CALL STREAMICE_ADVECT_THICKNESS_X ( myThid,        CALL STREAMICE_ADV_FLUX_FL_X ( myThid ,
140         I   utrans ,
141         I   H_streamice ,
142         I   BCMASKX,
143         I   BCVALX,
144       O   hflux_x_SI,       O   hflux_x_SI,
      O   h_after_uflux_SI,  
145       I   time_step_loc )       I   time_step_loc )
146    
 !       PRINT *, "H in last row ", H_streamice(81,20,1,1)  
   
       DO bj=myByLo(myThid),myByHi(myThid)  
        DO bi=myBxLo(myThid),myBxHi(myThid)  
         DO j=1-OLy,sNy+OLy  
          DO i=1-OLx,sNx+OLx  
           h_after_vflux_SI (i,j,bi,bj) =  
      &     h_after_uflux_SI (i,j,bi,bj)  
          ENDDO  
         ENDDO  
        ENDDO  
       ENDDO  
   
       CALL STREAMICE_ADVECT_THICKNESS_Y ( myThid,  
      O   hflux_y_SI,  
      O   h_after_vflux_SI,  
      I   time_step_loc )  
147    
 !       PRINT *, "H in last row ", H_streamice(81,20,1,1)  
148    
149        DO bj=myByLo(myThid),myByHi(myThid)        DO bj=myByLo(myThid),myByHi(myThid)
150         DO bi=myBxLo(myThid),myBxHi(myThid)         DO bi=myBxLo(myThid),myBxHi(myThid)
151          DO j=1-OLy,sNy+OLy          DO j=1-3,sNy+3
152           DO i=1-OLx,sNx+OLx           DO i=1-1,sNx+1
153            IF (STREAMICE_hmask(i,j,bi,bj).eq.1.0) THEN            IF (STREAMICE_hmask(i,j,bi,bj).eq.1.0) THEN
154             H_streamice (i,j,bi,bj) =             h_after_uflux_SI (i,j,bi,bj) = H_streamice(i,j,bi,bj) -
155       &      h_after_vflux_SI (i,j,bi,bj)       &      (hflux_x_SI(i+1,j,bi,bj)*dyG(i+1,j,bi,bj) -
156         &        hflux_x_SI(i,j,bi,bj)*dyG(i,j,bi,bj))
157         &        * recip_rA (i,j,bi,bj) * time_step_loc
158               IF ( h_after_uflux_SI (i,j,bi,bj).le.0.0) THEN
159                PRINT *, "h neg after x", i,j,hflux_x_SI(i+1,j,bi,bj),
160         &        hflux_x_SI(i,j,bi,bj)
161               ENDIF
162            ENDIF            ENDIF
163           ENDDO           ENDDO
164          ENDDO          ENDDO
165         ENDDO         ENDDO
166        ENDDO        ENDDO
167    
 !       PRINT *, "H in last row ", H_streamice(81,20,1,1)  
   
       CALL STREAMICE_ADV_FRONT ( myThid, time_step_loc )  
   
 !       PRINT *, "H in last row ", H_streamice(81,20,1,1)  
168    
       _EXCH_XY_RL( H_streamice, myThid )  
       _EXCH_XY_RL( area_shelf_streamice, myThid )  
       _EXCH_XY_RL( STREAMICE_hmask, myThid )  
         
       PRINT *, "END STREAMICE_ADVECT_THICKNESS"  
169    
170    #ifdef ALLOW_AUTODIFF_TAMC
171    CADJ STORE streamice_hmask  = comlev1, key=ikey_dynamics
172  #endif  #endif
       RETURN  
       END SUBROUTINE STREAMICE_ADVECT_THICKNESS  
   
 !     NEED TO ADD SOME SORT OF CHECK THAT THE HALOS ARE LARGE ENOUGH  
   
       SUBROUTINE STREAMICE_ADVECT_THICKNESS_X ( myThid ,      
      O   hflux_x ,  
      O   h ,  
      I   time_step )  
   
       IMPLICIT NONE  
   
 C     O   hflux_x ! flux per unit width across face  
 C     O   h  
 C     I   time_step  
   
 C     === Global variables ===  
 #include "SIZE.h"  
 #include "GRID.h"  
 #include "EEPARAMS.h"  
 #include "PARAMS.h"  
 #include "STREAMICE.h"  
   
       INTEGER myThid  
       _RL hflux_x          (1-Olx:sNx+Olx,1-Oly:sNy+Oly,nSx,nSy)  
       _RL h                (1-Olx:sNx+Olx,1-Oly:sNy+Oly,nSx,nSy)    
       _RL time_step  
         
 #ifdef ALLOW_STREAMICE  
   
 C     LOCAL VARIABLES  
173    
174        INTEGER i, j, bi, bj, Gi, Gj, k  !      CALL STREAMICE_ADVECT_THICKNESS_Y ( myThid,
175        _RL uface, phi  !     O   hflux_y_SI,
176        _RL stencil (-1:1)  !     O   h_after_vflux_SI,
177        LOGICAL H0_valid  ! there are valid cells to calculate a  !     I   time_step_loc )
178                          ! slope-limited 2nd order flux  
179        _RL SLOPE_LIMITER        CALL STREAMICE_ADV_FLUX_FL_Y ( myThid ,
180        _RL total_vol_out       I   vtrans ,
181        external SLOPE_LIMITER       I   h_after_uflux_si ,
182         I   BCMASKY,
183         I   BCVALY,
184         O   hflux_y_SI,
185         I   time_step_loc )
186    
        total_vol_out = 0.0  
187    
188        DO bj=myByLo(myThid),myByHi(myThid)        DO bj=myByLo(myThid),myByHi(myThid)
189         DO bi=myBxLo(myThid),myBxHi(myThid)         DO bi=myBxLo(myThid),myBxHi(myThid)
190          DO j=1-3,sNy+3          DO j=1-1,sNy+1
191           Gj = (myYGlobalLo-1)+(bj-1)*sNy+j           DO i=1-1,sNx+1
192           IF ((Gj .ge. 1) .and. (Gj .le. Ny)) THEN            IF (STREAMICE_hmask(i,j,bi,bj).eq.1.0) THEN
193            DO i=1-2,sNx+3             h_after_vflux_SI (i,j,bi,bj) = h_after_uflux_SI(i,j,bi,bj) -
194  C        THESE ARRAY BOUNDS INSURE THAT AFTER THIS STEP,       &      (hflux_y_SI(i,j+1,bi,bj)*dxG(i,j+1,bi,bj) -
195  C        VALUES WILL BE RELIABLE 2 GRID CELLS OUT IN THE       &        hflux_y_SI(i,j,bi,bj)*dxG(i,j,bi,bj)) *
196  C        X DIRECTION AND 3 CELLS OUT IN THE Y DIR       &        recip_rA (i,j,bi,bj) * time_step_loc
197             IF ((STREAMICE_hmask(i,j,bi,bj).eq.1.0) .or.             IF ( h_after_vflux_SI (i,j,bi,bj).le.0.0) THEN
198       &         ((STREAMICE_hmask(i-1,j,bi,bj).eq.1.0) .and.              PRINT *, "h neg after y", i,j,hflux_y_SI(i,j+1,bi,bj),
199       &          (STREAMICE_hmask(i,j,bi,bj).ne.1.0))) THEN       &        hflux_y_SI(i,j,bi,bj)
   
             Gi = (myXGlobalLo-1)+(bi-1)*sNx+i  
               
             IF (STREAMICE_ufacemask(i,j,bi,bj).eq.4.0) THEN  
              hflux_x (i,j,bi,bj) = u_flux_bdry_SI (i,j,bi,bj)  
             ELSE  
             
              uface = .5 *  
      &        (U_streamice(i,j,bi,bj)+U_streamice(i,j+1,bi,bj))  
   
   
              IF (uface .gt. 0. _d 0) THEN  
               DO k=-1,1  
                stencil (k) = h(i+k-1,j,bi,bj)  
               ENDDO  
               IF ((STREAMICE_hmask(i,j,bi,bj).eq.1.0) .and.  
      &            (STREAMICE_hmask(i-2,j,bi,bj).eq.1.0)) H0_valid=.true.  
               
               IF ((Gi.eq.1).and.(STREAMICE_hmask(i-1,j,bi,bj).eq.3.0))  
      &         THEN  ! we are at western bdry and there is a thick. bdry cond  
                hflux_x (i,j,bi,bj) = h(i-1,j,bi,bj) * uface  
               ELSEIF (H0_valid) THEN  
                phi = SLOPE_LIMITER (  
      &          stencil(0)-stencil(-1),  
      &          stencil(1)-stencil(0))  
                hflux_x (i,j,bi,bj) = uface *  
      &          (stencil(0) - phi * .5 * (stencil(0)-stencil(1)))  
               ELSE ! one of the two cells needed for a HO scheme is missing, use FO scheme  
                hflux_x (i,j,bi,bj) = uface * stencil(0)  
               ENDIF  
               
              ELSE ! uface <= 0  
   
               DO k=-1,1  
                stencil (k) = h(i-k,j,bi,bj)  
               ENDDO  
               IF ((STREAMICE_hmask(i-1,j,bi,bj).eq.1.0) .and.  
      &            (STREAMICE_hmask(i+1,j,bi,bj).eq.1.0)) H0_valid=.true.  
   
               IF ((Gi.eq.Nx).and.(STREAMICE_hmask(i+1,j,bi,bj).eq.3.0))  
      &         THEN  ! we are at western bdry and there is a thick. bdry cond  
                hflux_x (i,j,bi,bj) = h(i+1,j,bi,bj) * uface  
               ELSEIF (H0_valid) THEN  
                phi = SLOPE_LIMITER (  
      &          stencil(0)-stencil(-1),  
      &          stencil(1)-stencil(0))  
                hflux_x (i,j,bi,bj) = uface *  
      &          (stencil(0) - phi * .5 * (stencil(0)-stencil(1)))  
               ELSE ! one of the two cells needed for a HO scheme is missing, use FO scheme  
                hflux_x (i,j,bi,bj) = uface * stencil(0)  
               ENDIF  
   
              ENDIF  
   
             ENDIF  
   
             if (streamice_ufacemask(i,j,bi,bj).eq.2.0) THEN  
              total_vol_out = total_vol_out +  
      &         hflux_x (i,j,bi,bj) * time_step  
             ENDIF  
   
200             ENDIF             ENDIF
201            ENDDO  
202           ENDIF            ENDIF
203             ENDDO
204          ENDDO          ENDDO
205         ENDDO         ENDDO
206        ENDDO        ENDDO
207    
 C     X-FLUXES AT CELL BOUNDARIES CALCULATED; NOW TAKE FLUX DIVERGENCE TO INCREMENT THICKNESS  
         
208        DO bj=myByLo(myThid),myByHi(myThid)        DO bj=myByLo(myThid),myByHi(myThid)
209         DO bi=myBxLo(myThid),myBxHi(myThid)         DO bi=myBxLo(myThid),myBxHi(myThid)
210          DO j=1-3,sNy+3          DO j=1,sNy
211           Gj = (myYGlobalLo-1)+(bj-1)*sNy+j           DO i=1,sNx
212           IF ((Gj .ge. 1) .and. (Gj .le. Ny)) THEN            IF (STREAMICE_hmask(i,j,bi,bj).eq.1.0) THEN
213            DO i=1-2,sNx+2             H_streamice (i,j,bi,bj) =
214             IF (STREAMICE_hmask(i,j,bi,bj).eq.1.0) THEN       &      h_after_vflux_SI (i,j,bi,bj)
215              h(i,j,bi,bj) = h(i,j,bi,bj) - time_step *            ENDIF
216       &       (hflux_x(i+1,j,bi,bj)*dyG(i+1,j,bi,bj) -           ENDDO
      &        hflux_x(i,j,bi,bj)*dyG(i,j,bi,bj)) *  
      &       recip_rA (i,j,bi,bj)  
            ENDIF  
           ENDDO  
          ENDIF  
217          ENDDO          ENDDO
218         ENDDO         ENDDO
219        ENDDO        ENDDO
220    
221  !       PRINT *, "TOTAL VOLUME OUT: ", total_vol_out  !      CALL STREAMICE_ADV_FRONT (
222          !     &  myThid, time_step_loc,
223    !     &  hflux_x_SI, hflux_y_SI )
224    
225    
226    #ifdef ALLOW_STREAMICE_2DTRACER
227          CALL STREAMICE_ADVECT_2DTRACER(
228         &  myThid,
229         &  myIter,
230         &  time_step,
231         &  uTrans,
232         &  vTrans,
233         &  bcMaskx,
234         &  bcMasky )
235  #endif  #endif
       RETURN  
       END SUBROUTINE STREAMICE_ADVECT_THICKNESS_X  
   
       SUBROUTINE STREAMICE_ADVECT_THICKNESS_Y ( myThid ,      
      O   hflux_y ,  
      O   h ,  
      I   time_step )  
   
       IMPLICIT NONE  
   
 C     O   hflux_y ! flux per unit width across face  
 C     O   h  
 C     I   time_step  
   
 C     === Global variables ===  
 #include "SIZE.h"  
 #include "GRID.h"  
 #include "EEPARAMS.h"  
 #include "PARAMS.h"  
 #include "STREAMICE.h"  
   
       INTEGER myThid  
       _RL hflux_y          (1-Olx:sNx+Olx,1-Oly:sNy+Oly,nSx,nSy)  
       _RL h                (1-Olx:sNx+Olx,1-Oly:sNy+Oly,nSx,nSy)    
       _RL time_step  
         
 #ifdef ALLOW_STREAMICE  
236    
 C     LOCAL VARIABLES  
237    
238        INTEGER i, j, bi, bj, Gi, Gj, k  ! NOW WE APPLY MELT RATES !!
239        _RL vface, phi  ! THIS MAY BE MOVED TO A SEPARATE SUBROUTINE
       _RL stencil (-1:1)  
       LOGICAL H0_valid  ! there are valid cells to calculate a  
                         ! slope-limited 2nd order flux  
       _RL SLOPE_LIMITER  
       external SLOPE_LIMITER  
240    
241        DO bj=myByLo(myThid),myByHi(myThid)        DO bj=myByLo(myThid),myByHi(myThid)
242         DO bi=myBxLo(myThid),myBxHi(myThid)         DO bi=myBxLo(myThid),myBxHi(myThid)
243          DO j=1-1,sNy+2          DO j=1,sNy
244           Gj = (myYGlobalLo-1)+(bj-1)*sNy+j           DO i=1,sNx
245           DO i=1-2,sNx+2             IF (STREAMICE_hmask(i,j,bi,bj).eq.1.0 .or.
246            Gi = (myXGlobalLo-1)+(bi-1)*sNx+i       &       STREAMICE_hmask(i,j,bi,bj).eq.2.0) THEN
247            IF ((Gi.ge.1) .and. (Gi.le.Nx)) THEN               MR = (1.-float_frac_streamice(i,j,bi,bj)) *
248  C         THESE ARRAY BOUNDS INSURE THAT AFTER THIS STEP,       &             BDOT_STREAMICE(i,j,bi,bj)
249  C         VALUES WILL BE RELIABLE 1 GRID CELLS OUT IN THE               SMB = ADOT_STREAMICE(i,j,bi,bj)
250  C         Y DIRECTION               TMB = SMB - MR
251             IF ((STREAMICE_hmask(i,j,bi,bj).eq.1.0) .or.               IF ((TMB.lt.0.0) .and.
252       &         ((STREAMICE_hmask(i,j-1,bi,bj).eq.1.0) .and.       &         (MR * time_step_loc .gt.
253       &          (STREAMICE_hmask(i,j,bi,bj).ne.1.0))) THEN       &          H_streamice (i,j,bi,bj))) THEN
254                    H_streamice (i,j,bi,bj) = 0. _d 0
255              IF (STREAMICE_vfacemask(i,j,bi,bj).eq.4.0) THEN                  STREAMICE_hmask(i,j,bi,bj) = 0.
256               hflux_y (i,j,bi,bj) = v_flux_bdry_SI (i,j,bi,bj)               ELSE
257              ELSE                 H_streamice (i,j,bi,bj) =
258                   &          H_streamice (i,j,bi,bj) + TMB * time_step_loc
259               vface = .5 *               ENDIF
      &        (V_streamice(i,j,bi,bj)+V_streamice(i+1,j,bi,bj))  
   
              IF (vface .gt. 0. _d 0) THEN  
               DO k=-1,1  
                stencil (k) = h(i,j+k-1,bi,bj)  
               ENDDO  
               IF ((STREAMICE_hmask(i,j,bi,bj).eq.1.0) .and.  
      &            (STREAMICE_hmask(i,j-2,bi,bj).eq.1.0)) H0_valid=.true.  
               
               IF ((Gj.eq.1).and.(STREAMICE_hmask(i,j-1,bi,bj).eq.3.0))  
      &         THEN  ! we are at western bdry and there is a thick. bdry cond  
                hflux_y (i,j,bi,bj) = h(i,j-1,bi,bj) * vface  
               ELSEIF (H0_valid) THEN  
                phi = SLOPE_LIMITER (  
      &          stencil(0)-stencil(-1),  
      &          stencil(1)-stencil(0))  
                hflux_y (i,j,bi,bj) = vface *  
      &          (stencil(0) - phi * .5 * (stencil(0)-stencil(1)))  
               ELSE ! one of the two cells needed for a HO scheme is missing, use FO scheme  
                hflux_y (i,j,bi,bj) = vface * stencil(0)  
               ENDIF  
              ELSE ! uface <= 0  
               DO k=-1,1  
                stencil (k) = h(i,j-k,bi,bj)  
               ENDDO  
               IF ((STREAMICE_hmask(i,j-1,bi,bj).eq.1.0) .and.  
      &            (STREAMICE_hmask(i,j+1,bi,bj).eq.1.0)) H0_valid=.true.  
   
               IF ((Gj.eq.Ny).and.(STREAMICE_hmask(i,j+1,bi,bj).eq.3.0))  
      &         THEN  ! we are at western bdry and there is a thick. bdry cond  
                hflux_y (i,j,bi,bj) = h(i,j+1,bi,bj) * vface  
               ELSEIF (H0_valid) THEN  
                phi = SLOPE_LIMITER (  
      &          stencil(0)-stencil(-1),  
      &          stencil(1)-stencil(0))  
                hflux_y (i,j,bi,bj) = vface *  
      &          (stencil(0) - phi * .5 * (stencil(0)-stencil(1)))  
               ELSE ! one of the two cells needed for a HO scheme is missing, use FO scheme  
                hflux_y (i,j,bi,bj) = vface * stencil(0)  
               ENDIF  
   
              ENDIF ! uface  0  
   
             ENDIF  
260             ENDIF             ENDIF
           ENDIF  
261           ENDDO           ENDDO
262          ENDDO          ENDDO
263         ENDDO         ENDDO
264        ENDDO        ENDDO    
   
 C     X-FLUXES AT CELL BOUNDARIES CALCULATED; NOW TAKE FLUX DIVERGENCE TO INCREMENT THICKNESS  
265    
266          _EXCH_XY_RL (H_streamice,myThid)
267                
268          WRITE(msgBuf,'(A)') 'END STREAMICE_ADVECT_THICKNESS'
269           CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
270         &                     SQUEEZE_RIGHT , 1)
271                
       DO bj=myByLo(myThid),myByHi(myThid)  
        DO bi=myBxLo(myThid),myBxHi(myThid)  
         DO j=1-1,sNy+1  
          DO i=1-2,sNx+2  
           Gi = (myXGlobalLo-1)+(bi-1)*sNx+i  
           IF ((Gi .ge. 1) .and. (Gi .le. Nx)) THEN  
            IF (STREAMICE_hmask(i,j,bi,bj).eq.1.0) THEN  
             h(i,j,bi,bj) = h(i,j,bi,bj) - time_step *  
      &       (hflux_y(i,j+1,bi,bj)*dxG(i,j+1,bi,bj) -  
      &        hflux_y(i,j,bi,bj)*dxG(i,j,bi,bj)) *  
      &       recip_rA (i,j,bi,bj)  
            ENDIF  
           ENDIF  
          ENDDO  
         ENDDO  
        ENDDO  
       ENDDO  
   
 !       CALL WRITE_FLD_XY_RL ("h_after_yflux","",  
 !      & h, 0, myThid)  
   
272  #endif  #endif
273        RETURN        END
       END SUBROUTINE STREAMICE_ADVECT_THICKNESS_Y  
274    

Legend:
Removed from v.1.1  
changed lines
  Added in v.1.8

  ViewVC Help
Powered by ViewVC 1.1.22