Skip to content

Commit 5f320f9

Browse files
committed
subroutine version, non in-place
1 parent db714bb commit 5f320f9

File tree

3 files changed

+66
-12
lines changed

3 files changed

+66
-12
lines changed

doc/specs/stdlib_linalg.md

Lines changed: 8 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -948,12 +948,16 @@ The solver is based on LAPACK's `*GETRF` and `*GETRI` backends.
948948

949949
### Syntax
950950

951-
`call ` [[stdlib_linalg(module):invert(interface)]] `(a, [, pivot] [, err])`
951+
`call ` [[stdlib_linalg(module):invert(interface)]] `(a, [,inva] [, pivot] [, err])`
952952

953953
### Arguments
954954

955-
`a`: Shall be a rank-2, square, `real` or `complex` array containing the coefficient matrix. It is an `intent(inout)` argument.
956-
On output, it is replaced by the inverse of `a`.
955+
`a`: Shall be a rank-2, square, `real` or `complex` array containing the coefficient matrix.
956+
If `inva` is provided, it is an `intent(in)` argument.
957+
If `inva` is not provided, it is an `intent(inout)` argument: on output, it is replaced by the inverse of `a`.
958+
959+
`inva` (optional): Shall be a rank-2, square, `real` or `complex` array with the same size, and kind as `a`.
960+
On output, it contains the inverse of `a`.
957961

958962
`pivot` (optional): Shall be a rank-1 array of the same kind and matrix dimension as `a`, providing storage for the diagonal pivot indices. It is an `intent(inout)` arguments, and returns the diagonal pivot indices.
959963

@@ -964,6 +968,7 @@ On output, it is replaced by the inverse of `a`.
964968
Replaces matrix \( A \) with its inverse, \(A^{-1}\).
965969

966970
Raises `LINALG_ERROR` if the matrix is singular or has invalid size.
971+
Raises `LINALG_VALUE_ERROR` if `inva` and `a` do not have the same size.
967972
If `err` is not present, exceptions trigger an `error stop`.
968973

969974
### Example

src/stdlib_linalg.fypp

Lines changed: 19 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -604,25 +604,38 @@ module stdlib_linalg
604604
!!
605605
!!### Description
606606
!!
607-
!! This subroutine interface provides a way to compute the inverse of a matrix in-place.
607+
!! This subroutine interface provides a way to compute the inverse of a matrix.
608608
!! Supported data types include `real` and `complex`.
609-
!! On completion, matrix `a` is replaced by the inverse matrix. Pre-allocated storage may be provided
610-
!! for the array of pivot indices, `pivot`. If all pre-allocated work spaces are provided, no internal
611-
!! memory allocations take place when using this interface.
609+
!! The user may provide a unique matrix argument `a`. In this case, `a` is replaced by the inverse matrix.
610+
!! on output. Otherwise, one may provide two separate arguments: an input matrix `a` and an output matrix
611+
!! `inva`. In this case, `a` will not be modified, and the inverse is returned in `inva`.
612+
!! Pre-allocated storage may be provided for the array of pivot indices, `pivot`. If all pre-allocated
613+
!! work spaces are provided, no internal memory allocations take place when using this interface.
612614
!!
613615
!!@note The provided subroutines are intended for square matrices.
614616
!!@note BLAS/LAPACK backends do not currently support extended precision (``xdp``).
615617
!!
616618
#:for rk,rt,ri in RC_KINDS_TYPES
617619
#:if rk!="xdp"
618-
module subroutine stdlib_linalg_invert_${ri}$(a,pivot,err)
620+
module subroutine stdlib_linalg_invert_inplace_${ri}$(a,pivot,err)
619621
!> Input matrix a[n,n]
620622
${rt}$, intent(inout) :: a(:,:)
621623
!> [optional] Storage array for the diagonal pivot indices
622624
integer(ilp), optional, intent(inout), target :: pivot(:)
623625
!> [optional] state return flag. On error if not requested, the code will stop
624626
type(linalg_state_type), optional, intent(out) :: err
625-
end subroutine stdlib_linalg_invert_${ri}$
627+
end subroutine stdlib_linalg_invert_inplace_${ri}$
628+
! Compute the square matrix inverse of a
629+
module subroutine stdlib_linalg_invert_split_${ri}$(a,inva,pivot,err)
630+
!> Input matrix a[n,n].
631+
${rt}$, intent(in) :: a(:,:)
632+
!> Inverse matrix a[n,n].
633+
${rt}$, intent(out) :: inva(:,:)
634+
!> [optional] Storage array for the diagonal pivot indices
635+
integer(ilp), optional, intent(inout), target :: pivot(:)
636+
!> [optional] state return flag. On error if not requested, the code will stop
637+
type(linalg_state_type), optional, intent(out) :: err
638+
end subroutine stdlib_linalg_invert_split_${ri}$
626639
#:endif
627640
#:endfor
628641
end interface invert

src/stdlib_linalg_inverse.fypp

Lines changed: 39 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -34,7 +34,7 @@ submodule (stdlib_linalg) stdlib_linalg_inverse
3434
#:for rk,rt,ri in RC_KINDS_TYPES
3535
#:if rk!="xdp"
3636
! Compute the in-place square matrix inverse of a
37-
module subroutine stdlib_linalg_invert_${ri}$(a,pivot,err)
37+
module subroutine stdlib_linalg_invert_inplace_${ri}$(a,pivot,err)
3838
!> Input matrix a[n,n]. On return, A is destroyed and replaced by the inverse
3939
${rt}$, intent(inout) :: a(:,:)
4040
!> [optional] Storage array for the diagonal pivot indices
@@ -92,7 +92,43 @@ submodule (stdlib_linalg) stdlib_linalg_inverse
9292
if (.not.present(pivot)) deallocate(ipiv)
9393
call linalg_error_handling(err0,err)
9494

95-
end subroutine stdlib_linalg_invert_${ri}$
95+
end subroutine stdlib_linalg_invert_inplace_${ri}$
96+
97+
! Compute the square matrix inverse of a
98+
module subroutine stdlib_linalg_invert_split_${ri}$(a,inva,pivot,err)
99+
!> Input matrix a[n,n].
100+
${rt}$, intent(in) :: a(:,:)
101+
!> Inverse matrix a[n,n].
102+
${rt}$, intent(out) :: inva(:,:)
103+
!> [optional] Storage array for the diagonal pivot indices
104+
integer(ilp), optional, intent(inout), target :: pivot(:)
105+
!> [optional] state return flag. On error if not requested, the code will stop
106+
type(linalg_state_type), optional, intent(out) :: err
107+
108+
type(linalg_state_type) :: err0
109+
integer(ilp) :: sa(2),sinva(2)
110+
111+
sa = shape(a,kind=ilp)
112+
sinva = shape(inva,kind=ilp)
113+
114+
if (any(sa/=sinva)) then
115+
116+
err0 = linalg_state_type(this,LINALG_VALUE_ERROR,'invalid matrix size: a=',sa,' inva=',sinva)
117+
118+
else
119+
120+
!> Copy data in
121+
inva = a
122+
123+
!> Compute matrix inverse
124+
call stdlib_linalg_invert_inplace_${ri}$(inva,err=err0)
125+
126+
end if
127+
128+
! Process output and return
129+
call linalg_error_handling(err0,err)
130+
131+
end subroutine stdlib_linalg_invert_split_${ri}$
96132

97133
! Invert matrix in place
98134
module function stdlib_linalg_inverse_${ri}$(a,err) result(inva)
@@ -107,7 +143,7 @@ submodule (stdlib_linalg) stdlib_linalg_inverse
107143
allocate(inva,source=a)
108144

109145
!> Compute matrix inverse
110-
call stdlib_linalg_invert_${ri}$(inva,err=err)
146+
call stdlib_linalg_invert_inplace_${ri}$(inva,err=err)
111147

112148
end function stdlib_linalg_inverse_${ri}$
113149

0 commit comments

Comments
 (0)