Skip to content

Commit 15023e1

Browse files
committed
submodule version
1 parent 4beab1f commit 15023e1

File tree

2 files changed

+96
-75
lines changed

2 files changed

+96
-75
lines changed

src/stdlib_linalg.fypp

Lines changed: 92 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1,18 +1,19 @@
11
#:include "common.fypp"
2-
#:set RCI_KINDS_TYPES = REAL_KINDS_TYPES + CMPLX_KINDS_TYPES + INT_KINDS_TYPES
2+
#:set RC_KINDS_TYPES = REAL_KINDS_TYPES + CMPLX_KINDS_TYPES
3+
#:set RCI_KINDS_TYPES = RC_KINDS_TYPES + INT_KINDS_TYPES
34
module stdlib_linalg
45
!!Provides a support for various linear algebra procedures
56
!! ([Specification](../page/specs/stdlib_linalg.html))
6-
use stdlib_kinds, only: sp, dp, xdp, qp, &
7+
use stdlib_kinds, only: sp, dp, xdp, qp, lk, &
78
int8, int16, int32, int64
89
use stdlib_error, only: error_stop
910
use stdlib_optval, only: optval
1011
use stdlib_linalg_state, only: linalg_state_type, linalg_error_handling
11-
use stdlib_linalg_determinant, only: det
1212
implicit none
1313
private
1414

1515
public :: det
16+
public :: operator(.det.)
1617
public :: diag
1718
public :: eye
1819
public :: trace
@@ -220,6 +221,94 @@ module stdlib_linalg
220221
#:endfor
221222
end interface is_hessenberg
222223

224+
225+
interface det
226+
!!### Summary
227+
!! Interface for computing matrix determinant.
228+
!!
229+
!!### Description
230+
!!
231+
!! This interface provides methods for computing the determinant of a matrix.
232+
!! Supported data types include real and complex.
233+
!!
234+
!!@note The provided functions are intended for square matrices.
235+
!!
236+
!!### Example
237+
!!
238+
!!```fortran
239+
!!
240+
!! real(sp) :: a(3,3), d
241+
!! type(linalg_state_type) :: state
242+
!! a = reshape([1, 2, 3, 4, 5, 6, 7, 8, 9], [3, 3])
243+
!!
244+
!! d = det(a,err=state)
245+
!! if (state%ok()) then
246+
!! print *, 'Success! det=',d
247+
!! else
248+
!! print *, state%print()
249+
!! endif
250+
!!
251+
!!```
252+
!!
253+
#:for rk,rt in RC_KINDS_TYPES
254+
#:if rk!="xdp"
255+
module procedure stdlib_linalg_${rt[0]}$${rk}$determinant
256+
module procedure stdlib_linalg_pure_${rt[0]}$${rk}$determinant
257+
#:endif
258+
#:endfor
259+
end interface det
260+
261+
interface operator(.det.)
262+
!!### Summary
263+
!! Pure operator interface for computing matrix determinant.
264+
!!
265+
!!### Description
266+
!!
267+
!! This pure operator interface provides a convenient way to compute the determinant of a matrix.
268+
!! Supported data types include real and complex.
269+
!!
270+
!!@note The provided functions are intended for square matrices.
271+
!!
272+
!!### Example
273+
!!
274+
!!```fortran
275+
!!
276+
!! real(sp) :: matrix(3,3), d
277+
!! matrix = reshape([1, 2, 3, 4, 5, 6, 7, 8, 9], [3, 3])
278+
!! d = .det.matrix
279+
!!
280+
!!```
281+
!
282+
#:for rk,rt in RC_KINDS_TYPES
283+
#:if rk!="xdp"
284+
module procedure stdlib_linalg_pure_${rt[0]}$${rk}$determinant
285+
#:endif
286+
#:endfor
287+
end interface operator(.det.)
288+
289+
interface
290+
#:for rk,rt in RC_KINDS_TYPES
291+
#:if rk!="xdp"
292+
module function stdlib_linalg_${rt[0]}$${rk}$determinant(a,overwrite_a,err) result(det)
293+
!> Input matrix a[m,n]
294+
${rt}$, intent(inout), target :: a(:,:)
295+
!> [optional] Can A data be overwritten and destroyed?
296+
logical(lk), optional, intent(in) :: overwrite_a
297+
!> State return flag.
298+
type(linalg_state_type), intent(out) :: err
299+
!> Matrix determinant
300+
${rt}$ :: det
301+
end function stdlib_linalg_${rt[0]}$${rk}$determinant
302+
module function stdlib_linalg_pure_${rt[0]}$${rk}$determinant(a) result(det)
303+
!> Input matrix a[m,n]
304+
${rt}$, intent(in) :: a(:,:)
305+
!> Matrix determinant
306+
${rt}$ :: det
307+
end function stdlib_linalg_pure_${rt[0]}$${rk}$determinant
308+
#:endif
309+
#:endfor
310+
end interface
311+
223312
contains
224313

225314

src/stdlib_linalg_determinant.fypp

Lines changed: 4 additions & 72 deletions
Original file line numberDiff line numberDiff line change
@@ -1,89 +1,21 @@
11
#:include "common.fypp"
22
#:set RC_KINDS_TYPES = REAL_KINDS_TYPES + CMPLX_KINDS_TYPES
3-
module stdlib_linalg_determinant
3+
submodule (stdlib_linalg) stdlib_linalg_determinant
44
!! 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)
10-
private
1110

1211
! Function interface
13-
public :: det
14-
public :: operator(.det.)
15-
1612
character(*), parameter :: this = 'determinant'
1713

18-
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-
!!
46-
#:for rk,rt in RC_KINDS_TYPES
47-
#:if rk!="xdp"
48-
module procedure stdlib_linalg_${rt[0]}$${rk}$determinant
49-
module procedure stdlib_linalg_pure_${rt[0]}$${rk}$determinant
50-
#:endif
51-
#:endfor
52-
end interface det
53-
54-
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-
!
75-
#:for rk,rt in RC_KINDS_TYPES
76-
#:if rk!="xdp"
77-
module procedure stdlib_linalg_pure_${rt[0]}$${rk}$determinant
78-
#:endif
79-
#:endfor
80-
end interface operator(.det.)
81-
8214
contains
8315

8416
#:for rk,rt in RC_KINDS_TYPES
8517
#:if rk!="xdp"
86-
pure function stdlib_linalg_pure_${rt[0]}$${rk}$determinant(a) result(det)
18+
module function stdlib_linalg_pure_${rt[0]}$${rk}$determinant(a) result(det)
8719
!!### Summary
8820
!! Compute determinant of a real square matrix (pure interface).
8921
!!
@@ -180,7 +112,7 @@ module stdlib_linalg_determinant
180112

181113
end function stdlib_linalg_pure_${rt[0]}$${rk}$determinant
182114

183-
function stdlib_linalg_${rt[0]}$${rk}$determinant(a,overwrite_a,err) result(det)
115+
module function stdlib_linalg_${rt[0]}$${rk}$determinant(a,overwrite_a,err) result(det)
184116
!!### Summary
185117
!! Compute determinant of a square matrix (with error control).
186118
!!
@@ -299,4 +231,4 @@ module stdlib_linalg_determinant
299231
#:endif
300232
#:endfor
301233

302-
end module stdlib_linalg_determinant
234+
end submodule stdlib_linalg_determinant

0 commit comments

Comments
 (0)