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

Contents 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.2 - (show annotations) (download)
Thu May 17 21:30:17 2012 UTC (13 years, 2 months ago) by heimbach
Branch: MAIN
Changes since 1.1: +18 -5 lines
Small modifs (don't do much)

1 C $Header: /u/gcmpack/MITgcm/pkg/streamice/streamice_init_varia.F,v 1.6 2011/06/29 16:24:10 dng Exp $
2 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 LOGICAL H0_valid(1-Olx:sNx+Olx,1-Oly:sNy+Oly,nSx,nSy)
40 ! there are valid cells to calculate a
41 ! 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 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 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 & (STREAMICE_hmask(i,j-2,bi,bj).eq.1.0))
82 & H0_valid(i,j,bi,bj)=.true.
83
84 IF ((Gj.eq.1).and.(STREAMICE_hmask(i,j-1,bi,bj).eq.3.0))
85 & 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 ELSEIF (H0_valid(i,j,bi,bj)) THEN
88 phi = SLOPE_LIMITER (
89 & stencil(0)-stencil(-1),
90 & stencil(1)-stencil(0))
91 hflux_y (i,j,bi,bj) = vface *
92 & (stencil(0) - phi * .5 * (stencil(0)-stencil(1)))
93 ELSE ! one of the two cells needed for a HO scheme is missing, use FO scheme
94 hflux_y (i,j,bi,bj) = vface * stencil(0)
95 ENDIF
96 ELSE ! uface <= 0
97 DO k=-1,1
98 stencil (k) = h(i,j-k,bi,bj)
99 ENDDO
100 IF ((STREAMICE_hmask(i,j-1,bi,bj).eq.1.0) .and.
101 & (STREAMICE_hmask(i,j+1,bi,bj).eq.1.0))
102 & H0_valid(i,j,bi,bj)=.true.
103
104 IF ((Gj.eq.Ny).and.(STREAMICE_hmask(i,j+1,bi,bj).eq.3.0))
105 & THEN ! we are at western bdry and there is a thick. bdry cond
106 hflux_y (i,j,bi,bj) = h(i,j+1,bi,bj) * vface
107 ELSEIF (H0_valid(i,j,bi,bj)) THEN
108 phi = SLOPE_LIMITER (
109 & stencil(0)-stencil(-1),
110 & stencil(1)-stencil(0))
111 hflux_y (i,j,bi,bj) = vface *
112 & (stencil(0) - phi * .5 * (stencil(0)-stencil(1)))
113 ELSE ! one of the two cells needed for a HO scheme is missing, use FO scheme
114 hflux_y (i,j,bi,bj) = vface * stencil(0)
115 ENDIF
116
117 ENDIF ! uface 0
118
119 ENDIF
120 ENDIF
121 ENDIF
122 ENDDO
123 ENDDO
124 ENDDO
125 ENDDO
126
127 C X-FLUXES AT CELL BOUNDARIES CALCULATED; NOW TAKE FLUX DIVERGENCE TO INCREMENT THICKNESS
128
129
130
131 DO bj=myByLo(myThid),myByHi(myThid)
132 DO bi=myBxLo(myThid),myBxHi(myThid)
133 DO j=1-1,sNy+1
134 DO i=1-2,sNx+2
135 Gi = (myXGlobalLo-1)+(bi-1)*sNx+i
136 IF ((Gi .ge. 1) .and. (Gi .le. Nx)) THEN
137 IF (STREAMICE_hmask(i,j,bi,bj).eq.1.0) THEN
138 h(i,j,bi,bj) = h(i,j,bi,bj) - time_step *
139 & (hflux_y(i,j+1,bi,bj)*dxG(i,j+1,bi,bj) -
140 & hflux_y(i,j,bi,bj)*dxG(i,j,bi,bj)) *
141 & recip_rA (i,j,bi,bj)
142 ENDIF
143 ENDIF
144 ENDDO
145 ENDDO
146 ENDDO
147 ENDDO
148
149 ! CALL WRITE_FLD_XY_RL ("h_after_yflux","",
150 ! & h, 0, myThid)
151
152 #endif
153 RETURN
154 END SUBROUTINE STREAMICE_ADVECT_THICKNESS_Y
155
156

  ViewVC Help
Powered by ViewVC 1.1.22