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

Annotation of /MITgcm_contrib/dgoldberg/streamice/streamice_advect_thickness_y.F

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


Revision 1.3 - (hide annotations) (download)
Fri May 10 18:38:07 2013 UTC (12 years, 2 months ago) by dgoldberg
Branch: MAIN
CVS Tags: HEAD
Changes since 1.2: +8 -4 lines
dirich boundaries at non-grid boundaries

1 dgoldberg 1.3 C $Header: /u/gcmpack/MITgcm_contrib/dgoldberg/streamice/streamice_advect_thickness_y.F,v 1.2 2012/05/17 21:30:17 heimbach Exp $
2 heimbach 1.1 C $Name: $
3    
4     #include "STREAMICE_OPTIONS.h"
5    
6     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
7    
8    
9     SUBROUTINE STREAMICE_ADVECT_THICKNESS_Y ( myThid ,
10     O hflux_y ,
11     O h ,
12     I time_step )
13    
14     IMPLICIT NONE
15    
16     C O hflux_y ! flux per unit width across face
17     C O h
18     C I time_step
19    
20     C === Global variables ===
21     #include "SIZE.h"
22     #include "GRID.h"
23     #include "EEPARAMS.h"
24     #include "PARAMS.h"
25     #include "STREAMICE.h"
26    
27     INTEGER myThid
28     _RL hflux_y (1-Olx:sNx+Olx,1-Oly:sNy+Oly,nSx,nSy)
29     _RL h (1-Olx:sNx+Olx,1-Oly:sNy+Oly,nSx,nSy)
30     _RL time_step
31    
32     #ifdef ALLOW_STREAMICE
33    
34     C LOCAL VARIABLES
35    
36     INTEGER i, j, bi, bj, Gi, Gj, k
37     _RL vface, phi
38     _RL stencil (-1:1)
39 heimbach 1.2 LOGICAL H0_valid(1-Olx:sNx+Olx,1-Oly:sNy+Oly,nSx,nSy)
40     ! there are valid cells to calculate a
41 heimbach 1.1 ! slope-limited 2nd order flux
42     _RL SLOPE_LIMITER
43     external SLOPE_LIMITER
44    
45     DO bj=myByLo(myThid),myByHi(myThid)
46     DO bi=myBxLo(myThid),myBxHi(myThid)
47 heimbach 1.2 DO j=1-oly,sNy+oly
48     DO i=1-olx,sNx+olx
49     H0_valid(i,j,bi,bj)=.false.
50     ENDDO
51     ENDDO
52     ENDDO
53     ENDDO
54    
55     DO bj=myByLo(myThid),myByHi(myThid)
56     DO bi=myBxLo(myThid),myBxHi(myThid)
57 heimbach 1.1 DO j=1-1,sNy+2
58     Gj = (myYGlobalLo-1)+(bj-1)*sNy+j
59     DO i=1-2,sNx+2
60     Gi = (myXGlobalLo-1)+(bi-1)*sNx+i
61     IF ((Gi.ge.1) .and. (Gi.le.Nx)) THEN
62     C THESE ARRAY BOUNDS INSURE THAT AFTER THIS STEP,
63     C VALUES WILL BE RELIABLE 1 GRID CELLS OUT IN THE
64     C Y DIRECTION
65     IF ((STREAMICE_hmask(i,j,bi,bj).eq.1.0) .or.
66     & ((STREAMICE_hmask(i,j-1,bi,bj).eq.1.0) .and.
67     & (STREAMICE_hmask(i,j,bi,bj).ne.1.0))) THEN
68    
69     IF (STREAMICE_vfacemask(i,j,bi,bj).eq.4.0) THEN
70     hflux_y (i,j,bi,bj) = v_flux_bdry_SI (i,j,bi,bj)
71     ELSE
72    
73     vface = .5 *
74     & (V_streamice(i,j,bi,bj)+V_streamice(i+1,j,bi,bj))
75    
76     IF (vface .gt. 0. _d 0) THEN
77     DO k=-1,1
78     stencil (k) = h(i,j+k-1,bi,bj)
79     ENDDO
80     IF ((STREAMICE_hmask(i,j,bi,bj).eq.1.0) .and.
81 heimbach 1.2 & (STREAMICE_hmask(i,j-2,bi,bj).eq.1.0))
82     & H0_valid(i,j,bi,bj)=.true.
83 heimbach 1.1
84 dgoldberg 1.3 IF ((STREAMICE_hmask(i,j-1,bi,bj).eq.3.0))
85 heimbach 1.1 & THEN ! we are at western bdry and there is a thick. bdry cond
86     hflux_y (i,j,bi,bj) = h(i,j-1,bi,bj) * vface
87 dgoldberg 1.3 ! PRINT *, "BOUNDARY FLUX UP", hflux_y (i,j,bi,bj),
88     ! & h(i,j-1,bi,bj),vface
89 heimbach 1.2 ELSEIF (H0_valid(i,j,bi,bj)) THEN
90 heimbach 1.1 phi = SLOPE_LIMITER (
91     & stencil(0)-stencil(-1),
92     & stencil(1)-stencil(0))
93     hflux_y (i,j,bi,bj) = vface *
94     & (stencil(0) - phi * .5 * (stencil(0)-stencil(1)))
95     ELSE ! one of the two cells needed for a HO scheme is missing, use FO scheme
96     hflux_y (i,j,bi,bj) = vface * stencil(0)
97     ENDIF
98     ELSE ! uface <= 0
99     DO k=-1,1
100     stencil (k) = h(i,j-k,bi,bj)
101     ENDDO
102     IF ((STREAMICE_hmask(i,j-1,bi,bj).eq.1.0) .and.
103 heimbach 1.2 & (STREAMICE_hmask(i,j+1,bi,bj).eq.1.0))
104     & H0_valid(i,j,bi,bj)=.true.
105 heimbach 1.1
106 dgoldberg 1.3 IF ((STREAMICE_hmask(i,j,bi,bj).eq.3.0))
107 heimbach 1.1 & THEN ! we are at western bdry and there is a thick. bdry cond
108 dgoldberg 1.3 hflux_y (i,j,bi,bj) = h(i,j,bi,bj) * vface
109     ! PRINT *, "BOUNDARY FLUX DOWN", hflux_y (i,j,bi,bj),
110     ! & h(i,j,bi,bj),vface
111 heimbach 1.2 ELSEIF (H0_valid(i,j,bi,bj)) THEN
112 heimbach 1.1 phi = SLOPE_LIMITER (
113     & stencil(0)-stencil(-1),
114     & stencil(1)-stencil(0))
115     hflux_y (i,j,bi,bj) = vface *
116     & (stencil(0) - phi * .5 * (stencil(0)-stencil(1)))
117     ELSE ! one of the two cells needed for a HO scheme is missing, use FO scheme
118     hflux_y (i,j,bi,bj) = vface * stencil(0)
119     ENDIF
120    
121     ENDIF ! uface 0
122    
123     ENDIF
124     ENDIF
125     ENDIF
126     ENDDO
127     ENDDO
128     ENDDO
129     ENDDO
130    
131     C X-FLUXES AT CELL BOUNDARIES CALCULATED; NOW TAKE FLUX DIVERGENCE TO INCREMENT THICKNESS
132    
133    
134    
135     DO bj=myByLo(myThid),myByHi(myThid)
136     DO bi=myBxLo(myThid),myBxHi(myThid)
137     DO j=1-1,sNy+1
138     DO i=1-2,sNx+2
139     Gi = (myXGlobalLo-1)+(bi-1)*sNx+i
140     IF ((Gi .ge. 1) .and. (Gi .le. Nx)) THEN
141     IF (STREAMICE_hmask(i,j,bi,bj).eq.1.0) THEN
142     h(i,j,bi,bj) = h(i,j,bi,bj) - time_step *
143     & (hflux_y(i,j+1,bi,bj)*dxG(i,j+1,bi,bj) -
144     & hflux_y(i,j,bi,bj)*dxG(i,j,bi,bj)) *
145     & recip_rA (i,j,bi,bj)
146     ENDIF
147     ENDIF
148     ENDDO
149     ENDDO
150     ENDDO
151     ENDDO
152    
153     ! CALL WRITE_FLD_XY_RL ("h_after_yflux","",
154     ! & h, 0, myThid)
155    
156     #endif
157     RETURN
158     END SUBROUTINE STREAMICE_ADVECT_THICKNESS_Y
159    
160    

  ViewVC Help
Powered by ViewVC 1.1.22