Report Typos and Errors    
Semi-Lagrangian Library
Modular library for kinetic and gyrokinetic simulations of plasmas in fusion energy devices.
particle_fourier_modes_test.F90
Go to the documentation of this file.
2 !+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
3 #include "sll_memory.h"
4 #include "sll_working_precision.h"
5 
6  use sll_m_constants, only: &
7  sll_p_i1, &
9 
10  use sll_m_timer, only: &
14 
15  implicit none
16 !+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
17 
18 !sll_real64 ::time
19  sll_int32 :: ierr
20  sll_int32 :: npart !number of particles
21  sll_real64, dimension(:), allocatable :: x !particle coordinate
22  type(sll_t_time_mark) :: tstart, tstop
23  sll_int32 :: maxmode = 10
24  sll_comp64, dimension(:), allocatable :: fmodes
25 !sll_comp64, dimension(:), allocatable :: modeone
26 !sll_int32 :: idx
27 
28 !Load some particles
29 
30  print *, "Test for small number of particles"
31  npart = 10**5
32  sll_clear_allocate(x(1:npart), ierr)
33  call random_number(x);
34  x = x*2*sll_p_pi
35 
36  do maxmode = 20, 22
37  sll_allocate(fmodes(1:maxmode), ierr)
38  fmodes = (0.0_f64, 0.0_f64)
39 
40  call sll_s_set_time_mark(tstart)
41  call calc_modes_std(maxmode, fmodes, x)
42  call sll_s_set_time_mark(tstop)
43 
44  print *, 'Standard: ', sll_f_time_elapsed_between(tstart, tstop)
45 
46  call sll_s_set_time_mark(tstart)
47  call calc_modes_fast(maxmode, fmodes, x)
48  call sll_s_set_time_mark(tstop)
49 
50  print *, 'Fast: ', sll_f_time_elapsed_between(tstart, tstop)
51 
52  call sll_s_set_time_mark(tstart)
53  call calc_modes_fast2(maxmode, fmodes, x)
54  call sll_s_set_time_mark(tstop)
55 
56  print *, 'Fast2: ', sll_f_time_elapsed_between(tstart, tstop)
57 
58  call sll_s_set_time_mark(tstart)
59  call calc_modes_fast2_chunked(maxmode, fmodes, x, 500)
60  call sll_s_set_time_mark(tstop)
61 
62  print *, 'Fast2_chunk: ', sll_f_time_elapsed_between(tstart, tstop)
63 
64  call sll_s_set_time_mark(tstart)
65  call calc_modes_fast_chunked(maxmode, fmodes, x, 500)
66  call sll_s_set_time_mark(tstop)
67 
68  print *, 'Fast_chunk: ', sll_f_time_elapsed_between(tstart, tstop)
69 
70  sll_deallocate_array(fmodes, ierr)
71  end do
72  sll_deallocate_array(x, ierr)
73 
74 !-------------------------------
75 !
76 ! print *,"Test for big number of particles"
77 ! npart=1e6
78 ! npart=npart*128
79 ! SLL_CLEAR_ALLOCATE(x(1:npart), ierr)
80 ! call random_number(x);
81 ! x=x*2*sll_p_pi
82 
83 ! do maxmode=1,100
84 ! SLL_CLEAR_ALLOCATE(fmodes(1:maxmode), ierr)
85 !
86 ! call sll_s_set_time_mark(tstart)
87 ! call calc_modes_std(maxmode,fmodes,x)
88 ! call sll_s_set_time_mark(tstop)
89 !
90 ! print *, 'Standard: ', sll_f_time_elapsed_between(tstart,tstop)
91 ! call sll_s_set_time_mark(tstart)
92 ! call calc_modes_fast2_chunked(maxmode,fmodes,x,128)
93 ! call sll_s_set_time_mark(tstop)
94 !
95 ! print *, 'Fast2_chunk: ', sll_f_time_elapsed_between(tstart,tstop)
96 !
97 ! SLL_DEALLOCATE_ARRAY(fmodes,ierr)
98 ! enddo
99 
100 ! do fmode=1,this%num_modes
101 ! !Be careful here, the dot_product tends to complex conjugate stuff
102 ! !which we don't want in this case
103 ! !rhs(fmode)=dot_product(exp(-sll_p_i1*fmode*ppos*2.0_f64*sll_p_pi/this%Ilength), pweight )
104 ! rhs(fmode)=sum(exp(-sll_p_i1*fmode*ppos*sll_p_kx/this%Ilength)*pweight)
105 
106 contains
107 
108  subroutine calc_modes_std(maxmode, fmodes, x)
109  sll_comp64, intent(out), dimension(:):: fmodes
110  sll_int32, intent(in):: maxmode
111  sll_real64, dimension(:), intent(in) :: x
112  sll_int32 :: fmode
113  do fmode = 1, maxmode
114  fmodes(fmode) = sum(exp(-sll_p_i1*fmode*x))
115  end do
116  end subroutine calc_modes_std
117 
118  subroutine calc_modes_fast(maxmode, fmodes, x)
119  sll_comp64, intent(out), dimension(:):: fmodes
120  sll_int32, intent(in):: maxmode
121  sll_real64, dimension(:), intent(in) :: x
122  sll_comp64, dimension(size(x)) :: modeone
123  sll_int32 :: fmode
124  modeone = exp(-sll_p_i1*x)
125  do fmode = 1, maxmode
126  fmodes(fmode) = sum(modeone**fmode)
127  end do
128  end subroutine calc_modes_fast
129 
130  subroutine calc_modes_fast_chunked(maxmode, fmodes, x, chunksize)
131  sll_comp64, intent(out), dimension(:):: fmodes
132  sll_int32, intent(in):: maxmode
133  sll_real64, dimension(:), intent(in) :: x
134  sll_int32, intent(in):: chunksize
135  sll_int32 :: numx, chunk
136  sll_comp64, dimension(maxmode):: fmodes_chunk
137 
138  numx = size(x)
139  do chunk = 1, numx/chunksize
140  call calc_modes_fast(maxmode, fmodes_chunk, x((chunk - 1)*chunksize + 1:chunk*chunksize))
141  fmodes = fmodes + fmodes_chunk;
142  end do
143  end subroutine calc_modes_fast_chunked
144 
145  subroutine calc_modes_fast2(maxmode, fmodes, x)
146  sll_comp64, intent(out), dimension(:):: fmodes
147  sll_int32, intent(in):: maxmode
148  sll_real64, dimension(:), intent(in) :: x
149  sll_comp64, dimension(size(x)) :: modeone
150  sll_comp64, dimension(size(x)) :: mode
151  sll_int32 :: fmode
152  modeone = exp(-sll_p_i1*x)
153  mode = modeone
154  do fmode = 1, maxmode
155  mode = mode*modeone;
156  fmodes(fmode) = sum(mode)
157  end do
158  end subroutine calc_modes_fast2
159 
160  subroutine calc_modes_fast2_chunked(maxmode, fmodes, x, chunksize)
161  sll_comp64, intent(out), dimension(:):: fmodes
162  sll_int32, intent(in):: maxmode
163  sll_real64, dimension(:), intent(in) :: x
164  sll_int32, intent(in):: chunksize
165  sll_int32 :: numx, chunk
166  sll_comp64, dimension(maxmode):: fmodes_chunk
167 
168  numx = size(x)
169  do chunk = 1, numx/chunksize
170  call calc_modes_fast2(maxmode, fmodes_chunk, x((chunk - 1)*chunksize + 1:chunk*chunksize))
171  fmodes = fmodes + fmodes_chunk;
172  end do
173  end subroutine calc_modes_fast2_chunked
174 ! subroutine
175 
176 end program particle_fourier_modes_test
177 
Fortran module where set some physical and mathematical constants.
real(kind=f64), parameter, public sll_p_pi
complex(kind=f64), parameter, public sll_p_i1
We can now use the functions.
Definition: sll_m_timer.F90:40
subroutine, public sll_s_set_time_mark(timer_obj)
reads time parameters from system and stores in its argument. param timer_obj an object of type sll_t...
Definition: sll_m_timer.F90:72
real(kind=f64) function, public sll_f_time_elapsed_between(t0, t1)
Computes the time elapsed between two time marks.
Definition: sll_m_timer.F90:83
program particle_fourier_modes_test
subroutine calc_modes_fast2(maxmode, fmodes, x)
subroutine calc_modes_fast2_chunked(maxmode, fmodes, x, chunksize)
subroutine calc_modes_std(maxmode, fmodes, x)
subroutine calc_modes_fast(maxmode, fmodes, x)
subroutine calc_modes_fast_chunked(maxmode, fmodes, x, chunksize)
type use for clock reading
Definition: sll_m_timer.F90:61
    Report Typos and Errors