handle_heev_info Subroutine

public elemental subroutine handle_heev_info(this, err, info, m, n)

Process SYEV/HEEV output flags

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: this
type(linalg_state_type), intent(inout) :: err

Error handler

integer(kind=ilp), intent(in) :: info

SYEV/HEEV return flag

integer(kind=ilp), intent(in) :: m

Input matrix size

integer(kind=ilp), intent(in) :: n

Input matrix size


Source Code

     elemental subroutine handle_heev_info(this,err,info,m,n)
        character(len=*), intent(in) :: this
        !> Error handler
        type(linalg_state_type), intent(inout) :: err
        !> SYEV/HEEV return flag
        integer(ilp), intent(in) :: info
        !> Input matrix size
        integer(ilp), intent(in) :: m,n

        select case (info)
           case (0)
               ! Success!
               err%state = LINALG_SUCCESS
           case (-1)
               err = linalg_state_type(this,LINALG_INTERNAL_ERROR,'Invalid eigenvector request.')
           case (-2)
               err = linalg_state_type(this,LINALG_INTERNAL_ERROR,'Invalid triangular section request.')
           case (-5,-3)
               err = linalg_state_type(this,LINALG_VALUE_ERROR,'invalid matrix size: a=',[m,n])
           case (-8)
               err = linalg_state_type(this,LINALG_INTERNAL_ERROR,'insufficient workspace size.')
           case (1:)
               err = linalg_state_type(this,LINALG_ERROR,'Eigenvalue computation did not converge.')
           case default
               err = linalg_state_type(this,LINALG_INTERNAL_ERROR,'Unknown error returned by syev/heev.')
        end select

     end subroutine handle_heev_info