|
V3FIT
|
Go to the documentation of this file.
67 CHARACTER (len=path_length) :: vacuum_file_name
69 REAL (rprec),
DIMENSION(:),
POINTER :: extcur => null()
91 CHARACTER (len=*),
INTENT(in) :: file_name
92 INTEGER,
INTENT(in) :: iou
95 TYPE (bsc_rs) :: bsc_rs_object
96 REAL (rprec),
DIMENSION(3) :: center, mean_r
97 REAL (rprec) :: total_current
99 REAL (rprec) :: start_time
104 WRITE (*,*)
' *** Initializing vacuum equilibrium from file ' //
106 WRITE (iou,*)
' *** Initializing vacuum equilibrium from file ' //
127 DO j = 1, coil_group(i)%ncoil
128 total_current = total_current
129 & + coil_group(i)%coils(j)%current
130 CALL bsc_mean_r(coil_group(i)%coils(j), mean_r)
131 center = center + mean_r*coil_group(i)%coils(j)%current
133 IF (total_current .ne. 0.0)
THEN
134 center = center/total_current
139 CALL bsc_construct_rs(bsc_rs_object, 0.0_dp, 0.0_dp, 0.0_dp,
140 & (/ 0.0_dp, 0.0_dp, 0.0_dp /),
142 CALL bsc_rot_shift(coil_group(i), bsc_rs_object)
148 CALL bsc_rot_shift(coil_group(i), bsc_rs_object)
170 TYPE (vacuum_class),
POINTER :: this
173 IF (
ASSOCIATED(this%extcur))
THEN
174 DEALLOCATE(this%extcur)
175 this%extcur => null()
202 TYPE (vacuum_class),
INTENT(inout) :: this
203 INTEGER,
INTENT(in) :: id
204 INTEGER,
INTENT(in) :: i_index
205 REAL (rprec),
INTENT(in) :: value
208 REAL (rprec) :: start_time
216 this%extcur(i_index) =
value
243 CHARACTER (len=*),
INTENT(in) :: param_name
246 REAL (rprec) :: start_time
251 SELECT CASE (trim(param_name))
257 WRITE (*,1000) trim(param_name)
264 1000
FORMAT(
'ERROR: ',a,
' is not a valid parameter.')
285 INTEGER,
INTENT(in) :: id
286 INTEGER,
INTENT(in) :: i_index
289 REAL (rprec) :: start_time
324 INTEGER,
INTENT(in) :: id
327 REAL (rprec) :: start_time
338 stop
'Invalid vacuum parameter id.'
365 REAL (rprec),
DIMENSION(3),
INTENT(in) :: x_cart
366 LOGICAL,
INTENT(in) :: cyl
370 REAL (rprec),
DIMENSION(3) :: b_vec
371 REAL (rprec) :: start_time
377 DO i = 1,
SIZE(this%extcur)
378 CALL bsc_b(coil_group(i), x_cart, b_vec, this%extcur(i))
404 USE stel_constants,
only: twopi
412 REAL (rprec),
INTENT(in) :: r
413 REAL (rprec),
INTENT(in) :: theta
416 REAL (rprec),
DIMENSION(3) :: b_cart
417 REAL (rprec),
DIMENSION(3) :: r_cyl
418 REAL (rprec),
DIMENSION(3) :: dl
420 REAL (rprec) :: start_time
427 r_cyl(1) = r*cos(theta)
429 r_cyl(3) = r*sin(theta)
431 dphi = 0.001/r_cyl(1)
432 DO WHILE (r_cyl(2) .lt. twopi)
436 & + dot_product(b_cart, dl)
437 r_cyl(2) = r_cyl(2) + dphi
463 LOGICAL,
INTENT(out) :: scale_currents
466 REAL (rprec) :: start_time
472 scale_currents = .false.
497 INTEGER,
INTENT(in) :: id
500 REAL (rprec) :: start_time
536 INTEGER,
INTENT(in) :: id
539 REAL (rprec) :: start_time
574 TYPE (vacuum_class),
INTENT(in) :: this
575 INTEGER,
INTENT(in) :: iou
578 REAL (rprec) :: start_time
584 WRITE (iou,*)
'Equilibrium Type : vacuum'
606 TYPE (vacuum_class),
INTENT(in) :: this
607 INTEGER,
INTENT(in) :: current_step
610 CHARACTER (len=path_length) :: filename
611 REAL (rprec) :: start_time
616 WRITE (filename,1000) trim(this%vacuum_file_name), current_step
621 1000
FORMAT(a,
'_',i0.3)
logical function vacuum_is_recon_param(this, id)
Checks if a parameter id is a reconstruction parameter.
Defines functions for measuring an tabulating performance of function and subroutine calls....
Module is part of the LIBSTELL. This modules containes code to convert from different coordinate syst...
real(rprec) function, dimension(3) vacuum_get_b_vec(this, x_cart, cyl)
Gets the magnetic field vector at a position.
integer, parameter vacuum_extcur_id
1D Array of external currents.
pure real(rprec) function, dimension(3) cart_to_cyl_vec(cart, vec)
Convert vector from cartesian coordinates to cylindical coordinates.
real(rprec) function, dimension(:), pointer vacuum_get_ext_currents(this, scale_currents)
Get external current.
real(rprec) function vacuum_get_int_b_dphi(this, r, theta)
Gets the loop integrated magnetic field at a position.
subroutine vacuum_destruct(this)
Deconstruct a vacuum_class object.
pure real(rprec) function, dimension(3), public cyl_to_cart_vec(cyl, vec)
Convert vector from cylindical coordinates to cartesian coordinates.
Umbrella module avoid multiple inlcudes of the mpif.h header.
real(rprec) function vacuum_get_param_value(this, id, i_index)
Get the value of a reconstruction vacuum parameter.
real(rprec) function profiler_get_start_time()
Gets the start time of profiled function.
subroutine vacuum_write(this, iou)
Write out the equilibrium to an output file.
pure real(rprec) function, dimension(3), public cyl_to_cart(cyl)
Convert a point from cylindical coordinates to cartesian coordinates.
character(len=data_name_length) function vacuum_get_param_name(this, id)
Get the name of a reconstruction vacuum parameter.
type(vacuum_class) function, pointer vacuum_construct(file_name, iou)
Construct a vacuum_class object.
integer function vacuum_get_param_id(this, param_name)
Get the id for a reconstruction parameter.
This modules contains parameters used by equilibrium models.
subroutine profiler_set_stop_time(symbol_name, start_time)
Gets the end time of profiled function.
logical function vacuum_is_1d_array(this, id)
Checks if a parameter id is a 1d array.
subroutine vacuum_write_input(this, current_step)
Write the current valid input.
subroutine vacuum_set_param(this, id, i_index, value)
Sets the value of a reconstruction equilibrium parameter.
Base class representing a vacuum_equilibrium.
Defines the base class of the type vacuum_class. This module contains all the code necessary to inter...