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 | |
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 |
|
|
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 |
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 |
|
|
72 |
#ifdef ALLOW_AUTODIFF_TAMC |
#ifdef ALLOW_AUTODIFF_TAMC |
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 |
|
|
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) |
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 ((Gi .ge. 1) .and. (Gi .le. Nx) .and. |
150 |
IF ((STREAMICE_Hmask(i,j,bi,bj).eq.0.0 .or. |
& (STREAMICE_Hmask(i,j,bi,bj).eq.0.0 .or. |
151 |
& STREAMICE_Hmask(i,j,bi,bj).eq.2.0)) THEN |
& STREAMICE_Hmask(i,j,bi,bj).eq.2.0)) THEN |
152 |
n_flux_1 = 0. _d 0 |
n_flux_1 = 0. _d 0 |
153 |
href = 0. _d 0 |
href = 0. _d 0 |
215 |
& rA(i,j,bi,bj) |
& rA(i,j,bi,bj) |
216 |
ELSEIF (hpot .lt. href) THEN ! cell still unfilled |
ELSEIF (hpot .lt. href) THEN ! cell still unfilled |
217 |
|
|
218 |
! PRINT *, "PARTIAL CELL INCREASED", tot_flux, i, |
|
|
! & area_shelf_streamice (i,j,bi,bj), |
|
|
! & H_streamice (i,j,bi,bj) |
|
219 |
|
|
220 |
STREAMICE_hmask (i,j,bi,bj) = 2.0 |
STREAMICE_hmask (i,j,bi,bj) = 2.0 |
221 |
area_shelf_streamice (i,j,bi,bj) = partial_vol / href |
area_shelf_streamice (i,j,bi,bj) = partial_vol / href |
222 |
H_streamice (i,j,bi,bj) = href |
H_streamice (i,j,bi,bj) = href |
223 |
ELSE ! cell is filled - do overflow |
ELSE ! cell is filled - do overflow |
224 |
|
|
|
! PRINT *, "CELL FILLED" |
|
225 |
|
|
226 |
STREAMICE_hmask (i,j,bi,bj) = 1.0 |
STREAMICE_hmask (i,j,bi,bj) = 1.0 |
227 |
area_shelf_streamice(i,j,bi,bj) = |
area_shelf_streamice(i,j,bi,bj) = |
282 |
|
|
283 |
ENDIF |
ENDIF |
284 |
ENDDO |
ENDDO |
285 |
cph ENDIF |
ENDIF |
286 |
ENDDO |
ENDDO |
287 |
c |
c |
288 |
ENDDO |
ENDDO |
292 |
ENDDO |
ENDDO |
293 |
|
|
294 |
IF (iter_rpt.gt.1) THEN |
IF (iter_rpt.gt.1) THEN |
295 |
PRINT *, "FRONT ADVANCE: ", iter_rpt, " ITERATIONS" |
WRITE(msgBuf,'(A,I5,A)') 'FRONT ADVANCE: ',iter_rpt, |
296 |
|
& ' ITERATIONS' |
297 |
|
CALL PRINT_MESSAGE( msgBuf, standardMessageUnit, |
298 |
|
& SQUEEZE_RIGHT , 1) |
299 |
ENDIF |
ENDIF |
300 |
|
|
301 |
|
|