intitial_spatial_distribution Subroutine

public subroutine intitial_spatial_distribution(params, spp, P, F)

In addition to spatial distribution function, Avalanche_4D samples the avalanche distribution function used to initialize the components of velocity for all particles.

Arguments

Type IntentOptional AttributesName
type(KORC_PARAMS), intent(inout) :: params

Core KORC simulation parameters.

type(SPECIES), intent(inout), DIMENSION(:), ALLOCATABLE:: spp

An instance of the derived type SPECIES containing all the parameters and simulation variables of the different species in the simulation.

type(PROFILES), intent(in) :: P

An instance of the KORC derived type PROFILES.

type(FIELDS), intent(in) :: F

An instance of the KORC derived type FIELDS.


Calls

proc~~intitial_spatial_distribution~~CallsGraph proc~intitial_spatial_distribution intitial_spatial_distribution proc~korc_abort korc_abort proc~intitial_spatial_distribution->proc~korc_abort mpi_abort mpi_abort proc~korc_abort->mpi_abort

Called by

proc~~intitial_spatial_distribution~~CalledByGraph proc~intitial_spatial_distribution intitial_spatial_distribution proc~set_up_particles_ic set_up_particles_ic proc~set_up_particles_ic->proc~intitial_spatial_distribution program~main main program~main->proc~set_up_particles_ic

Contents


Source Code

subroutine intitial_spatial_distribution(params,spp,P,F)
  !! @note Subroutine that contains calls to the different subroutines 
  !! for initializing the simulated particles with various
  !! spatial distribution functions. @endnote
  TYPE(KORC_PARAMS), INTENT(INOUT) 			  :: params
  !! Core KORC simulation parameters.
  TYPE(SPECIES), DIMENSION(:), ALLOCATABLE, INTENT(INOUT) :: spp
  !! An instance of the derived type SPECIES containing all the parameters and 
  !! simulation variables of the different species in the simulation.
  TYPE(PROFILES), INTENT(IN)                              :: P
  !! An instance of the KORC derived type PROFILES.
  TYPE(FIELDS), INTENT(IN)                                   :: F
  !! An instance of the KORC derived type FIELDS.
  INTEGER 						  :: ss
  !! Species iterator.
  INTEGER 				:: mpierr

  do ss=1_idef,params%num_species
     SELECT CASE (TRIM(spp(ss)%spatial_distribution))
     CASE ('UNIFORM')
        call uniform(spp(ss))
     CASE ('DISK')
        call disk(params,spp(ss))
     CASE ('TORUS')
        call torus(params,spp(ss))
     CASE ('EXPONENTIAL-TORUS')
        call exponential_torus(params,spp(ss))
     CASE ('GAUSSIAN-TORUS')
        call gaussian_torus(params,spp(ss))
     CASE ('ELLIPTIC-TORUS')
        call elliptic_torus(params,spp(ss))
     CASE ('EXPONENTIAL-ELLIPTIC-TORUS')
        call exponential_elliptic_torus(params,spp(ss))
     CASE ('GAUSSIAN-ELLIPTIC-TORUS')
        call gaussian_elliptic_torus(params,spp(ss))
     CASE ('2D-GAUSSIAN-ELLIPTIC-TORUS-MH')
        call MH_gaussian_elliptic_torus(params,spp(ss))
     CASE ('AVALANCHE-4D')
        call get_Avalanche_4D(params,spp(ss),P,F)
        !! In addition to spatial distribution function, [[Avalanche_4D]]
        !! samples the avalanche distribution function used to initialize
        !! the components of velocity for all particles.
     CASE ('TRACER')
        spp(ss)%vars%X(:,1)=spp(ss)%Xtrace(1)
        spp(ss)%vars%X(:,2)=spp(ss)%Xtrace(2)
        spp(ss)%vars%X(:,3)=spp(ss)%Xtrace(3)
     CASE ('SPONG-3D')
        call Spong_3D(params,spp(ss))
     CASE ('HOLLMANN-3D')
        call get_Hollmann_distribution_3D(params,spp(ss),F)
     CASE ('HOLLMANN-3D-PSI')
        call get_Hollmann_distribution_3D_psi(params,spp(ss),F)
     CASE ('HOLLMANN-1DTRANSPORT')
        call get_Hollmann_distribution_1Dtransport(params,spp(ss),F)
     CASE('MH_psi')

#if DBG_CHECK        
#else
        if (spp(ss)%ppp*params%mpi_params%nmpi.lt.10) then
           if(params%mpi_params%rank.eq.0) then
              write(6,*) &
                   'num_samples need to be atleast 10 but is only: ', &
                   spp(ss)%ppp*params%mpi_params%nmpi
           end if
           call korc_abort(19)
        end if
#endif
        
        call MH_psi(params,spp(ss),F)
     CASE('FIO_therm')

        if (spp(ss)%ppp*params%mpi_params%nmpi.lt.10) then
           if(params%mpi_params%rank.eq.0) then
              write(6,*) &
                   'num_samples need to be atleast 10 but is only: ', &
                   spp(ss)%ppp*params%mpi_params%nmpi
           end if
           call korc_abort(19)
        end if
        
        call FIO_therm(params,spp(ss),F,P)
     CASE('BMC_radial')

        if (spp(ss)%ppp*params%mpi_params%nmpi.lt.10) then
           if(params%mpi_params%rank.eq.0) then
              write(6,*) &
                   'num_samples need to be atleast 10 but is only: ', &
                   spp(ss)%ppp*params%mpi_params%nmpi
           end if
           call korc_abort(19)
        end if
        
        call BMC_radial(params,spp(ss),F,P)
     CASE DEFAULT
        call torus(params,spp(ss))
     END SELECT
  end do
end subroutine intitial_spatial_distribution