params_equi_slab_m.f90 Source File


Source Code

module params_equi_slab_m
    !! Module for parameter reading for the slab 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) :: boxsize = 64.0_FP
    !! Size of the domain in x and y
    logical :: sol = .true.
    !! Indicates if slab is open or closed field lines
    ! NOTE: We choose open field lines as the default to enable the
    !       testing of boundary conditions for open field lines with
    !       unit tests.
    logical :: yperiodic = .true.
    !! Indicates if box is periodic in y direction

    public :: read_params_slab
    public :: write_params_slab

    public :: get_slab_boxsize
    public :: get_slab_sol
    public :: get_slab_yperiodic

    namelist / equi_slab_params / boxsize, sol, yperiodic

contains

    pure real(FP) function get_slab_boxsize()
        get_slab_boxsize = boxsize
    end function

    pure logical function get_slab_sol()
        get_slab_sol = sol
    end function

    pure logical function get_slab_yperiodic()
        get_slab_yperiodic = yperiodic
    end function

    subroutine read_params_slab(filename)
        !! Reads the equi slab 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_slab_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_slab_params not present."
        elseif (io_error /= 0) then
            call handle_error("Reading slab 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_slab(filename)
        !! Writes the equi slab 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_slab_params, iostat=io_error)
        if (io_error /= 0) then
            call handle_error("Writing slab equi parameters failed!", &
                              PARALLAX_ERR_PARAMETERS, __LINE__, __FILE__, &
                              additional_info=&
                                error_info_t("Iostat:", [io_error]))
        end if

        close(funit)
    end subroutine

end module