module dispersion ! use const_and_precisions, only : wp_,zero,one,half,two,im,czero,cunit,pi, & sqrt_pi implicit none ! local constants integer, parameter :: npts=500 real(wp_), parameter :: tmax=5.0_wp_,dtex=2.0_wp_*tmax/dble(npts) ! variables real(wp_), dimension(npts+1), save :: ttv,extv ! contains ! ! subroutine colddisp(xg,yg,npl,nprf,sox) ! solution cold dispersion relation ! implicit none ! arguments ! xg = omegap^2/omega^2 ! yg = omegac/omega ! npl = N parallel to B ! nprf = N perpendicular to B (cold) ! sox = mode (-1 => O mode, +1 => X mode) real(wp_) :: xg,yg,npl,nprf,sox ! local variables real(wp_) :: yg2,npl2,dnl,del,dxg ! npl2=npl*npl dnl=one-npl2 dxg=one-xg yg2=yg*yg del=sqrt(dnl*dnl+4.0_wp_*npl2*dxg/yg2) nprf=sqrt(dxg-npl2-xg*yg2*(one+npl2+sox*del)/(dxg-yg2)/2.0_wp_) ! end subroutine colddisp ! ! ! subroutine harmnumber(yg,mu,npl,nhmin,nhmax,iwr) ! computation of minimum and maximum harmonic ! implicit none ! local constants ! expcr = maximum value for mu*(gamma-1) above which the distribution function ! is considered to be 0 real(wp_), parameter :: expcr=16.0_wp_ ! arguments ! yg = omegac/omega ! npl = parallel N ! mu = mc^2/Te ! nh = number of the armonic (min/max) ! iwr = weakly (iwr=1) or fully relativistic approximation integer :: nhmin,nhmax,iwr real(wp_) :: yg,npl,mu ! local variables integer :: nh,nhc real(wp_) :: ygc,ygn,npl2,gg,dnl,rdu2,argexp,uu2 ! nhmin=0 nhmax=0 npl2=npl**2 dnl=one-npl2 ! if(iwr.eq.1) then ygc=max(one-0.5_wp_*npl2,zero) else ygc=sqrt(max(dnl,zero)) end if nhc=int(ygc/yg) if (nhc*ygrmaxreal).or.(yabs>rmaxreal)) then iflag=1 return end if qrho = x**2 + y**2 xabsq = xabs**2 xquad = xabsq - yabs**2 yquad = 2*xabs*yabs if (qrho<0.085264_wp_) then ! ! if (qrho<0.085264_wp_) then the faddeeva-function is evaluated ! using a power-series (abramowitz/stegun, equation (7.1.5), p.297) ! n is the minimum number of terms needed to obtain the required ! accuracy ! qrho = (1-0.85_wp_*y)*sqrt(qrho) n = idnint(6 + 72*qrho) j = 2*n+1 xsum = 1.0_wp_/j ysum = 0.0_wp_ do i=n, 1, -1 j = j - 2 xaux = (xsum*xquad - ysum*yquad)/i ysum = (xsum*yquad + ysum*xquad)/i xsum = xaux + 1.0_wp_/j end do u1 = -factor*(xsum*yabs + ysum*xabs) + 1.0_wp_ v1 = factor*(xsum*xabs - ysum*yabs) daux = exp(-xquad) u2 = daux*cos(yquad) v2 = -daux*sin(yquad) u = u1*u2 - v1*v2 v = u1*v2 + v1*u2 else ! ! if (qrho>1.o) then w(z) is evaluated using the laplace ! continued fraction ! nu is the minimum number of terms needed to obtain the required ! accuracy ! ! if ((qrho>0.085264_wp_).and.(qrho<1.0)) then w(z) is evaluated ! by a truncated taylor expansion, where the laplace continued fraction ! is used to calculate the derivatives of w(z) ! kapn is the minimum number of terms in the taylor expansion needed ! to obtain the required accuracy ! nu is the minimum number of terms of the continued fraction needed ! to calculate the derivatives with the required accuracy ! if (qrho>1.0_wp_) then h = 0.0_wp_ kapn = 0 qrho = sqrt(qrho) nu = idint(3 + (1442/(26*qrho+77))) else qrho = (1-y)*sqrt(1-qrho) h = 1.88_wp_*qrho h2 = 2*h kapn = idnint(7 + 34*qrho) nu = idnint(16 + 26*qrho) endif if (h>0.0_wp_) qlambda = h2**kapn rx = 0.0_wp_ ry = 0.0_wp_ sx = 0.0_wp_ sy = 0.0_wp_ do n=nu, 0, -1 np1 = n + 1 tx = yabs + h + np1*rx ty = xabs - np1*ry c = 0.5_wp_/(tx**2 + ty**2) rx = c*tx ry = c*ty if ((h>0.0_wp_).and.(n<=kapn)) then tx = qlambda + sx sx = rx*tx - ry*sy sy = ry*tx + rx*sy qlambda = qlambda/h2 endif end do if (h==0.0_wp_) then u = factor*rx v = factor*ry else u = factor*sx v = factor*sy end if if (yabs==0.0_wp_) u = exp(-xabs**2) end if ! ! evaluation of w(z) in the other quadrants ! if (yi<0.0_wp_) then if (qrho<0.085264_wp_) then u2 = 2*u2 v2 = 2*v2 else xquad = -xquad ! ! the following if-statement protects 2*exp(-z**2) ! against overflow ! if ((yquad>rmaxgoni).or. (xquad>rmaxexp)) then iflag=1 return end if w1 = 2.0_wp_*exp(xquad) u2 = w1*cos(yquad) v2 = -w1*sin(yquad) end if u = u2 - u v = v2 - v if (xi>0.0_wp_) v = -v else if (xi<0.0_wp_) v = -v end if zr = -v*rpi zi = u*rpi end subroutine zetac ! end module dispersion