-
Notifications
You must be signed in to change notification settings - Fork 0
/
Copy pathgeneral_tunnel_asymptotic.f90
126 lines (126 loc) · 5.35 KB
/
general_tunnel_asymptotic.f90
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
!
! hydrogen-tunnel: Static-field tunneling in a central potential
! Copyright (C) 2018-2022 Serguei Patchkovskii, [email protected]
!
! This program is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation, either version 3 of the License, or
! (at your option) any later version.
!
! This program is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with this program. If not, see <https://www.gnu.org/licenses/>.
!
! Routines dealing with the continuum-direction integration for general_tunnel.f90
!
module general_tunnel_asymptotic
use accuracy
use constants
use general_tunnel_data
use timer
!$ use OMP_LIB
implicit none
public
public rcsid_general_tunnel_asymptotic
!
character(len=clen), save :: rcsid_general_tunnel_asymptotic = "$Id: $"
!
contains
!
! Constructs an asymptotic solution as a power-series expansion:
!
! sqrt(x)*psi = Sum cn(k) x**(-k) exp( pm I [(sqrt(F)/3)*x**3 + (E/sqrt(F))*x ] )
!
! where pm = +1 for the outgoing solution and -1 for the incoming wave.
!
! The coefficients cn(k) are determined using recursively.
!
! The coefficients in the power series can grow rather large. In order to avoid
! exceeding the dynamic range of the underlying floating-point type, we'll
! scale coefficient cn(k) by x**-k, where x is the coordinate where we plan
! to evaluate the series. This way, all we need to do at the end is to sum
! up the coefficients.
!
subroutine asymptotic_solution(efield,energy,zeta2,pm,x,cn)
real(rk), intent(in) :: efield ! Electric field strength
complex(rk), intent(in) :: energy ! Energy of the solution
complex(rk), intent(in) :: zeta2 ! Separation parameter
real(rk), intent(in) :: pm ! +1 for outgoing solution; -1 for an incoming
real(rk), intent(in) :: x ! Coordinate where we need to evaluate the series
complex(rk), intent(out) :: cn(1:asymp_order) ! Power series coefficients for the solution
! cn(1) is arbitrarily chosen as 1.
!
integer(ik) :: l
complex(rk) :: temp
real(rk) :: xm ! 1/x
!
if (efield<=0) stop 'general_tunnel%asymptotic_solution - efield must be positive'
!
xm = 1._rk/x
cn(1) = xm
recurrence: do l=1,asymp_order-1
temp = pm*(0,1)*((energy**2)/efield - zeta2) * cn(l) * xm
if (l>1) temp = temp - 2*(energy/sqrt(efield))*(l-1) * cn(l-1) * xm**2
if (l>2) temp = temp - pm*(0,1)*((l-2)*(l-1) + (0.25_rk-mval**2)) * cn(l-2) * xm**3
cn(l+1) = temp/(2*l*sqrt(efield))
end do recurrence
!
if (verbose>=3) then
write (out,"(/'Asymptotic solution for pm=',f3.0)") pm
write (out,"(2(1x,g34.22e3,1x,g34.22e3,1x))") cn
write (out,"()")
end if
end subroutine asymptotic_solution
!
! Evaluates asymptotic series for the gradient of the incoming/outgoing solution
!
subroutine asymptotic_gradient(efield,energy,pm,x,cn,gr)
real(rk), intent(in) :: efield ! Electric field strength
complex(rk), intent(in) :: energy ! Energy of the solution
real(rk), intent(in) :: pm ! +1 for outgoing solution; -1 for an incoming
real(rk), intent(in) :: x ! Coordinate where we need to evaluate the series
complex(rk), intent(in) :: cn( 1:asymp_order) ! Solution coefficients
complex(rk), intent(out) :: gr(-1:asymp_order+1) ! Gradient coefficients
!
integer(ik) :: l
complex(rk) :: temp
real(rk) :: xm ! 1/x
!
if (efield<=0) stop 'general_tunnel%asymptotic_gradient - efield must be positive'
!
xm = 1._rk / x
gradient: do l=-1,asymp_order+1
temp = 0
if (l>= 1 .and. l<=asymp_order ) temp = temp + pm*(0,1)*(energy/sqrt(efield)) * cn(l)
if (l>= 2 .and. l<=asymp_order+1) temp = temp - (l-1) * cn(l-1) * xm
if (l>=-1 .and. l<=asymp_order-2) temp = temp + pm*(0,1)*sqrt(efield) * cn(l+2) * x**2
gr(l) = temp
end do gradient
!
if (verbose>=4) then
write (out,"(/'Asymptotic gradient for pm=',f3.0)") pm
write (out,"(2(1x,g34.22e3,1x,g34.22e3,1x))") gr
write (out,"()")
end if
end subroutine asymptotic_gradient
!
function evaluate_asymptote(efield,energy,pm,cn,x) result (v)
real(rk), intent(in) :: efield ! Electric field strength
complex(rk), intent(in) :: energy ! Energy of the solution
real(rk), intent(in) :: pm ! +1 for outgoing solution; -1 for an incoming
complex(rk), intent(in) :: cn(:) ! Solution coefficients
real(rk), intent(in) :: x ! Coordinate where we need the solution
complex(rk) :: v
!
complex(rk) :: phase
!
v = sum(cn)
phase = (sqrt(efield)/3._rk)*x**3 + (energy/sqrt(efield))*x
v = v * exp(pm*(0,1)*phase)
end function evaluate_asymptote
!
end module general_tunnel_asymptotic