screen_io_m.f90 Source File


Source Code

module screen_io_m
    !! parameter and routines usefule for screen I/O
    use netcdf
    use precision_m, only : FP
    use, intrinsic :: iso_fortran_env, only: OUTPUT_UNIT, ERROR_UNIT

    implicit none
    private

    integer :: stdout = OUTPUT_UNIT
    integer :: stderr = ERROR_UNIT

    public :: progress_bar
    public :: nf90_handle_err
    public :: set_stdout, get_stdout
    public :: set_stderr, get_stderr

contains

    subroutine set_stdout(new_unit)
        !! Redirects the stdout in PARALLAX to the given unit
        integer, intent(in) :: new_unit
        !! Unit the output is redirected to
        stdout = new_unit
    end subroutine

    integer function get_stdout()
        !! Returns the stdout in PARALLAX
        get_stdout = stdout
    end function

    subroutine set_stderr(new_unit)
        !! Redirects the stderr in PARALLAX to the given unit
        integer, intent(in) :: new_unit
        !! Unit the output is redirected to
        stderr = new_unit
    end subroutine

    integer function get_stderr()
        !! Returns the stdout in PARALLAX
        get_stderr = stderr
    end function

    subroutine progress_bar(i,n,nsteps)
        !! prints a progress bar for loops  to screen
        integer,intent(in) :: i
        !! position of progress bar, e.g. loop index
        integer, intent(in) ::n
        !! final index of loop
        integer, intent(in) :: nsteps
        !! number of steps at which a single 'bar' is printed

        integer::nst

        real(FP)::fprog

        fprog = (100.0_FP * i) / n
        nst = min(n, nsteps)

        if (i == n) then
            write(stdout, 102, advance = 'yes') nint(fprog)
        else
            if (mod(i,n/nst).eq.0) then
                write(stdout, 101, advance = 'no') nint(fprog)
            endif
        endif

        call flush(6)

101     FORMAT((I3,'%',1X))
102     FORMAT(I3,'%',1X)

    end subroutine progress_bar

    subroutine nf90_handle_err(istatus, subroutine_name)
        !! Checks for NetCDF errors and prints a standardized error message
        integer, intent(in) :: istatus
        !! Status integer returned by the NetCDF function
        character(len=*), intent(in) :: subroutine_name
        !! Name of the subroutine that called the NetCDF function

        if(istatus /= nf90_noerr) then
            write(stderr, *) 'error(',subroutine_name,'): NetCDF-error message:'
            write(stderr, *) trim(nf90_strerror(istatus))
            error stop
        end if

    end subroutine nf90_handle_err

end module screen_io_m