2019-03-26 15:21:22 +01:00
|
|
|
module multipass
|
2024-07-07 13:18:55 +02:00
|
|
|
use const_and_precisions, only : wp_
|
|
|
|
use polarization, only : pol_limit, field_to_ellipse
|
|
|
|
use reflections, only : wall_refl
|
replace equilibrium module with an object
Similarly to eb648039 this change replaces the `equilibrium` module with
a new `gray_equil` module providing the same functionality without using
global variables.
- `read_eqdsk`, `read_equil_an` are replaced by a single `load_equil`
routine that handles all equilibrium kind (analytical, numerical,
and vacuum).
- `scale_equil` is merged into `load_equil`, which besides reading
the equilibrium from file peforms the rescaling and interpolation based
on the `gray_parameters` settings and the equilibrium kind.
To operate on G-EQDSK data specifically, the `change_cocors` and
`scale_eqdsk` are still available. The numeric equilibrium must then
be initialised manually by calling equil%init().
- `set_equil_spline`, `set_equil_an`, `unset_equil_spline`
are completely removed as the module no longer has any internal state.
- `fq` is replaced by `equil%safety`; `bfield` by `equil%b_field`;
`frhotor`, `frhopol` by `equil%pol2tor` and `equil%pol2tor`;
and the remaining subroutines by other methods of `abstract_equil`
retaining the old name.
- the `contours_psi` subroutine is replaced by `equil%flux_contour`,
with a slightly changed invocation but same functionality.
- the `gray_data` type is no longer required ans has been removed: all
the core subroutines now access the input data only though either
`abstract_equil`, `abstract_plasma` or the `limiter` contour.
2024-08-29 17:16:33 +02:00
|
|
|
use gray_equil, only : abstract_equil
|
2024-01-27 12:09:56 +01:00
|
|
|
|
2019-03-26 15:21:22 +01:00
|
|
|
implicit none
|
|
|
|
|
|
|
|
contains
|
|
|
|
|
replace equilibrium module with an object
Similarly to eb648039 this change replaces the `equilibrium` module with
a new `gray_equil` module providing the same functionality without using
global variables.
- `read_eqdsk`, `read_equil_an` are replaced by a single `load_equil`
routine that handles all equilibrium kind (analytical, numerical,
and vacuum).
- `scale_equil` is merged into `load_equil`, which besides reading
the equilibrium from file peforms the rescaling and interpolation based
on the `gray_parameters` settings and the equilibrium kind.
To operate on G-EQDSK data specifically, the `change_cocors` and
`scale_eqdsk` are still available. The numeric equilibrium must then
be initialised manually by calling equil%init().
- `set_equil_spline`, `set_equil_an`, `unset_equil_spline`
are completely removed as the module no longer has any internal state.
- `fq` is replaced by `equil%safety`; `bfield` by `equil%b_field`;
`frhotor`, `frhopol` by `equil%pol2tor` and `equil%pol2tor`;
and the remaining subroutines by other methods of `abstract_equil`
retaining the old name.
- the `contours_psi` subroutine is replaced by `equil%flux_contour`,
with a slightly changed invocation but same functionality.
- the `gray_data` type is no longer required ans has been removed: all
the core subroutines now access the input data only though either
`abstract_equil`, `abstract_plasma` or the `limiter` contour.
2024-08-29 17:16:33 +02:00
|
|
|
subroutine plasma_in(i, equil, x, N, Bres, sox, cpl, &
|
|
|
|
psi, chi, iop, ext, eyt, perfect)
|
fix coupling for subsequent beams
In situations when multiple beams are traced, either when allowing
multiple plasma crossings (raytracing.ipass > 0) or the initial polarisation
is mixed (raytracing.ipol == .true.), the couplings of all but the first
beam (with least index_rt) were invalid.
The bug is due to the re-use of the psipol,chipol variables as the beams
are traced sequentially over the beam_loop. For the first beam being
traced the psipol,chipol are correctly initialised to the user-defined
value and the resulting coupling is correct.
However, in each subsequent beam the values were not set to those of the
parent beam (or to the user-defined value in the case of the first X
mode beam), but to those of the previous beams (current index_rt - 1).
This change repurposes the psipv,chipv arrays to store the polarisation
of the parent beams, including the initial user-defined value and makes
plasma_in always use these to compute the coupling.
In addition, in the case the polarisation is not immediately known (i.e.
if raytracing.ipol == .false.), this change postpones the computation of
the Jones vector (ext, eyt) from the launch point, if the magnetic
equilibrium is available, to when the ray actually crosses the
plasma boundary.
The original code, besides being strictly incorrect, can lead to
non-negligible alterations to the coupling. This change also mean:
1. most of the functionality of `set_pol` has been merged with
`plasma_in`
2. the polarisation is undefined and the Jones vector is set to the
placeholder value [1, 0] till `plasma_im` is called
Finally, `polarcold` is removed because it's unused.
2024-03-02 17:32:03 +01:00
|
|
|
! Computes the ray polarisation and power couplings when it enteres the plasma
|
2024-07-07 13:18:55 +02:00
|
|
|
use const_and_precisions, only : cm
|
fix coupling for subsequent beams
In situations when multiple beams are traced, either when allowing
multiple plasma crossings (raytracing.ipass > 0) or the initial polarisation
is mixed (raytracing.ipol == .true.), the couplings of all but the first
beam (with least index_rt) were invalid.
The bug is due to the re-use of the psipol,chipol variables as the beams
are traced sequentially over the beam_loop. For the first beam being
traced the psipol,chipol are correctly initialised to the user-defined
value and the resulting coupling is correct.
However, in each subsequent beam the values were not set to those of the
parent beam (or to the user-defined value in the case of the first X
mode beam), but to those of the previous beams (current index_rt - 1).
This change repurposes the psipv,chipv arrays to store the polarisation
of the parent beams, including the initial user-defined value and makes
plasma_in always use these to compute the coupling.
In addition, in the case the polarisation is not immediately known (i.e.
if raytracing.ipol == .false.), this change postpones the computation of
the Jones vector (ext, eyt) from the launch point, if the magnetic
equilibrium is available, to when the ray actually crosses the
plasma boundary.
The original code, besides being strictly incorrect, can lead to
non-negligible alterations to the coupling. This change also mean:
1. most of the functionality of `set_pol` has been merged with
`plasma_in`
2. the polarisation is undefined and the Jones vector is set to the
placeholder value [1, 0] till `plasma_im` is called
Finally, `polarcold` is removed because it's unused.
2024-03-02 17:32:03 +01:00
|
|
|
|
|
|
|
! subroutine arguments
|
replace equilibrium module with an object
Similarly to eb648039 this change replaces the `equilibrium` module with
a new `gray_equil` module providing the same functionality without using
global variables.
- `read_eqdsk`, `read_equil_an` are replaced by a single `load_equil`
routine that handles all equilibrium kind (analytical, numerical,
and vacuum).
- `scale_equil` is merged into `load_equil`, which besides reading
the equilibrium from file peforms the rescaling and interpolation based
on the `gray_parameters` settings and the equilibrium kind.
To operate on G-EQDSK data specifically, the `change_cocors` and
`scale_eqdsk` are still available. The numeric equilibrium must then
be initialised manually by calling equil%init().
- `set_equil_spline`, `set_equil_an`, `unset_equil_spline`
are completely removed as the module no longer has any internal state.
- `fq` is replaced by `equil%safety`; `bfield` by `equil%b_field`;
`frhotor`, `frhopol` by `equil%pol2tor` and `equil%pol2tor`;
and the remaining subroutines by other methods of `abstract_equil`
retaining the old name.
- the `contours_psi` subroutine is replaced by `equil%flux_contour`,
with a slightly changed invocation but same functionality.
- the `gray_data` type is no longer required ans has been removed: all
the core subroutines now access the input data only though either
`abstract_equil`, `abstract_plasma` or the `limiter` contour.
2024-08-29 17:16:33 +02:00
|
|
|
integer, intent(in) :: i ! ray index
|
|
|
|
class(abstract_equil), intent(in) :: equil ! MHD equilibrium
|
|
|
|
real(wp_), intent(in) :: x(3), N(3) ! position, refactive index
|
|
|
|
real(wp_), intent(in) :: Bres ! resonant B field
|
|
|
|
integer, intent(in) :: sox ! sign of polarisation mode: -1 ⇒ O, +1 ⇒ X
|
|
|
|
real(wp_), intent(out) :: cpl(2) ! power coupling vector (O, X)
|
|
|
|
real(wp_), intent(out) :: psi, chi ! polarisation ellipse angles
|
|
|
|
integer, intent(inout) :: iop(:) ! inside/outside plasma flag
|
|
|
|
complex(wp_), intent(inout) :: ext(:), eyt(:) ! ray polarisation vector (e_x, e_y)
|
|
|
|
logical, intent(in) :: perfect ! whether to assume perfect coupling
|
fix coupling for subsequent beams
In situations when multiple beams are traced, either when allowing
multiple plasma crossings (raytracing.ipass > 0) or the initial polarisation
is mixed (raytracing.ipol == .true.), the couplings of all but the first
beam (with least index_rt) were invalid.
The bug is due to the re-use of the psipol,chipol variables as the beams
are traced sequentially over the beam_loop. For the first beam being
traced the psipol,chipol are correctly initialised to the user-defined
value and the resulting coupling is correct.
However, in each subsequent beam the values were not set to those of the
parent beam (or to the user-defined value in the case of the first X
mode beam), but to those of the previous beams (current index_rt - 1).
This change repurposes the psipv,chipv arrays to store the polarisation
of the parent beams, including the initial user-defined value and makes
plasma_in always use these to compute the coupling.
In addition, in the case the polarisation is not immediately known (i.e.
if raytracing.ipol == .false.), this change postpones the computation of
the Jones vector (ext, eyt) from the launch point, if the magnetic
equilibrium is available, to when the ray actually crosses the
plasma boundary.
The original code, besides being strictly incorrect, can lead to
non-negligible alterations to the coupling. This change also mean:
1. most of the functionality of `set_pol` has been merged with
`plasma_in`
2. the polarisation is undefined and the Jones vector is set to the
placeholder value [1, 0] till `plasma_im` is called
Finally, `polarcold` is removed because it's unused.
2024-03-02 17:32:03 +01:00
|
|
|
|
|
|
|
! local variables
|
2024-10-17 00:56:02 +02:00
|
|
|
real(wp_) :: R, z, phi
|
fix coupling for subsequent beams
In situations when multiple beams are traced, either when allowing
multiple plasma crossings (raytracing.ipass > 0) or the initial polarisation
is mixed (raytracing.ipol == .true.), the couplings of all but the first
beam (with least index_rt) were invalid.
The bug is due to the re-use of the psipol,chipol variables as the beams
are traced sequentially over the beam_loop. For the first beam being
traced the psipol,chipol are correctly initialised to the user-defined
value and the resulting coupling is correct.
However, in each subsequent beam the values were not set to those of the
parent beam (or to the user-defined value in the case of the first X
mode beam), but to those of the previous beams (current index_rt - 1).
This change repurposes the psipv,chipv arrays to store the polarisation
of the parent beams, including the initial user-defined value and makes
plasma_in always use these to compute the coupling.
In addition, in the case the polarisation is not immediately known (i.e.
if raytracing.ipol == .false.), this change postpones the computation of
the Jones vector (ext, eyt) from the launch point, if the magnetic
equilibrium is available, to when the ray actually crosses the
plasma boundary.
The original code, besides being strictly incorrect, can lead to
non-negligible alterations to the coupling. This change also mean:
1. most of the functionality of `set_pol` has been merged with
`plasma_in`
2. the polarisation is undefined and the Jones vector is set to the
placeholder value [1, 0] till `plasma_im` is called
Finally, `polarcold` is removed because it's unused.
2024-03-02 17:32:03 +01:00
|
|
|
real(wp_) :: B(3)
|
|
|
|
real(wp_) :: c
|
|
|
|
complex(wp_) :: e_mode(2), e_ray(2)
|
|
|
|
|
|
|
|
! Update the inside/outside flag
|
|
|
|
iop(i) = iop(i) + 1
|
|
|
|
|
2024-10-17 00:56:02 +02:00
|
|
|
! Compute magnetic field
|
fix coupling for subsequent beams
In situations when multiple beams are traced, either when allowing
multiple plasma crossings (raytracing.ipass > 0) or the initial polarisation
is mixed (raytracing.ipol == .true.), the couplings of all but the first
beam (with least index_rt) were invalid.
The bug is due to the re-use of the psipol,chipol variables as the beams
are traced sequentially over the beam_loop. For the first beam being
traced the psipol,chipol are correctly initialised to the user-defined
value and the resulting coupling is correct.
However, in each subsequent beam the values were not set to those of the
parent beam (or to the user-defined value in the case of the first X
mode beam), but to those of the previous beams (current index_rt - 1).
This change repurposes the psipv,chipv arrays to store the polarisation
of the parent beams, including the initial user-defined value and makes
plasma_in always use these to compute the coupling.
In addition, in the case the polarisation is not immediately known (i.e.
if raytracing.ipol == .false.), this change postpones the computation of
the Jones vector (ext, eyt) from the launch point, if the magnetic
equilibrium is available, to when the ray actually crosses the
plasma boundary.
The original code, besides being strictly incorrect, can lead to
non-negligible alterations to the coupling. This change also mean:
1. most of the functionality of `set_pol` has been merged with
`plasma_in`
2. the polarisation is undefined and the Jones vector is set to the
placeholder value [1, 0] till `plasma_im` is called
Finally, `polarcold` is removed because it's unused.
2024-03-02 17:32:03 +01:00
|
|
|
R = norm2(x(1:2)) * cm
|
|
|
|
z = x(3) * cm
|
2024-10-17 00:56:02 +02:00
|
|
|
phi = atan2(x(2), x(1))
|
|
|
|
call equil%b_field(R, z, phi, B=B)
|
fix coupling for subsequent beams
In situations when multiple beams are traced, either when allowing
multiple plasma crossings (raytracing.ipass > 0) or the initial polarisation
is mixed (raytracing.ipol == .true.), the couplings of all but the first
beam (with least index_rt) were invalid.
The bug is due to the re-use of the psipol,chipol variables as the beams
are traced sequentially over the beam_loop. For the first beam being
traced the psipol,chipol are correctly initialised to the user-defined
value and the resulting coupling is correct.
However, in each subsequent beam the values were not set to those of the
parent beam (or to the user-defined value in the case of the first X
mode beam), but to those of the previous beams (current index_rt - 1).
This change repurposes the psipv,chipv arrays to store the polarisation
of the parent beams, including the initial user-defined value and makes
plasma_in always use these to compute the coupling.
In addition, in the case the polarisation is not immediately known (i.e.
if raytracing.ipol == .false.), this change postpones the computation of
the Jones vector (ext, eyt) from the launch point, if the magnetic
equilibrium is available, to when the ray actually crosses the
plasma boundary.
The original code, besides being strictly incorrect, can lead to
non-negligible alterations to the coupling. This change also mean:
1. most of the functionality of `set_pol` has been merged with
`plasma_in`
2. the polarisation is undefined and the Jones vector is set to the
placeholder value [1, 0] till `plasma_im` is called
Finally, `polarcold` is removed because it's unused.
2024-03-02 17:32:03 +01:00
|
|
|
|
|
|
|
! Get the polarisation vector of the given mode
|
|
|
|
call pol_limit(N, B, Bres, sox, e_mode(1), e_mode(2))
|
|
|
|
|
|
|
|
if(i == 1) then
|
|
|
|
! For the central ray, compute the polarization ellipse
|
2024-03-12 16:42:19 +01:00
|
|
|
call field_to_ellipse(e_mode(1), e_mode(2), psi, chi)
|
2019-03-26 15:21:22 +01:00
|
|
|
else
|
fix coupling for subsequent beams
In situations when multiple beams are traced, either when allowing
multiple plasma crossings (raytracing.ipass > 0) or the initial polarisation
is mixed (raytracing.ipol == .true.), the couplings of all but the first
beam (with least index_rt) were invalid.
The bug is due to the re-use of the psipol,chipol variables as the beams
are traced sequentially over the beam_loop. For the first beam being
traced the psipol,chipol are correctly initialised to the user-defined
value and the resulting coupling is correct.
However, in each subsequent beam the values were not set to those of the
parent beam (or to the user-defined value in the case of the first X
mode beam), but to those of the previous beams (current index_rt - 1).
This change repurposes the psipv,chipv arrays to store the polarisation
of the parent beams, including the initial user-defined value and makes
plasma_in always use these to compute the coupling.
In addition, in the case the polarisation is not immediately known (i.e.
if raytracing.ipol == .false.), this change postpones the computation of
the Jones vector (ext, eyt) from the launch point, if the magnetic
equilibrium is available, to when the ray actually crosses the
plasma boundary.
The original code, besides being strictly incorrect, can lead to
non-negligible alterations to the coupling. This change also mean:
1. most of the functionality of `set_pol` has been merged with
`plasma_in`
2. the polarisation is undefined and the Jones vector is set to the
placeholder value [1, 0] till `plasma_im` is called
Finally, `polarcold` is removed because it's unused.
2024-03-02 17:32:03 +01:00
|
|
|
psi = 0
|
|
|
|
chi = 0
|
|
|
|
end if
|
|
|
|
|
|
|
|
if (perfect) then
|
|
|
|
! Ignore the given vector and use the expected one
|
|
|
|
! Note: this will give 100% coupling to the current mode
|
|
|
|
ext(i) = e_mode(1)
|
|
|
|
eyt(i) = e_mode(2)
|
2019-03-26 15:21:22 +01:00
|
|
|
end if
|
fix coupling for subsequent beams
In situations when multiple beams are traced, either when allowing
multiple plasma crossings (raytracing.ipass > 0) or the initial polarisation
is mixed (raytracing.ipol == .true.), the couplings of all but the first
beam (with least index_rt) were invalid.
The bug is due to the re-use of the psipol,chipol variables as the beams
are traced sequentially over the beam_loop. For the first beam being
traced the psipol,chipol are correctly initialised to the user-defined
value and the resulting coupling is correct.
However, in each subsequent beam the values were not set to those of the
parent beam (or to the user-defined value in the case of the first X
mode beam), but to those of the previous beams (current index_rt - 1).
This change repurposes the psipv,chipv arrays to store the polarisation
of the parent beams, including the initial user-defined value and makes
plasma_in always use these to compute the coupling.
In addition, in the case the polarisation is not immediately known (i.e.
if raytracing.ipol == .false.), this change postpones the computation of
the Jones vector (ext, eyt) from the launch point, if the magnetic
equilibrium is available, to when the ray actually crosses the
plasma boundary.
The original code, besides being strictly incorrect, can lead to
non-negligible alterations to the coupling. This change also mean:
1. most of the functionality of `set_pol` has been merged with
`plasma_in`
2. the polarisation is undefined and the Jones vector is set to the
placeholder value [1, 0] till `plasma_im` is called
Finally, `polarcold` is removed because it's unused.
2024-03-02 17:32:03 +01:00
|
|
|
|
|
|
|
! Compute the power coupling with the current mode
|
|
|
|
e_ray = [ext(i), eyt(i)]
|
|
|
|
c = abs(dot_product(e_mode, e_ray))**2
|
|
|
|
|
|
|
|
! Store both O and X couplings, in this order
|
|
|
|
c = merge(c, 1-c, sox == -1)
|
|
|
|
cpl = [c, 1-c]
|
2019-03-26 15:21:22 +01:00
|
|
|
end subroutine plasma_in
|
fix coupling for subsequent beams
In situations when multiple beams are traced, either when allowing
multiple plasma crossings (raytracing.ipass > 0) or the initial polarisation
is mixed (raytracing.ipol == .true.), the couplings of all but the first
beam (with least index_rt) were invalid.
The bug is due to the re-use of the psipol,chipol variables as the beams
are traced sequentially over the beam_loop. For the first beam being
traced the psipol,chipol are correctly initialised to the user-defined
value and the resulting coupling is correct.
However, in each subsequent beam the values were not set to those of the
parent beam (or to the user-defined value in the case of the first X
mode beam), but to those of the previous beams (current index_rt - 1).
This change repurposes the psipv,chipv arrays to store the polarisation
of the parent beams, including the initial user-defined value and makes
plasma_in always use these to compute the coupling.
In addition, in the case the polarisation is not immediately known (i.e.
if raytracing.ipol == .false.), this change postpones the computation of
the Jones vector (ext, eyt) from the launch point, if the magnetic
equilibrium is available, to when the ray actually crosses the
plasma boundary.
The original code, besides being strictly incorrect, can lead to
non-negligible alterations to the coupling. This change also mean:
1. most of the functionality of `set_pol` has been merged with
`plasma_in`
2. the polarisation is undefined and the Jones vector is set to the
placeholder value [1, 0] till `plasma_im` is called
Finally, `polarcold` is removed because it's unused.
2024-03-02 17:32:03 +01:00
|
|
|
|
|
|
|
|
2024-10-17 00:56:02 +02:00
|
|
|
subroutine plasma_out(i, equil, x, N, Bres, sox, iop, ext, eyt)
|
2024-04-23 17:00:40 +02:00
|
|
|
! Ray exits plasma
|
2024-10-17 00:56:02 +02:00
|
|
|
use const_and_precisions, only : cm
|
2024-04-23 17:00:40 +02:00
|
|
|
|
|
|
|
! subroutine arguments
|
replace equilibrium module with an object
Similarly to eb648039 this change replaces the `equilibrium` module with
a new `gray_equil` module providing the same functionality without using
global variables.
- `read_eqdsk`, `read_equil_an` are replaced by a single `load_equil`
routine that handles all equilibrium kind (analytical, numerical,
and vacuum).
- `scale_equil` is merged into `load_equil`, which besides reading
the equilibrium from file peforms the rescaling and interpolation based
on the `gray_parameters` settings and the equilibrium kind.
To operate on G-EQDSK data specifically, the `change_cocors` and
`scale_eqdsk` are still available. The numeric equilibrium must then
be initialised manually by calling equil%init().
- `set_equil_spline`, `set_equil_an`, `unset_equil_spline`
are completely removed as the module no longer has any internal state.
- `fq` is replaced by `equil%safety`; `bfield` by `equil%b_field`;
`frhotor`, `frhopol` by `equil%pol2tor` and `equil%pol2tor`;
and the remaining subroutines by other methods of `abstract_equil`
retaining the old name.
- the `contours_psi` subroutine is replaced by `equil%flux_contour`,
with a slightly changed invocation but same functionality.
- the `gray_data` type is no longer required ans has been removed: all
the core subroutines now access the input data only though either
`abstract_equil`, `abstract_plasma` or the `limiter` contour.
2024-08-29 17:16:33 +02:00
|
|
|
integer, intent(in) :: i ! ray index
|
|
|
|
class(abstract_equil), intent(in) :: equil ! MHD equilibrium
|
2024-10-17 00:56:02 +02:00
|
|
|
real(wp_), intent(in) :: x(3), N(3)
|
|
|
|
real(wp_), intent(in) :: Bres
|
replace equilibrium module with an object
Similarly to eb648039 this change replaces the `equilibrium` module with
a new `gray_equil` module providing the same functionality without using
global variables.
- `read_eqdsk`, `read_equil_an` are replaced by a single `load_equil`
routine that handles all equilibrium kind (analytical, numerical,
and vacuum).
- `scale_equil` is merged into `load_equil`, which besides reading
the equilibrium from file peforms the rescaling and interpolation based
on the `gray_parameters` settings and the equilibrium kind.
To operate on G-EQDSK data specifically, the `change_cocors` and
`scale_eqdsk` are still available. The numeric equilibrium must then
be initialised manually by calling equil%init().
- `set_equil_spline`, `set_equil_an`, `unset_equil_spline`
are completely removed as the module no longer has any internal state.
- `fq` is replaced by `equil%safety`; `bfield` by `equil%b_field`;
`frhotor`, `frhopol` by `equil%pol2tor` and `equil%pol2tor`;
and the remaining subroutines by other methods of `abstract_equil`
retaining the old name.
- the `contours_psi` subroutine is replaced by `equil%flux_contour`,
with a slightly changed invocation but same functionality.
- the `gray_data` type is no longer required ans has been removed: all
the core subroutines now access the input data only though either
`abstract_equil`, `abstract_plasma` or the `limiter` contour.
2024-08-29 17:16:33 +02:00
|
|
|
integer, intent(in) :: sox
|
|
|
|
integer, intent(inout) :: iop(:) ! in/out plasma flag
|
|
|
|
complex(wp_), intent(out) :: ext(:), eyt(:)
|
2024-04-23 17:00:40 +02:00
|
|
|
|
|
|
|
! local variables
|
2024-10-17 00:56:02 +02:00
|
|
|
real(wp_) :: R, z, phi, B(3)
|
|
|
|
|
|
|
|
iop(i) = iop(i)+1 ! in->out
|
|
|
|
|
|
|
|
! Compute magnetic field
|
|
|
|
R = norm2(x(1:2)) * cm
|
|
|
|
z = x(3) * cm
|
|
|
|
phi = atan2(x(2), x(1))
|
|
|
|
call equil%b_field(R, z, phi, B=B)
|
|
|
|
|
|
|
|
! Compute polarisation on the boundary
|
|
|
|
call pol_limit(N, B, Bres, sox, ext(i), eyt(i))
|
2019-03-26 15:21:22 +01:00
|
|
|
end subroutine plasma_out
|
2024-04-23 17:00:40 +02:00
|
|
|
|
|
|
|
|
replace equilibrium module with an object
Similarly to eb648039 this change replaces the `equilibrium` module with
a new `gray_equil` module providing the same functionality without using
global variables.
- `read_eqdsk`, `read_equil_an` are replaced by a single `load_equil`
routine that handles all equilibrium kind (analytical, numerical,
and vacuum).
- `scale_equil` is merged into `load_equil`, which besides reading
the equilibrium from file peforms the rescaling and interpolation based
on the `gray_parameters` settings and the equilibrium kind.
To operate on G-EQDSK data specifically, the `change_cocors` and
`scale_eqdsk` are still available. The numeric equilibrium must then
be initialised manually by calling equil%init().
- `set_equil_spline`, `set_equil_an`, `unset_equil_spline`
are completely removed as the module no longer has any internal state.
- `fq` is replaced by `equil%safety`; `bfield` by `equil%b_field`;
`frhotor`, `frhopol` by `equil%pol2tor` and `equil%pol2tor`;
and the remaining subroutines by other methods of `abstract_equil`
retaining the old name.
- the `contours_psi` subroutine is replaced by `equil%flux_contour`,
with a slightly changed invocation but same functionality.
- the `gray_data` type is no longer required ans has been removed: all
the core subroutines now access the input data only though either
`abstract_equil`, `abstract_plasma` or the `limiter` contour.
2024-08-29 17:16:33 +02:00
|
|
|
subroutine wall_out(i, equil, wall, ins, xv, anv, dst, bres, &
|
|
|
|
sox, psipol1, chipol1, iow, iop, ext, eyt)
|
2024-04-23 17:00:40 +02:00
|
|
|
! Ray exits vessel
|
2024-07-30 10:57:07 +02:00
|
|
|
use types, only : contour
|
2024-04-23 17:00:40 +02:00
|
|
|
|
|
|
|
! subroutine arguments
|
replace equilibrium module with an object
Similarly to eb648039 this change replaces the `equilibrium` module with
a new `gray_equil` module providing the same functionality without using
global variables.
- `read_eqdsk`, `read_equil_an` are replaced by a single `load_equil`
routine that handles all equilibrium kind (analytical, numerical,
and vacuum).
- `scale_equil` is merged into `load_equil`, which besides reading
the equilibrium from file peforms the rescaling and interpolation based
on the `gray_parameters` settings and the equilibrium kind.
To operate on G-EQDSK data specifically, the `change_cocors` and
`scale_eqdsk` are still available. The numeric equilibrium must then
be initialised manually by calling equil%init().
- `set_equil_spline`, `set_equil_an`, `unset_equil_spline`
are completely removed as the module no longer has any internal state.
- `fq` is replaced by `equil%safety`; `bfield` by `equil%b_field`;
`frhotor`, `frhopol` by `equil%pol2tor` and `equil%pol2tor`;
and the remaining subroutines by other methods of `abstract_equil`
retaining the old name.
- the `contours_psi` subroutine is replaced by `equil%flux_contour`,
with a slightly changed invocation but same functionality.
- the `gray_data` type is no longer required ans has been removed: all
the core subroutines now access the input data only though either
`abstract_equil`, `abstract_plasma` or the `limiter` contour.
2024-08-29 17:16:33 +02:00
|
|
|
integer, intent(in) :: i ! ray index
|
|
|
|
class(abstract_equil), intent(in) :: equil ! MHD equilibrium
|
|
|
|
type(contour), intent(in) :: wall ! wall contour
|
|
|
|
logical, intent(in) :: ins ! inside plasma? (ins=1 plasma/wall overlap)
|
|
|
|
real(wp_), intent(inout) :: xv(3), anv(3)
|
|
|
|
real(wp_), intent(in) :: dst ! step size
|
|
|
|
real(wp_), intent(in) :: bres
|
|
|
|
integer, intent(in) :: sox
|
|
|
|
real(wp_), intent(out) :: psipol1, chipol1
|
|
|
|
integer, intent(inout) :: iow(:) ! in/out vessel and plasma flags
|
|
|
|
integer, intent(inout) :: iop(:) ! in/out vessel and plasma flags
|
|
|
|
complex(wp_), intent(inout) :: ext(:), eyt(:)
|
2024-04-23 17:00:40 +02:00
|
|
|
|
|
|
|
! local variables
|
2019-03-26 15:21:22 +01:00
|
|
|
integer :: irfl
|
|
|
|
real(wp_), dimension(3) :: xvrfl,anvrfl,walln
|
|
|
|
complex(wp_) :: ext1,eyt1
|
2024-04-23 17:00:40 +02:00
|
|
|
|
replace equilibrium module with an object
Similarly to eb648039 this change replaces the `equilibrium` module with
a new `gray_equil` module providing the same functionality without using
global variables.
- `read_eqdsk`, `read_equil_an` are replaced by a single `load_equil`
routine that handles all equilibrium kind (analytical, numerical,
and vacuum).
- `scale_equil` is merged into `load_equil`, which besides reading
the equilibrium from file peforms the rescaling and interpolation based
on the `gray_parameters` settings and the equilibrium kind.
To operate on G-EQDSK data specifically, the `change_cocors` and
`scale_eqdsk` are still available. The numeric equilibrium must then
be initialised manually by calling equil%init().
- `set_equil_spline`, `set_equil_an`, `unset_equil_spline`
are completely removed as the module no longer has any internal state.
- `fq` is replaced by `equil%safety`; `bfield` by `equil%b_field`;
`frhotor`, `frhopol` by `equil%pol2tor` and `equil%pol2tor`;
and the remaining subroutines by other methods of `abstract_equil`
retaining the old name.
- the `contours_psi` subroutine is replaced by `equil%flux_contour`,
with a slightly changed invocation but same functionality.
- the `gray_data` type is no longer required ans has been removed: all
the core subroutines now access the input data only though either
`abstract_equil`, `abstract_plasma` or the `limiter` contour.
2024-08-29 17:16:33 +02:00
|
|
|
iow(i) = iow(i) + 1 ! out->in
|
|
|
|
if(ins) call plasma_out(i, equil, xv, anv, bres, sox, iop, ext, eyt) ! plasma-wall overlapping
|
2024-07-30 10:57:07 +02:00
|
|
|
call wall_refl(wall, xv-dst*anv, anv, ext(i), eyt(i), &
|
replace equilibrium module with an object
Similarly to eb648039 this change replaces the `equilibrium` module with
a new `gray_equil` module providing the same functionality without using
global variables.
- `read_eqdsk`, `read_equil_an` are replaced by a single `load_equil`
routine that handles all equilibrium kind (analytical, numerical,
and vacuum).
- `scale_equil` is merged into `load_equil`, which besides reading
the equilibrium from file peforms the rescaling and interpolation based
on the `gray_parameters` settings and the equilibrium kind.
To operate on G-EQDSK data specifically, the `change_cocors` and
`scale_eqdsk` are still available. The numeric equilibrium must then
be initialised manually by calling equil%init().
- `set_equil_spline`, `set_equil_an`, `unset_equil_spline`
are completely removed as the module no longer has any internal state.
- `fq` is replaced by `equil%safety`; `bfield` by `equil%b_field`;
`frhotor`, `frhopol` by `equil%pol2tor` and `equil%pol2tor`;
and the remaining subroutines by other methods of `abstract_equil`
retaining the old name.
- the `contours_psi` subroutine is replaced by `equil%flux_contour`,
with a slightly changed invocation but same functionality.
- the `gray_data` type is no longer required ans has been removed: all
the core subroutines now access the input data only though either
`abstract_equil`, `abstract_plasma` or the `limiter` contour.
2024-08-29 17:16:33 +02:00
|
|
|
xvrfl, anvrfl, ext1, eyt1, walln, irfl) ! ray reflects at wall
|
|
|
|
ext(i) = ext1 ! save parameters at wall reflection
|
2019-03-26 15:21:22 +01:00
|
|
|
eyt(i) = eyt1
|
|
|
|
xv = xvrfl
|
|
|
|
anv = anvrfl
|
|
|
|
|
2024-07-07 13:18:55 +02:00
|
|
|
if(i == 1) then
|
2024-03-12 16:42:19 +01:00
|
|
|
call field_to_ellipse(ext1, eyt1, psipol1, chipol1)
|
2019-03-26 15:21:22 +01:00
|
|
|
else
|
2024-07-07 13:18:55 +02:00
|
|
|
psipol1 = 0
|
|
|
|
chipol1 = 0
|
2019-03-26 15:21:22 +01:00
|
|
|
end if
|
|
|
|
|
|
|
|
end subroutine wall_out
|
2024-04-23 17:00:40 +02:00
|
|
|
|
|
|
|
|
|
|
|
subroutine initbeam(i, iroff, iboff, iwait, stv, jphi_beam, pins_beam, &
|
|
|
|
currins_beam, dpdv_beam, jcd_beam)
|
|
|
|
! Initialization at beam propagation start
|
|
|
|
|
2021-12-18 18:57:38 +01:00
|
|
|
use logger, only : log_info, log_warning
|
|
|
|
|
2024-04-23 17:00:40 +02:00
|
|
|
! subroutine arguments
|
|
|
|
integer, intent(in) :: i ! beam index
|
|
|
|
logical, intent(in) :: iroff(:,:) ! global ray status (F=active, T=inactive)
|
|
|
|
logical, intent(out) :: iboff
|
|
|
|
logical, intent(out) :: iwait(:)
|
|
|
|
real(wp_), dimension(:), intent(out) :: jphi_beam, pins_beam, currins_beam
|
|
|
|
real(wp_), dimension(:), intent(out) :: dpdv_beam, jcd_beam, stv
|
2021-12-18 18:57:38 +01:00
|
|
|
character(256) :: msg ! buffer for formatting log messages
|
2024-07-07 13:18:55 +02:00
|
|
|
|
2024-04-23 17:00:40 +02:00
|
|
|
iboff = .false. ! beam status (F = active, T = inactive)
|
|
|
|
iwait = iroff(:,i) ! copy ray status for current beam from global ray status
|
|
|
|
if(all(iwait)) then ! no rays active => stop beam
|
2019-03-26 15:21:22 +01:00
|
|
|
iboff = .true.
|
2023-03-26 16:08:03 +02:00
|
|
|
else if (any(iwait)) then
|
|
|
|
! only some rays active
|
|
|
|
write (msg,'(" beam ",g0,": only some rays are active!")') i
|
2021-12-18 18:57:38 +01:00
|
|
|
call log_warning(msg, mod='multipass', proc='initbeam')
|
2019-03-26 15:21:22 +01:00
|
|
|
end if
|
|
|
|
|
2024-07-07 13:18:55 +02:00
|
|
|
stv = 0 ! starting step
|
|
|
|
jphi_beam = 0 ! 1D beam profiles
|
|
|
|
pins_beam = 0
|
|
|
|
currins_beam = 0
|
|
|
|
dpdv_beam = 0
|
|
|
|
jcd_beam = 0
|
2019-03-26 15:21:22 +01:00
|
|
|
end subroutine initbeam
|
2024-04-23 17:00:40 +02:00
|
|
|
|
|
|
|
|
2024-07-07 13:18:55 +02:00
|
|
|
subroutine initmultipass(params, iroff, yynext, yypnext, yw0, ypw0, stnext, &
|
|
|
|
p0ray, taus, tau1, etau1, cpls, cpl1, lgcpl1, psipv, chipv)
|
2024-04-23 17:00:40 +02:00
|
|
|
! Initialization before pass loop
|
2024-07-07 13:18:55 +02:00
|
|
|
use gray_params, only : gray_parameters
|
2024-04-23 17:00:40 +02:00
|
|
|
|
|
|
|
! subroutine arguments
|
2024-07-07 13:18:55 +02:00
|
|
|
type(gray_parameters), intent(in) :: params
|
2024-04-23 17:00:40 +02:00
|
|
|
logical, dimension(:,:), intent(out) :: iroff ! global ray status (F = active, T = inactive)
|
|
|
|
real(wp_), dimension(:), intent(out) :: p0ray, tau1, etau1, cpl1
|
|
|
|
real(wp_), dimension(:), intent(out) :: lgcpl1, psipv, chipv
|
|
|
|
real(wp_), dimension(:,:), intent(out) :: yw0, ypw0, stnext, taus, cpls
|
|
|
|
real(wp_), dimension(:,:,:), intent(out) :: yynext, yypnext
|
|
|
|
|
2024-07-07 13:18:55 +02:00
|
|
|
iroff = .false. ! global ray status (F = active, T = inactive)
|
|
|
|
|
|
|
|
if(.not. params%raytracing%ipol) then
|
|
|
|
! stop other mode (iox=1/2 -> stop ib=2/1 at first pass)
|
|
|
|
call turnoffray(0, 1, params%raytracing%ipass, 3-params%antenna%iox, iroff)
|
|
|
|
end if
|
|
|
|
|
|
|
|
yynext = 0 ! starting beam coordinates (1)
|
|
|
|
yypnext = 0 ! starting beam coordinates (2)
|
|
|
|
yw0 = 0 ! temporary beam coordinates (1)
|
|
|
|
ypw0 = 0 ! temporary beam coordinates (2)
|
|
|
|
stnext = 0 ! starting beam step
|
|
|
|
p0ray = 0 ! starting beam power
|
|
|
|
taus = 0 ! beam tau from previous passes
|
|
|
|
tau1 = 0
|
|
|
|
etau1 = 1
|
|
|
|
cpls = 1 ! beam coupling from previous passes
|
|
|
|
cpl1 = 1
|
|
|
|
lgcpl1 = 0
|
|
|
|
psipv = 0 ! psi polarization angle at vacuum-plasma boundary
|
|
|
|
chipv = 0 ! chi polarization angle at vacuum-plasma boundary
|
2019-03-26 15:21:22 +01:00
|
|
|
end subroutine initmultipass
|
2024-04-23 17:00:40 +02:00
|
|
|
|
|
|
|
|
2024-07-07 13:18:55 +02:00
|
|
|
subroutine turnoffray(jk, ip, npass, ib, iroff)
|
2024-04-23 17:00:40 +02:00
|
|
|
! Turn off ray propagation
|
|
|
|
|
|
|
|
! subroutine arguments
|
|
|
|
integer, intent(in) :: jk, ip, ib ! ray (0=all rays), pass, beam indexes
|
2024-07-07 13:18:55 +02:00
|
|
|
integer, intent(in) :: npass ! total number of passes
|
2024-04-23 17:00:40 +02:00
|
|
|
logical, dimension(:,:), intent(out) :: iroff ! global ray status (F = active, T = inactive)
|
|
|
|
|
|
|
|
! local variables
|
2019-03-26 15:21:22 +01:00
|
|
|
integer :: ipx, i1, i2
|
2024-04-23 17:00:40 +02:00
|
|
|
|
|
|
|
if(jk==0) then ! stop all rays
|
2024-07-07 13:18:55 +02:00
|
|
|
do ipx=ip,npass ! from pass ip to last pass
|
2024-04-23 17:00:40 +02:00
|
|
|
i1 = 2**ipx-2+2**(ipx-ip)*(ib-1)+1 ! first derived beam at pass ipx
|
|
|
|
i2 = 2**ipx-2+2**(ipx-ip)*ib ! last derived beam at pass ipx (i1=i2 for ipx=ip)
|
2019-03-26 15:21:22 +01:00
|
|
|
iroff(:,i1:i2) = .true.
|
|
|
|
end do
|
2024-04-23 17:00:40 +02:00
|
|
|
else ! only stop ray jk
|
2024-07-07 13:18:55 +02:00
|
|
|
do ipx=ip,npass
|
2019-03-26 15:21:22 +01:00
|
|
|
i1 = 2**ipx-2+2**(ipx-ip)*(ib-1)+1
|
|
|
|
i2 = 2**ipx-2+2**(ipx-ip)*ib
|
|
|
|
iroff(jk,i1:i2) = .true.
|
|
|
|
end do
|
|
|
|
end if
|
|
|
|
end subroutine turnoffray
|
|
|
|
|
|
|
|
end module multipass
|