SICOPOLIS V3.2
 All Classes Files Functions Variables Macros
calc_vis_ssa.F90
Go to the documentation of this file.
1 !+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
2 !
3 ! Subroutine : c a l c _ v i s _ s s a
4 !
5 !> @file
6 !!
7 !! Computation of the depth-integrated viscosity vis_int_g in the
8 !! shallow shelf approximation.
9 !!
10 !! @section Copyright
11 !!
12 !! Copyright 2009-2016 Ralf Greve, Tatsuru Sato
13 !!
14 !! @section License
15 !!
16 !! This file is part of SICOPOLIS.
17 !!
18 !! SICOPOLIS is free software: you can redistribute it and/or modify
19 !! it under the terms of the GNU General Public License as published by
20 !! the Free Software Foundation, either version 3 of the License, or
21 !! (at your option) any later version.
22 !!
23 !! SICOPOLIS is distributed in the hope that it will be useful,
24 !! but WITHOUT ANY WARRANTY; without even the implied warranty of
25 !! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
26 !! GNU General Public License for more details.
27 !!
28 !! You should have received a copy of the GNU General Public License
29 !! along with SICOPOLIS. If not, see <http://www.gnu.org/licenses/>.
30 !<
31 !+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
32 
33 !-------------------------------------------------------------------------------
34 !> Computation of the depth-integrated viscosity vis_int_g in the
35 !! shallow shelf approximation.
36 !<------------------------------------------------------------------------------
37 subroutine calc_vis_ssa(dxi, deta, dzeta_c, dzeta_t)
38 
39 use sico_types
41 use sico_vars
42 
43 implicit none
44 
45 real(dp), intent(in) :: dxi, deta, dzeta_c, dzeta_t
46 
47 integer(i4b) :: i, j, kc, kt
48 real(dp) :: dxi_inv, deta_inv
49 real(dp) :: dvx_dxi, dvx_deta, dvy_dxi, dvy_deta
50 real(dp) :: aqxy1(0:kcmax)
51 real(dp) :: cvis0(0:ktmax), cvis1(0:kcmax)
52 
53 !-------- Term abbreviations --------
54 
55 dxi_inv = 1.0_dp/dxi
56 deta_inv = 1.0_dp/deta
57 
58 do kc=0, kcmax
59  if (flag_aa_nonzero) then
60  aqxy1(kc) = aa/(ea-1.0_dp)*eaz_c(kc)*dzeta_c
61  else
62  aqxy1(kc) = dzeta_c
63  end if
64 end do
65 
66 !-------- Computation of the depth-integrated viscosity --------
67 
68 do i=0, imax
69 do j=0, jmax
70 
71  if ((maske(j,i)==0_i2b).and.(.not.flag_shelfy_stream(j,i))) then
72  ! grounded ice, but
73  ! not shelfy stream
74  de_ssa(j,i) = 0.0_dp ! dummy value
75 
76  vis_int_g(j,i) = (h_c(j,i)+h_t(j,i)) / flui_ave_sia(j,i)
77 
78  else if ((maske(j,i)==1_i2b).or.(maske(j,i)==2_i2b)) then
79  ! ice-free land or ocean
80  de_ssa(j,i) = 0.0_dp ! dummy value
81 
82  vis_int_g(j,i) = 0.0_dp ! dummy value
83 
84  else ! (maske(j,i)==3_i2b).or.(flag_shelfy_stream(j,i)),
85  ! floating ice or shelfy stream;
86  ! must not be at the margin of the computational domain
87 
88 ! ------ Effective strain rate
89 
90  dvx_dxi = (vx_m(j,i)-vx_m(j,i-1))*dxi_inv
91  dvy_deta = (vy_m(j,i)-vy_m(j-1,i))*deta_inv
92 
93  dvx_deta = 0.25_dp*deta_inv &
94  *(vx_m(j+1,i)+vx_m(j+1,i-1)-vx_m(j-1,i)-vx_m(j-1,i-1))
95  dvy_dxi = 0.25_dp*dxi_inv &
96  *(vy_m(j,i+1)+vy_m(j-1,i+1)-vy_m(j,i-1)-vy_m(j-1,i-1))
97 
98  de_ssa(j,i) = sqrt( dvx_dxi*dvx_dxi &
99  + dvy_deta*dvy_deta &
100  + dvx_dxi*dvy_deta &
101  + 0.25_dp*(dvx_deta+dvy_dxi)*(dvx_deta+dvy_dxi) )
102 
103 ! ------ Term abbreviations
104 
105 #if (DYNAMICS==2)
106  if (.not.flag_shelfy_stream(j,i)) then
107 #endif
108 
109  do kc=0, kcmax
110  cvis1(kc) = aqxy1(kc)*h_c(j,i) &
111  *viscosity(de_ssa(j,i), &
112  temp_c(kc,j,i), temp_c_m(kc,j,i), 0.0_dp, &
113  enh_c(kc,j,i), 0_i2b)
114  end do
115  ! Ice shelves (floating ice) are assumed to consist of cold ice only
116 
117 #if (DYNAMICS==2)
118  else ! flag_shelfy_stream(j,i) == .true.
119 
120 #if (CALCMOD==-1 || CALCMOD==0)
121 
122  do kc=0, kcmax
123  cvis1(kc) = aqxy1(kc)*h_c(j,i) &
124  *viscosity(de_ssa(j,i), &
125  temp_c(kc,j,i), temp_c_m(kc,j,i), 0.0_dp, &
126  enh_c(kc,j,i), 0_i2b)
127  end do
128 
129 #elif (CALCMOD==1)
130 
131  do kt=0, ktmax
132  cvis0(kt) = dzeta_t*h_t(j,i) &
133  *viscosity(de_ssa(j,i), &
134  temp_t_m(kt,j,i), temp_t_m(kt,j,i), omega_t(kt,j,i), &
135  enh_t(kt,j,i), 1_i2b)
136  end do
137 
138  do kc=0, kcmax
139  cvis1(kc) = aqxy1(kc)*h_c(j,i) &
140  *viscosity(de_ssa(j,i), &
141  temp_c(kc,j,i), temp_c_m(kc,j,i), 0.0_dp, &
142  enh_c(kc,j,i), 0_i2b)
143  end do
144 
145 #elif (CALCMOD==2 || CALCMOD==3)
146 
147  do kc=0, kcmax
148  cvis1(kc) = aqxy1(kc)*h_c(j,i) &
149  *viscosity(de_ssa(j,i), &
150  temp_c(kc,j,i), temp_c_m(kc,j,i), omega_c(kc,j,i), &
151  enh_c(kc,j,i), 2_i2b)
152  end do
153 
154 #else
155  stop ' calc_vis_ssa: CALCMOD must be either -1, 0, 1, 2 or 3!'
156 #endif
157 
158  end if
159 #endif
160 
161 ! ------ Depth-integrated viscosity
162 
163  vis_int_g(j,i) = 0.0_dp
164 
165 #if (CALCMOD==1)
166  do kt=0, ktmax-1
167  vis_int_g(j,i) = vis_int_g(j,i)+0.5_dp*(cvis0(kt+1)+cvis0(kt))
168  end do
169 #endif
170 
171  do kc=0, kcmax-1
172  vis_int_g(j,i) = vis_int_g(j,i)+0.5_dp*(cvis1(kc+1)+cvis1(kc))
173  end do
174 
175  end if
176 
177 end do
178 end do
179 
180 end subroutine calc_vis_ssa
181 !
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
real(dp) function viscosity(de_val, temp_val, temp_m_val, omega_val, enh_val, i_flag_cold_temp)
Ice viscosity as a function of the effective strain rate and the temperature (in cold ice) or the wat...
Definition: viscosity.F90:39
Declarations of global variables for SICOPOLIS (for the ANT domain).
Definition: sico_vars.F90:35
Declarations of global variables for SICOPOLIS.