Skip to content

Commit

Permalink
Merge branch 'norms' of github.com:perazz/stdlib into norms
Browse files Browse the repository at this point in the history
  • Loading branch information
perazz committed Sep 23, 2024
2 parents 9e020a8 + 1a79128 commit 0e798ff
Show file tree
Hide file tree
Showing 3 changed files with 8 additions and 8 deletions.
4 changes: 2 additions & 2 deletions example/linalg/example_get_norm.f90
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,7 @@ program example_get_norm
use stdlib_linalg, only: get_norm, linalg_state_type
implicit none

real :: a(3,3),nrm,nrmd(3)
real :: a(3,3), nrm, nrmd(3)
integer :: j
type(linalg_state_type) :: err

Expand Down Expand Up @@ -44,7 +44,7 @@ program example_get_norm
print *, 'minval(||a(:,i)||) = ',nrmd ! 1.00000000 0.00000000 3.00000000

! Catch Error:
! [norm] returned Value Error: dimension 4 is out of rank for shape(a)= [3 3]
! [norm] returned Value Error: dimension 4 is out of rank for shape(a)= [3, 3]
call get_norm(a, nrmd, 'inf', dim=4, err=err)
print *, 'invalid: ',err%print()

Expand Down
2 changes: 1 addition & 1 deletion example/linalg/example_norm.f90
Original file line number Diff line number Diff line change
Expand Up @@ -33,7 +33,7 @@ program example_norm
print *, 'minval(||a(:,i)||) = ',norm(a, '-inf', dim=1) ! 1.00000000 0.00000000 3.00000000

! Catch Error:
! [norm] returned Value Error: dimension 4 is out of rank for shape(a)= [3 3]
! [norm] returned Value Error: dimension 4 is out of rank for shape(a)= [3, 3]
print *, 'invalid: ',norm(a,'inf', dim=4, err=err)
print *, 'error = ',err%print()

Expand Down
10 changes: 5 additions & 5 deletions src/stdlib_linalg_norms.fypp
Original file line number Diff line number Diff line change
Expand Up @@ -53,11 +53,11 @@ submodule(stdlib_linalg) stdlib_linalg_norms
norm_type = NORM_ONE
case (2_ilp)
norm_type = NORM_TWO
case (3_ilp:huge(0_ilp)-1_ilp)
case (3_ilp:NORM_POW_LAST)
norm_type = order
case (huge(0_ilp):)
case (NORM_INF:)
norm_type = NORM_INF
case (:-huge(0_ilp))
case (:NORM_MINUSINF)
norm_type = NORM_MINUSINF

case default
Expand Down Expand Up @@ -209,7 +209,7 @@ submodule(stdlib_linalg) stdlib_linalg_norms
#:endif
case(NORM_INF)
nrm = maxval( abs(a) )
case(-NORM_INF)
case(NORM_MINUSINF)
nrm = minval( abs(a) )
case (NORM_POW_FIRST:NORM_POW_LAST)
rorder = 1.0_${rk}$ / norm_request
Expand Down Expand Up @@ -317,7 +317,7 @@ submodule(stdlib_linalg) stdlib_linalg_norms
#:endif
case(NORM_INF)
nrm = maxval( abs(a) , dim = dim )
case(-NORM_INF)
case(NORM_MINUSINF)
nrm = minval( abs(a) , dim = dim )
case (NORM_POW_FIRST:NORM_POW_LAST)
rorder = 1.0_${rk}$ / norm_request
Expand Down

0 comments on commit 0e798ff

Please sign in to comment.