read_and_set Subroutine

private subroutine read_and_set(self, inputs)

Type Bound

ceq_type

Arguments

Type IntentOptional Attributes Name
class(ceq_type), intent(inout) :: self
type(geo_input_type), intent(in) :: inputs

Contents

Source Code


Source Code

  subroutine read_and_set(self, inputs)
    use read_chease, only: read_infile, finish
    use constants, only: pi, twopi
    implicit none
    class(ceq_type), intent(in out) :: self
    type(geo_input_type), intent(in) :: inputs
    real :: f_N, psi_N
    integer :: j
    logical, parameter :: debug = .true.
    self%type_name = 'ceq'
    self%filename = trim(adjustl(inputs%eqfile))
    if (.not. skip_file_read) then ! Primarily for testing
       write (*,*)  'Reading CHEASE input file: ', trim(self%filename)
       !    Read the data
       call read_infile(self%filename)
       call self%set_ceq_from_chease
       call finish
    end if

    !     Normalize, rename quantities
    psi_N = abs(self%B_T) * self%aminor**2
    self%psi_a = self%psi_a / psi_N
    self%psi_0 = self%psi_0 / psi_N
    self%eqpsi = self%eqpsi / psi_N
    f_N = abs(self%B_T) * self%aminor
    self%fp = self%fp / f_N

    do j = 1, self%nt
       self%eqth(:, j) = (j-1) * twopi / real(self%nt-1) - pi
       self%eqpsi_2d(:, j) = self%eqpsi
    end do

    self%diam = abs(self%R_psi(:, self%nt/2 + 1) - self%R_psi(:, 1))
    self%rc = 0.5*(self%R_psi(:, 1) + self%R_psi(:, self%nt/2 + 1))
    self%has_full_theta_range = .true.

    if (debug) then
       write (*,*) "Finished ceqin... imported CHEASE equilibrium"
       write (*,*) 'Some important quantities:'
       write (*,*) "aminor", self%aminor
       write (*,*) 'R_mag', self%R_mag
       write (*,*) 'B_T0', abs(self%B_T)
       write (*,*) 'f_N', abs(self%B_T) * self%aminor
       write (*,*) 'nthg', self%nt
       write (*,*) 'beta', self%beta_0
    end if
  end subroutine read_and_set