Skip to content

Commit c5f0300

Browse files
committed
docimp: add links to code
1 parent 575cf2c commit c5f0300

6 files changed

+63
-18
lines changed

src/stdlib_experimental_error.f90

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,5 @@
11
module stdlib_experimental_error
2-
!! Provide support for catching and handling errors ([spec](../page/specs/stdlib_experimental_error.html))
2+
!! Provide support for catching and handling errors.
33
!!
44
!! __Read the [specification here](../page/specs/stdlib_experimental_error.html).__
55
use, intrinsic :: iso_fortran_env, only: stderr => error_unit

src/stdlib_experimental_io.fypp

Lines changed: 28 additions & 15 deletions
Original file line numberDiff line numberDiff line change
@@ -3,7 +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.
6+
!! Provides a support for file handling.
7+
!!
8+
!! __Read the [specification here](../page/specs/stdlib_experimental_io.html).__
79
use stdlib_experimental_kinds, only: sp, dp, qp, &
810
int8, int16, int32, int64
911
use stdlib_experimental_error, only: error_stop
@@ -18,12 +20,18 @@ module stdlib_experimental_io
1820
public :: parse_mode
1921

2022
interface loadtxt
23+
!! Loads a 2D array from a text file
24+
!!
25+
!! __Read the [specification here](../page/specs/stdlib_experimental_io.html#description)__
2126
#:for k1, t1 in KINDS_TYPES
2227
module procedure loadtxt_${t1[0]}$${k1}$
2328
#:endfor
2429
end interface loadtxt
2530

2631
interface savetxt
32+
!! Saves a 2D array into a text file
33+
!!
34+
!! __Read the [specification here](../page/specs/stdlib_experimental_io.html#description_2)__
2735
#:for k1, t1 in KINDS_TYPES
2836
module procedure savetxt_${t1[0]}$${k1}$
2937
#:endfor
@@ -157,20 +165,25 @@ contains
157165

158166

159167
integer function open(filename, mode, iostat) result(u)
160-
! Open a file
161-
!
162-
! To open a file to read:
163-
!
164-
! u = open("somefile.txt") # The default `mode` is "rt"
165-
! u = open("somefile.txt", "r")
166-
!
167-
! To open a file to write:
168-
!
169-
! u = open("somefile.txt", "w")
170-
171-
! To append to the end of the file if it exists:
172-
!
173-
! u = open("somefile.txt", "a")
168+
!! Opens a file
169+
!!
170+
!! __Read the [specification here](../page/specs/stdlib_experimental_io.html#description_1)__
171+
!!
172+
!!##### Behavior
173+
!!
174+
!!
175+
!! To open a file to read:
176+
!!
177+
!! u = open("somefile.txt") # The default `mode` is "rt"
178+
!! u = open("somefile.txt", "r")
179+
!!
180+
!! To open a file to write:
181+
!!
182+
!! u = open("somefile.txt", "w")
183+
!!
184+
!! To append to the end of the file if it exists:
185+
!!
186+
!! u = open("somefile.txt", "a")
174187

175188
character(*), intent(in) :: filename
176189
character(*), intent(in), optional :: mode

src/stdlib_experimental_linalg.fypp

Lines changed: 9 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -12,6 +12,9 @@ module stdlib_experimental_linalg
1212
public :: trace
1313

1414
interface diag
15+
!! 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)__
1518
!
1619
! Vector to matrix
1720
!
@@ -49,6 +52,9 @@ module stdlib_experimental_linalg
4952

5053
! Matrix trace
5154
interface trace
55+
!! Computes the trace of a matrix
56+
!!
57+
!! __Read the [specification here](../page/specs/stdlib_experimental_linalg.html#description_2)__
5258
#:for k1, t1 in RCI_KINDS_TYPES
5359
module procedure trace_${t1[0]}$${k1}$
5460
#:endfor
@@ -57,6 +63,9 @@ module stdlib_experimental_linalg
5763
contains
5864

5965
function eye(n) result(res)
66+
!! Constructs the identity matrix
67+
!!
68+
!! __Read the [specification here](../page/specs/stdlib_experimental_linalg.html#description_1)__
6069
integer, intent(in) :: n
6170
integer(int8) :: res(n, n)
6271
integer :: i

src/stdlib_experimental_optval.fypp

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -22,6 +22,9 @@ module stdlib_experimental_optval
2222

2323

2424
interface optval
25+
!! Fallback value for optional arguments
26+
!!
27+
!! __Read the [specification here](../page/specs/stdlib_experimental_optval.html#description)__
2528
#:for k1, t1 in KINDS_TYPES
2629
module procedure optval_${t1[0]}$${k1}$
2730
#:endfor

src/stdlib_experimental_quadrature.fypp

Lines changed: 6 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -15,6 +15,9 @@ module stdlib_experimental_quadrature
1515

1616

1717
interface trapz
18+
!! Integrates sampled values using trapezoidal rule
19+
!!
20+
!! __Read the [specification here](../page/specs/stdlib_experimental_quadrature.html#description)__
1821
#:for KIND in REAL_KINDS
1922
pure module function trapz_dx_${KIND}$(y, dx) result(integral)
2023
real(${KIND}$), dimension(:), intent(in) :: y
@@ -33,6 +36,9 @@ module stdlib_experimental_quadrature
3336

3437

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

src/stdlib_experimental_stats.fypp

Lines changed: 16 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -3,8 +3,10 @@
33
#:set REDRANKS = range(2, MAXRANK + 1)
44
#:set RC_KINDS_TYPES = REAL_KINDS_TYPES + CMPLX_KINDS_TYPES
55
module stdlib_experimental_stats
6-
!!Provides a support for various statistical methods. This includes currently
7-
!!descriptive statistics.
6+
!! Provides support for various statistical methods. This includes currently
7+
!! descriptive statistics.
8+
!!
9+
!! __Read the [specification here](../page/specs/stdlib_experimental_stats.html).__
810
use stdlib_experimental_kinds, only: sp, dp, qp, &
911
int8, int16, int32, int64
1012
implicit none
@@ -13,6 +15,9 @@ module stdlib_experimental_stats
1315
public :: cov, mean, moment, var
1416

1517
interface cov
18+
!! Covariance of array elements
19+
!!
20+
!! __Read the [specification here](../page/specs/stdlib_experimental_stats.html#description)__
1621
#:for k1, t1 in RC_KINDS_TYPES
1722
#:set RName = rname("cov",1, t1, k1)
1823
module function ${RName}$(x, dim, mask, corrected) result(res)
@@ -108,6 +113,9 @@ module stdlib_experimental_stats
108113

109114

110115
interface mean
116+
!! Mean of array elements
117+
!!
118+
!! __Read the [specification here](../page/specs/stdlib_experimental_stats.html#description_1)__
111119
#:for k1, t1 in RC_KINDS_TYPES
112120
#:for rank in RANKS
113121
#:set RName = rname("mean_all",rank, t1, k1)
@@ -204,6 +212,9 @@ module stdlib_experimental_stats
204212

205213

206214
interface var
215+
!! Variance of array elements
216+
!!
217+
!! __Read the [specification here](../page/specs/stdlib_experimental_stats.html#description_3)__
207218

208219
#:for k1, t1 in RC_KINDS_TYPES
209220
#:for rank in RANKS
@@ -309,6 +320,9 @@ module stdlib_experimental_stats
309320

310321

311322
interface moment
323+
!! Central moment of array elements
324+
!!
325+
!! __Read the [specification here](../page/specs/stdlib_experimental_stats.html#description_2)__
312326
#:for k1, t1 in RC_KINDS_TYPES
313327
#:for rank in RANKS
314328
#:set RName = rname("moment_all",rank, t1, k1)

0 commit comments

Comments
 (0)