module reflections use const_and_precisions, only : wp_, comp_tiny, comp_eps, comp_huge, zero, one implicit none private public :: reflect, inters_linewall public :: linecone_coord, interssegm_coord, interssegm public :: wall_refl contains subroutine reflect(ki,nsurf,ko) implicit none real(wp_), intent(in), dimension(3) :: ki real(wp_), intent(in), dimension(3) :: nsurf real(wp_), intent(out), dimension(3) :: ko real(wp_) :: twokn,norm2 norm2 = dot_product(nsurf,nsurf) if (norm2>zero) then twokn = 2.0_wp_*dot_product(ki,nsurf)/norm2 ko=ki-twokn*nsurf else ko=ki end if end subroutine reflect subroutine inters_linewall(xv,kv,rw,zw,nw,sint,normw) implicit none real(wp_), intent(in), dimension(3) :: xv,kv integer, intent(in) :: nw real(wp_), dimension(nw), intent(in) :: rw,zw real(wp_), intent(out) :: sint real(wp_), dimension(3), intent(out) :: normw integer :: i,j,ni,iint,first real(wp_), dimension(2) :: si,ti real(wp_) :: drw,dzw,xint,yint,rint,l,kxy sint=comp_huge iint=0 normw=zero do i=1,nw-1 !search intersections with i-th wall segment call linecone_coord(xv,kv,rw(i:i+1),zw(i:i+1),si,ti,ni) !discard solutions with s<=0 first=ni+1 do j=1,ni if (si(j)>zero) then first=j exit end if end do do j=first,ni if ((si(j)=zero .and. ti(j)<=one) then !check intersection is in r,z range and keep the closest sint = si(j) iint = i end if end do end do if (iint==0) return !calculate wall normal at intersection point drw = rw(iint+1)-rw(iint) dzw = zw(iint+1)-zw(iint) xint = xv(1) + sint*kv(1) yint = xv(2) + sint*kv(2) rint = hypot(xint, yint) l = hypot(drw, dzw) kxy = norm2(kv(1:2)) normw(3) = -drw/l if (rint>zero) then normw(1) = xint/rint*dzw/l normw(2) = yint/rint*dzw/l else normw(1) = kv(1)/kxy*dzw/l normw(2) = kv(2)/kxy*dzw/l end if !reverse normal if k.n>0 if (dot_product(normw,kv)>zero) normw=-normw end subroutine inters_linewall subroutine linecone_coord(xv,kv,rs,zs,s,t,n) use utils, only : bubble implicit none real(wp_), intent(in), dimension(3) :: xv,kv real(wp_), intent(in), dimension(2) :: rs,zs real(wp_), dimension(2), intent(out) :: s,t integer, intent(out) :: n real(wp_) :: x0,y0,z0,kx,ky,kz real(wp_) :: dr,dz,r,a,bhalf,c,delta,tvertex,zvertex,srmin,rmin,zrmin x0=xv(1) y0=xv(2) z0=xv(3) kx=kv(1) ky=kv(2) kz=kv(3) dr = rs(2)-rs(1) dz = zs(2)-zs(1) s = 0 t = 0 if (abs(dz)=zero .and. s<=one .and. & t>=zero .and. t<=one) interssegm = .true. end function interssegm subroutine wall_refl(xv,anv,ext,eyt,xvrfl,anvrfl,extr,eytr,walln,irfl) use limiter, only : rlim,zlim,nlim use utils, only : inside implicit none ! arguments integer :: irfl real(wp_), dimension(3) :: xv,anv,xvrfl,anvrfl,walln complex(wp_) :: ext,eyt,extr,eytr ! local variables real(wp_) :: smax,rrm,zzm real(wp_), dimension(3) :: anv0,vv1,vv2,vv3 complex(wp_) :: eztr complex(wp_), dimension(3) :: evin,evrfl ! anv0=anv/sqrt(anv(1)**2+anv(2)**2+anv(3)**2) rrm=1.0e-2_wp_*sqrt(xv(1)**2+xv(2)**2) zzm=1.0e-2_wp_*xv(3) ! ! computation of reflection coordinates and normal to the wall call inters_linewall(xv/1.0e2_wp_,anv0,rlim(1:nlim),zlim(1:nlim), & nlim,smax,walln) smax=smax*1.0e2_wp_ xvrfl=xv+smax*anv0 irfl=1 if (.not.inside(rlim,zlim,rrm,zzm)) then ! first wall interface is outside-inside if (dot_product(walln,walln)