get_fio_electric_fields Subroutine

public subroutine get_fio_electric_fields(prtcls, F, params)

Arguments

Type IntentOptional AttributesName
type(PARTICLES), intent(inout) :: prtcls
type(FIELDS), intent(in) :: F
type(KORC_PARAMS), intent(in) :: params

Calls

proc~~get_fio_electric_fields~~CallsGraph proc~get_fio_electric_fields get_fio_electric_fields interface~fio_eval_field fio_eval_field proc~get_fio_electric_fields->interface~fio_eval_field

Called by

proc~~get_fio_electric_fields~~CalledByGraph proc~get_fio_electric_fields get_fio_electric_fields proc~interp_fields interp_fields proc~interp_fields->proc~get_fio_electric_fields proc~get_fields get_fields proc~get_fields->proc~interp_fields proc~mh_psi MH_psi proc~mh_psi->proc~get_fields proc~sample_hollmann_distribution_3d_psi sample_Hollmann_distribution_3D_psi proc~sample_hollmann_distribution_3d_psi->proc~get_fields proc~unitvectors unitVectors proc~unitvectors->proc~get_fields proc~get_hollmann_distribution_3d_psi get_Hollmann_distribution_3D_psi proc~get_hollmann_distribution_3d_psi->proc~sample_hollmann_distribution_3d_psi proc~gyro_distribution gyro_distribution proc~gyro_distribution->proc~unitvectors

Contents


Source Code

  subroutine get_fio_electric_fields(prtcls, F, params)
    TYPE(PARTICLES), INTENT(INOUT) :: prtcls
    TYPE(FIELDS), INTENT(IN)       :: F
    TYPE(KORC_PARAMS), INTENT(IN)  :: params
    INTEGER (C_INT)                :: status
    INTEGER                        :: pp
    REAL(rp), DIMENSION(3)         :: x
    REAL(rp), DIMENSION(3)         :: Etmp

    if (prtcls%cart) then
       !$OMP PARALLEL DO DEFAULT(SHARED) PRIVATE(pp,status,x)
       do pp = 1, SIZE(prtcls%hint)
          if (prtcls%flagCon(pp) .EQ. 1_is) then
             x = prtcls%X(pp,:)*params%cpp%length
             status = fio_eval_field(F%FIO_E, x(1),                      &
                  prtcls%E(pp,1),                        &
                  prtcls%hint(pp))

             if (status .eq. FIO_NO_DATA) then
                prtcls%E(pp,:) = 0
             else if (status .ne. FIO_SUCCESS) then
                prtcls%flagCon(pp) = 0_is
             end if
          end if
       end do
       !$OMP END PARALLEL DO
    else

       Etmp=0._rp
       
       !$OMP PARALLEL DO DEFAULT(none) &
       !$OMP& SHARED(prtcls,params,F) &
       !$OMP& PRIVATE(pp,status,x) &
       !$OMP& FIRSTPRIVATE(Etmp)
       do pp = 1, SIZE(prtcls%hint)
          if (prtcls%flagCon(pp) .EQ. 1_is) then
             x(1) = prtcls%Y(pp,1)*params%cpp%length
             x(2) = prtcls%Y(pp,2)
             x(3) = prtcls%Y(pp,3)*params%cpp%length
             
             status = fio_eval_field(F%FIO_E, x(1),                      &
                  Etmp(1),prtcls%hint(pp))

             if (status .eq. FIO_NO_DATA) then
                prtcls%E(pp,:) = 0
                prtcls%flagCon(pp) = 0_is
             else if (status .ne. FIO_SUCCESS) then
                prtcls%flagCon(pp) = 0_is
             end if

             if (.not.params%GC_coords) then             
                prtcls%E(pp,1)=(Etmp(1)*cos(x(2))-Etmp(2)*sin(x(2)))/ &
                     params%cpp%Eo
                prtcls%E(pp,2)=(Etmp(1)*sin(x(2))+Etmp(2)*cos(x(2)))/ &
                     params%cpp%Eo
                prtcls%E(pp,3)=Etmp(3)/params%cpp%Eo
             else
                prtcls%E(pp,1)=Etmp(1)/params%cpp%Eo
                prtcls%E(pp,2)=Etmp(2)/params%cpp%Eo
                prtcls%E(pp,3)=Etmp(3)/params%cpp%Eo
             end if
             
          end if
       end do
       !$OMP END PARALLEL DO
    end if
  end subroutine get_fio_electric_fields