11#:include "common.fypp"
22#:set RC_KINDS_TYPES = REAL_KINDS_TYPES + CMPLX_KINDS_TYPES
3- !> Determinant of a rectangular matrix
43module stdlib_linalg_determinant
4+ !! Determinant of a rectangular matrix
55 use stdlib_linalg_constants
66 use stdlib_linalg_lapack, only: getrf
77 use stdlib_linalg_state, only: linalg_state_type, linalg_error_handling, LINALG_ERROR, &
88 LINALG_INTERNAL_ERROR, LINALG_VALUE_ERROR
99 implicit none(type,external)
1010 private
1111
12- !> Function interface
12+ ! Function interface
1313 public :: det
1414 public :: operator(.det.)
1515
1616 character(*), parameter :: this = 'determinant'
1717
18- ! Numpy: det(a)
19- ! Scipy: det(a, overwrite_a=False, check_finite=True)
20- ! IMSL: DET(a)
21-
2218 interface det
19+ !!### Summary
20+ !! Interface for computing matrix determinant.
21+ !!
22+ !!### Description
23+ !!
24+ !! This interface provides methods for computing the determinant of a matrix.
25+ !! Supported data types include real and complex.
26+ !!
27+ !!@note The provided functions are intended for square matrices.
28+ !!
29+ !!### Example
30+ !!
31+ !!```fortran
32+ !!
33+ !! real(sp) :: a(3,3), d
34+ !! type(linalg_state_type) :: state
35+ !! a = reshape([1, 2, 3, 4, 5, 6, 7, 8, 9], [3, 3])
36+ !!
37+ !! d = det(a,err=state)
38+ !! if (state%ok()) then
39+ !! print *, 'Success! det=',d
40+ !! else
41+ !! print *, state%print()
42+ !! endif
43+ !!
44+ !!```
45+ !!
2346 #:for rk,rt in RC_KINDS_TYPES
2447 #:if rk!="xdp"
25- ! Interface with error control
26- module procedure stdlib_linalg_${rt[0]}$${rk}$determinant
27- ! Pure interface
48+ module procedure stdlib_linalg_${rt[0]}$${rk}$determinant
2849 module procedure stdlib_linalg_pure_${rt[0]}$${rk}$determinant
2950 #:endif
3051 #:endfor
3152 end interface det
3253
33- ! Pure Operator interface
3454 interface operator(.det.)
55+ !!### Summary
56+ !! Pure operator interface for computing matrix determinant.
57+ !!
58+ !!### Description
59+ !!
60+ !! This pure operator interface provides a convenient way to compute the determinant of a matrix.
61+ !! Supported data types include real and complex.
62+ !!
63+ !!@note The provided functions are intended for square matrices.
64+ !!
65+ !!### Example
66+ !!
67+ !!```fortran
68+ !!
69+ !! real(sp) :: matrix(3,3), d
70+ !! matrix = reshape([1, 2, 3, 4, 5, 6, 7, 8, 9], [3, 3])
71+ !! d = .det.matrix
72+ !!
73+ !!```
74+ !
3575 #:for rk,rt in RC_KINDS_TYPES
3676 #:if rk!="xdp"
3777 module procedure stdlib_linalg_pure_${rt[0]}$${rk}$determinant
@@ -43,20 +83,39 @@ module stdlib_linalg_determinant
4383
4484 #:for rk,rt in RC_KINDS_TYPES
4585 #:if rk!="xdp"
46- ! Compute determinant of a square matrix A: pure interface
47- pure function stdlib_linalg_pure_${rt[0]}$${rk}$determinant(a) result(det)
86+ pure function stdlib_linalg_pure_${rt[0]}$${rk}$determinant(a) result(det)
87+ !!### Summary
88+ !! Compute determinant of a real square matrix (pure interface).
89+ !!
90+ !!### Description
91+ !!
92+ !! This function computes the determinant of a real square matrix.
93+ !!
94+ !! param: a Input matrix of size [m,n].
95+ !! return: det Matrix determinant.
96+ !!
97+ !!### Example
98+ !!
99+ !!```fortran
100+ !!
101+ !! ${rt}$ :: matrix(3,3)
102+ !! ${rt}$ :: determinant
103+ !! matrix = reshape([1, 2, 3, 4, 5, 6, 7, 8, 9], [3, 3])
104+ !! determinant = det(matrix)
105+ !!
106+ !!```
48107 !> Input matrix a[m,n]
49108 ${rt}$, intent(in) :: a(:,:)
50- !> Result: matrix determinant
109+ !> Matrix determinant
51110 ${rt}$ :: det
52111
53- !> Local variables
112+ !! Local variables
54113 type(linalg_state_type) :: err0
55114 integer(ilp) :: m,n,info,perm,k
56115 integer(ilp), allocatable :: ipiv(:)
57116 ${rt}$, allocatable :: amat(:,:)
58117
59- !> Matrix determinant size
118+ ! Matrix determinant size
60119 m = size(a,1,kind=ilp)
61120 n = size(a,2,kind=ilp)
62121
@@ -121,25 +180,47 @@ module stdlib_linalg_determinant
121180
122181 end function stdlib_linalg_pure_${rt[0]}$${rk}$determinant
123182
124- ! Compute determinant of a square matrix A, with error control
125183 function stdlib_linalg_${rt[0]}$${rk}$determinant(a,overwrite_a,err) result(det)
184+ !!### Summary
185+ !! Compute determinant of a square matrix (with error control).
186+ !!
187+ !!### Description
188+ !!
189+ !! This function computes the determinant of a square matrix with error control.
190+ !!
191+ !! param: a Input matrix of size [m,n].
192+ !! param: overwrite_a [optional] Flag indicating if the input matrix can be overwritten.
193+ !! param: err State return flag.
194+ !! return: det Matrix determinant.
195+ !!
196+ !!### Example
197+ !!
198+ !!```fortran
199+ !!
200+ !! ${rt}$ :: matrix(3,3)
201+ !! ${rt}$ :: determinant
202+ !! matrix = reshape([1, 2, 3, 4, 5, 6, 7, 8, 9], [3, 3])
203+ !! determinant = det(matrix, err=err)
204+ !!
205+ !!```
206+ !
126207 !> Input matrix a[m,n]
127208 ${rt}$, intent(inout), target :: a(:,:)
128209 !> [optional] Can A data be overwritten and destroyed?
129210 logical(lk), optional, intent(in) :: overwrite_a
130- !> [optional] state return flag. On error if not requested, the code will stop
211+ !> State return flag.
131212 type(linalg_state_type), intent(out) :: err
132- !> Result: matrix determinant
213+ !> Matrix determinant
133214 ${rt}$ :: det
134215
135- !> Local variables
216+ !! Local variables
136217 type(linalg_state_type) :: err0
137218 integer(ilp) :: m,n,info,perm,k
138219 integer(ilp), allocatable :: ipiv(:)
139220 logical(lk) :: copy_a
140221 ${rt}$, pointer :: amat(:,:)
141222
142- !> Matrix determinant size
223+ ! Matrix determinant size
143224 m = size(a,1,kind=ilp)
144225 n = size(a,2,kind=ilp)
145226
0 commit comments