Skip to content

Commit aa734de

Browse files
committed
improve argument descriptions
1 parent b405671 commit aa734de

File tree

1 file changed

+6
-7
lines changed

1 file changed

+6
-7
lines changed

src/stdlib_linalg.fypp

Lines changed: 6 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -1147,21 +1147,21 @@ module stdlib_linalg
11471147
${rt}$, intent(in), target :: a${ranksuffix(rank)}$
11481148
!> Order of the matrix norm being computed.
11491149
${it}$, intent(in) :: order
1150-
!> Dimension to collapse by computing the norm w.r.t other dimensions
1150+
!> Dimension the norm is computed along
11511151
integer(ilp), intent(in) :: dim
1152-
!> Norm of the matrix.
1152+
!> Norm of the matrix. (Same shape as `a`, with `dim` dropped).
11531153
real(${rk}$) :: nrm${reduced_shape('a', rank, 'dim')}$
11541154
end function stdlib_linalg_norm_${rank}$D_to_${rank-1}$D_${ii}$_${ri}$
11551155
module function stdlib_linalg_norm_${rank}$D_to_${rank-1}$D_err_${ii}$_${ri}$(a, order, dim, err) result(nrm)
11561156
!> Input matrix a[..]
11571157
${rt}$, intent(in), target :: a${ranksuffix(rank)}$
11581158
!> Order of the matrix norm being computed.
11591159
${it}$, intent(in) :: order
1160-
!> Dimension to collapse by computing the norm w.r.t other dimensions
1160+
!> Dimension the norm is computed along
11611161
integer(ilp), intent(in) :: dim
11621162
!> Output state return flag.
11631163
type(linalg_state_type), intent(out) :: err
1164-
!> Norm of the matrix.
1164+
!> Norm of the matrix. (Same shape as `a`, with `dim` dropped).
11651165
real(${rk}$) :: nrm${reduced_shape('a', rank, 'dim')}$
11661166
end function stdlib_linalg_norm_${rank}$D_to_${rank-1}$D_err_${ii}$_${ri}$
11671167
#:endfor
@@ -1235,10 +1235,9 @@ module stdlib_linalg
12351235
pure module subroutine norm_${rank}$D_to_${rank-1}$D_${ii}$_${ri}$(a, nrm, order, dim, err)
12361236
!> Input matrix a[..]
12371237
${rt}$, intent(in), target :: a${ranksuffix(rank)}$
1238-
!> Dimension to collapse by computing the norm w.r.t other dimensions
1239-
! (dim must be defined before it is used for `nrm`)
1238+
!> Dimension the norm is computed along
12401239
integer(ilp), intent(in) :: dim
1241-
!> Norm of the matrix.
1240+
!> Norm of the matrix. (Same shape as `a`, with `dim` dropped).
12421241
real(${rk}$), intent(out) :: nrm${reduced_shape('a', rank, 'dim')}$
12431242
!> Order of the matrix norm being computed.
12441243
${it}$, intent(in) :: order

0 commit comments

Comments
 (0)