1 | MODULE fast_subs_univ |
---|
2 | |
---|
3 | implicit none |
---|
4 | |
---|
5 | CONTAINS |
---|
6 | |
---|
7 | !***************************************************** |
---|
8 | ! Commonly used subroutines for fast method |
---|
9 | ! written by Norbert Schorghofer 2007-2011 |
---|
10 | !***************************************************** |
---|
11 | |
---|
12 | pure function zint(y1,y2,z1,z2) |
---|
13 | ! interpolate between two values, y1*y2<0 |
---|
14 | implicit none |
---|
15 | real(8), intent(IN) :: y1,y2,z1,z2 |
---|
16 | real(8) zint |
---|
17 | zint = (y1*z2 - y2*z1)/(y1-y2) |
---|
18 | end function zint |
---|
19 | |
---|
20 | |
---|
21 | |
---|
22 | pure function equildepth(nz, z, rhosatav, rhosatav0, avrho1) |
---|
23 | !*********************************************************************** |
---|
24 | ! returns equilibrium depth for given ice content |
---|
25 | ! this is not the true (final) equilibrium depth |
---|
26 | !*********************************************************************** |
---|
27 | implicit none |
---|
28 | integer, intent(IN) :: nz |
---|
29 | real(8), intent(IN) :: z(nz), rhosatav(nz) |
---|
30 | real(8), intent(IN) :: rhosatav0, avrho1 |
---|
31 | integer i, typeE |
---|
32 | real(8) equildepth ! =zdepthE |
---|
33 | !real(8), external :: zint ! defined in allinterfaces.mod |
---|
34 | |
---|
35 | typeE = -9; equildepth = -9999. |
---|
36 | do i=1,nz |
---|
37 | if (rhosatav(i) <= avrho1) then |
---|
38 | typeE=i |
---|
39 | exit |
---|
40 | endif |
---|
41 | enddo |
---|
42 | if (typeE>1) then ! interpolate |
---|
43 | equildepth=zint(avrho1-rhosatav(typeE-1),avrho1-rhosatav(typeE),z(typeE-1),z(typeE)) |
---|
44 | end if |
---|
45 | if (typeE==1) equildepth=zint(avrho1-rhosatav0,avrho1-rhosatav(1),0.d0,z(1)) |
---|
46 | if (equildepth>z(nz)) equildepth=-9999. ! happens very rarely |
---|
47 | end function equildepth |
---|
48 | |
---|
49 | |
---|
50 | |
---|
51 | subroutine depths_avmeth(typeT, nz, z, rhosatav, rhosatav0, rlow, avrho1, & |
---|
52 | & porefill, typeF, zdepthF, B, ypp, typeG, zdepthG) |
---|
53 | !*********************************************************************** |
---|
54 | ! returns interface depth and ypp |
---|
55 | ! also returns lower geothermally limited boundary, if applicable |
---|
56 | ! |
---|
57 | ! this is a crucial subroutine |
---|
58 | ! |
---|
59 | ! B = Diff*bigstep/(porosity*icedensity) [SI units] |
---|
60 | !*********************************************************************** |
---|
61 | use math_mod, only: deriv2_simple, deriv1_onesided, deriv1, colint |
---|
62 | use ice_table_mod, only: constriction |
---|
63 | implicit none |
---|
64 | integer, intent(IN) :: nz, typeT |
---|
65 | real(8), intent(IN), dimension(nz) :: z, rhosatav, porefill |
---|
66 | real(8), intent(IN) :: rhosatav0, rlow, avrho1 |
---|
67 | integer, intent(OUT) :: typeF ! index of depth below which filling occurs |
---|
68 | real(8), intent(INOUT) :: zdepthF |
---|
69 | real(8), intent(IN) :: B |
---|
70 | real(8), intent(OUT) :: ypp(nz), zdepthG |
---|
71 | integer, intent(INOUT) :: typeG ! positive on input when Fgeotherm>0 |
---|
72 | |
---|
73 | integer i, typeP, nlb, newtypeG |
---|
74 | real(8) eta(nz), Jpump1, help(nz), yp(nz), zdepthFold, ap_one, ap(nz) |
---|
75 | real(8) leak, cumfill, cumfillabove |
---|
76 | |
---|
77 | if (typeT<0) then |
---|
78 | nlb = nz |
---|
79 | do i=1,nz |
---|
80 | eta(i) = constriction(porefill(i)) |
---|
81 | enddo |
---|
82 | else |
---|
83 | !nlb = typeT-1 |
---|
84 | nlb = typeT ! changed 2010-09-29 |
---|
85 | do i=1,typeT-1 |
---|
86 | eta(i) = constriction(porefill(i)) |
---|
87 | enddo |
---|
88 | do i=typeT,nz |
---|
89 | eta(i)=0. |
---|
90 | enddo |
---|
91 | end if |
---|
92 | |
---|
93 | !-fill depth |
---|
94 | zdepthFold = zdepthF |
---|
95 | typeF = -9; zdepthF = -9999. |
---|
96 | call deriv1(z,nz,rhosatav,rhosatav0,rlow,yp) ! yp also used below |
---|
97 | do i=1,nlb |
---|
98 | Jpump1 = (rhosatav(i)-avrho1)/z(i) ! <0 when stable |
---|
99 | ! yp is always <0 |
---|
100 | help(i) = Jpump1 - eta(i)*yp(i) |
---|
101 | leak = porefill(i)/B*(z(i)-zdepthFold)/(18./8314.) |
---|
102 | !help(i) = help(i)-leak ! optional |
---|
103 | if (help(i) <= 0.) then |
---|
104 | typeF=i |
---|
105 | !print *,'#',typeF,Jpump1,eta(typeF)*yp(typeF),leak |
---|
106 | exit |
---|
107 | endif |
---|
108 | enddo |
---|
109 | if (typeF>1) zdepthF = zint(help(typeF-1),help(typeF),z(typeF-1),z(typeF)) |
---|
110 | if (typeF==1) zdepthF=z(1) |
---|
111 | |
---|
112 | |
---|
113 | !-depth to shallowest perennial ice |
---|
114 | typeP = -9 |
---|
115 | do i=1,nz |
---|
116 | if (porefill(i)>0.) then |
---|
117 | typeP = i ! first point with ice |
---|
118 | exit |
---|
119 | endif |
---|
120 | enddo |
---|
121 | |
---|
122 | !-calculate ypp |
---|
123 | !call deriv1(z,nz,rhosatav,rhosatav0,rlow,yp) |
---|
124 | call deriv1(z,nz,eta(:),1.d0,eta(nz-1),ap) |
---|
125 | if (typeP>0 .and. typeP<nz-2) then |
---|
126 | call deriv1_onesided(typeP,z,nz,eta(:),ap_one) |
---|
127 | ! print *,typeP,ap(typeP),ap_one |
---|
128 | ap(typeP)=ap_one |
---|
129 | endif |
---|
130 | call deriv2_simple(z,nz,rhosatav(1:nz),rhosatav0,rlow,ypp(:)) |
---|
131 | !call deriv2_full(z,nz,eta(:),rhosatav(:),1.d0,rhosatav0,rhosatav(nz-1),ypp(:)) |
---|
132 | !write(40,*) rhosatav |
---|
133 | !write(41,*) yp |
---|
134 | !write(42,*) ypp |
---|
135 | ypp(:) = ap(:)*yp(1:)+eta(:)*ypp(:) |
---|
136 | !write(43,*) ypp |
---|
137 | !write(44,*) eta(1:nz) |
---|
138 | !write(45,*) (rhosatav(:)-avrho1)/z(:) |
---|
139 | ypp(:) = ypp(:)*18./8314. |
---|
140 | ! ypp values beyond nlb should not be used |
---|
141 | |
---|
142 | !-geothermal stuff |
---|
143 | if (typeT>0) typeG=-9 |
---|
144 | if (typeG<0) zdepthG=-9999. |
---|
145 | if (typeG>0 .and. typeT<0) then |
---|
146 | typeG=-9 |
---|
147 | do i=2,nz |
---|
148 | if (yp(i)>0.) then ! first point with reversed flux |
---|
149 | typeG=i |
---|
150 | zdepthG=zint(yp(i-1),yp(i),z(i-1),z(i)) |
---|
151 | !zdepthG=z(typeG) |
---|
152 | exit |
---|
153 | endif |
---|
154 | enddo |
---|
155 | else |
---|
156 | typeG = -9 |
---|
157 | endif |
---|
158 | if (typeG>0 .and. typeT<0) then |
---|
159 | call colint(porefill(:)/eta(:),z,nz,typeG-1,nz,cumfillabove) |
---|
160 | newtypeG = -9 |
---|
161 | do i=typeG,nz |
---|
162 | if (minval(eta(i:nz))<=0.) cycle ! eta=0 means completely full |
---|
163 | call colint(porefill(:)/eta(:),z,nz,i,nz,cumfill) |
---|
164 | if (cumfill<yp(i)*18./8314.*B) then ! usually executes on i=typeG |
---|
165 | if (i>typeG) then |
---|
166 | write(34,*) '# adjustment to geotherm depth by',i-typeG |
---|
167 | zdepthG = zint(yp(i-1)*18./8314.*B-cumfillabove, & ! no good |
---|
168 | & yp(i)*18./8314.*B-cumfill,z(i-1),z(i)) |
---|
169 | if (zdepthG>z(i) .or. zdepthG<z(i-1)) write(34,*) & |
---|
170 | & '# WARNING: zdepthG interpolation failed',i,z(i-1),zdepthG,z(i) |
---|
171 | newtypeG=i |
---|
172 | endif |
---|
173 | ! otherwise leave zdepthG untouched |
---|
174 | exit |
---|
175 | endif |
---|
176 | cumfillabove = cumfill |
---|
177 | enddo |
---|
178 | if (newtypeG>0) typeG=newtypeG |
---|
179 | end if |
---|
180 | ! if typeG>0, then all ice at and below typeG should be erased |
---|
181 | end subroutine depths_avmeth |
---|
182 | |
---|
183 | |
---|
184 | |
---|
185 | pure subroutine icechanges(nz,z,typeF,avdrho,avdrhoP,ypp, & |
---|
186 | & Diff,porosity,icefrac,bigstep,zdepthT,porefill,typeG) |
---|
187 | !*********************************************************** |
---|
188 | ! advances ice table, advances interface, grows pore ice |
---|
189 | ! |
---|
190 | ! a crucial subroutine |
---|
191 | !*********************************************************** |
---|
192 | use math_mod, only: colint |
---|
193 | use ice_table_mod, only: rho_ice |
---|
194 | implicit none |
---|
195 | integer, intent(IN) :: nz, typeF, typeG |
---|
196 | real(8), intent(IN) :: z(nz), ypp(nz), avdrho, avdrhoP |
---|
197 | real(8), intent(IN) :: Diff, porosity, icefrac, bigstep |
---|
198 | real(8), intent(INOUT) :: zdepthT, porefill(nz) |
---|
199 | integer j, erase, newtypeP, ub, typeP, typeT |
---|
200 | real(8) B, beta, integ |
---|
201 | |
---|
202 | B = Diff*bigstep*86400.*365.24/(porosity*927.) |
---|
203 | !B = Diff*bigstep*86400.*365.24/(porosity*rho_ice(T,'h2o')) |
---|
204 | |
---|
205 | ! advance ice table, avdrho>0 is retreat |
---|
206 | if (zdepthT>=0. .and. avdrho>0.) then |
---|
207 | typeP=-9999; typeT=-9999 |
---|
208 | do j=1,nz |
---|
209 | if (z(j)>zdepthT) then |
---|
210 | typeT=j |
---|
211 | exit |
---|
212 | endif |
---|
213 | enddo |
---|
214 | do j=1,nz |
---|
215 | if (porefill(j)>0.) then |
---|
216 | typeP=j |
---|
217 | exit |
---|
218 | endif |
---|
219 | enddo |
---|
220 | if (typeP==typeT) then ! new 2011-09-01 |
---|
221 | beta = (1-icefrac)/(1-porosity)/icefrac |
---|
222 | beta = Diff*bigstep*beta*86400*365.24/927. |
---|
223 | !beta = Diff*bigstep*beta*86400*365.24/rho_ice(T,'h2o') |
---|
224 | zdepthT = sqrt(2*beta*avdrho*18./8314. + zdepthT**2) |
---|
225 | endif |
---|
226 | endif |
---|
227 | if (zdepthT>z(nz)) zdepthT=-9999. |
---|
228 | |
---|
229 | ! advance interface, avdrhoP>0 is loss from zdepthP |
---|
230 | if (avdrhoP>0.) then |
---|
231 | erase=0 |
---|
232 | do j=1,nz |
---|
233 | if (typeF>0 .and. j>=typeF) exit ! don't retreat beyond typeF |
---|
234 | if (zdepthT>=0. .and. z(j)>zdepthT) exit |
---|
235 | call colint(porefill(1:nz)*z(1:nz),z(1:nz),nz,1,j,integ) |
---|
236 | erase = j |
---|
237 | if (integ>B*avdrhoP*18./8314.) exit |
---|
238 | end do |
---|
239 | if (erase>0) porefill(1:erase)=0. |
---|
240 | endif |
---|
241 | |
---|
242 | ! new depth |
---|
243 | newtypeP = -9 |
---|
244 | do j=1,nz |
---|
245 | if (zdepthT>=0. .and. z(j)>zdepthT) exit |
---|
246 | if (porefill(j)>0.) then |
---|
247 | newtypeP = j ! first point with pore ice |
---|
248 | exit |
---|
249 | endif |
---|
250 | enddo |
---|
251 | |
---|
252 | ! diffusive filling |
---|
253 | ub = typeF |
---|
254 | if (newtypeP>0 .and. typeF>0 .and. newtypeP<ub) ub=newtypeP |
---|
255 | if (ub>0) then |
---|
256 | do j=ub,nz |
---|
257 | porefill(j) = porefill(j) + B*ypp(j) |
---|
258 | if (porefill(j)<0.) porefill(j)=0. |
---|
259 | if (porefill(j)>1.) porefill(j)=1. |
---|
260 | if (zdepthT>=0. .and. z(j)>zdepthT) exit |
---|
261 | enddo |
---|
262 | end if |
---|
263 | |
---|
264 | ! below icetable |
---|
265 | if (zdepthT>=0.) then |
---|
266 | do j=1,nz |
---|
267 | if (z(j)>zdepthT) porefill(j) = icefrac/porosity |
---|
268 | enddo |
---|
269 | else |
---|
270 | ! geothermal lower boundary |
---|
271 | if (typeG>0) porefill(typeG:nz)=0. |
---|
272 | end if |
---|
273 | end subroutine icechanges |
---|
274 | |
---|
275 | END MODULE fast_subs_univ |
---|