Skip to content

Commit

Permalink
moved to submodules
Browse files Browse the repository at this point in the history
how to use pure functions in submodules
  • Loading branch information
jvdp1 committed Jan 19, 2020
1 parent d9af336 commit 965f37b
Show file tree
Hide file tree
Showing 3 changed files with 49 additions and 38 deletions.
1 change: 1 addition & 0 deletions src/CMakeLists.txt
Original file line number Diff line number Diff line change
Expand Up @@ -5,6 +5,7 @@ set(SRC
stdlib_experimental_kinds.f90
stdlib_experimental_optval.f90
stdlib_experimental_system.F90
stdlib_experimental_stat_mean.f90
stdlib_experimental_stat.f90
)

Expand Down
47 changes: 9 additions & 38 deletions src/stdlib_experimental_stat.f90
Original file line number Diff line number Diff line change
@@ -1,50 +1,21 @@
module stdlib_experimental_stat
use stdlib_experimental_kinds, only: sp, dp, qp
use stdlib_experimental_error, only: error_stop
use stdlib_experimental_optval, only: optval
implicit none
private
! Public API
public :: mean


interface mean
module procedure mean_1_dp_dp
module procedure mean_2_dp_dp
module function mean_1_dp_dp(mat) result(res)
real(dp), intent(in) :: mat(:)
real(dp) ::res
end function
module function mean_2_dp_dp(mat, dim) result(res)
real(dp), intent(in) :: mat(:,:)
integer, intent(in), optional :: dim
real(dp), allocatable ::res(:)
end function
end interface

contains

pure function mean_1_dp_dp(mat) result(res)
real(dp), intent(in) :: mat(:)
real(dp) ::res

res = sum(mat) / real(size(mat), dp)

end function mean_1_dp_dp

function mean_2_dp_dp(mat, dim) result(res)
real(dp), intent(in) :: mat(:,:)
integer, intent(in), optional :: dim
real(dp), allocatable ::res(:)

integer :: i
integer :: dim_

dim_ = optval(dim, 1)

allocate(res(size(mat, dim_)))

if (dim_ == 1) then
do i=1, size(mat, dim_)
res(i) = mean_1_dp_dp(mat(i,:))
end do
else if (dim_ == 2) then
do i=1, size(mat, dim_)
res(i) = mean_1_dp_dp(mat(:,i))
end do
end if

end function mean_2_dp_dp

end module
39 changes: 39 additions & 0 deletions src/stdlib_experimental_stat_mean.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,39 @@
submodule (stdlib_experimental_stat) stdlib_experimental_stat_mean
use stdlib_experimental_optval, only: optval
implicit none

contains

module function mean_1_dp_dp(mat) result(res)
real(dp), intent(in) :: mat(:)
real(dp) ::res

res = sum(mat) / real(size(mat), dp)

end function mean_1_dp_dp

module function mean_2_dp_dp(mat, dim) result(res)
real(dp), intent(in) :: mat(:,:)
integer, intent(in), optional :: dim
real(dp), allocatable ::res(:)

integer :: i
integer :: dim_

dim_ = optval(dim, 1)

allocate(res(size(mat, dim_)))

if (dim_ == 1) then
do i=1, size(mat, dim_)
res(i) = mean_1_dp_dp(mat(i,:))
end do
else if (dim_ == 2) then
do i=1, size(mat, dim_)
res(i) = mean_1_dp_dp(mat(:,i))
end do
end if

end function mean_2_dp_dp

end submodule

0 comments on commit 965f37b

Please sign in to comment.