5 |
|
|
6 |
C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----| |
C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----| |
7 |
|
|
|
|
|
8 |
CBOP |
CBOP |
9 |
SUBROUTINE STREAMICE_ADVECT_2DTRACER ( |
SUBROUTINE STREAMICE_ADVECT_2DTRACER ( |
10 |
& myThid, |
& myThid, |
11 |
& myIter, |
& myIter, |
12 |
& time_step, |
& time_step, |
13 |
& uTrans, |
& uTrans, |
14 |
& vTrans, |
& vTrans, |
15 |
& bcMaskx, |
& bcMaskx, |
16 |
& bcMasky) |
& bcMasky) |
17 |
|
|
18 |
C /============================================================\ |
C *============================================================* |
19 |
C | SUBROUTINE | |
C | SUBROUTINE | |
20 |
C | o | |
C | o | |
21 |
C |============================================================| |
C *============================================================* |
22 |
C | | |
C | | |
23 |
C \============================================================/ |
C *============================================================* |
24 |
IMPLICIT NONE |
IMPLICIT NONE |
25 |
|
|
26 |
C === Global variables === |
C === Global variables === |
38 |
_RL time_step |
_RL time_step |
39 |
_RL uTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy) |
_RL uTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy) |
40 |
_RL vTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy) |
_RL vTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy) |
41 |
_RL bcMaskx(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy) |
_RS bcMaskx(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy) |
42 |
_RL bcMasky(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy) |
_RS bcMasky(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy) |
43 |
! _RL trac(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy) |
! _RL trac(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy) |
44 |
|
|
45 |
#ifdef ALLOW_STREAMICE |
#ifdef ALLOW_STREAMICE |
69 |
DO j=1-3,sNy+3 |
DO j=1-3,sNy+3 |
70 |
DO i=1-3,sNx+3 |
DO i=1-3,sNx+3 |
71 |
|
|
72 |
! H_streamice_prev(i,j,bi,bj) = |
! H_streamice_prev(i,j,bi,bj) = |
73 |
! & H_streamice(i,j,bi,bj) |
! & H_streamice(i,j,bi,bj) |
74 |
|
|
75 |
ytracflux (i,j,bi,bj) = 0. _d 0 |
ytracflux (i,j,bi,bj) = 0. _d 0 |
126 |
& .or.STREAMICE_NS_PERIODIC) THEN |
& .or.STREAMICE_NS_PERIODIC) THEN |
127 |
|
|
128 |
|
|
129 |
IF (STREAMICE_hmask(i,j,bi,bj).eq.1.0 .or. |
IF (STREAMICE_hmask(i,j,bi,bj).eq.1.0 .or. |
130 |
& STREAMICE_hmask(i,j,bi,bj).eq.2.0) THEN |
& STREAMICE_hmask(i,j,bi,bj).eq.2.0) THEN |
131 |
|
|
132 |
|
|
133 |
|
|
134 |
#ifdef STREAMICE_TRACER_AB |
#ifdef STREAMICE_TRACER_AB |
135 |
GAD_trac_2d(i,j,bi,bj) = GAD_trac_2d(i,j,bi,bj) - |
GAD_trac_2d(i,j,bi,bj) = GAD_trac_2d(i,j,bi,bj) - |
136 |
#else |
#else |
137 |
trac2d(i,j,bi,bj) = trac2d(i,j,bi,bj) - |
trac2d(i,j,bi,bj) = trac2d(i,j,bi,bj) - |
138 |
#endif |
#endif |
139 |
& ((xtracflux(i+1,j,bi,bj)*dyG(i+1,j,bi,bj) - |
& ((xtracflux(i+1,j,bi,bj)*dyG(i+1,j,bi,bj) - |
140 |
& xtracflux(i,j,bi,bj)*dyG(i,j,bi,bj)) * |
& xtracflux(i,j,bi,bj)*dyG(i,j,bi,bj)) * |
141 |
& recip_rA (i,j,bi,bj) - |
& recip_rA (i,j,bi,bj) - |
142 |
& trac2d(i,j,bi,bj) * |
& trac2d(i,j,bi,bj) * |
143 |
& (utrans(i+1,j,bi,bj)*dyG(i+1,j,bi,bj)- |
& (utrans(i+1,j,bi,bj)*dyG(i+1,j,bi,bj)- |
144 |
& utrans(i,j,bi,bj)*dyG(i,j,bi,bj)) * |
& utrans(i,j,bi,bj)*dyG(i,j,bi,bj)) * |
145 |
& recip_rA(i,j,bi,bj)) |
& recip_rA(i,j,bi,bj)) |
146 |
#ifndef STREAMICE_TRACER_AB |
#ifndef STREAMICE_TRACER_AB |
147 |
& * time_step_loc |
& * time_step_loc |
148 |
#endif |
#endif |
149 |
ENDIF |
ENDIF |
157 |
#ifdef ALLOW_AUTODIFF_TAMC |
#ifdef ALLOW_AUTODIFF_TAMC |
158 |
# ifndef STREAMICE_TRACER_AB |
# ifndef STREAMICE_TRACER_AB |
159 |
CADJ STORE trac2d = comlev1, key=ikey_dynamics |
CADJ STORE trac2d = comlev1, key=ikey_dynamics |
160 |
# endif |
# endif |
161 |
#endif |
#endif |
162 |
|
|
163 |
|
|
177 |
Gi = (myXGlobalLo-1)+(bi-1)*sNx+i |
Gi = (myXGlobalLo-1)+(bi-1)*sNx+i |
178 |
Gj = (myYGlobalLo-1)+(bj-1)*sNy+j |
Gj = (myYGlobalLo-1)+(bj-1)*sNy+j |
179 |
|
|
180 |
IF (STREAMICE_hmask(i,j,bi,bj).eq.1.0 .or. |
IF (STREAMICE_hmask(i,j,bi,bj).eq.1.0 .or. |
181 |
& STREAMICE_hmask(i,j,bi,bj).eq.2.0) THEN |
& STREAMICE_hmask(i,j,bi,bj).eq.2.0) THEN |
182 |
! IF (Gi.eq.34.and.Gj.eq.94) THEN |
! IF (Gi.eq.34.and.Gj.eq.94) THEN |
183 |
! print *, "GOT HERE YFLUX", ytracflux(i,j,bi,bj), |
! print *, "GOT HERE YFLUX", ytracflux(i,j,bi,bj), |
186 |
! & bcmasky(i,j,bi,bj) |
! & bcmasky(i,j,bi,bj) |
187 |
! ENDIF |
! ENDIF |
188 |
|
|
189 |
#ifdef STREAMICE_TRACER_AB |
#ifdef STREAMICE_TRACER_AB |
190 |
GAD_trac_2d(i,j,bi,bj) = GAD_trac_2d(i,j,bi,bj) - |
GAD_trac_2d(i,j,bi,bj) = GAD_trac_2d(i,j,bi,bj) - |
191 |
#else |
#else |
192 |
trac2d(i,j,bi,bj) = trac2d(i,j,bi,bj) - |
trac2d(i,j,bi,bj) = trac2d(i,j,bi,bj) - |
214 |
DO j=1,sNy |
DO j=1,sNy |
215 |
DO i=1,sNx |
DO i=1,sNx |
216 |
|
|
217 |
trac2d(i,j,bi,bj) = trac2d(i,j,bi,bj) + time_step_loc * |
trac2d(i,j,bi,bj) = trac2d(i,j,bi,bj) + time_step_loc * |
218 |
& GAD_trac_2d(i,j,bi,bj) |
& GAD_trac_2d(i,j,bi,bj) |
219 |
|
|
220 |
IF (myIter.eq.0) THEN |
IF (myIter.eq.0) THEN |
221 |
trac2d(i,j,bi,bj) = trac2d(i,j,bi,bj) + time_step_loc * |
trac2d(i,j,bi,bj) = trac2d(i,j,bi,bj) + time_step_loc * |
222 |
& (.5+.01) * |
& (.5+.01) * |
223 |
& (GAD_trac_2d(i,j,bi,bj) - GAD_trac_2dNm1(i,j,bi,bj)) |
& (GAD_trac_2d(i,j,bi,bj) - GAD_trac_2dNm1(i,j,bi,bj)) |
224 |
ENDIF |
ENDIF |
225 |
|
|
232 |
#endif |
#endif |
233 |
|
|
234 |
_EXCH_XY_RL (trac2d, myThid) |
_EXCH_XY_RL (trac2d, myThid) |
235 |
|
|
236 |
WRITE(msgBuf,'(A)') 'END STREAMICE_ADVECT_THICKNESS' |
WRITE(msgBuf,'(A)') 'END STREAMICE_ADVECT_THICKNESS' |
237 |
CALL PRINT_MESSAGE( msgBuf, standardMessageUnit, |
CALL PRINT_MESSAGE( msgBuf, standardMessageUnit, |
238 |
& SQUEEZE_RIGHT , 1) |
& SQUEEZE_RIGHT , 1) |
239 |
|
|
240 |
#endif |
#endif |
241 |
#endif |
#endif |
242 |
END |
END |
|
|
|