Skip to content

Commit 40033e1

Browse files
committed
mention the link to spec in the column description
1 parent a27692a commit 40033e1

6 files changed

+32
-44
lines changed

src/stdlib_experimental_error.f90

Lines changed: 6 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -1,17 +1,15 @@
11
module stdlib_experimental_error
2-
!! Provide support for catching and handling errors.
3-
!!
4-
!! __Read the [specification here](../page/specs/stdlib_experimental_error.html).__
2+
!! Provides support for catching and handling errors
3+
!! ([Specification](../page/specs/stdlib_experimental_error.html))
54
use, intrinsic :: iso_fortran_env, only: stderr => error_unit
65
use stdlib_experimental_optval, only: optval
76
implicit none
87
private
98

109
interface ! f{08,18}estop.f90
1110
module subroutine error_stop(msg, code)
12-
!! Provides a call to `error stop` and allows the user to specify a code and message.
13-
!!
14-
!! __Read the [specification here](..//page/specs/stdlib_experimental_error.html#description_1).__
11+
!! Provides a call to `error stop` and allows the user to specify a code and message
12+
!! ([Specification](..//page/specs/stdlib_experimental_error.html#description_1))
1513
character(*), intent(in) :: msg
1614
integer, intent(in), optional :: code
1715
end subroutine error_stop
@@ -22,9 +20,8 @@ end subroutine error_stop
2220
contains
2321

2422
subroutine check(condition, msg, code, warn)
25-
!! Checks the value of a logical condition.
26-
!!
27-
!! __Read the [specification here](../page/specs/stdlib_experimental_error.html#description).__
23+
!! Checks the value of a logical condition
24+
!! ([Specification](../page/specs/stdlib_experimental_error.html#description))
2825
!!
2926
!!##### Behavior
3027
!!

src/stdlib_experimental_io.fypp

Lines changed: 6 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -3,9 +3,9 @@
33
#:set KINDS_TYPES = REAL_KINDS_TYPES + INT_KINDS_TYPES + CMPLX_KINDS_TYPES
44

55
module stdlib_experimental_io
6-
!! Provides a support for file handling.
7-
!!
8-
!! __Read the [specification here](../page/specs/stdlib_experimental_io.html).__
6+
!! Provides a support for file handling
7+
!! ([Specification](../page/specs/stdlib_experimental_io.html))
8+
99
use stdlib_experimental_kinds, only: sp, dp, qp, &
1010
int8, int16, int32, int64
1111
use stdlib_experimental_error, only: error_stop
@@ -21,17 +21,15 @@ module stdlib_experimental_io
2121

2222
interface loadtxt
2323
!! Loads a 2D array from a text file
24-
!!
25-
!! __Read the [specification here](../page/specs/stdlib_experimental_io.html#description)__
24+
!! ([Specification](../page/specs/stdlib_experimental_io.html#description))
2625
#:for k1, t1 in KINDS_TYPES
2726
module procedure loadtxt_${t1[0]}$${k1}$
2827
#:endfor
2928
end interface loadtxt
3029

3130
interface savetxt
3231
!! Saves a 2D array into a text file
33-
!!
34-
!! __Read the [specification here](../page/specs/stdlib_experimental_io.html#description_2)__
32+
!! ([Specification](../page/specs/stdlib_experimental_io.html#description_2))
3533
#:for k1, t1 in KINDS_TYPES
3634
module procedure savetxt_${t1[0]}$${k1}$
3735
#:endfor
@@ -171,8 +169,7 @@ contains
171169

172170
integer function open(filename, mode, iostat) result(u)
173171
!! Opens a file
174-
!!
175-
!! __Read the [specification here](../page/specs/stdlib_experimental_io.html#description_1)__
172+
!! ([Specification](../page/specs/stdlib_experimental_io.html#description_1))
176173
!!
177174
!!##### Behavior
178175
!!

src/stdlib_experimental_linalg.fypp

Lines changed: 5 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,8 @@
11
#:include "common.fypp"
22
#:set RCI_KINDS_TYPES = REAL_KINDS_TYPES + CMPLX_KINDS_TYPES + INT_KINDS_TYPES
33
module stdlib_experimental_linalg
4-
!!Provides a support for various linear algebra procedures.
4+
!!Provides a support for various linear algebra procedures
5+
!! ([Specification](../page/specs/stdlib_experimental_linalg.html))
56
use stdlib_experimental_kinds, only: sp, dp, qp, &
67
int8, int16, int32, int64
78
implicit none
@@ -13,8 +14,7 @@ module stdlib_experimental_linalg
1314

1415
interface diag
1516
!! Creates a diagonal array or extract the diagonal elements of an array
16-
!!
17-
!! __Read the [specification here](../page/specs/stdlib_experimental_linalg.html#description)__
17+
!! ([Specification](../page/specs/stdlib_experimental_linalg.html#description))
1818
!
1919
! Vector to matrix
2020
!
@@ -53,8 +53,7 @@ module stdlib_experimental_linalg
5353
! Matrix trace
5454
interface trace
5555
!! Computes the trace of a matrix
56-
!!
57-
!! __Read the [specification here](../page/specs/stdlib_experimental_linalg.html#description_2)__
56+
!! ([Specification](../page/specs/stdlib_experimental_linalg.html#description_2))
5857
#:for k1, t1 in RCI_KINDS_TYPES
5958
module procedure trace_${t1[0]}$${k1}$
6059
#:endfor
@@ -64,8 +63,7 @@ contains
6463

6564
function eye(n) result(res)
6665
!! Constructs the identity matrix
67-
!!
68-
!! __Read the [specification here](../page/specs/stdlib_experimental_linalg.html#description_1)__
66+
!! ([Specification](../page/specs/stdlib_experimental_linalg.html#description_1))
6967
integer, intent(in) :: n
7068
integer(int8) :: res(n, n)
7169
integer :: i

src/stdlib_experimental_optval.fypp

Lines changed: 5 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -7,7 +7,10 @@ module stdlib_experimental_optval
77
!!
88
!! Provides a generic function `optval`, which can be used to
99
!! conveniently implement fallback values for optional arguments
10-
!! to subprograms. If `x` is an `optional` parameter of a
10+
!! to subprograms
11+
!! ([Specification](../page/specs/stdlib_experimental_optval.html))
12+
!!
13+
!! If `x` is an `optional` parameter of a
1114
!! subprogram, then the expression `optval(x, default)` inside that
1215
!! subprogram evaluates to `x` if it is present, otherwise `default`.
1316
!!
@@ -23,8 +26,7 @@ module stdlib_experimental_optval
2326

2427
interface optval
2528
!! Fallback value for optional arguments
26-
!!
27-
!! __Read the [specification here](../page/specs/stdlib_experimental_optval.html#description)__
29+
!! ([Specification](../page/specs/stdlib_experimental_optval.html#description))
2830
#:for k1, t1 in KINDS_TYPES
2931
module procedure optval_${t1[0]}$${k1}$
3032
#:endfor

src/stdlib_experimental_quadrature.fypp

Lines changed: 3 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,7 @@
11
#:include "common.fypp"
22

33
module stdlib_experimental_quadrature
4+
!! ([Specification](../page/specs/stdlib_experimental_quadrature.html#description))
45
use stdlib_experimental_kinds, only: sp, dp, qp
56

67
implicit none
@@ -16,8 +17,7 @@ module stdlib_experimental_quadrature
1617

1718
interface trapz
1819
!! Integrates sampled values using trapezoidal rule
19-
!!
20-
!! __Read the [specification here](../page/specs/stdlib_experimental_quadrature.html#description)__
20+
!! ([Specification](../page/specs/stdlib_experimental_quadrature.html#description))
2121
#:for KIND in REAL_KINDS
2222
pure module function trapz_dx_${KIND}$(y, dx) result(integral)
2323
real(${KIND}$), dimension(:), intent(in) :: y
@@ -37,8 +37,7 @@ module stdlib_experimental_quadrature
3737

3838
interface trapz_weights
3939
!! Integrates sampled values using trapezoidal rule weights for given abscissas
40-
!!
41-
!! __Read the [specification here](../page/specs/stdlib_experimental_quadrature.html#description_1)__
40+
!! ([Specification](../page/specs/stdlib_experimental_quadrature.html#description_1))
4241
#:for KIND in REAL_KINDS
4342
pure module function trapz_weights_${KIND}$(x) result(w)
4443
real(${KIND}$), dimension(:), intent(in) :: x

src/stdlib_experimental_stats.fypp

Lines changed: 7 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -4,9 +4,8 @@
44
#:set RC_KINDS_TYPES = REAL_KINDS_TYPES + CMPLX_KINDS_TYPES
55
module stdlib_experimental_stats
66
!! Provides support for various statistical methods. This includes currently
7-
!! descriptive statistics.
8-
!!
9-
!! __Read the [specification here](../page/specs/stdlib_experimental_stats.html).__
7+
!! descriptive statistics
8+
!! ([Specification](../page/specs/stdlib_experimental_stats.html))
109
use stdlib_experimental_kinds, only: sp, dp, qp, &
1110
int8, int16, int32, int64
1211
implicit none
@@ -16,8 +15,7 @@ module stdlib_experimental_stats
1615

1716
interface cov
1817
!! Covariance of array elements
19-
!!
20-
!! __Read the [specification here](../page/specs/stdlib_experimental_stats.html#description)__
18+
!! ([Specification](../page/specs/stdlib_experimental_stats.html#description))
2119
#:for k1, t1 in RC_KINDS_TYPES
2220
#:set RName = rname("cov",1, t1, k1)
2321
module function ${RName}$(x, dim, mask, corrected) result(res)
@@ -114,8 +112,7 @@ module stdlib_experimental_stats
114112

115113
interface mean
116114
!! Mean of array elements
117-
!!
118-
!! __Read the [specification here](../page/specs/stdlib_experimental_stats.html#description_1)__
115+
!! ([Specification](../page/specs/stdlib_experimental_stats.html#description_1))
119116
#:for k1, t1 in RC_KINDS_TYPES
120117
#:for rank in RANKS
121118
#:set RName = rname("mean_all",rank, t1, k1)
@@ -213,8 +210,7 @@ module stdlib_experimental_stats
213210

214211
interface var
215212
!! Variance of array elements
216-
!!
217-
!! __Read the [specification here](../page/specs/stdlib_experimental_stats.html#description_3)__
213+
!! ([Specification](../page/specs/stdlib_experimental_stats.html#description_3))
218214

219215
#:for k1, t1 in RC_KINDS_TYPES
220216
#:for rank in RANKS
@@ -320,9 +316,8 @@ module stdlib_experimental_stats
320316

321317

322318
interface moment
323-
!! Central moment of array elements
324-
!!
325-
!! __Read the [specification here](../page/specs/stdlib_experimental_stats.html#description_2)__
319+
!! Central moment of array elements
320+
!! ([Specification](../page/specs/stdlib_experimental_stats.html#description_2))
326321
#:for k1, t1 in RC_KINDS_TYPES
327322
#:for rank in RANKS
328323
#:set RName = rname("moment_all",rank, t1, k1)

0 commit comments

Comments
 (0)