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

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

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

revision 1.2 by heimbach, Thu May 3 15:39:22 2012 UTC revision 1.9 by dgoldberg, Wed Aug 27 19:29:13 2014 UTC
# Line 6  C $Name$ Line 6  C $Name$
6  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
7    
8  CBOP  CBOP
9        SUBROUTINE STREAMICE_ADV_FRONT ( myThid, time_step )        SUBROUTINE STREAMICE_ADV_FRONT (
10         & myThid,
11         & time_step,
12         & hflux_x_si,
13         & hflux_y_si )
14    
15  C     /============================================================\  C     /============================================================\
16  C     | SUBROUTINE                                                 |    C     | SUBROUTINE                                                 |  
# Line 29  C     === Global variables === Line 33  C     === Global variables ===
33    
34        INTEGER myThid        INTEGER myThid
35        _RL time_step        _RL time_step
36          _RL hflux_x_SI (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
37          _RL hflux_y_SI (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
38    
39  #ifdef ALLOW_STREAMICE  #ifdef ALLOW_STREAMICE
40    
41        INTEGER i, j, bi, bj, k, iter_count        INTEGER i, j, bi, bj, k, iter_count, iter_rpt
42        INTEGER Gi, Gj        INTEGER Gi, Gj
43        INTEGER new_partial(4)        INTEGER new_partial(4)
44        INTEGER ikey_front, ikey_1        INTEGER ikey_front, ikey_1
45        _RL iter_flag        _RL iter_flag
46        _RL n_flux_1, n_flux_2        _RL n_flux_1, n_flux_2
47        _RL href, rho, partial_vol, tot_flux, hpot        _RL href, rho, partial_vol, tot_flux, hpot
48          CHARACTER*(MAX_LEN_MBUF) msgBuf
49          _RL hflux_x_SI2 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
50          _RL hflux_y_SI2 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
51    
52    
53        rho = streamice_density        rho = streamice_density
54  cph      iter_count = 0  cph      iter_count = 0
55        iter_flag = 1. _d 0        iter_flag = 1. _d 0
56          iter_rpt = 0
57    
58            DO bj=myByLo(myThid),myByHi(myThid)
59             DO bi=myBxLo(myThid),myBxHi(myThid)
60              DO j=1-OLy,sNy+OLy
61               DO i=1-OLx,sNx+OLx
62                hflux_x_SI2(i,j,bi,bj) = 0. _d 0
63                hflux_y_SI2(i,j,bi,bj) = 0. _d 0
64               ENDDO
65              ENDDO
66             ENDDO
67            ENDDO
68    
69    
70        DO iter_count = 0, 3        DO iter_count = 0, 3
71    
# Line 86  CADJ &     = comlev1_stream_front, key = Line 109  CADJ &     = comlev1_stream_front, key =
109         ENDIF         ENDIF
110    
111  !       iter_count = iter_count + 1  !       iter_count = iter_count + 1
112           iter_rpt = iter_rpt + 1
113    
114         DO bj=myByLo(myThid),myByHi(myThid)         DO bj=myByLo(myThid),myByHi(myThid)
115          DO bi=myBxLo(myThid),myBxHi(myThid)          DO bi=myBxLo(myThid),myBxHi(myThid)
116    
117           DO j=1-1,sNy+1           DO j=1-1,sNy+1
118            Gj = (myYGlobalLo-1)+(bj-1)*sNy+j            Gj = (myYGlobalLo-1)+(bj-1)*sNy+j
119  cph          IF ((Gj .ge. 1) .and. (Gj .le. Ny)) THEN            IF ((Gj .ge. 1) .and. (Gj .le. Ny)) THEN
120             DO i=1-1,sNx+1             DO i=1-1,sNx+1
121              Gi = (myXGlobalLo-1)+(bi-1)*sNx+i              Gi = (myXGlobalLo-1)+(bi-1)*sNx+i
122    
# Line 104  cph          IF ((Gj .ge. 1) .and. (Gj . Line 128  cph          IF ((Gj .ge. 1) .and. (Gj .
128            act3 = myThid - 1            act3 = myThid - 1
129            max3 = nTx*nTy            max3 = nTx*nTy
130            act4 = ikey_front - 1            act4 = ikey_front - 1
131            ikey_1 = i            ikey_1 = i + 1
132       &         + sNx*(j-1)       &         + (sNx+2)*(j)
133       &         + sNx*sNy*act1       &         + (sNx+2)*(sNy+2)*act1
134       &         + sNx*sNy*max1*act2       &         + (sNx+2)*(sNy+2)*max1*act2
135       &         + sNx*sNy*max1*max2*act3       &         + (sNx+2)*(sNy+2)*max1*max2*act3
136       &         + sNx*sNy*max1*max2*max3*act4       &         + (sNx+2)*(sNy+2)*max1*max2*max3*act4
137  CADJ STORE area_shelf_streamice(i,j,bi,bj)  CADJ STORE area_shelf_streamice(i,j,bi,bj)
138  CADJ &     = comlev1_stream_ij, key = ikey_1  CADJ &     = comlev1_stream_ij, key = ikey_1
139  CADJ STORE h_streamice(i,j,bi,bj)  CADJ STORE h_streamice(i,j,bi,bj)
# Line 122  CADJ STORE streamice_hmask(i,j,bi,bj) Line 146  CADJ STORE streamice_hmask(i,j,bi,bj)
146  CADJ &     = comlev1_stream_ij, key = ikey_1  CADJ &     = comlev1_stream_ij, key = ikey_1
147  #endif  #endif
148    
149  cph            IF ((Gi .ge. 1) .and. (Gi .le. Nx) .and.              IF (.not. STREAMICE_calve_to_mask .OR.
150              IF ((STREAMICE_Hmask(i,j,bi,bj).eq.0.0 .or.       &       STREAMICE_calve_mask (i,j,bi,bj) .eq. 1.0) THEN
151    
152                IF ((Gi .ge. 1) .and. (Gi .le. Nx) .and.
153         &          (STREAMICE_Hmask(i,j,bi,bj).eq.0.0 .or.
154       &           STREAMICE_Hmask(i,j,bi,bj).eq.2.0)) THEN       &           STREAMICE_Hmask(i,j,bi,bj).eq.2.0)) THEN
155               n_flux_1 = 0. _d 0               n_flux_1 = 0. _d 0
156               href = 0. _d 0               href = 0. _d 0
# Line 191  CADJ &     = comlev1_stream_ij, key = ik Line 218  CADJ &     = comlev1_stream_ij, key = ik
218       &           rA(i,j,bi,bj)       &           rA(i,j,bi,bj)
219                ELSEIF (hpot .lt. href) THEN ! cell still unfilled                ELSEIF (hpot .lt. href) THEN ! cell still unfilled
220    
221  !                PRINT *, "PARTIAL CELL INCREASED", tot_flux, i,  
 !      &         area_shelf_streamice (i,j,bi,bj),  
 !      &         H_streamice (i,j,bi,bj)  
222    
223                 STREAMICE_hmask (i,j,bi,bj) = 2.0                 STREAMICE_hmask (i,j,bi,bj) = 2.0
224                 area_shelf_streamice (i,j,bi,bj) = partial_vol / href                 area_shelf_streamice (i,j,bi,bj) = partial_vol / href
225                 H_streamice (i,j,bi,bj) = href                 H_streamice (i,j,bi,bj) = href
226                ELSE ! cell is filled - do overflow                ELSE ! cell is filled - do overflow
227    
228  !                PRINT *, "CELL FILLED"                
229    
230                 STREAMICE_hmask (i,j,bi,bj) = 1.0                 STREAMICE_hmask (i,j,bi,bj) = 1.0
231                 area_shelf_streamice(i,j,bi,bj) =                 area_shelf_streamice(i,j,bi,bj) =
232       &           rA(i,j,bi,bj)       &           rA(i,j,bi,bj)
233    
234                                 PRINT *, "GOT HERE OVERFLOW ", i,j,
235         &          area_shelf_streamice(i,j,bi,bj)
236                 partial_vol = partial_vol - href * rA(i,j,bi,bj)                 partial_vol = partial_vol - href * rA(i,j,bi,bj)
237    
238                 iter_flag  = 1. _d 0                 iter_flag  = 1. _d 0
# Line 217  CADJ &     = comlev1_stream_ij, key = ik Line 243  CADJ &     = comlev1_stream_ij, key = ik
243                 ENDDO                 ENDDO
244    
245                 DO k=1,2                 DO k=1,2
246                  IF (STREAMICE_ufacemask(i-1+k,j,bi,bj).eq.2.0) THEN  ! at a permanent calving boundary - no advance allowed                  IF ( (STREAMICE_ufacemask(i-1+k,j,bi,bj).eq.2.0) .or.
247         &            (STREAMICE_calve_to_mask .and.
248         &             STREAMICE_calve_mask(i+2*k-3,j,bi,bj).ne.1.0)
249         &             ) THEN  ! at a permanent calving boundary - no advance allowed
250                     n_flux_2 = n_flux_2 + 1. _d 0                     n_flux_2 = n_flux_2 + 1. _d 0
251                  ELSEIF (STREAMICE_hmask(i+2*k-3,j,bi,bj).eq.0 _d 0) THEN ! adjacent cell is completely ice free                  ELSEIF (STREAMICE_hmask(i+2*k-3,j,bi,bj).eq.0 _d 0) THEN ! adjacent cell is completely ice free
252                     n_flux_2 = n_flux_2 + 1. _d 0                     n_flux_2 = n_flux_2 + 1. _d 0
# Line 225  CADJ &     = comlev1_stream_ij, key = ik Line 254  CADJ &     = comlev1_stream_ij, key = ik
254                  ENDIF                  ENDIF
255                 ENDDO                 ENDDO
256                 DO k=1,2                 DO k=1,2
257                  IF (STREAMICE_vfacemask (i,j-1+k,bi,bj).eq.2.0) THEN                  IF ( (STREAMICE_vfacemask (i,j-1+k,bi,bj).eq.2.0) .or.
258         &            (STREAMICE_calve_to_mask .and.
259         &             STREAMICE_calve_mask(i,j+2*k-3,bi,bj).ne.1.0)
260         &             ) THEN  ! at a permanent calving boundary - no advance allowed
261                      n_flux_2 = n_flux_2 + 1. _d 0                      n_flux_2 = n_flux_2 + 1. _d 0
262                  ELSEIF (STREAMICE_hmask(i,j+2*k-3,bi,bj).eq.0 _d 0) THEN                  ELSEIF (STREAMICE_hmask(i,j+2*k-3,bi,bj).eq.0 _d 0) THEN
263                      n_flux_2 = n_flux_2 + 1. _d 0                      n_flux_2 = n_flux_2 + 1. _d 0
# Line 260  CADJ &     = comlev1_stream_ij, key = ik Line 292  CADJ &     = comlev1_stream_ij, key = ik
292               ENDIF               ENDIF
293    
294              ENDIF              ENDIF
295                ENDIF
296             ENDDO             ENDDO
297  cph          ENDIF            ENDIF
298           ENDDO           ENDDO
299  c  c
300          ENDDO          ENDDO
# Line 270  c Line 303  c
303        ENDIF        ENDIF
304        ENDDO        ENDDO
305    
306  cph      IF (iter_count.gt.1) THEN        IF (iter_rpt.gt.1) THEN
307  cph       PRINT *, "FRONT ADVANCE: ", iter_count, " ITERATIONS"         WRITE(msgBuf,'(A,I5,A)') 'FRONT ADVANCE: ',iter_rpt,
308  cph      ENDIF       &  ' ITERATIONS'
309           CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
310         &                     SQUEEZE_RIGHT , 1)      
311          ENDIF
312    
313    
314    

Legend:
Removed from v.1.2  
changed lines
  Added in v.1.9

  ViewVC Help
Powered by ViewVC 1.1.22