SICOPOLIS V3.2
 All Classes Files Functions Variables Macros
calc_vxy_ssa.F90
Go to the documentation of this file.
1 !+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
2 !
3 ! Subroutine : c a l c _ v x y _ s s a
4 !
5 !> @file
6 !!
7 !! Computation of the horizontal velocity vx, vy, the horizontal volume flux
8 !! qx, qy and the flux across the grounding line q_gl_g in the shallow shelf
9 !! approximation.
10 !!
11 !! @section Copyright
12 !!
13 !! Copyright 2009-2016 Ralf Greve, Tatsuru Sato
14 !!
15 !! @section License
16 !!
17 !! This file is part of SICOPOLIS.
18 !!
19 !! SICOPOLIS is free software: you can redistribute it and/or modify
20 !! it under the terms of the GNU General Public License as published by
21 !! the Free Software Foundation, either version 3 of the License, or
22 !! (at your option) any later version.
23 !!
24 !! SICOPOLIS is distributed in the hope that it will be useful,
25 !! but WITHOUT ANY WARRANTY; without even the implied warranty of
26 !! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
27 !! GNU General Public License for more details.
28 !!
29 !! You should have received a copy of the GNU General Public License
30 !! along with SICOPOLIS. If not, see <http://www.gnu.org/licenses/>.
31 !<
32 !+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
33 
34 !-------------------------------------------------------------------------------
35 !> Computation of the horizontal velocity vx, vy, the horizontal volume flux
36 !! qx, qy and the flux across the grounding line q_gl_g in the shallow shelf
37 !! approximation.
38 !<------------------------------------------------------------------------------
39 subroutine calc_vxy_ssa(z_sl, dxi, deta, dzeta_c, dzeta_t, ii, jj, nn)
40 
41 use sico_types
43 use sico_vars
44 
45 implicit none
46 
47 integer(i4b), intent(in) :: ii((imax+1)*(jmax+1)), jj((imax+1)*(jmax+1))
48 integer(i4b), intent(in) :: nn(0:jmax,0:imax)
49 real(dp), intent(in) :: z_sl, dxi, deta, dzeta_c, dzeta_t
50 
51 integer(i4b) :: i, j, kc, kt, m
52 real(dp), dimension(0:JMAX,0:IMAX) :: vx_m_sia, vy_m_sia
53 real(dp), dimension(0:JMAX,0:IMAX) :: vx_m_prev, vy_m_prev
54 real(dp) :: dxi_inv, deta_inv
55 real(dp) :: vh_max
56 real(dp) :: ratio_sl_threshold, ratio_help, weigh_ssa_sia
57 real(dp) :: qx_gl_g, qy_gl_g
58 
59 integer(i4b), parameter :: iter_ssa = 2 ! number of iterations
60 real(dp), parameter :: rel = 0.7_dp ! relaxation factor
61 
62 !-------- Detection of the grounding line and the calving front --------
63 
64 flag_grounding_line_1 = .false.
65 flag_grounding_line_2 = .false.
66 
67 flag_calving_front_1 = .false.
68 flag_calving_front_2 = .false.
69 
70 do i=1, imax-1
71 do j=1, jmax-1
72 
73  if ( (maske(j,i)==0_i2b) & ! grounded ice
74  .and. &
75  ( (maske(j,i+1)==3_i2b) & ! with
76  .or.(maske(j,i-1)==3_i2b) & ! one
77  .or.(maske(j+1,i)==3_i2b) & ! neighbouring
78  .or.(maske(j-1,i)==3_i2b) ) & ! floating ice point
79  ) &
80  flag_grounding_line_1(j,i) = .true.
81 
82  if ( (maske(j,i)==3_i2b) & ! floating ice
83  .and. &
84  ( (maske(j,i+1)==0_i2b) & ! with
85  .or.(maske(j,i-1)==0_i2b) & ! one
86  .or.(maske(j+1,i)==0_i2b) & ! neighbouring
87  .or.(maske(j-1,i)==0_i2b) ) & ! grounded ice point
88  ) &
89  flag_grounding_line_2(j,i) = .true.
90 
91  if ( (maske(j,i)==3_i2b) & ! floating ice
92  .and. &
93  ( (maske(j,i+1)==2_i2b) & ! with
94  .or.(maske(j,i-1)==2_i2b) & ! one
95  .or.(maske(j+1,i)==2_i2b) & ! neighbouring
96  .or.(maske(j-1,i)==2_i2b) ) & ! ocean point
97  ) &
98  flag_calving_front_1(j,i) = .true.
99 
100  if ( (maske(j,i)==2_i2b) & ! ocean
101  .and. &
102  ( (maske(j,i+1)==3_i2b) & ! with
103  .or.(maske(j,i-1)==3_i2b) & ! one
104  .or.(maske(j+1,i)==3_i2b) & ! neighbouring
105  .or.(maske(j-1,i)==3_i2b) ) & ! floating ice point
106  ) &
107  flag_calving_front_2(j,i) = .true.
108 
109 end do
110 end do
111 
112 do i=1, imax-1
113 
114  j=0
115  if ( (maske(j,i)==2_i2b) & ! ocean
116  .and. (maske(j+1,i)==3_i2b) & ! with one neighbouring
117  ) & ! floating ice point
118  flag_calving_front_2(j,i) = .true.
119 
120  j=jmax
121  if ( (maske(j,i)==2_i2b) & ! ocean
122  .and. (maske(j-1,i)==3_i2b) & ! with one neighbouring
123  ) & ! floating ice point
124  flag_calving_front_2(j,i) = .true.
125 
126 end do
127 
128 do j=1, jmax-1
129 
130  i=0
131  if ( (maske(j,i)==2_i2b) & ! ocean
132  .and. (maske(j,i+1)==3_i2b) & ! with one neighbouring
133  ) & ! floating ice point
134  flag_calving_front_2(j,i) = .true.
135 
136  i=imax
137  if ( (maske(j,i)==2_i2b) & ! ocean
138  .and. (maske(j,i-1)==3_i2b) & ! with one neighbouring
139  ) & ! floating ice point
140  flag_calving_front_2(j,i) = .true.
141 
142 end do
143 
144 !-------- Save mean (depth-averaged) horizontal velocities from SIA --------
145 
146 vx_m_sia = vx_m
147 vy_m_sia = vy_m
148 
149 !-------- First iteration --------
150 
151 m=1
152 
153 ! ------ Depth-integrated viscosity vis_int_g
154 
155 do i=0, imax
156 do j=0, jmax
157  vis_int_g(j,i) = 1.0e+15_dp*(h_c(j,i)+h_t(j,i))
158  ! viscosity of 10^15 Pa s assumed
159 end do
160 end do
161 
162 ! ------ Horizontal velocity vx_m, vy_m
163 
164 call calc_vxy_ssa_matrix(z_sl, dxi, deta, ii, jj, nn, m)
165 
166 !-------- Further iterations --------
167 
168 do m=2, iter_ssa
169 
170 ! ------ Save velocities from previous iteration
171 
172  vx_m_prev = vx_m
173  vy_m_prev = vy_m
174 
175 ! ------ Depth-integrated viscosity vis_int_g
176 
177  call calc_vis_ssa(dxi, deta, dzeta_c, dzeta_t)
178 
179 ! ------ Horizontal velocity vx_m, vy_m
180 
181  call calc_vxy_ssa_matrix(z_sl, dxi, deta, ii, jj, nn, m)
182 
183 ! ------ Relaxation scheme
184 
185  do i=0, imax
186  do j=0, jmax
187  vx_m(j,i) = rel*vx_m(j,i) + (1.0_dp-rel)*vx_m_prev(j,i)
188  vy_m(j,i) = rel*vy_m(j,i) + (1.0_dp-rel)*vy_m_prev(j,i)
189  end do
190  end do
191 
192 end do
193 
194 ! ------ Depth-integrated viscosity vis_int_g
195 
196 call calc_vis_ssa(dxi, deta, dzeta_c, dzeta_t)
197 
198 !-------- Limitation of computed vx_m and vy_m to the interval
199 ! [-VH_MAX, VH_MAX] --------
200 
201 vh_max = vh_max/year_sec
202 
203 do i=0, imax
204 do j=0, jmax
205  vx_m(j,i) = max(vx_m(j,i), -vh_max)
206  vx_m(j,i) = min(vx_m(j,i), vh_max)
207  vy_m(j,i) = max(vy_m(j,i), -vh_max)
208  vy_m(j,i) = min(vy_m(j,i), vh_max)
209 end do
210 end do
211 
212 !-------- 3-D velocities, basal velocities and volume flux --------
213 
214 #if (DYNAMICS==0 || DYNAMICS==1)
215 
216 ratio_sl_threshold = 1.11e+11_dp ! dummy value
217 ratio_help = 0.0_dp
218 
219 #elif (DYNAMICS==2)
220 
221 #if ( defined(RATIO_SL_THRESH) )
222 ratio_sl_threshold = ratio_sl_thresh
223 #else
224 ratio_sl_threshold = 0.5_dp ! default value
225 #endif
226 
227 ratio_help = 1.0_dp/(1.0_dp-ratio_sl_threshold)
228 
229 #else
230 stop ' calc_vxy_ssa: DYNAMICS must be either 0, 1 or 2!'
231 #endif
232 
233 ! ------ x-component
234 
235 do i=0, imax-1
236 do j=0, jmax
237 
238  if (flag_shelfy_stream_x(j,i)) then
239  ! shelfy stream
240 
241  weigh_ssa_sia = (ratio_sl_x(j,i)-ratio_sl_threshold)*ratio_help
242 
243  do kt=0, ktmax
244  vx_t(kt,j,i) = weigh_ssa_sia*vx_m(j,i) &
245  + (1.0_dp-weigh_ssa_sia)*vx_t(kt,j,i)
246  end do
247 
248  do kc=0, kcmax
249  vx_c(kc,j,i) = weigh_ssa_sia*vx_m(j,i) &
250  + (1.0_dp-weigh_ssa_sia)*vx_c(kc,j,i)
251  end do
252 
253  vx_b(j,i) = vx_t(0,j,i)
254 
255  vx_m(j,i) = weigh_ssa_sia*vx_m(j,i) &
256  + (1.0_dp-weigh_ssa_sia)*vx_m_sia(j,i)
257 
258  qx(j,i) = vx_m(j,i) * 0.5_dp*(h_c(j,i)+h_t(j,i)+h_c(j,i+1)+h_t(j,i+1))
259 
260  else if ( (maske(j,i)==3_i2b).or.(maske(j,i+1)==3_i2b) ) then
261  ! at least one neighbour point is floating ice
262  do kt=0, ktmax
263  vx_t(kt,j,i) = vx_m(j,i)
264  end do
265 
266  do kc=0, kcmax
267  vx_c(kc,j,i) = vx_m(j,i)
268  end do
269 
270  vx_b(j,i) = vx_m(j,i)
271 
272  qx(j,i) = vx_m(j,i) * 0.5_dp*(h_c(j,i)+h_t(j,i)+h_c(j,i+1)+h_t(j,i+1))
273 
274  end if
275 
276 end do
277 end do
278 
279 ! ------ y-component
280 
281 do i=0, imax
282 do j=0, jmax-1
283 
284  if (flag_shelfy_stream_y(j,i)) then
285  ! shelfy stream
286 
287  weigh_ssa_sia = (ratio_sl_y(j,i)-ratio_sl_threshold)*ratio_help
288 
289  do kt=0, ktmax
290  vy_t(kt,j,i) = weigh_ssa_sia*vy_m(j,i) &
291  + (1.0_dp-weigh_ssa_sia)*vy_t(kt,j,i)
292  end do
293 
294  do kc=0, kcmax
295  vy_c(kc,j,i) = weigh_ssa_sia*vy_m(j,i) &
296  + (1.0_dp-weigh_ssa_sia)*vy_c(kc,j,i)
297  end do
298 
299  vy_b(j,i) = vy_t(0,j,i)
300 
301  vy_m(j,i) = weigh_ssa_sia*vy_m(j,i) &
302  + (1.0_dp-weigh_ssa_sia)*vy_m_sia(j,i)
303 
304  qy(j,i) = vy_m(j,i) * 0.5_dp*(h_c(j,i)+h_t(j,i)+h_c(j+1,i)+h_t(j+1,i))
305 
306  else if ( (maske(j,i)==3_i2b).or.(maske(j+1,i)==3_i2b) ) then
307  ! at least one neighbour point is floating ice
308  do kt=0, ktmax
309  vy_t(kt,j,i) = vy_m(j,i)
310  end do
311 
312  do kc=0, kcmax
313  vy_c(kc,j,i) = vy_m(j,i)
314  end do
315 
316  vy_b(j,i) = vy_m(j,i)
317 
318  qy(j,i) = vy_m(j,i) * 0.5_dp*(h_c(j,i)+h_t(j,i)+h_c(j+1,i)+h_t(j+1,i))
319 
320  end if
321 
322 end do
323 end do
324 
325 !-------- Surface and basal velocities vx_s_g vy_s_g, vx_b_g vy_b_g
326 ! (defined at (i,j)) --------
327 
328 do i=1, imax-1
329 do j=1, jmax-1
330 
331  if (flag_shelfy_stream(j,i)) then ! shelfy stream
332 
333  vx_s_g(j,i) = 0.5_dp*(vx_c(kcmax,j,i-1)+vx_c(kcmax,j,i))
334  vx_b_g(j,i) = 0.5_dp*(vx_b( j,i-1)+vx_b( j,i))
335 
336  vy_s_g(j,i) = 0.5_dp*(vy_c(kcmax,j-1,i)+vy_c(kcmax,j,i))
337  vy_b_g(j,i) = 0.5_dp*(vy_b( j-1,i)+vy_b( j,i))
338 
339  else if (maske(j,i)==3_i2b) then ! floating ice
340 
341  vx_s_g(j,i) = 0.5_dp*(vx_m(j,i-1)+vx_m(j,i))
342  vx_b_g(j,i) = vx_s_g(j,i)
343 
344  vy_s_g(j,i) = 0.5_dp*(vy_m(j-1,i)+vy_m(j,i))
345  vy_b_g(j,i) = vy_s_g(j,i)
346 
347  end if
348 
349 end do
350 end do
351 
352 !-------- Computation of the flux across the grounding line q_gl_g
353 
354 do i=1, imax-1
355 do j=1, jmax-1
356 
357  if ( flag_grounding_line_1(j,i) ) then ! grounding line
358 
359  qx_gl_g = 0.5_dp*(qx(j,i)+qx(j,i-1))
360  qy_gl_g = 0.5_dp*(qy(j,i)+qy(j-1,i))
361 
362  q_gl_g(j,i) = sqrt(qx_gl_g*qx_gl_g+qy_gl_g*qy_gl_g)
363 
364  end if
365 
366 end do
367 end do
368 
369 end subroutine calc_vxy_ssa
370 !
subroutine calc_vxy_ssa_matrix(z_sl, dxi, deta, ii, jj, nn, m)
Solution of the system of linear equations for the horizontal velocities vx_m, vy_m in the shallow sh...
subroutine calc_vis_ssa(dxi, deta, dzeta_c, dzeta_t)
Computation of the depth-integrated viscosity vis_int_g in the shallow shelf approximation.
Declarations of kind types for SICOPOLIS.
Definition: sico_types.F90:35
subroutine calc_vxy_ssa(z_sl, dxi, deta, dzeta_c, dzeta_t, ii, jj, nn)
Computation of the horizontal velocity vx, vy, the horizontal volume flux qx, qy and the flux across ...
Declarations of global variables for SICOPOLIS (for the ANT domain).
Definition: sico_vars.F90:35
Declarations of global variables for SICOPOLIS.