Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
type(KORC_PARAMS), | intent(in) | :: | params | Core KORC simulation parameters. |
||
type(FIELDS), | intent(in) | :: | F | An instance of the KORC derived type FIELDS. |
||
real(kind=rp), | intent(in), | DIMENSION(:,:), ALLOCATABLE | :: | Y | Cylindrical coordinates of each particle in the simulation; Y(1,:) = , Y(2,:) = , Y(3,:) = . |
|
real(kind=rp), | intent(inout), | DIMENSION(:,:), ALLOCATABLE | :: | E | Electric field components in cylindricalcoordinates; E(1,:) = , E(2,:) = , E(3,:) = |
|
real(kind=rp), | intent(inout), | DIMENSION(:,:), ALLOCATABLE | :: | B | Magnetic field components in cylindrical coordinates; B(1,:) = , B(2,:) = , B(3,:) = |
|
real(kind=rp), | intent(inout), | DIMENSION(:,:), ALLOCATABLE | :: | gradB | Gradient of magnitude of magnetic field in cylindrical coordinates; gradB(1,:) = , B(2,:) = , B(3,:) = |
|
real(kind=rp), | intent(inout), | DIMENSION(:,:), ALLOCATABLE | :: | curlB | Curl of magnetic field unit vector in cylindrical coordinates |
|
integer(kind=is), | intent(in), | DIMENSION(:), ALLOCATABLE | :: | flag | Flag for each particle to decide whether it is being followed (flag=T) or not (flag=F). |
|
real(kind=rp), | intent(inout), | DIMENSION(:), ALLOCATABLE | :: | PSIp |
subroutine analytical_fields_GC_init(params,F,Y,E,B,gradB,curlb,flag,PSIp)
TYPE(KORC_PARAMS), INTENT(IN) :: params
!! Core KORC simulation parameters.
TYPE(FIELDS), INTENT(IN) :: F
!! An instance of the KORC derived type FIELDS.
REAL(rp), DIMENSION(:,:), ALLOCATABLE, INTENT(IN) :: Y
!! Cylindrical coordinates of each particle in the simulation;
!! Y(1,:) = \(r\), Y(2,:) = \(\theta\), Y(3,:) = \(\zeta\).
REAL(rp), DIMENSION(:,:), ALLOCATABLE, INTENT(INOUT) :: B
!! Magnetic field components in cylindrical coordinates;
!! B(1,:) = \(B_R\), B(2,:) = \(B_\phi\), B(3,:) = \(B_Z\)
REAL(rp), DIMENSION(3) :: Btmp
!! Placeholder for magnetic field components in cylindrical coordinates;
!! B(1,:) = \(B_R\), B(2,:) = \(B_\phi\), B(3,:) = \(B_Z\)
REAL(rp), DIMENSION(:,:), ALLOCATABLE, INTENT(INOUT) :: gradB
!! Gradient of magnitude of magnetic field in cylindrical coordinates;
!! gradB(1,:) = \(\nabla_R B\), B(2,:) = \(\nabla_\phi B_\),
!! B(3,:) = \(\nabla_Z B\)
REAL(rp), DIMENSION(:,:), ALLOCATABLE, INTENT(INOUT) :: curlB
!! Curl of magnetic field unit vector in cylindrical coordinates
REAL(rp), DIMENSION(:,:), ALLOCATABLE, INTENT(INOUT) :: E
!! Electric field components in cylindricalcoordinates;
!! E(1,:) = \(E_R\), E(2,:) = \(E_\phi\), E(3,:) = \(E_Z\)
REAL(rp), DIMENSION(:), ALLOCATABLE, INTENT(INOUT) :: PSIp
INTEGER(is), DIMENSION(:), ALLOCATABLE, INTENT(IN) :: flag
!! Flag for each particle to decide whether it is being followed (flag=T)
!! or not (flag=F).
REAL(rp) :: Ezeta
!! Toroidal electric field \(E_\zeta\).
REAL(rp) :: Bzeta
!! Toroidal magnetic field \(B_\zeta\).
REAL(rp) :: Bp
!! Poloidal magnetic field \(B_\theta(r)\).
REAL(rp) :: eta
!! Aspect ratio \(\eta\).
REAL(rp) :: q
!! Safety profile \(q(r)\).
INTEGER(ip) :: pp ! Iterator(s)
!! Particle iterator.
INTEGER(ip) :: ss
!! Particle species iterator.
REAL(rp) :: dRBR
REAL(rp) :: dRBPHI
REAL(rp) :: dRBZ
REAL(rp) :: dZBR
REAL(rp) :: dZBPHI
REAL(rp) :: dZBZ
REAL(rp) :: Bmag
REAL(rp) :: dRbhatPHI
REAL(rp) :: dRbhatZ
REAL(rp) :: dZbhatR
REAL(rp) :: dZbhatPHI
REAL(rp) :: qprof
REAL(rp) :: rm,theta
!write(output_unit_write,'("Y: ",E17.10)') Y
ss = SIZE(Y,1)
!$OMP PARALLEL DO FIRSTPRIVATE(ss) PRIVATE(pp,rm,Btmp,qprof,dRBR,dRBPHI, &
!$OMP dRBZ,dZBR,dZBPHI,dZBZ,Bmag,dRbhatPHI,dRbhatZ,dZbhatR,dZbhatPHI, &
!$OMP theta,PSIp) &
!$OMP& SHARED(F,Y,E,B,gradB,curlb,flag)
do pp=1_idef,ss
! if ( flag(pp) .EQ. 1_is ) then
rm=sqrt((Y(pp,1)-F%AB%Ro)**2+Y(pp,3)**2)
theta=atan2(Y(pp,3),(Y(pp,1)-F%AB%Ro))
qprof = 1.0_rp + (rm/F%AB%lambda)**2
! write(output_unit_write,*) 'rm: ',rm
! write(output_unit_write,*) 'R0: ',F%AB%Ro
! write(output_unit_write,*) 'Y_R: ',Y(pp,1)
! write(output_unit_write,*) 'theta: ',theta
PSIp(pp)=Y(pp,1)*F%AB%lambda**2*F%Bo/ &
(2*F%AB%qo*(F%AB%Ro+rm*cos(theta)))* &
log(1+(rm/F%AB%lambda)**2)
Btmp(1)=F%AB%Bo*Y(pp,3)/(F%AB%qo*qprof*Y(pp,1))
Btmp(2)=-F%AB%Bo*F%AB%Ro/Y(pp,1)
Btmp(3)=-F%AB%Bo*(Y(pp,1)-F%AB%Ro)/(F%AB%qo*qprof*Y(pp,1))
B(pp,1) = Btmp(1)*COS(Y(pp,2)) - Btmp(2)*SIN(Y(pp,2))
B(pp,2) = Btmp(1)*SIN(Y(pp,2)) + Btmp(2)*COS(Y(pp,2))
B(pp,3) = Btmp(3)
dRBR=-F%AB%Bo*Y(pp,3)/(F%AB%qo*qprof*Y(pp,1))*(1./Y(pp,1)+ &
2*(Y(pp,1)-F%AB%Ro)/(F%AB%lambda**2*qprof))
dRBPHI=F%AB%Bo*F%AB%Ro/Y(pp,1)**2
dRBZ=F%AB%Bo/(F%AB%qo*qprof*Y(pp,1))*(-F%AB%Ro/Y(pp,1)+2*(Y(pp,1)- &
F%AB%Ro)**2/(F%AB%lambda**2*qprof))
dZBR=F%AB%Bo/(F%AB%qo*qprof*Y(pp,1))*(1-2*Y(pp,3)*Y(pp,3)/ &
(F%AB%lambda**2*qprof))
dZBPHI=0._rp
dZBZ=F%AB%Bo*(Y(pp,1)-F%AB%Ro)/(F%AB%qo*Y(pp,1))*2*Y(pp,3)/ &
((F%AB%lambda*qprof)**2)
Bmag=sqrt(B(pp,1)*B(pp,1)+B(pp,2)*B(pp,2)+B(pp,3)*B(pp,3))
gradB(pp,1)=(B(pp,1)*dRBR+B(pp,2)*dRBPHI+B(pp,3)*dRBZ)/Bmag
gradB(pp,2)=0._rp
gradB(pp,3)=(B(pp,1)*dZBR+B(pp,2)*dZBPHI+B(pp,3)*dZBZ)/Bmag
dRbhatPHI=(Bmag*dRBPHI-B(pp,2)*gradB(pp,1))/Bmag**2
dRbhatZ=(Bmag*dRBZ-B(pp,3)*gradB(pp,1))/Bmag**2
dZbhatR=(Bmag*dZBR-B(pp,1)*gradB(pp,3))/Bmag**2
dZbhatPHI=(Bmag*dZBPHI-B(pp,2)*gradB(pp,3))/Bmag**2
curlb(pp,1)=-dZbhatPHI
curlb(pp,2)=dZbhatR-dRbhatZ
curlb(pp,3)=B(pp,2)/(Bmag*Y(pp,1))+dRbhatPHI
! if (abs(F%Eo) > 0) then
E(pp,1) = 0.0_rp
E(pp,2) = F%Eo*F%AB%Ro/Y(pp,1)
E(pp,3) = 0.0_rp
! end if
! end if
end do
!$OMP END PARALLEL DO
!write(output_unit_write,'("B: ",E17.10)') B
end subroutine analytical_fields_GC_init