Skip to content

Commit 965f37b

Browse files
committed
moved to submodules
how to use pure functions in submodules
1 parent d9af336 commit 965f37b

File tree

3 files changed

+49
-38
lines changed

3 files changed

+49
-38
lines changed

Diff for: src/CMakeLists.txt

+1
Original file line numberDiff line numberDiff line change
@@ -5,6 +5,7 @@ set(SRC
55
stdlib_experimental_kinds.f90
66
stdlib_experimental_optval.f90
77
stdlib_experimental_system.F90
8+
stdlib_experimental_stat_mean.f90
89
stdlib_experimental_stat.f90
910
)
1011

Diff for: src/stdlib_experimental_stat.f90

+9-38
Original file line numberDiff line numberDiff line change
@@ -1,50 +1,21 @@
11
module stdlib_experimental_stat
22
use stdlib_experimental_kinds, only: sp, dp, qp
3-
use stdlib_experimental_error, only: error_stop
4-
use stdlib_experimental_optval, only: optval
53
implicit none
64
private
75
! Public API
86
public :: mean
97

108

119
interface mean
12-
module procedure mean_1_dp_dp
13-
module procedure mean_2_dp_dp
10+
module function mean_1_dp_dp(mat) result(res)
11+
real(dp), intent(in) :: mat(:)
12+
real(dp) ::res
13+
end function
14+
module function mean_2_dp_dp(mat, dim) result(res)
15+
real(dp), intent(in) :: mat(:,:)
16+
integer, intent(in), optional :: dim
17+
real(dp), allocatable ::res(:)
18+
end function
1419
end interface
1520

16-
contains
17-
18-
pure function mean_1_dp_dp(mat) result(res)
19-
real(dp), intent(in) :: mat(:)
20-
real(dp) ::res
21-
22-
res = sum(mat) / real(size(mat), dp)
23-
24-
end function mean_1_dp_dp
25-
26-
function mean_2_dp_dp(mat, dim) result(res)
27-
real(dp), intent(in) :: mat(:,:)
28-
integer, intent(in), optional :: dim
29-
real(dp), allocatable ::res(:)
30-
31-
integer :: i
32-
integer :: dim_
33-
34-
dim_ = optval(dim, 1)
35-
36-
allocate(res(size(mat, dim_)))
37-
38-
if (dim_ == 1) then
39-
do i=1, size(mat, dim_)
40-
res(i) = mean_1_dp_dp(mat(i,:))
41-
end do
42-
else if (dim_ == 2) then
43-
do i=1, size(mat, dim_)
44-
res(i) = mean_1_dp_dp(mat(:,i))
45-
end do
46-
end if
47-
48-
end function mean_2_dp_dp
49-
5021
end module

Diff for: src/stdlib_experimental_stat_mean.f90

+39
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,39 @@
1+
submodule (stdlib_experimental_stat) stdlib_experimental_stat_mean
2+
use stdlib_experimental_optval, only: optval
3+
implicit none
4+
5+
contains
6+
7+
module function mean_1_dp_dp(mat) result(res)
8+
real(dp), intent(in) :: mat(:)
9+
real(dp) ::res
10+
11+
res = sum(mat) / real(size(mat), dp)
12+
13+
end function mean_1_dp_dp
14+
15+
module function mean_2_dp_dp(mat, dim) result(res)
16+
real(dp), intent(in) :: mat(:,:)
17+
integer, intent(in), optional :: dim
18+
real(dp), allocatable ::res(:)
19+
20+
integer :: i
21+
integer :: dim_
22+
23+
dim_ = optval(dim, 1)
24+
25+
allocate(res(size(mat, dim_)))
26+
27+
if (dim_ == 1) then
28+
do i=1, size(mat, dim_)
29+
res(i) = mean_1_dp_dp(mat(i,:))
30+
end do
31+
else if (dim_ == 2) then
32+
do i=1, size(mat, dim_)
33+
res(i) = mean_1_dp_dp(mat(:,i))
34+
end do
35+
end if
36+
37+
end function mean_2_dp_dp
38+
39+
end submodule

0 commit comments

Comments
 (0)