Skip to content

Commit 98b9b55

Browse files
committed
submodule
1 parent a9f4c7d commit 98b9b55

File tree

2 files changed

+100
-39
lines changed

2 files changed

+100
-39
lines changed

src/stdlib_linalg.fypp

Lines changed: 98 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -31,6 +31,8 @@ module stdlib_linalg
3131
public :: operator(.inv.)
3232
public :: lstsq
3333
public :: lstsq_space
34+
public :: norm
35+
public :: get_norm
3436
public :: solve
3537
public :: solve_lu
3638
public :: solve_lstsq
@@ -1065,6 +1067,102 @@ module stdlib_linalg
10651067
#:endfor
10661068
end interface svdvals
10671069

1070+
1071+
#! Allow for integer or character norm input: i.e., norm(a,2) or norm(a, '2')
1072+
#:set NORM_INPUT_TYPE = ["character(len=*)","integer(ilp)"]
1073+
#:set NORM_INPUT_SHORT = ["char","int"]
1074+
#:set NORM_INPUT_OPTIONS = list(zip(NORM_INPUT_TYPE,NORM_INPUT_SHORT))
1075+
! Vector norms: function interface
1076+
interface norm
1077+
#:for rk,rt,ri in RC_KINDS_TYPES
1078+
#:for it,ii in NORM_INPUT_OPTIONS
1079+
!> Scalar norms: ${rt}$
1080+
#:for rank in range(1, MAXRANK + 1)
1081+
pure module function stdlib_linalg_norm_${rank}$D_order_${ii}$_${ri}$(a, order) result(nrm)
1082+
!> Input ${rank}$-d matrix a${ranksuffix(rank)}$
1083+
${rt}$, intent(in) :: a${ranksuffix(rank)}$
1084+
!> Order of the matrix norm being computed.
1085+
${it}$, intent(in) :: order
1086+
!> Norm of the matrix.
1087+
real(${rk}$) :: nrm
1088+
end function stdlib_linalg_norm_${rank}$D_order_${ii}$_${ri}$
1089+
module function stdlib_linalg_norm_${rank}$D_order_err_${ii}$_${ri}$(a, order, err) result(nrm)
1090+
!> Input ${rank}$-d matrix a${ranksuffix(rank)}$
1091+
${rt}$, intent(in) :: a${ranksuffix(rank)}$
1092+
!> Order of the matrix norm being computed.
1093+
${it}$, intent(in) :: order
1094+
!> Output state return flag.
1095+
type(linalg_state_type), intent(out) :: err
1096+
!> Norm of the matrix.
1097+
real(${rk}$) :: nrm
1098+
end function stdlib_linalg_norm_${rank}$D_order_err_${ii}$_${ri}$
1099+
#:endfor
1100+
!> Array norms: ${rt}$
1101+
#:for rank in range(2, MAXRANK + 1)
1102+
pure module function stdlib_linalg_norm_${rank}$D_to_${rank-1}$D_${ii}$_${ri}$(a, order, dim) result(nrm)
1103+
!> Input matrix a[..]
1104+
${rt}$, intent(in), target :: a${ranksuffix(rank)}$
1105+
!> Order of the matrix norm being computed.
1106+
${it}$, intent(in) :: order
1107+
!> Dimension to collapse by computing the norm w.r.t other dimensions
1108+
integer(ilp), intent(in) :: dim
1109+
!> Norm of the matrix.
1110+
real(${rk}$) :: nrm${reduced_shape('a', rank, 'dim')}$
1111+
end function stdlib_linalg_norm_${rank}$D_to_${rank-1}$D_${ii}$_${ri}$
1112+
module function stdlib_linalg_norm_${rank}$D_to_${rank-1}$D_err_${ii}$_${ri}$(a, order, dim, err) result(nrm)
1113+
!> Input matrix a[..]
1114+
${rt}$, intent(in), target :: a${ranksuffix(rank)}$
1115+
!> Order of the matrix norm being computed.
1116+
${it}$, intent(in) :: order
1117+
!> Dimension to collapse by computing the norm w.r.t other dimensions
1118+
integer(ilp), intent(in) :: dim
1119+
!> Output state return flag.
1120+
type(linalg_state_type), intent(out) :: err
1121+
!> Norm of the matrix.
1122+
real(${rk}$) :: nrm${reduced_shape('a', rank, 'dim')}$
1123+
end function stdlib_linalg_norm_${rank}$D_to_${rank-1}$D_err_${ii}$_${ri}$
1124+
#:endfor
1125+
#:endfor
1126+
#:endfor
1127+
end interface norm
1128+
1129+
!> Vector norm: subroutine interface
1130+
interface get_norm
1131+
#:for rk,rt,ri in RC_KINDS_TYPES
1132+
#:for it,ii in NORM_INPUT_OPTIONS
1133+
!> Scalar norms: ${rt}$
1134+
#:for rank in range(1, MAXRANK + 1)
1135+
pure module subroutine norm_${rank}$D_${ii}$_${ri}$(a, nrm, order, err)
1136+
!> Input ${rank}$-d matrix a${ranksuffix(rank)}$
1137+
${rt}$, intent(in) :: a${ranksuffix(rank)}$
1138+
!> Norm of the matrix.
1139+
real(${rk}$), intent(out) :: nrm
1140+
!> Order of the matrix norm being computed.
1141+
${it}$, intent(in) :: order
1142+
!> [optional] state return flag. On error if not requested, the code will stop
1143+
type(linalg_state_type), intent(out), optional :: err
1144+
end subroutine norm_${rank}$D_${ii}$_${ri}$
1145+
#:endfor
1146+
!> Array norms: ${rt}$
1147+
#:for rank in range(2, MAXRANK + 1)
1148+
pure module subroutine norm_${rank}$D_to_${rank-1}$D_${ii}$_${ri}$(a, nrm, order, dim, err)
1149+
!> Input matrix a[..]
1150+
${rt}$, intent(in), target :: a${ranksuffix(rank)}$
1151+
!> Dimension to collapse by computing the norm w.r.t other dimensions
1152+
! (dim must be defined before it is used for `nrm`)
1153+
integer(ilp), intent(in) :: dim
1154+
!> Norm of the matrix.
1155+
real(${rk}$), intent(out) :: nrm${reduced_shape('a', rank, 'dim')}$
1156+
!> Order of the matrix norm being computed.
1157+
${it}$, intent(in) :: order
1158+
!> [optional] state return flag. On error if not requested, the code will stop
1159+
type(linalg_state_type), intent(out), optional :: err
1160+
end subroutine norm_${rank}$D_to_${rank-1}$D_${ii}$_${ri}$
1161+
#:endfor
1162+
#:endfor
1163+
#:endfor
1164+
end interface get_norm
1165+
10681166
contains
10691167

10701168

src/stdlib_linalg_norms.fypp

Lines changed: 2 additions & 39 deletions
Original file line numberDiff line numberDiff line change
@@ -6,17 +6,14 @@
66
#:set INPUT_SHORT = ["char","int"]
77
#:set INPUT_OPTIONS = list(zip(INPUT_TYPE,INPUT_SHORT))
88
! Vector norms
9-
module stdlib_linalg_norms
9+
submodule(stdlib_linalg) stdlib_linalg_norms
1010
use stdlib_linalg_constants
1111
use stdlib_linalg_blas, only: nrm2
1212
use stdlib_linalg_lapack, only: lange
1313
use stdlib_linalg_state, only: linalg_state_type, linalg_error_handling, LINALG_ERROR, &
1414
LINALG_INTERNAL_ERROR, LINALG_VALUE_ERROR
1515
implicit none(type,external)
16-
private
1716

18-
public :: norm, get_norm
19-
2017
character(*), parameter :: this = 'norm'
2118

2219
!> List of internal norm flags
@@ -27,40 +24,6 @@ module stdlib_linalg_norms
2724
integer(ilp), parameter :: NORM_POW_LAST = NORM_INF - 1_ilp
2825
integer(ilp), parameter :: NORM_MINUSINF = -huge(0_ilp)
2926

30-
!> Vector norm: function interface
31-
interface norm
32-
#:for rk,rt,ri in ALL_KINDS_TYPES
33-
#:for it,ii in INPUT_OPTIONS
34-
!> Scalar norms: ${rt}$
35-
#:for rank in range(1, MAXRANK + 1)
36-
module procedure stdlib_linalg_norm_${rank}$D_order_${ii}$_${ri}$
37-
module procedure stdlib_linalg_norm_${rank}$D_order_err_${ii}$_${ri}$
38-
#:endfor
39-
!> Array norms: ${rt}$
40-
#:for rank in range(2, MAXRANK + 1)
41-
module procedure stdlib_linalg_norm_${rank}$D_to_${rank-1}$D_${ii}$_${ri}$
42-
module procedure stdlib_linalg_norm_${rank}$D_to_${rank-1}$D_err_${ii}$_${ri}$
43-
#:endfor
44-
#:endfor
45-
#:endfor
46-
end interface norm
47-
48-
!> Vector norm: subroutine interface
49-
interface get_norm
50-
#:for rk,rt,ri in ALL_KINDS_TYPES
51-
#:for it,ii in INPUT_OPTIONS
52-
!> Scalar norms: ${rt}$
53-
#:for rank in range(1, MAXRANK + 1)
54-
module procedure norm_${rank}$D_${ii}$_${ri}$
55-
#:endfor
56-
!> Array norms: ${rt}$
57-
#:for rank in range(2, MAXRANK + 1)
58-
module procedure norm_${rank}$D_to_${rank-1}$D_${ii}$_${ri}$
59-
#:endfor
60-
#:endfor
61-
#:endfor
62-
end interface get_norm
63-
6427
interface parse_norm_type
6528
module procedure parse_norm_type_integer
6629
module procedure parse_norm_type_character
@@ -335,4 +298,4 @@ module stdlib_linalg_norms
335298
#:endfor
336299
#:endfor
337300

338-
end module stdlib_linalg_norms
301+
end submodule stdlib_linalg_norms

0 commit comments

Comments
 (0)