Skip to content

Commit 17e3d16

Browse files
committed
second try cmake
1 parent 397eb18 commit 17e3d16

File tree

3 files changed

+43
-1
lines changed

3 files changed

+43
-1
lines changed

CMakeLists.txt

+1-1
Original file line numberDiff line numberDiff line change
@@ -15,7 +15,7 @@ endif()
1515
include(CheckFortranSourceCompiles)
1616
include(CheckFortranSourceRuns)
1717
check_fortran_source_compiles("error stop i; end" f18errorstop SRC_EXT f90)
18-
check_fortran_source_compiles("real,allocatable :: array(:, :, :, :, :, :, :, :, :, :)" f03rank SRC_EXT f90)
18+
check_fortran_source_compiles("real, allocatable :: array(:, :, :, :, :, :, :, :, :, :); end" f03rank SRC_EXT f90)
1919
check_fortran_source_runs("use, intrinsic :: iso_fortran_env, only : real128; real(real128) :: x; x = x+1; end" f03real128)
2020

2121
add_subdirectory(src)

src/tests/stats/CMakeLists.txt

+4
Original file line numberDiff line numberDiff line change
@@ -1 +1,5 @@
11
ADDTEST(mean)
2+
3+
if(f03rank)
4+
ADDTEST(mean_f03)
5+
endif()

src/tests/stats/test_mean_f03.f90

+38
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,38 @@
1+
program test_mean
2+
use stdlib_experimental_error, only: assert
3+
use stdlib_experimental_kinds, only: sp, dp, int32, int64
4+
use stdlib_experimental_io, only: loadtxt
5+
use stdlib_experimental_stats, only: mean
6+
implicit none
7+
8+
real(dp), allocatable :: d(:, :)
9+
real(dp), allocatable :: d8(:, :, :, :, :, :, :, :)
10+
11+
12+
!dp
13+
call loadtxt("array3.dat", d)
14+
15+
call assert( mean(d) - sum(d)/real(size(d), dp) == 0.0_dp)
16+
call assert( sum( abs( mean(d,1) - sum(d,1)/real(size(d,1), dp) )) == 0.0_dp)
17+
call assert( sum( abs( mean(d,2) - sum(d,2)/real(size(d,2), dp) )) == 0.0_dp)
18+
19+
!dp rank 8
20+
allocate(d8(size(d,1), size(d,2), 3, 4, 5, 6, 7, 8))
21+
d8(:, :, 1, 4, 5 ,6 ,7 ,8)=d;
22+
d8(:, :, 2, 4, 5 ,6 ,7 ,8)=d * 1.5_dp;
23+
d8(:, :, 3, 4, 5 ,6 ,7 ,8)=d * 4._dp;
24+
25+
call assert( mean(d8) - sum(d8)/real(size(d8), dp) == 0.0_dp)
26+
27+
call assert( sum( abs( mean(d8,1) - sum(d8,1)/real(size(d8,1), dp) )) == 0.0_dp)
28+
call assert( sum( abs( mean(d8,2) - sum(d8,2)/real(size(d8,2), dp) )) == 0.0_dp)
29+
call assert( sum( abs( mean(d8,3) - sum(d8,3)/real(size(d8,3), dp) )) == 0.0_dp)
30+
call assert( sum( abs( mean(d8,4) - sum(d8,4)/real(size(d8,4), dp) )) == 0.0_dp)
31+
call assert( sum( abs( mean(d8,5) - sum(d8,5)/real(size(d8,5), dp) )) == 0.0_dp)
32+
call assert( sum( abs( mean(d8,6) - sum(d8,6)/real(size(d8,6), dp) )) == 0.0_dp)
33+
call assert( sum( abs( mean(d8,7) - sum(d8,7)/real(size(d8,7), dp) )) == 0.0_dp)
34+
call assert( sum( abs( mean(d8,8) - sum(d8,8)/real(size(d8,8), dp) )) == 0.0_dp)
35+
36+
contains
37+
38+
end program

0 commit comments

Comments
 (0)