Skip to content

Commit

Permalink
Provide state/error handling for linear algebra (#774)
Browse files Browse the repository at this point in the history
  • Loading branch information
perazz authored Apr 11, 2024
2 parents e19d4b6 + dfd03fc commit 407798c
Show file tree
Hide file tree
Showing 9 changed files with 701 additions and 6 deletions.
1 change: 1 addition & 0 deletions doc/specs/index.md
Original file line number Diff line number Diff line change
Expand Up @@ -22,6 +22,7 @@ This is an index/directory of the specifications (specs) for each new module/fea
- [io](./stdlib_io.html) - Input/output helper & convenience
- [kinds](./stdlib_kinds.html) - Kind parameters
- [linalg](./stdlib_linalg.html) - Linear Algebra
- [linalg_state_type](./stdlib_linalg_state_type.html) - Linear Algebra state and error handling
- [logger](./stdlib_logger.html) - Runtime logging system
- [math](./stdlib_math.html) - General purpose mathematical functions
- [optval](./stdlib_optval.html) - Fallback value for optional arguments
Expand Down
64 changes: 64 additions & 0 deletions doc/specs/stdlib_linalg_state_type.md
Original file line number Diff line number Diff line change
@@ -0,0 +1,64 @@
---
title: linalg_state_type
---

# Linear Algebra -- State and Error Handling Module

[TOC]

## Introduction

The `stdlib_linalg_state` module provides a derived type holding information on the
state of linear algebra operations, and procedures for expert control of linear algebra workflows.
All linear algebra procedures are engineered to support returning an optional `linalg_state_type`
variable to holds such information, as a form of expert API. If the user does not require state
information, but fatal errors are encountered during the execution of linear algebra routines, the
program will undergo a hard stop.
Instead, if the state argument is present, the program will never stop, but will return detailed error
information into the state handler.

## Derived types provided

<!-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -->
### The `linalg_state_type` derived type

The `linalg_state_type` is defined as a derived type containing an integer error flag, and
fixed-size character strings to store an error message and the location of the error state change.
Fixed-size string storage was chosen to facilitate the compiler's memory allocation and ultimately
ensure maximum computational performance.

A similarly named generic interface, `linalg_state_type`, is provided to allow the developer to
create diagnostic messages and raise error flags easily. The call starts with an error flag or
the location of the event, and is followed by an arbitrary list of `integer`, `real`, `complex` or
`character` variables. Numeric variables may be provided as either scalars or rank-1 (array) inputs.

#### Type-bound procedures

The following convenience type-bound procedures are provided:
- `print()` returns an allocatable character string containing state location, message, and error flag;
- `print_message()` returns an allocatable character string containing the state message;
- `ok()` returns a `logical` flag that is `.true.` in case of successful state (`flag==LINALG_SUCCESS`);
- `error()` returns a `logical` flag that is `.true.` in case of error state (`flag/=LINALG_SUCCESS`).

#### Status

Experimental

#### Example

```fortran
{!example/linalg/example_state1.f90!}
```

## Error flags provided

The module provides the following state flags:
- `LINALG_SUCCESS`: Successful execution
- `LINALG_VALUE_ERROR`: Numerical errors (such as infinity, not-a-number, range bounds) are encountered.
- `LINALG_ERROR`: Linear Algebra errors are encountered, such as: non-converging iterations, impossible operations, etc.
- `LINALG_INTERNAL_ERROR`: Provided as a developer safeguard for internal errors that should never occur.

## Comparison operators provided

The module provides overloaded comparison operators for all comparisons of a `linalg_state_type` variable
with an integer error flag: `<`, `<=`, `==`, `>=`, `>`, `/=`.
4 changes: 4 additions & 0 deletions example/linalg/CMakeLists.txt
Original file line number Diff line number Diff line change
Expand Up @@ -14,3 +14,7 @@ ADD_EXAMPLE(is_symmetric)
ADD_EXAMPLE(is_triangular)
ADD_EXAMPLE(outer_product)
ADD_EXAMPLE(trace)
ADD_EXAMPLE(state1)
ADD_EXAMPLE(state2)
ADD_EXAMPLE(blas_gemv)
ADD_EXAMPLE(lapack_getrf)
20 changes: 20 additions & 0 deletions example/linalg/example_state1.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,20 @@
program example_state1
use stdlib_linalg_state, only: linalg_state_type, LINALG_SUCCESS, LINALG_VALUE_ERROR, &
operator(/=)
implicit none
type(linalg_state_type) :: err

! To create a state variable, we enter its integer state flag, followed by a list of variables
! that will be automatically assembled into a formatted error message. No need to provide string formats
err = linalg_state_type(LINALG_VALUE_ERROR,'just an example with scalar ',&
'integer=',1,'real=',2.0,'complex=',(3.0,1.0),'and array ',[1,2,3],'inputs')

! Print flag
print *, err%print()

! Check success
print *, 'Check error: ',err%error()
print *, 'Check flag : ',err /= LINALG_SUCCESS


end program example_state1
64 changes: 64 additions & 0 deletions example/linalg/example_state2.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,64 @@
program example_state2
!! This example shows how to set a `type(linalg_state_type)` variable to process output conditions
!! out of a simple division routine. The example is meant to highlight:
!! 1) the different mechanisms that can be used to initialize the `linalg_state` variable providing
!! strings, scalars, or arrays, on input to it;
!! 2) `pure` setup of the error control
use stdlib_linalg_state, only: linalg_state_type, LINALG_VALUE_ERROR, LINALG_SUCCESS, &
linalg_error_handling
implicit none
integer :: info
type(linalg_state_type) :: err
real :: a_div_b

! OK
call very_simple_division(0.0,2.0,a_div_b,err)
print *, err%print()

! Division by zero
call very_simple_division(1.0,0.0,a_div_b,err)
print *, err%print()

! Out of bounds
call very_simple_division(huge(0.0),0.001,a_div_b,err)
print *, err%print()

contains

!> Simple division returning an integer flag (LAPACK style)
elemental subroutine very_simple_division(a,b,a_div_b,err)
real, intent(in) :: a,b
real, intent(out) :: a_div_b
type(linalg_state_type), optional, intent(out) :: err

type(linalg_state_type) :: err0
real, parameter :: MAXABS = huge(0.0)
character(*), parameter :: this = 'simple division'

!> Check a
if (b==0.0) then
! Division by zero
err0 = linalg_state_type(this,LINALG_VALUE_ERROR,'Division by zero trying ',a,'/',b)
elseif (.not.abs(b)<MAXABS) then
! B is out of bounds
err0 = linalg_state_type(this,LINALG_VALUE_ERROR,'B is infinity in a/b: ',[a,b]) ! use an array
elseif (.not.abs(a)<MAXABS) then
! A is out of bounds
err0 = linalg_state_type(this,LINALG_VALUE_ERROR,'A is infinity in a/b: a=',a,' b=',b)
else
a_div_b = a/b
if (.not.abs(a_div_b)<MAXABS) then
! Result is out of bounds
err0 = linalg_state_type(this,LINALG_VALUE_ERROR,'A/B is infinity in a/b: a=',a,' b=',b)
else
err0%state = LINALG_SUCCESS
end if
end if

! Return error flag, or hard stop on failure
call linalg_error_handling(err0,err)

end subroutine very_simple_division


end program example_state2
1 change: 1 addition & 0 deletions src/CMakeLists.txt
Original file line number Diff line number Diff line change
Expand Up @@ -24,6 +24,7 @@ set(fppFiles
stdlib_linalg_outer_product.fypp
stdlib_linalg_kronecker.fypp
stdlib_linalg_cross_product.fypp
stdlib_linalg_state.fypp
stdlib_optval.fypp
stdlib_selection.fypp
stdlib_sorting.fypp
Expand Down
1 change: 0 additions & 1 deletion src/stdlib_linalg_constants.fypp
Original file line number Diff line number Diff line change
Expand Up @@ -7,7 +7,6 @@ module stdlib_linalg_constants
public



! Integer size support for ILP64 builds should be done here
integer, parameter :: ilp = int32
private :: int32, int64
Expand Down
Loading

0 comments on commit 407798c

Please sign in to comment.