cart_to_cyl Subroutine

public subroutine cart_to_cyl(X, Xcyl)

Here, the coordinate transformation is:

Arguments

Type IntentOptional AttributesName
real(kind=rp), intent(in), DIMENSION(:,:), ALLOCATABLE:: X

Particles' position in Cartesian coordinates. X(1,:) = , X(2,:) = , X(3,:) =

real(kind=rp), intent(inout), DIMENSION(:,:), ALLOCATABLE:: Xcyl

Particles' position in cylindrical coordinates. Xcyl(1,:) = , Xcyl(2,:) = , Xcyl(3,:) =


Contents

Source Code


Source Code

  subroutine cart_to_cyl(X,Xcyl)
    !! @note  Subroutine that converts the position of simulated particles
    !! from Cartesian \((x,y,z)\) to cylindrical \((R,\phi,Z)\) coordinates.
    !! @endnote
    !! Here, the coordinate transformation is:
    !!
    !! $$R = \sqrt{x^2 + y^2},$$
    !! $$\phi = \arctan{\left( \frac{y}{x} \right)},$$
    !! $$Z = z.$$
    implicit none
    REAL(rp), DIMENSION(:,:), ALLOCATABLE, INTENT(IN)      :: X
    !! Particles' position in Cartesian coordinates. X(1,:) = \(x\), X(2,:)
    !! = \(y\), X(3,:) = \(z\)
    REAL(rp), DIMENSION(:,:), ALLOCATABLE, INTENT(INOUT)   :: Xcyl
    !! Particles' position in cylindrical coordinates. Xcyl(1,:) = \(R\),
    !! Xcyl(2,:) = \(\phi\), Xcyl(3,:) = \(Z\)
    INTEGER                                                :: pp
    !! Iterator.
    INTEGER                                                :: ss
    !! Iterator.

!    write(6,'("X_X: ",E17.10)') X(1:10,1)
!    write(6,'("X_Y: ",E17.10)') X(1:10,2)
!    write(6,'("X_Z: ",E17.10)') X(1:10,3)
    
    if (X(2,1).eq.0) then
       ss=1_idef
    else
       ss = size(X,1)
    end if

!    write(6,*) 'varX',X(:,1)
!    write(6,*) 'varY',X(:,2)
!    write(6,*) 'varR',Xcyl(:,1)
!    write(6,*) 'varPHI',Xcyl(:,2)

!    !$OMP PARALLEL DO FIRSTPRIVATE(ss) PRIVATE(pp) SHARED(X,Xcyl)
    do pp=1_idef,ss
!       write(6,*) 'pp',pp
       Xcyl(pp,1) = SQRT(X(pp,1)**2 + X(pp,2)**2)
       Xcyl(pp,2) = ATAN2(X(pp,2), X(pp,1))
       Xcyl(pp,2) = MODULO(Xcyl(pp,2), 2.0_rp*C_PI)
       Xcyl(pp,3) = X(pp,3)
    end do
!    !$OMP END PARALLEL DO

!    write(6,*) 'varX',X(:,1)
!    write(6,*) 'varY',X(:,2)
!    write(6,*) 'varR',Xcyl(:,1)
!    write(6,*) 'varPHI',Xcyl(:,2)


    
  end subroutine cart_to_cyl