Report Typos and Errors    
Semi-Lagrangian Library
Modular library for kinetic and gyrokinetic simulations of plasmas in fusion energy devices.
sll_m_particle_sampling_interface.F90
Go to the documentation of this file.
1 !**************************************************************
2 ! Copyright INRIA
3 ! Authors :
4 ! CALVI project team
5 !
6 ! This code SeLaLib (for Semi-Lagrangian-Library)
7 ! is a parallel library for simulating the plasma turbulence
8 ! in a tokamak.
9 !
10 ! This software is governed by the CeCILL-B license
11 ! under French law and abiding by the rules of distribution
12 ! of free software. You can use, modify and redistribute
13 ! the software under the terms of the CeCILL-B license as
14 ! circulated by CEA, CNRS and INRIA at the following URL
15 ! "http://www.cecill.info".
16 !**************************************************************
17 
21 
23 
24 !+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
25 #include "sll_assert.h"
26 #include "sll_errors.h"
27 #include "sll_memory.h"
28 #include "sll_working_precision.h"
29 
30  use sll_m_particle_group_base, only: &
32 
33  use sll_m_particle_sampling, only: &
35 
38 
39  use sll_m_initial_distribution, only : &
41 
42  use sll_m_control_variate, only : &
44 
45  implicit none
46 
47  public :: &
51 
52  private
53 !+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
54 
57  sll_real64 :: total_charge
58  contains
59  procedure :: set_total_charge
61 
62 
63 contains
64 
65  subroutine set_total_charge(self, target_total_charge)
66  class(sll_t_conservative_sampling_params), intent( inout ) :: self
67  sll_real64, intent( in ) :: target_total_charge
68  self%total_charge = target_total_charge
69  end subroutine
70 
71  !------------------------------------------------------------------------------------------
72 
75  particle_group, &
76  distribution_params, &
77  random_sampler, &
78  nb_weights, &
79  control_variate, &
80  conservative_sampling_params, &
81  xmin, &
82  Lx )
83 
84  class(sll_c_particle_group_base), pointer, intent( inout ) :: particle_group
85  class(sll_c_distribution_params), intent( inout ) :: distribution_params
86  type(sll_t_particle_sampling), intent( inout ), optional :: random_sampler
87  sll_int32, intent( in ), optional :: nb_weights
88  class(sll_t_control_variate), intent( in ), optional :: control_variate
89  class(sll_t_conservative_sampling_params), intent( in ), optional :: conservative_sampling_params
90  sll_real64, intent( in ), optional :: xmin(:)
91  sll_real64, intent( in ), optional :: lx(:)
92 
93  sll_real64 :: target_total_charge
94  logical :: enforce_total_charge
95 
96  select type ( particle_group )
97 
99 
101  if( present(conservative_sampling_params) )then
102  enforce_total_charge = .true.
103  target_total_charge = conservative_sampling_params%total_charge
104  else
105  enforce_total_charge = .false. ! no charge conservation
106  target_total_charge = 0._f64 ! value does not matter then
107  end if
108  call particle_group%sample( target_total_charge, enforce_total_charge, distribution_params )
109 
110  class default
111 
113  sll_assert( present( random_sampler ) )
114  sll_assert( present( xmin ) )
115  sll_assert( present( lx ) )
116  call random_sampler%sample( particle_group, distribution_params, xmin, lx )
117 
118 
119  if (nb_weights == 1 ) then
120  call random_sampler%sample ( particle_group, distribution_params, xmin, lx )
121  elseif ( nb_weights == 3 ) then
122  sll_assert( present( control_variate ) )
123  call random_sampler%sample_cv ( particle_group, distribution_params, xmin, lx, control_variate )
124  else
125  sll_error("sll_s_sample_particle_group", "random sampling interface not implemented for this nb of weights")
126  end if
127 
128  end select
129 
130  end subroutine sll_s_sample_particle_group
131 
132 
133 
136  particle_group, &
137  conservative_sampling_params ) !< whether charge must be conserved
138 
139  class(sll_c_particle_group_base), pointer, intent( inout ) :: particle_group
140  class(sll_t_conservative_sampling_params), intent( in ), optional :: conservative_sampling_params
141  sll_real64 :: target_total_charge
142  logical :: enforce_total_charge
143 
144  select type ( particle_group )
145 
147  if( present(conservative_sampling_params) )then
148  enforce_total_charge = .true.
149  target_total_charge = conservative_sampling_params%total_charge
150  else
151  enforce_total_charge = .false. ! no charge conservation
152  target_total_charge = 0._f64 ! value does not matter then
153  end if
154  call particle_group%resample( target_total_charge, enforce_total_charge )
155 
156  class default
157  sll_error("sll_s_resample_particle_group", "resampling interface not implemented for this type of particle group")
158 
159  end select
160 
161  end subroutine sll_s_resample_particle_group
162 
163 
164 
Parameters to define common initial distributions.
Module for a particle group with linearized-backward-flow (lbf) resamplings.
Interface routines for sampling and resampling particle groups.
subroutine, public sll_s_sample_particle_group(particle_group, distribution_params, random_sampler, nb_weights, control_variate, conservative_sampling_params, xmin, Lx)
sampling interface
subroutine, public sll_s_resample_particle_group(particle_group, conservative_sampling_params)
resampling interface
subroutine set_total_charge(self, target_total_charge)
Particle initializer class with various functions to initialize a particle.
real(kind=f64) function, dimension(size(particle, 2)) control_variate(particle)
Abstract data type for parameters of initial distribution.
type used to enforce some conservation properties in the sampling – (there may be more than just one ...
    Report Typos and Errors