/[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.6 by dgoldberg, Wed Jan 9 21:56:18 2013 UTC
# 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
32        _RL time_step        _RL time_step
# Line 33  C     === Global variables === Line 36  C     === Global variables ===
36        INTEGER i, j, bi, bj        INTEGER i, j, bi, bj
37        _RL thick_bd        _RL thick_bd
38        _RL SLOPE_LIMITER        _RL SLOPE_LIMITER
39        _RL sec_per_year, time_step_loc        _RL sec_per_year, time_step_loc, MR, SMB, TMB
40          CHARACTER*(MAX_LEN_MBUF) msgBuf
41        external SLOPE_LIMITER        external SLOPE_LIMITER
42    
43        sec_per_year = 365.*86400.        sec_per_year = 365.*86400.
44    
45        time_step_loc = time_step / sec_per_year        time_step_loc = time_step / sec_per_year
46    
47    #ifdef ALLOW_AUTODIFF_TAMC
48    CADJ STORE streamice_hmask  = comlev1, key=ikey_dynamics
49    #endif
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,sNy+OLy
54           DO i=1-OLx,sNx+OLx           DO i=1-OLx,sNx+OLx
55              H_streamice_prev(i,j,bi,bj) =
56         &     H_streamice(i,j,bi,bj)
57            hflux_x_SI (i,j,bi,bj) = 0. _d 0            hflux_x_SI (i,j,bi,bj) = 0. _d 0
58            hflux_y_SI (i,j,bi,bj) = 0. _d 0            hflux_y_SI (i,j,bi,bj) = 0. _d 0
59            hflux_x_SI2 (i,j,bi,bj) = 0. _d 0            hflux_x_SI2 (i,j,bi,bj) = 0. _d 0
# Line 62  C     === Global variables === Line 72  C     === Global variables ===
72         ENDDO         ENDDO
73        ENDDO        ENDDO
74    
75  !       PRINT *, "H in last row ", H_streamice(81,20,1,1)  
76    #ifdef ALLOW_AUTODIFF_TAMC
77    CADJ STORE h_after_uflux_si = comlev1, key=ikey_dynamics
78    CADJ STORE streamice_hmask  = comlev1, key=ikey_dynamics
79    #endif
80    
81        CALL STREAMICE_ADVECT_THICKNESS_X ( myThid,        CALL STREAMICE_ADVECT_THICKNESS_X ( myThid,
82       O   hflux_x_SI,       O   hflux_x_SI,
83       O   h_after_uflux_SI,       O   h_after_uflux_SI,
84       I   time_step_loc )       I   time_step_loc )
85    
86  !       PRINT *, "H in last row ", H_streamice(81,20,1,1)  
87    
88        DO bj=myByLo(myThid),myByHi(myThid)        DO bj=myByLo(myThid),myByHi(myThid)
89         DO bi=myBxLo(myThid),myBxHi(myThid)         DO bi=myBxLo(myThid),myBxHi(myThid)
# Line 82  C     === Global variables === Line 96  C     === Global variables ===
96         ENDDO         ENDDO
97        ENDDO        ENDDO
98    
99    #ifdef ALLOW_AUTODIFF_TAMC
100    CADJ STORE h_after_vflux_si = comlev1, key=ikey_dynamics
101    CADJ STORE streamice_hmask  = comlev1, key=ikey_dynamics
102    #endif
103    
104        CALL STREAMICE_ADVECT_THICKNESS_Y ( myThid,        CALL STREAMICE_ADVECT_THICKNESS_Y ( myThid,
105       O   hflux_y_SI,       O   hflux_y_SI,
106       O   h_after_vflux_SI,       O   h_after_vflux_SI,
107       I   time_step_loc )       I   time_step_loc )
108    
109  !       PRINT *, "H in last row ", H_streamice(81,20,1,1)  
110    
111        DO bj=myByLo(myThid),myByHi(myThid)        DO bj=myByLo(myThid),myByHi(myThid)
112         DO bi=myBxLo(myThid),myBxHi(myThid)         DO bi=myBxLo(myThid),myBxHi(myThid)
# Line 102  C     === Global variables === Line 121  C     === Global variables ===
121         ENDDO         ENDDO
122        ENDDO        ENDDO
123    
 !       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)  
   
       _EXCH_XY_RL( H_streamice, myThid )  
       _EXCH_XY_RL( area_shelf_streamice, myThid )  
       _EXCH_XY_RL( STREAMICE_hmask, myThid )  
         
       PRINT *, "END STREAMICE_ADVECT_THICKNESS"  
   
 #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  
   
       INTEGER i, j, bi, bj, Gi, Gj, k  
       _RL uface, phi  
       _RL stencil (-1:1)  
       LOGICAL H0_valid  ! there are valid cells to calculate a  
                         ! slope-limited 2nd order flux  
       _RL SLOPE_LIMITER  
       _RL total_vol_out  
       external SLOPE_LIMITER  
124    
        total_vol_out = 0.0  
125    
126        DO bj=myByLo(myThid),myByHi(myThid)        CALL STREAMICE_ADV_FRONT ( myThid, time_step_loc )
        DO bi=myBxLo(myThid),myBxHi(myThid)  
         DO j=1-3,sNy+3  
          Gj = (myYGlobalLo-1)+(bj-1)*sNy+j  
          IF ((Gj .ge. 1) .and. (Gj .le. Ny)) THEN  
           DO i=1-2,sNx+3  
 C        THESE ARRAY BOUNDS INSURE THAT AFTER THIS STEP,  
 C        VALUES WILL BE RELIABLE 2 GRID CELLS OUT IN THE  
 C        X DIRECTION AND 3 CELLS OUT IN THE Y DIR  
            IF ((STREAMICE_hmask(i,j,bi,bj).eq.1.0) .or.  
      &         ((STREAMICE_hmask(i-1,j,bi,bj).eq.1.0) .and.  
      &          (STREAMICE_hmask(i,j,bi,bj).ne.1.0))) THEN  
   
             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  
   
            ENDIF  
           ENDDO  
          ENDIF  
         ENDDO  
        ENDDO  
       ENDDO  
   
 C     X-FLUXES AT CELL BOUNDARIES CALCULATED; NOW TAKE FLUX DIVERGENCE TO INCREMENT THICKNESS  
         
       DO bj=myByLo(myThid),myByHi(myThid)  
        DO bi=myBxLo(myThid),myBxHi(myThid)  
         DO j=1-3,sNy+3  
          Gj = (myYGlobalLo-1)+(bj-1)*sNy+j  
          IF ((Gj .ge. 1) .and. (Gj .le. Ny)) THEN  
           DO i=1-2,sNx+2  
            IF (STREAMICE_hmask(i,j,bi,bj).eq.1.0) THEN  
             h(i,j,bi,bj) = h(i,j,bi,bj) - time_step *  
      &       (hflux_x(i+1,j,bi,bj)*dyG(i+1,j,bi,bj) -  
      &        hflux_x(i,j,bi,bj)*dyG(i,j,bi,bj)) *  
      &       recip_rA (i,j,bi,bj)  
            ENDIF  
           ENDDO  
          ENDIF  
         ENDDO  
        ENDDO  
       ENDDO  
   
 !       PRINT *, "TOTAL VOLUME OUT: ", total_vol_out  
         
 #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  
127    
 C     LOCAL VARIABLES  
128    
129        INTEGER i, j, bi, bj, Gi, Gj, k  ! NOW WE APPLY MELT RATES !!
130        _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  
131    
132        DO bj=myByLo(myThid),myByHi(myThid)        DO bj=myByLo(myThid),myByHi(myThid)
133         DO bi=myBxLo(myThid),myBxHi(myThid)         DO bi=myBxLo(myThid),myBxHi(myThid)
134          DO j=1-1,sNy+2          DO j=1-OLy,sNy+OLy
135           Gj = (myYGlobalLo-1)+(bj-1)*sNy+j           DO i=1-OLx,sNx+OLx
136           DO i=1-2,sNx+2             IF (STREAMICE_hmask(i,j,bi,bj).eq.1.0 .or.
137            Gi = (myXGlobalLo-1)+(bi-1)*sNx+i       &       STREAMICE_hmask(i,j,bi,bj).eq.2.0) THEN
138            IF ((Gi.ge.1) .and. (Gi.le.Nx)) THEN               MR = (1.-float_frac_streamice(i,j,bi,bj)) *
139  C         THESE ARRAY BOUNDS INSURE THAT AFTER THIS STEP,       &             BDOT_STREAMICE(i,j,bi,bj)
140  C         VALUES WILL BE RELIABLE 1 GRID CELLS OUT IN THE               SMB = ADOT_STREAMICE(i,j,bi,bj)
141  C         Y DIRECTION               TMB = SMB - MR
142             IF ((STREAMICE_hmask(i,j,bi,bj).eq.1.0) .or.               IF ((TMB.lt.0.0) .and.
143       &         ((STREAMICE_hmask(i,j-1,bi,bj).eq.1.0) .and.       &         (MR * time_step_loc .gt.
144       &          (STREAMICE_hmask(i,j,bi,bj).ne.1.0))) THEN       &          H_streamice (i,j,bi,bj))) THEN
145                    H_streamice (i,j,bi,bj) = 0. _d 0
146              IF (STREAMICE_vfacemask(i,j,bi,bj).eq.4.0) THEN                  STREAMICE_hmask(i,j,bi,bj) = 0.
147               hflux_y (i,j,bi,bj) = v_flux_bdry_SI (i,j,bi,bj)               ELSE
148              ELSE                 H_streamice (i,j,bi,bj) =
149                   &          H_streamice (i,j,bi,bj) + TMB
150               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  
151             ENDIF             ENDIF
           ENDIF  
152           ENDDO           ENDDO
153          ENDDO          ENDDO
154         ENDDO         ENDDO
155        ENDDO        ENDDO    
156    
 C     X-FLUXES AT CELL BOUNDARIES CALCULATED; NOW TAKE FLUX DIVERGENCE TO INCREMENT THICKNESS  
   
157                
158          WRITE(msgBuf,'(A)') 'END STREAMICE_ADVECT_THICKNESS'
159           CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
160         &                     SQUEEZE_RIGHT , 1)
161                
       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)  
   
162  #endif  #endif
163        RETURN        END
       END SUBROUTINE STREAMICE_ADVECT_THICKNESS_Y  
164    

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

  ViewVC Help
Powered by ViewVC 1.1.22