stdlib_error Module

Provides support for catching and handling errors (Specification) Version: experimental

A fixed-storage state variable for error handling of linear algebra routines

Version: experimental

Interfaces for comparison operators of error states with integer flags


Used by


Variables

Type Visibility Attributes Name Initial
integer(kind=ilp), public, parameter :: STDLIB_FS_ERROR = -5_ilp
integer(kind=ilp), public, parameter :: STDLIB_INTERNAL_ERROR = -3_ilp
integer(kind=ilp), public, parameter :: STDLIB_IO_ERROR = -4_ilp
integer(kind=ilp), public, parameter :: STDLIB_LINALG_ERROR = -2_ilp
integer(kind=ilp), public, parameter :: STDLIB_SUCCESS = 0_ilp

Base state return types for

integer(kind=ilp), public, parameter :: STDLIB_VALUE_ERROR = -1_ilp

Interfaces

interface

  • public module subroutine error_stop(msg, code)

    Provides a call to error stop and allows the user to specify a code and message (Specification)

    Arguments

    Type IntentOptional Attributes Name
    character(len=*), intent(in) :: msg
    integer, intent(in), optional :: code

public interface operator(/=)

  • private elemental function state_neq_flag(err, flag)

    Compare the error state with an integer flag

    Arguments

    Type IntentOptional Attributes Name
    class(state_type), intent(in) :: err
    integer, intent(in) :: flag

    Return Value logical(kind=lk)

  • private elemental function flag_neq_state(flag, err)

    Compare an integer flag with the error state

    Arguments

    Type IntentOptional Attributes Name
    integer, intent(in) :: flag
    class(state_type), intent(in) :: err

    Return Value logical(kind=lk)

public interface operator(<)

  • private elemental function state_lt_flag(err, flag)

    Compare the error state with an integer flag

    Arguments

    Type IntentOptional Attributes Name
    class(state_type), intent(in) :: err
    integer, intent(in) :: flag

    Return Value logical(kind=lk)

  • private elemental function flag_lt_state(flag, err)

    Compare an integer flag with the error state

    Arguments

    Type IntentOptional Attributes Name
    integer, intent(in) :: flag
    class(state_type), intent(in) :: err

    Return Value logical(kind=lk)

public interface operator(<=)

  • private elemental function state_le_flag(err, flag)

    Compare the error state with an integer flag

    Arguments

    Type IntentOptional Attributes Name
    class(state_type), intent(in) :: err
    integer, intent(in) :: flag

    Return Value logical(kind=lk)

  • private elemental function flag_le_state(flag, err)

    Compare an integer flag with the error state

    Arguments

    Type IntentOptional Attributes Name
    integer, intent(in) :: flag
    class(state_type), intent(in) :: err

    Return Value logical(kind=lk)

public interface operator(==)

Comparison operators

  • private elemental function state_eq_flag(err, flag)

    Compare an error state with an integer flag

    Arguments

    Type IntentOptional Attributes Name
    class(state_type), intent(in) :: err
    integer, intent(in) :: flag

    Return Value logical(kind=lk)

  • private elemental function flag_eq_state(flag, err)

    Compare an integer flag with the error state

    Arguments

    Type IntentOptional Attributes Name
    integer, intent(in) :: flag
    class(state_type), intent(in) :: err

    Return Value logical(kind=lk)

public interface operator(>)

  • private elemental function state_gt_flag(err, flag)

    Compare the error state with an integer flag

    Arguments

    Type IntentOptional Attributes Name
    class(state_type), intent(in) :: err
    integer, intent(in) :: flag

    Return Value logical(kind=lk)

  • private elemental function flag_gt_state(flag, err)

    Compare an integer flag with the error state

    Arguments

    Type IntentOptional Attributes Name
    integer, intent(in) :: flag
    class(state_type), intent(in) :: err

    Return Value logical(kind=lk)

public interface operator(>=)

  • private elemental function state_ge_flag(err, flag)

    Compare the error state with an integer flag

    Arguments

    Type IntentOptional Attributes Name
    class(state_type), intent(in) :: err
    integer, intent(in) :: flag

    Return Value logical(kind=lk)

  • private elemental function flag_ge_state(flag, err)

    Compare an integer flag with the error state

    Arguments

    Type IntentOptional Attributes Name
    integer, intent(in) :: flag
    class(state_type), intent(in) :: err

    Return Value logical(kind=lk)

public interface state_type

  • private pure function new_state(where_at, flag, a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20)

    Error creation message, with location location

    Arguments

    Type IntentOptional Attributes Name
    character(len=*), intent(in) :: where_at

    Location

    integer, intent(in) :: flag

    Input error flag

    class(*), intent(in), optional, dimension(..) :: a1

    Optional rank-agnostic arguments

    class(*), intent(in), optional, dimension(..) :: a2

    Optional rank-agnostic arguments

    class(*), intent(in), optional, dimension(..) :: a3

    Optional rank-agnostic arguments

    class(*), intent(in), optional, dimension(..) :: a4

    Optional rank-agnostic arguments

    class(*), intent(in), optional, dimension(..) :: a5

    Optional rank-agnostic arguments

    class(*), intent(in), optional, dimension(..) :: a6

    Optional rank-agnostic arguments

    class(*), intent(in), optional, dimension(..) :: a7

    Optional rank-agnostic arguments

    class(*), intent(in), optional, dimension(..) :: a8

    Optional rank-agnostic arguments

    class(*), intent(in), optional, dimension(..) :: a9

    Optional rank-agnostic arguments

    class(*), intent(in), optional, dimension(..) :: a10

    Optional rank-agnostic arguments

    class(*), intent(in), optional, dimension(..) :: a11

    Optional rank-agnostic arguments

    class(*), intent(in), optional, dimension(..) :: a12

    Optional rank-agnostic arguments

    class(*), intent(in), optional, dimension(..) :: a13

    Optional rank-agnostic arguments

    class(*), intent(in), optional, dimension(..) :: a14

    Optional rank-agnostic arguments

    class(*), intent(in), optional, dimension(..) :: a15

    Optional rank-agnostic arguments

    class(*), intent(in), optional, dimension(..) :: a16

    Optional rank-agnostic arguments

    class(*), intent(in), optional, dimension(..) :: a17

    Optional rank-agnostic arguments

    class(*), intent(in), optional, dimension(..) :: a18

    Optional rank-agnostic arguments

    class(*), intent(in), optional, dimension(..) :: a19

    Optional rank-agnostic arguments

    class(*), intent(in), optional, dimension(..) :: a20

    Optional rank-agnostic arguments

    Return Value type(state_type)

  • private pure function new_state_nowhere(flag, a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20) result(new_state)

    Error creation message, from N input variables (numeric or strings)

    Arguments

    Type IntentOptional Attributes Name
    integer, intent(in) :: flag

    Input error flag

    class(*), intent(in), optional, dimension(..) :: a1

    Optional rank-agnostic arguments

    class(*), intent(in), optional, dimension(..) :: a2

    Optional rank-agnostic arguments

    class(*), intent(in), optional, dimension(..) :: a3

    Optional rank-agnostic arguments

    class(*), intent(in), optional, dimension(..) :: a4

    Optional rank-agnostic arguments

    class(*), intent(in), optional, dimension(..) :: a5

    Optional rank-agnostic arguments

    class(*), intent(in), optional, dimension(..) :: a6

    Optional rank-agnostic arguments

    class(*), intent(in), optional, dimension(..) :: a7

    Optional rank-agnostic arguments

    class(*), intent(in), optional, dimension(..) :: a8

    Optional rank-agnostic arguments

    class(*), intent(in), optional, dimension(..) :: a9

    Optional rank-agnostic arguments

    class(*), intent(in), optional, dimension(..) :: a10

    Optional rank-agnostic arguments

    class(*), intent(in), optional, dimension(..) :: a11

    Optional rank-agnostic arguments

    class(*), intent(in), optional, dimension(..) :: a12

    Optional rank-agnostic arguments

    class(*), intent(in), optional, dimension(..) :: a13

    Optional rank-agnostic arguments

    class(*), intent(in), optional, dimension(..) :: a14

    Optional rank-agnostic arguments

    class(*), intent(in), optional, dimension(..) :: a15

    Optional rank-agnostic arguments

    class(*), intent(in), optional, dimension(..) :: a16

    Optional rank-agnostic arguments

    class(*), intent(in), optional, dimension(..) :: a17

    Optional rank-agnostic arguments

    class(*), intent(in), optional, dimension(..) :: a18

    Optional rank-agnostic arguments

    class(*), intent(in), optional, dimension(..) :: a19

    Optional rank-agnostic arguments

    class(*), intent(in), optional, dimension(..) :: a20

    Optional rank-agnostic arguments

    Return Value type(state_type)


Derived Types

type, public ::  state_type

state_type defines a general state return type for a stdlib routine. State contains a status flag, a comment, and a procedure specifier that can be used to mark where the error happened

Components

Type Visibility Attributes Name Initial
character(len=MSG_LENGTH), public :: message = repeat(' ', MSG_LENGTH)

Message associated to the current state

integer(kind=ilp), public :: state = STDLIB_SUCCESS

The current exit state

character(len=NAME_LENGTH), public :: where_at = repeat(' ', NAME_LENGTH)

Location of the state change

Constructor

private pure function new_state (where_at, flag, a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20)

Error creation message, with location location

private pure function new_state_nowhere (flag, a1, a2, a3, a4, a5, a6, a7, a8, a9, a10, a11, a12, a13, a14, a15, a16, a17, a18, a19, a20)

Error creation message, from N input variables (numeric or strings)

Type-Bound Procedures

procedure, public :: destroy => state_destroy ../../

Cleanup

procedure, public :: error => state_is_error
procedure, public :: handle => error_handling ../../

Handle optional error message

procedure, public :: ok => state_is_ok ../../

State properties

generic, public :: parse => state_parse_at_location, state_parse_arguments
procedure, public :: print => state_print ../../

Print error message

procedure, public :: print_msg => state_message

Subroutines

public subroutine check(condition, msg, code, warn)

License
Creative Commons License
Version
experimental

Checks the value of a logical condition (Specification)

Read more…

Arguments

Type IntentOptional Attributes Name
logical, intent(in) :: condition
character(len=*), intent(in), optional :: msg
integer, intent(in), optional :: code
logical, intent(in), optional :: warn