stdlib_xerbla_array Subroutine

public pure subroutine stdlib_xerbla_array(srname_array, srname_len, info)

XERBLA_ARRAY assists other languages in calling XERBLA, the LAPACK and BLAS error handler. Rather than taking a Fortran string argument as the function's name, XERBLA_ARRAY takes an array of single characters along with the array's length. XERBLA_ARRAY then copies up to 32 characters of that array into a Fortran string and passes that to XERBLA. If called with a non-positive SRNAME_LEN, XERBLA_ARRAY will call XERBLA with a string of all blank characters. Say some macro or other device makes XERBLA_ARRAY available to C99 by a name lapack_xerbla and with a common Fortran calling convention. Then a C99 program could invoke XERBLA via: { int flen = strlen(func); lapack_xerbla(func, } Providing XERBLA_ARRAY is not necessary for intercepting LAPACK errors. XERBLA_ARRAY calls XERBLA.

Arguments

Type IntentOptional Attributes Name
character(len=1), intent(in) :: srname_array(srname_len)
integer(kind=ilp), intent(in) :: srname_len
integer(kind=ilp), intent(in) :: info

Source Code

     pure subroutine stdlib_xerbla_array(srname_array, srname_len, info)
     !! XERBLA_ARRAY assists other languages in calling XERBLA, the LAPACK
     !! and BLAS error handler.  Rather than taking a Fortran string argument
     !! as the function's name, XERBLA_ARRAY takes an array of single
     !! characters along with the array's length.  XERBLA_ARRAY then copies
     !! up to 32 characters of that array into a Fortran string and passes
     !! that to XERBLA.  If called with a non-positive SRNAME_LEN,
     !! XERBLA_ARRAY will call XERBLA with a string of all blank characters.
     !! Say some macro or other device makes XERBLA_ARRAY available to C99
     !! by a name lapack_xerbla and with a common Fortran calling convention.
     !! Then a C99 program could invoke XERBLA via:
     !! {
     !! int flen = strlen(__func__);
     !! lapack_xerbla(__func__,
     !! }
     !! Providing XERBLA_ARRAY is not necessary for intercepting LAPACK
     !! errors.  XERBLA_ARRAY calls XERBLA.
        ! -- reference blas level1 routine --
        ! -- reference blas is a software package provided by univ. of tennessee,    --
        ! -- univ. of california berkeley, univ. of colorado denver and nag ltd..--
           ! Scalar Arguments 
           integer(ilp), intent(in) :: srname_len, info
           ! Array Arguments 
           character(1), intent(in) :: srname_array(srname_len)
       ! =====================================================================
           ! Local Scalars 
           integer(ilp) :: i
           ! Local Arrays 
           character*32 srname
           ! Intrinsic Functions 
           intrinsic :: min,len
           ! Executable Statements 
           srname = ''
           do i = 1, min( srname_len, len( srname ) )
              srname( i:i ) = srname_array( i )
           end do
           call stdlib_xerbla( srname, info )
           return
     end subroutine stdlib_xerbla_array