source: trunk/LMDZ.COMMON/libf/evolution/NS_fast_subs_univ.F90 @ 3526

Last change on this file since 3526 was 3526, checked in by jbclement, 4 days ago

PEM:
Removing unused or redundant Norbert Schorghofer's subroutines (follow-up of r3493) + cleaning and some modifications of related subroutines.
JBC

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