Skip to content

Commit d9af336

Browse files
committed
stat_dev: init
1 parent dc7e49b commit d9af336

9 files changed

+139
-0
lines changed

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.f90
89
)
910

1011
add_library(fortran_stdlib ${SRC})

src/stdlib_experimental_stat.f90

+50
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,50 @@
1+
module stdlib_experimental_stat
2+
use stdlib_experimental_kinds, only: sp, dp, qp
3+
use stdlib_experimental_error, only: error_stop
4+
use stdlib_experimental_optval, only: optval
5+
implicit none
6+
private
7+
! Public API
8+
public :: mean
9+
10+
11+
interface mean
12+
module procedure mean_1_dp_dp
13+
module procedure mean_2_dp_dp
14+
end interface
15+
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+
50+
end module

src/tests/CMakeLists.txt

+1
Original file line numberDiff line numberDiff line change
@@ -9,6 +9,7 @@ endmacro(ADDTEST)
99
add_subdirectory(ascii)
1010
add_subdirectory(io)
1111
add_subdirectory(optval)
12+
add_subdirectory(stat)
1213
add_subdirectory(system)
1314

1415
ADDTEST(always_skip)

src/tests/stat/CMakeLists.txt

+1
Original file line numberDiff line numberDiff line change
@@ -0,0 +1 @@
1+
ADDTEST(mean)

src/tests/stat/array1.dat

+4
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,4 @@
1+
1 2
2+
3 4
3+
5 6
4+
7 8

src/tests/stat/array2.dat

+4
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,4 @@
1+
1 2 9
2+
3 4 10
3+
5 6 11
4+
7 8 12

src/tests/stat/array3.dat

+16
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,16 @@
1+
1.000000000000000021e-08 9.199998759392489944e+01
2+
1.024113254885563425e-08 9.199998731474968849e+01
3+
1.048233721895820948e-08 9.199998703587728244e+01
4+
1.072361403187881949e-08 9.199998675729767683e+01
5+
1.096496300919481796e-08 9.199998647900135040e+01
6+
1.120638417249036630e-08 9.199998620097916557e+01
7+
1.144787754335570897e-08 9.199998592322251056e+01
8+
1.168944314338753750e-08 9.199998564572304360e+01
9+
1.193108099418952317e-08 9.199998536847290609e+01
10+
1.217279111737088596e-08 9.199998509146449521e+01
11+
1.241457353454836993e-08 9.199998481469057765e+01
12+
1.265642826734443823e-08 9.199998453814424693e+01
13+
1.289835533738818635e-08 9.199998426181879552e+01
14+
1.314035476631514857e-08 9.199998398570787117e+01
15+
1.338242657576766519e-08 9.199998370980536322e+01
16+
1.362457078739434161e-08 9.199998343410533153e+01

src/tests/stat/array4.dat

+3
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,3 @@
1+
1.56367173122998851E-010 4.51568171776229776E-007 4.96568621780730290E-006 5.01068666781180638E-005 5.01518671281225327E-004 5.01763629287519872E-003 5.58487648776459511E-002 0.32618374746711520 1.7639051761733842 9.4101331514118236
2+
8.23481961129666271E-010 4.58239319656296504E-007 5.03239769660796763E-006 5.07739814661247314E-005 5.08189819161291786E-004 5.09287863145356859E-003 5.62489258981838380E-002 0.32831192218075922 1.7752234390209392 9.4703270222745211
3+
2.02201163784892633E-009 4.70224616423489051E-007 5.15225066427989480E-006 5.19725111428439625E-005 5.20175115928484585E-004 5.22805802989171828E-003 5.69678499382489378E-002 0.33213537295325257 1.7955576815764616 9.5784705410250410

src/tests/stat/test_mean.f90

+59
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,59 @@
1+
program test_mean
2+
use stdlib_experimental_error, only: assert
3+
use stdlib_experimental_kinds, only: sp, dp
4+
use stdlib_experimental_io, only: loadtxt
5+
use stdlib_experimental_stat, only: mean
6+
use stdlib_experimental_error, only: error_stop
7+
implicit none
8+
9+
real(sp), allocatable :: s(:, :)
10+
real(dp), allocatable :: d(:, :)
11+
real(dp), allocatable :: res(:)
12+
13+
!call loadtxt("array1.dat", s)
14+
!call print_array(s)
15+
16+
call loadtxt("array1.dat", d)
17+
18+
res = mean(d)
19+
call print_array(d)
20+
print *,'Mean = ', res
21+
call assert(sum( res - [1.5_dp, 3.5_dp, 5.5_dp, 7.5_dp] ) == 0.0_dp)
22+
23+
res = mean(d, dim = 2)
24+
call print_array(d)
25+
print *,'Mean = ', res
26+
call assert(sum( res - [4.0_dp, 5.0_dp] ) == 0.0_dp)
27+
28+
!call loadtxt("array2.dat", d)
29+
!call print_array(d)
30+
!
31+
!call loadtxt("array3.dat", d)
32+
!call print_array(d)
33+
!
34+
!call loadtxt("array4.dat", d)
35+
!call print_array(d)
36+
37+
contains
38+
39+
subroutine print_array(a)
40+
class(*),intent(in) :: a(:, :)
41+
integer :: i
42+
print *, "Array, shape=(", size(a, 1), ",", size(a, 2), ")"
43+
44+
select type(a)
45+
type is(real(sp))
46+
do i = 1, size(a, 1)
47+
print *, a(i, :)
48+
end do
49+
type is(real(dp))
50+
do i = 1, size(a, 1)
51+
print *, a(i, :)
52+
end do
53+
class default
54+
call error_stop('The proposed type is not supported')
55+
end select
56+
57+
end subroutine
58+
59+
end program

0 commit comments

Comments
 (0)