Skip to content

Commit 14be974

Browse files
committed
change names to stdlib_*
1 parent 87ef502 commit 14be974

File tree

7 files changed

+68
-68
lines changed

7 files changed

+68
-68
lines changed

doc/specs/stdlib_intrinsics.md

Lines changed: 13 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -11,17 +11,17 @@ title: intrinsics
1111
The `stdlib_intrinsics` module provides replacements for some of the well known intrinsic functions found in Fortran compilers for which either a faster and/or more accurate implementation is found which has also proven of interest to the Fortran community.
1212

1313
<!-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -->
14-
### `fsum` function
14+
### `stdlib_sum` function
1515

1616
#### Description
1717

18-
The `fsum` function can replace the intrinsic `sum` for `real` or `complex` arrays. It follows a chunked implementation which maximizes vectorization potential as well as reducing the round-off error. This procedure is recommended when summing large arrays, for repetitive summation of smaller arrays consider the classical `sum`.
18+
The `stdlib_sum` function can replace the intrinsic `sum` for `real` or `complex` arrays. It follows a chunked implementation which maximizes vectorization potential as well as reducing the round-off error. This procedure is recommended when summing large arrays, for repetitive summation of smaller arrays consider the classical `sum`.
1919

2020
#### Syntax
2121

22-
`res = ` [[stdlib_intrinsics(module):fsum(interface)]] ` (x [,mask] )`
22+
`res = ` [[stdlib_intrinsics(module):stdlib_sum(interface)]] ` (x [,mask] )`
2323

24-
`res = ` [[stdlib_intrinsics(module):fsum(interface)]] ` (x, dim [,mask] )`
24+
`res = ` [[stdlib_intrinsics(module):stdlib_sum(interface)]] ` (x, dim [,mask] )`
2525

2626
#### Status
2727

@@ -44,11 +44,11 @@ Pure function.
4444
If `dim` is absent, the output is a scalar of the same `type` and `kind` as to that of `x`. Otherwise, an array of rank n-1, where n equals the rank of `x`, and a shape similar to that of `x` with dimension `dim` dropped is returned.
4545

4646
<!-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -->
47-
### `fsum_kahan` function
47+
### `stdlib_sum_kahan` function
4848

4949
#### Description
5050

51-
The `fsum_kahan` function can replace the intrinsic `sum` for 1D `real` or `complex` arrays. It follows a chunked implementation which maximizes vectorization potential, complemented by an `elemental` kernel based on the [kahan summation](https://en.wikipedia.org/wiki/Kahan_summation_algorithm) strategy to reduce the round-off error:
51+
The `stdlib_sum_kahan` function can replace the intrinsic `sum` for 1D `real` or `complex` arrays. It follows a chunked implementation which maximizes vectorization potential, complemented by an `elemental` kernel based on the [kahan summation](https://en.wikipedia.org/wiki/Kahan_summation_algorithm) strategy to reduce the round-off error:
5252

5353
```fortran
5454
elemental subroutine kahan_kernel_<kind>(a,s,c)
@@ -65,7 +65,7 @@ end subroutine
6565

6666
#### Syntax
6767

68-
`res = ` [[stdlib_intrinsics(module):fsum_kahan(interface)]] ` (x [,mask] )`
68+
`res = ` [[stdlib_intrinsics(module):stdlib_sum_kahan(interface)]] ` (x [,mask] )`
6969

7070
#### Status
7171

@@ -92,15 +92,15 @@ The output is a scalar of `type` and `kind` same as to that of `x`.
9292
```
9393

9494
<!-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -->
95-
### `fprod` function
95+
### `stdlib_dot_product` function
9696

9797
#### Description
9898

99-
The `fprod` function can replace the intrinsic `dot_product` for 1D `real` or `complex` arrays. It follows a chunked implementation which maximizes vectorization potential as well as reducing the round-off error. This procedure is recommended when crunching large arrays, for repetitive products of smaller arrays consider the classical `dot_product`.
99+
The `stdlib_dot_product` function can replace the intrinsic `dot_product` for 1D `real` or `complex` arrays. It follows a chunked implementation which maximizes vectorization potential as well as reducing the round-off error. This procedure is recommended when crunching large arrays, for repetitive products of smaller arrays consider the classical `dot_product`.
100100

101101
#### Syntax
102102

103-
`res = ` [[stdlib_intrinsics(module):fprod(interface)]] ` (x, y)`
103+
`res = ` [[stdlib_intrinsics(module):stdlib_dot_product(interface)]] ` (x, y)`
104104

105105
#### Status
106106

@@ -121,15 +121,15 @@ Pure function.
121121
The output is a scalar of `type` and `kind` same as to that of `x` and `y`.
122122

123123
<!-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -->
124-
### `fprod_kahan` function
124+
### `stdlib_dot_product_kahan` function
125125

126126
#### Description
127127

128-
The `fprod_kahan` function can replace the intrinsic `dot_product` for 1D `real` or `complex` arrays. It follows a chunked implementation which maximizes vectorization potential , complemented by the same `elemental` kernel based on the [kahan summation](https://en.wikipedia.org/wiki/Kahan_summation_algorithm) used for `fsum` to reduce the round-off error.
128+
The `stdlib_dot_product_kahan` function can replace the intrinsic `dot_product` for 1D `real` or `complex` arrays. It follows a chunked implementation which maximizes vectorization potential , complemented by the same `elemental` kernel based on the [kahan summation](https://en.wikipedia.org/wiki/Kahan_summation_algorithm) used for `stdlib_sum` to reduce the round-off error.
129129

130130
#### Syntax
131131

132-
`res = ` [[stdlib_intrinsics(module):fprod_kahan(interface)]] ` (x, y)`
132+
`res = ` [[stdlib_intrinsics(module):stdlib_dot_product_kahan(interface)]] ` (x, y)`
133133

134134
#### Status
135135

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,6 @@
11
program example_dot_product
22
use stdlib_kinds, only: sp
3-
use stdlib_intrinsics, only: fprod, fprod_kahan
3+
use stdlib_intrinsics, only: stdlib_dot_product, stdlib_dot_product_kahan
44
implicit none
55

66
real(sp), allocatable :: x(:), y(:)
@@ -11,8 +11,8 @@ program example_dot_product
1111
call random_number(y)
1212

1313
total_prod(1) = dot_product(x,y) !> compiler intrinsic
14-
total_prod(2) = fprod(x,y) !> chunked summation over inner product
15-
total_prod(3) = fprod_kahan(x,y) !> chunked kahan summation over inner product
14+
total_prod(2) = stdlib_dot_product(x,y) !> chunked summation over inner product
15+
total_prod(3) = stdlib_dot_product_kahan(x,y) !> chunked kahan summation over inner product
1616
print *, total_prod(1:3)
1717

1818
end program example_dot_product

example/intrinsics/example_sum.f90

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,6 @@
11
program example_sum
22
use stdlib_kinds, only: sp
3-
use stdlib_intrinsics, only: fsum, fsum_kahan
3+
use stdlib_intrinsics, only: stdlib_sum, stdlib_sum_kahan
44
implicit none
55

66
real(sp), allocatable :: x(:)
@@ -10,8 +10,8 @@ program example_sum
1010
call random_number(x)
1111

1212
total_sum(1) = sum(x) !> compiler intrinsic
13-
total_sum(2) = fsum(x) !> chunked summation
14-
total_sum(3) = fsum_kahan(x)!> chunked kahan summation
13+
total_sum(2) = stdlib_sum(x) !> chunked summation
14+
total_sum(3) = stdlib_sum_kahan(x)!> chunked kahan summation
1515
print *, total_sum(1:3)
1616

1717
end program example_sum

src/stdlib_intrinsics.fypp

Lines changed: 16 additions & 16 deletions
Original file line numberDiff line numberDiff line change
@@ -12,24 +12,24 @@ module stdlib_intrinsics
1212
implicit none
1313
private
1414

15-
interface fsum
15+
interface stdlib_sum
1616
#:for rk, rt, rs in RC_KINDS_TYPES
17-
pure module function fsum_1d_${rs}$(a) result(s)
17+
pure module function stdlib_sum_1d_${rs}$(a) result(s)
1818
${rt}$, intent(in) :: a(:)
1919
${rt}$ :: s
2020
end function
21-
pure module function fsum_1d_${rs}$_mask(a,mask) result(s)
21+
pure module function stdlib_sum_1d_${rs}$_mask(a,mask) result(s)
2222
${rt}$, intent(in) :: a(:)
2323
logical, intent(in) :: mask(:)
2424
${rt}$ :: s
2525
end function
2626
#:for rank in RANKS
27-
pure module function fsum_${rank}$d_${rs}$( x, mask ) result( s )
27+
pure module function stdlib_sum_${rank}$d_${rs}$( x, mask ) result( s )
2828
${rt}$, intent(in) :: x${ranksuffix(rank)}$
2929
logical, intent(in), optional :: mask${ranksuffix(rank)}$
3030
${rt}$ :: s
3131
end function
32-
pure module function fsum_${rank}$d_dim_${rs}$( x , dim, mask ) result( s )
32+
pure module function stdlib_sum_${rank}$d_dim_${rs}$( x , dim, mask ) result( s )
3333
${rt}$, intent(in) :: x${ranksuffix(rank)}$
3434
integer, intent(in):: dim
3535
logical, intent(in), optional :: mask${ranksuffix(rank)}$
@@ -38,44 +38,44 @@ module stdlib_intrinsics
3838
#:endfor
3939
#:endfor
4040
end interface
41-
public :: fsum
41+
public :: stdlib_sum
4242

43-
interface fsum_kahan
43+
interface stdlib_sum_kahan
4444
#:for rk, rt, rs in RC_KINDS_TYPES
45-
pure module function fsum_kahan_1d_${rs}$(a) result(s)
45+
pure module function stdlib_sum_kahan_1d_${rs}$(a) result(s)
4646
${rt}$, intent(in) :: a(:)
4747
${rt}$ :: s
4848
end function
49-
pure module function fsum_kahan_1d_${rs}$_mask(a,mask) result(s)
49+
pure module function stdlib_sum_kahan_1d_${rs}$_mask(a,mask) result(s)
5050
${rt}$, intent(in) :: a(:)
5151
logical, intent(in) :: mask(:)
5252
${rt}$ :: s
5353
end function
5454
#:endfor
5555
end interface
56-
public :: fsum_kahan
56+
public :: stdlib_sum_kahan
5757

58-
interface fprod
58+
interface stdlib_dot_product
5959
#:for rk, rt, rs in RC_KINDS_TYPES
60-
pure module function fprod_${rs}$(a,b) result(p)
60+
pure module function stdlib_dot_product_${rs}$(a,b) result(p)
6161
${rt}$, intent(in) :: a(:)
6262
${rt}$, intent(in) :: b(:)
6363
${rt}$ :: p
6464
end function
6565
#:endfor
6666
end interface
67-
public :: fprod
67+
public :: stdlib_dot_product
6868

69-
interface fprod_kahan
69+
interface stdlib_dot_product_kahan
7070
#:for rk, rt, rs in RC_KINDS_TYPES
71-
pure module function fprod_kahan_${rs}$(a,b) result(p)
71+
pure module function stdlib_dot_product_kahan_${rs}$(a,b) result(p)
7272
${rt}$, intent(in) :: a(:)
7373
${rt}$, intent(in) :: b(:)
7474
${rt}$ :: p
7575
end function
7676
#:endfor
7777
end interface
78-
public :: fprod_kahan
78+
public :: stdlib_dot_product_kahan
7979

8080
interface kahan_kernel
8181
#:for rk, rt, rs in RC_KINDS_TYPES

src/stdlib_intrinsics_dot_product.fypp

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -24,7 +24,7 @@ submodule(stdlib_intrinsics) stdlib_intrinsics_dot_product
2424
contains
2525

2626
#:for k1, t1, s1 in RC_KINDS_TYPES
27-
pure module function fprod_${s1}$(a,b) result(p)
27+
pure module function stdlib_dot_product_${s1}$(a,b) result(p)
2828
${t1}$, intent(in) :: a(:)
2929
${t1}$, intent(in) :: b(:)
3030
${t1}$ :: p
@@ -48,7 +48,7 @@ end function
4848
#:endfor
4949

5050
#:for k1, t1, s1 in RC_KINDS_TYPES
51-
pure module function fprod_kahan_${s1}$(a,b) result(p)
51+
pure module function stdlib_dot_product_kahan_${s1}$(a,b) result(p)
5252
${t1}$, intent(in) :: a(:)
5353
${t1}$, intent(in) :: b(:)
5454
${t1}$ :: p

src/stdlib_intrinsics_sum.fypp

Lines changed: 16 additions & 16 deletions
Original file line numberDiff line numberDiff line change
@@ -18,7 +18,7 @@ contains
1818

1919
!================= 1D Base implementations ============
2020
#:for rk, rt, rs in RC_KINDS_TYPES
21-
pure module function fsum_1d_${rs}$(a) result(s)
21+
pure module function stdlib_sum_1d_${rs}$(a) result(s)
2222
${rt}$, intent(in) :: a(:)
2323
${rt}$ :: s
2424
${rt}$ :: abatch(chunk)
@@ -39,7 +39,7 @@ pure module function fsum_1d_${rs}$(a) result(s)
3939
end do
4040
end function
4141

42-
pure module function fsum_1d_${rs}$_mask(a,mask) result(s)
42+
pure module function stdlib_sum_1d_${rs}$_mask(a,mask) result(s)
4343
${rt}$, intent(in) :: a(:)
4444
logical, intent(in) :: mask(:)
4545
${rt}$ :: s
@@ -61,7 +61,7 @@ pure module function fsum_1d_${rs}$_mask(a,mask) result(s)
6161
end do
6262
end function
6363

64-
pure module function fsum_kahan_1d_${rs}$(a) result(s)
64+
pure module function stdlib_sum_kahan_1d_${rs}$(a) result(s)
6565
${rt}$, intent(in) :: a(:)
6666
${rt}$ :: s
6767
${rt}$ :: sbatch(chunk)
@@ -83,7 +83,7 @@ pure module function fsum_kahan_1d_${rs}$(a) result(s)
8383
end do
8484
end function
8585

86-
pure module function fsum_kahan_1d_${rs}$_mask(a,mask) result(s)
86+
pure module function stdlib_sum_kahan_1d_${rs}$_mask(a,mask) result(s)
8787
${rt}$, intent(in) :: a(:)
8888
logical, intent(in) :: mask(:)
8989
${rt}$ :: s
@@ -110,7 +110,7 @@ end function
110110
!================= N-D implementations ============
111111
#:for rk, rt, rs in RC_KINDS_TYPES
112112
#:for rank in RANKS
113-
pure module function fsum_${rank}$d_${rs}$( x , mask ) result( s )
113+
pure module function stdlib_sum_${rank}$d_${rs}$( x , mask ) result( s )
114114
${rt}$, intent(in) :: x${ranksuffix(rank)}$
115115
logical, intent(in), optional :: mask${ranksuffix(rank)}$
116116
${rt}$ :: s
@@ -123,17 +123,17 @@ contains
123123
pure ${rt}$ function sum_recast(b,n)
124124
integer, intent(in) :: n
125125
${rt}$, intent(in) :: b(n)
126-
sum_recast = fsum(b)
126+
sum_recast = stdlib_sum(b)
127127
end function
128128
pure ${rt}$ function sum_recast_mask(b,m,n)
129129
integer, intent(in) :: n
130130
${rt}$, intent(in) :: b(n)
131131
logical, intent(in) :: m(n)
132-
sum_recast_mask = fsum(b,m)
132+
sum_recast_mask = stdlib_sum(b,m)
133133
end function
134134
end function
135135

136-
pure module function fsum_${rank}$d_dim_${rs}$( x , dim, mask ) result( s )
136+
pure module function stdlib_sum_${rank}$d_dim_${rs}$( x , dim, mask ) result( s )
137137
${rt}$, intent(in) :: x${ranksuffix(rank)}$
138138
integer, intent(in):: dim
139139
logical, intent(in), optional :: mask${ranksuffix(rank)}$
@@ -144,35 +144,35 @@ pure module function fsum_${rank}$d_dim_${rs}$( x , dim, mask ) result( s )
144144
if(dim<${rank}$)then
145145
do j = 1, size(x,dim=${rank}$)
146146
#:if rank == 2
147-
s${select_subarray(rank-1, [(rank-1, 'j')])}$ = fsum( x${select_subarray(rank, [(rank, 'j')])}$ )
147+
s${select_subarray(rank-1, [(rank-1, 'j')])}$ = stdlib_sum( x${select_subarray(rank, [(rank, 'j')])}$ )
148148
#:else
149-
s${select_subarray(rank-1, [(rank-1, 'j')])}$ = fsum( x${select_subarray(rank, [(rank, 'j')])}$, dim=dim )
149+
s${select_subarray(rank-1, [(rank-1, 'j')])}$ = stdlib_sum( x${select_subarray(rank, [(rank, 'j')])}$, dim=dim )
150150
#:endif
151151
end do
152152
else
153153
do j = 1, size(x,dim=1)
154154
#:if rank == 2
155-
s${select_subarray(rank-1, [(1, 'j')])}$ = fsum( x${select_subarray(rank, [(1, 'j')])}$ )
155+
s${select_subarray(rank-1, [(1, 'j')])}$ = stdlib_sum( x${select_subarray(rank, [(1, 'j')])}$ )
156156
#:else
157-
s${select_subarray(rank-1, [(1, 'j')])}$ = fsum( x${select_subarray(rank, [(1, 'j')])}$, dim=${rank-1}$ )
157+
s${select_subarray(rank-1, [(1, 'j')])}$ = stdlib_sum( x${select_subarray(rank, [(1, 'j')])}$, dim=${rank-1}$ )
158158
#:endif
159159
end do
160160
end if
161161
else
162162
if(dim<${rank}$)then
163163
do j = 1, size(x,dim=${rank}$)
164164
#:if rank == 2
165-
s${select_subarray(rank-1, [(rank-1, 'j')])}$ = fsum( x${select_subarray(rank, [(rank, 'j')])}$, mask=mask${select_subarray(rank, [(rank, 'j')])}$ )
165+
s${select_subarray(rank-1, [(rank-1, 'j')])}$ = stdlib_sum( x${select_subarray(rank, [(rank, 'j')])}$, mask=mask${select_subarray(rank, [(rank, 'j')])}$ )
166166
#:else
167-
s${select_subarray(rank-1, [(rank-1, 'j')])}$ = fsum( x${select_subarray(rank, [(rank, 'j')])}$, dim=dim, mask=mask${select_subarray(rank, [(rank, 'j')])}$ )
167+
s${select_subarray(rank-1, [(rank-1, 'j')])}$ = stdlib_sum( x${select_subarray(rank, [(rank, 'j')])}$, dim=dim, mask=mask${select_subarray(rank, [(rank, 'j')])}$ )
168168
#:endif
169169
end do
170170
else
171171
do j = 1, size(x,dim=1)
172172
#:if rank == 2
173-
s${select_subarray(rank-1, [(1, 'j')])}$ = fsum( x${select_subarray(rank, [(1, 'j')])}$, mask=mask${select_subarray(rank, [(1, 'j')])}$ )
173+
s${select_subarray(rank-1, [(1, 'j')])}$ = stdlib_sum( x${select_subarray(rank, [(1, 'j')])}$, mask=mask${select_subarray(rank, [(1, 'j')])}$ )
174174
#:else
175-
s${select_subarray(rank-1, [(1, 'j')])}$ = fsum( x${select_subarray(rank, [(1, 'j')])}$, dim=${rank-1}$, mask=mask${select_subarray(rank, [(1, 'j')])}$ )
175+
s${select_subarray(rank-1, [(1, 'j')])}$ = stdlib_sum( x${select_subarray(rank, [(1, 'j')])}$, dim=${rank-1}$, mask=mask${select_subarray(rank, [(1, 'j')])}$ )
176176
#:endif
177177
end do
178178
end if

0 commit comments

Comments
 (0)