params_equi_circular_m.f90 Source File


Source Code

module params_equi_circular_m
    !! Module for parameter reading for the circular equilibrium type
    use, intrinsic :: iso_fortran_env, only: IOSTAT_END, IOSTAT_EOR
    use screen_io_m, only: get_stdout
    use precision_m, only: FP
    use error_handling_m, only: handle_error, error_info_t
    use status_codes_m, only: PARALLAX_ERR_PARAMETERS

    implicit none
    private

    real(FP) :: rhomin = 0.2412_FP
    !! Minimum rho in the simulation domain
    real(FP) :: rhomax = 0.3685_FP
    !! Maximum rho in the simulation domain
    integer ::  qtype = 1
    !! Type of the safety factor q-profile. Available options are
    !! 0 => Linear q profile
    !! 1 => Inverse (1/x hyperbolic) q-profile
    real(FP) :: rhoq_ref = 0.305_FP
    !! Reference flux surface for definition of the q-profile
    real(FP) :: q_ref = 4.0_FP
    !! Safety factor value at reference flux surface
    real(FP) :: shear = 3.71_FP
    !! Magnetic shear
    real(FP) :: dtheta_limiter = 0.4_FP
    !! Poloidal width of the limiter. If smaller equal than zero, no limiter
    !! is used.
    real(FP) :: rho_limiter = 0.3235_FP
    !! Radial position (start) of the limiter
    real(FP) :: theta_limiter = 3.1415_FP
    !! Poloidal position of the limiter

    public :: read_params_circular
    public :: write_params_circular

    public :: get_circular_rhomin
    public :: get_circular_rhomax
    public :: get_circular_qtype
    public :: get_circular_rhoq_ref
    public :: get_circular_q_ref
    public :: get_circular_shear
    public :: get_circular_dtheta_limiter
    public :: get_circular_rho_limiter
    public :: get_circular_theta_limiter

    namelist / equi_circular_params / &
        rhomin, rhomax, qtype, rhoq_ref, q_ref, shear, &
        dtheta_limiter, rho_limiter, theta_limiter

contains

    pure real(FP) function get_circular_rhomin()
        get_circular_rhomin = rhomin
    end function

    pure real(FP) function get_circular_rhomax()
        get_circular_rhomax = rhomax
    end function

    pure integer function get_circular_qtype()
        get_circular_qtype = qtype
    end function

    pure real(FP) function get_circular_rhoq_ref()
        get_circular_rhoq_ref = rhoq_ref
    end function

    pure real(FP) function get_circular_q_ref()
        get_circular_q_ref = q_ref
    end function

    pure real(FP) function get_circular_shear()
        get_circular_shear = shear
    end function

    pure real(FP) function get_circular_dtheta_limiter()
        get_circular_dtheta_limiter = dtheta_limiter
    end function

    pure real(FP) function get_circular_rho_limiter()
        get_circular_rho_limiter = rho_limiter
    end function

    pure real(FP) function get_circular_theta_limiter()
        get_circular_theta_limiter = theta_limiter
    end function

    subroutine read_params_circular(filename)
        !! Reads the equi circular namelist from the given filename
        character(len=*), intent(in) :: filename
        !! Filename to read from

        integer :: funit, io_error

        open(newunit=funit, file=filename, status='old', action='read', &
             iostat=io_error)
        if (io_error /= 0) then
            call handle_error("Opening parameter file "//filename//" failed!", &
                              PARALLAX_ERR_PARAMETERS, __LINE__, __FILE__, &
                              additional_info=&
                                error_info_t("Iostat:", [io_error]))
        end if

        read(funit, nml=equi_circular_params, iostat=io_error)
        ! END and EOR are returned if namelist can not be found. We treat
        ! these cases as non fatal and write a notification.
        if (io_error == IOSTAT_END .or. io_error == IOSTAT_EOR) then
            write(get_stdout(), *) &
                "Info: Namelist equi_circular_params not present."
        elseif (io_error /= 0) then
            call handle_error("Reading circular equi parameters failed!", &
                              PARALLAX_ERR_PARAMETERS, __LINE__, __FILE__, &
                              additional_info=&
                                error_info_t("Iostat:", [io_error]))
        end if

        close(funit)
    end subroutine

    subroutine write_params_circular(filename)
        !! Writes the equi circular namelist to the given filename
        character(len=*), intent(in) :: filename
        !! Filename to read from

        integer :: funit, io_error

        open(newunit=funit, file=filename, action='write', position='append', &
             iostat=io_error)
        if (io_error /= 0) then
            call handle_error("Opening parameter file "//filename//" failed!", &
                              PARALLAX_ERR_PARAMETERS, __LINE__, __FILE__, &
                              additional_info=&
                                error_info_t("Iostat:", [io_error]))
        end if

        write(funit, nml=equi_circular_params, iostat=io_error)
        if (io_error /= 0) then
            call handle_error("Writing circular equi parameters failed!", &
                              PARALLAX_ERR_PARAMETERS, __LINE__, __FILE__, &
                              additional_info=&
                                error_info_t("Iostat:", [io_error]))
        end if

        close(funit)
    end subroutine

end module