Skip to content

Commit 3d00b1d

Browse files
authored
Merge branch 'fortran-lang:master' into typed_eye
2 parents 57e3f89 + cc30d4c commit 3d00b1d

File tree

9 files changed

+635
-4
lines changed

9 files changed

+635
-4
lines changed

.github/workflows/CI.yml

Lines changed: 5 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -19,7 +19,7 @@ jobs:
1919
strategy:
2020
fail-fast: false
2121
matrix:
22-
os: [ubuntu-latest, macos-12]
22+
os: [ubuntu-latest, macos-13]
2323
toolchain:
2424
- {compiler: gcc, version: 10}
2525
- {compiler: gcc, version: 11}
@@ -34,9 +34,11 @@ jobs:
3434
toolchain:
3535
- {compiler: gcc, version: 10}
3636
exclude:
37-
- os: macos-12
37+
- os: macos-13
38+
toolchain: {compiler: intel-classic, version: '2021.9'}
39+
- os: macos-13
3840
toolchain: {compiler: intel, version: '2024.1'}
39-
- os: macos-12
41+
- os: macos-13
4042
toolchain: {compiler: gcc, version: 13}
4143
env:
4244
BUILD_DIR: ${{ matrix.build == 'cmake' && 'build' || '.' }}

doc/specs/stdlib_linalg.md

Lines changed: 49 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1562,4 +1562,53 @@ If `err` is not present, exceptions trigger an `error stop`.
15621562
{!example/linalg/example_norm.f90!}
15631563
```
15641564

1565+
## `mnorm` - Computes the matrix norm of a generic-rank array.
1566+
1567+
### Status
1568+
1569+
Experimental
1570+
1571+
### Description
1572+
1573+
This function computes one of several matrix norms of `real` or `complex` array \( A \), depending on
1574+
the value of the `order` input argument. \( A \) must be an array of rank 2 or higher. For arrays of rank > 2,
1575+
matrix norms are computed over specified dimensions.
1576+
1577+
### Syntax
1578+
1579+
`x = ` [[stdlib_linalg(module):mnorm(interface)]] `(a [, order, dim, err])`
1580+
1581+
### Arguments
1582+
1583+
`a`: Shall be a rank-n `real` or `complex` array containing the data, where n >= 2. It is an `intent(in)` argument.
1584+
1585+
`order` (optional): Shall be an `integer` value or a `character` flag that specifies the norm type, as follows. It is an `intent(in)` argument.
1586+
1587+
| Integer input | Character Input | Norm type |
1588+
|------------------|---------------------------------|-----------------------------------------------------------------------------|
1589+
| `1` | `'1'` | 1-norm (maximum column sum) \( \max_j \sum_i{ \left|a_{i,j}\right| } \) |
1590+
| `2` | `'2'` | 2-norm (largest singular value) |
1591+
| (not prov.) | `'Euclidean','Frobenius','Fro'` | Frobenius norm \( \sqrt{\sum_{i,j}{ \left|a_{i,j}\right|^2 }} \) |
1592+
| `huge(0)` | `'inf', 'Inf', 'INF'` | Infinity norm (maximum row sum) \( \max_i \sum_j{ \left|a_{i,j}\right| } \) |
1593+
1594+
`dim` (optional): For arrays of rank > 2, shall be an integer array of size 2 specifying the dimensions over which to compute the matrix norm. Default value is `[1,2]`. It is an `intent(in)` argument.
1595+
1596+
`err` (optional): Shall be a `type(linalg_state_type)` value. This is an `intent(out)` argument.
1597+
1598+
### Return value
1599+
1600+
For rank-2 input arrays, the return value `x` is a scalar containing the matrix norm.
1601+
For arrays of rank > 2, if the optional `dim` argument is present, `x` is a rank `n-2` array with the same shape as \( A \) except
1602+
for dimensions `dim(1)` and `dim(2)`, which are dropped. Each element of `x` contains the matrix norm of the corresponding submatrix of \( A \),
1603+
evaluated over the specified dimensions only, with the given order.
1604+
1605+
If an invalid norm type is provided, defaults to 1-norm and raises `LINALG_ERROR`.
1606+
Raises `LINALG_VALUE_ERROR` if any of the arguments has an invalid size.
1607+
If `err` is not present, exceptions trigger an `error stop`.
1608+
1609+
### Example
1610+
1611+
```fortran
1612+
{!example/linalg/example_mnorm.f90!}
1613+
```
15651614

example/linalg/CMakeLists.txt

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -29,6 +29,7 @@ ADD_EXAMPLE(lapack_getrf)
2929
ADD_EXAMPLE(lstsq1)
3030
ADD_EXAMPLE(lstsq2)
3131
ADD_EXAMPLE(norm)
32+
ADD_EXAMPLE(mnorm)
3233
ADD_EXAMPLE(get_norm)
3334
ADD_EXAMPLE(solve1)
3435
ADD_EXAMPLE(solve2)

example/linalg/example_mnorm.f90

Lines changed: 26 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,26 @@
1+
program example_mnorm
2+
use stdlib_linalg, only: mnorm
3+
use stdlib_kinds, only: sp
4+
implicit none
5+
real(sp) :: a(3,3), na
6+
real(sp) :: b(3,3,4), nb(4) ! Array of 4 3x3 matrices
7+
8+
! Initialize example matrix
9+
a = reshape([1, 2, 3, 4, 5, 6, 7, 8, 9], [3, 3])
10+
11+
! Compute Euclidean norm of single matrix
12+
na = mnorm(a, 'Euclidean')
13+
print *, "Euclidean norm of matrix a:", na
14+
15+
! Initialize array of matrices
16+
b(:,:,1) = a
17+
b(:,:,2) = 2*a
18+
b(:,:,3) = 3*a
19+
b(:,:,4) = 4*a
20+
21+
! Compute infinity norm of each 3x3 matrix in b
22+
nb = mnorm(b, 'inf', dim=[1,2])
23+
24+
! 18.0000000 36.0000000 54.0000000 72.0000000
25+
print *, "Infinity norms of matrices in b:", nb
26+
end program example_mnorm

include/common.fypp

Lines changed: 45 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -157,6 +157,22 @@ $:"s" if cmplx=="c" else "d" if cmplx=="z" else "x" if cmplx=="y" else "q" if cm
157157
#{if rank > 0}#(${"0" + ",0" * (rank - 1)}$)#{endif}#
158158
#:enddef
159159

160+
#! Generates an array rank suffix with a fixed integer size for all dimensions.
161+
#!
162+
#! Args:
163+
#! rank (int): Rank of the variable
164+
#! size (int): Size along each dimension
165+
#!
166+
#! Returns:
167+
#! Array rank suffix string
168+
#! E.g.,
169+
#! fixedranksuffix(3,4)
170+
#! -> (4,4,4)
171+
#!
172+
#:def fixedranksuffix(rank,size)
173+
#{if rank > 0}#(${str(size) + (","+str(size)) * (rank - 1)}$)#{endif}#
174+
#:enddef
175+
160176
#! Joins stripped lines with given character string
161177
#!
162178
#! Args:
@@ -227,7 +243,7 @@ ${prefix + joinstr.join([line.strip() for line in txt.split("\n")]) + suffix}$
227243
#! Array rank suffix string enclosed in braces
228244
#!
229245
#! E.g.,
230-
#! select_subarray(5 , [(4, 'i'), (5, 'j')])}$
246+
#! select_subarray(5 , [(4, 'i'), (5, 'j')])
231247
#! -> (:, :, :, i, j)
232248
#!
233249
#:def select_subarray(rank, selectors)
@@ -327,6 +343,34 @@ ${prefix + joinstr.join([line.strip() for line in txt.split("\n")]) + suffix}$
327343
#:endcall
328344
#:enddef
329345

346+
#!
347+
#! Generates a list of loop variables from an array
348+
#!
349+
#! Args:
350+
#! varname(str): Name of the array variable to be used as prefix
351+
#! n (int): Number of loop variables to be created
352+
#! offset (int): Optional index offset
353+
#!
354+
#! Returns:
355+
#! Variable definition string
356+
#!
357+
#! E.g.,
358+
#! loop_array_variables('j', 5)
359+
#! -> "j(1), j(2), j(3), j(4), j(5)
360+
#!
361+
#! loop_array_variables('j', 5, 2)
362+
#! -> "j(3), j(4), j(5), j(6), j(7)
363+
#!
364+
#:def loop_array_variables(varname, n, offset=0)
365+
#:assert n > 0
366+
#:call join_lines(joinstr=", ")
367+
#:for i in range(1, n + 1)
368+
${varname}$(${i+offset}$)
369+
#:endfor
370+
#:endcall
371+
#:enddef
372+
373+
330374
#! Generates an array shape specifier from an N-D array size
331375
#!
332376
#! Args:

src/stdlib_linalg.fypp

Lines changed: 84 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -32,6 +32,7 @@ module stdlib_linalg
3232
public :: lstsq
3333
public :: lstsq_space
3434
public :: norm
35+
public :: mnorm
3536
public :: get_norm
3637
public :: solve
3738
public :: solve_lu
@@ -1330,6 +1331,89 @@ module stdlib_linalg
13301331
#:endfor
13311332
end interface get_norm
13321333

1334+
!> Matrix norms: function interface
1335+
interface mnorm
1336+
!! version: experimental
1337+
!!
1338+
!! Computes the matrix norm of a generic-rank array \( A \).
1339+
!! ([Specification](../page/specs/stdlib_linalg.html#mnorm-computes-the-matrix-norm-of-a-generic-rank-array))
1340+
!!
1341+
!!### Summary
1342+
!! Return one of several matrix norm metrics of a `real` or `complex` input array \( A \),
1343+
!! that can have rank 2 or higher. For rank-2 arrays, the matrix norm is returned.
1344+
!! If rank>2 and the optional input dimensions `dim` are specified,
1345+
!! a rank `n-2` array is returned with dimensions `dim(1),dim(2)` collapsed, containing all
1346+
!! matrix norms evaluated over the specified dimensions only. `dim==[1,2]` are assumed as default
1347+
!! dimensions if not specified.
1348+
!!
1349+
!!### Description
1350+
!!
1351+
!! This interface provides methods for computing the matrix norm(s) of an array.
1352+
!! Supported data types include `real` and `complex`.
1353+
!! Input arrays must have rank >= 2.
1354+
!!
1355+
!! Norm type input is optional, and it is provided via the `order` argument.
1356+
!! This can be provided as either an `integer` value or a `character` string.
1357+
!! Allowed metrics are:
1358+
!! - 1-norm: `order` = 1 or '1'
1359+
!! - 2-norm: `order` = 2 or '2'
1360+
!! - Euclidean/Frobenius: `order` = 'Euclidean','Frobenius', or argument not specified
1361+
!! - Infinity norm: `order` = huge(0) or 'Inf'
1362+
!!
1363+
!! If an invalid norm type is provided, the routine returns an error state.
1364+
!!
1365+
!!### Example
1366+
!!
1367+
!!```fortran
1368+
!! real(sp) :: a(3,3), na
1369+
!! real(sp) :: b(3,3,4), nb(4) ! Array of 4 3x3 matrices
1370+
!! a = reshape([1, 2, 3, 4, 5, 6, 7, 8, 9], [3, 3])
1371+
!!
1372+
!! ! Euclidean/Frobenius norm of single matrix
1373+
!! na = mnorm(a)
1374+
!! na = mnorm(a, 'Euclidean')
1375+
!!
1376+
!! ! 1-norm of each 3x3 matrix in b
1377+
!! nb = mnorm(b, 1, dim=[1,2])
1378+
!!
1379+
!! ! Infinity-norm
1380+
!! na = mnorm(b, 'inf', dim=[3,2])
1381+
!!```
1382+
!!
1383+
#:for rk,rt,ri in RC_KINDS_TYPES
1384+
#:for it,ii in NORM_INPUT_OPTIONS
1385+
1386+
!> Matrix norms: ${rt}$ rank-2 arrays
1387+
module function matrix_norm_${ii}$_${ri}$(a, order, err) result(nrm)
1388+
!> Input matrix a(m,n)
1389+
${rt}$, intent(in), target :: a(:,:)
1390+
!> Norm of the matrix.
1391+
real(${rk}$) :: nrm
1392+
!> Order of the matrix norm being computed.
1393+
${it}$, #{if 'integer' in it}#optional, #{endif}#intent(in) :: order
1394+
!> [optional] state return flag. On error if not requested, the code will stop
1395+
type(linalg_state_type), intent(out), optional :: err
1396+
end function matrix_norm_${ii}$_${ri}$
1397+
1398+
!> Matrix norms: ${rt}$ higher rank arrays
1399+
#:for rank in range(3, MAXRANK + 1)
1400+
module function matrix_norm_${rank}$D_to_${rank-2}$D_${ii}$_${ri}$(a, order, dim, err) result(nrm)
1401+
!> Input matrix a(m,n)
1402+
${rt}$, intent(in), contiguous, target :: a${ranksuffix(rank)}$
1403+
!> Norm of the matrix.
1404+
real(${rk}$), allocatable :: nrm${ranksuffix(rank-2)}$
1405+
!> Order of the matrix norm being computed.
1406+
${it}$, #{if 'integer' in it}#optional, #{endif}#intent(in) :: order
1407+
!> [optional] dimensions of the sub-matrices the norms should be evaluated at (default = [1,2])
1408+
integer(ilp), optional, intent(in) :: dim(2)
1409+
!> [optional] state return flag. On error if not requested, the code will stop
1410+
type(linalg_state_type), intent(out), optional :: err
1411+
end function matrix_norm_${rank}$D_to_${rank-2}$D_${ii}$_${ri}$
1412+
#:endfor
1413+
#:endfor
1414+
#:endfor
1415+
end interface mnorm
1416+
13331417
contains
13341418

13351419

0 commit comments

Comments
 (0)