Skip to content

Commit

Permalink
second try cmake
Browse files Browse the repository at this point in the history
  • Loading branch information
jvdp1 committed Jan 21, 2020
1 parent 397eb18 commit 17e3d16
Show file tree
Hide file tree
Showing 3 changed files with 43 additions and 1 deletion.
2 changes: 1 addition & 1 deletion CMakeLists.txt
Original file line number Diff line number Diff line change
Expand Up @@ -15,7 +15,7 @@ endif()
include(CheckFortranSourceCompiles)
include(CheckFortranSourceRuns)
check_fortran_source_compiles("error stop i; end" f18errorstop SRC_EXT f90)
check_fortran_source_compiles("real,allocatable :: array(:, :, :, :, :, :, :, :, :, :)" f03rank SRC_EXT f90)
check_fortran_source_compiles("real, allocatable :: array(:, :, :, :, :, :, :, :, :, :); end" f03rank SRC_EXT f90)
check_fortran_source_runs("use, intrinsic :: iso_fortran_env, only : real128; real(real128) :: x; x = x+1; end" f03real128)

add_subdirectory(src)
4 changes: 4 additions & 0 deletions src/tests/stats/CMakeLists.txt
Original file line number Diff line number Diff line change
@@ -1 +1,5 @@
ADDTEST(mean)

if(f03rank)
ADDTEST(mean_f03)
endif()
38 changes: 38 additions & 0 deletions src/tests/stats/test_mean_f03.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,38 @@
program test_mean
use stdlib_experimental_error, only: assert
use stdlib_experimental_kinds, only: sp, dp, int32, int64
use stdlib_experimental_io, only: loadtxt
use stdlib_experimental_stats, only: mean
implicit none

real(dp), allocatable :: d(:, :)
real(dp), allocatable :: d8(:, :, :, :, :, :, :, :)


!dp
call loadtxt("array3.dat", d)

call assert( mean(d) - sum(d)/real(size(d), dp) == 0.0_dp)
call assert( sum( abs( mean(d,1) - sum(d,1)/real(size(d,1), dp) )) == 0.0_dp)
call assert( sum( abs( mean(d,2) - sum(d,2)/real(size(d,2), dp) )) == 0.0_dp)

!dp rank 8
allocate(d8(size(d,1), size(d,2), 3, 4, 5, 6, 7, 8))
d8(:, :, 1, 4, 5 ,6 ,7 ,8)=d;
d8(:, :, 2, 4, 5 ,6 ,7 ,8)=d * 1.5_dp;
d8(:, :, 3, 4, 5 ,6 ,7 ,8)=d * 4._dp;

call assert( mean(d8) - sum(d8)/real(size(d8), dp) == 0.0_dp)

call assert( sum( abs( mean(d8,1) - sum(d8,1)/real(size(d8,1), dp) )) == 0.0_dp)
call assert( sum( abs( mean(d8,2) - sum(d8,2)/real(size(d8,2), dp) )) == 0.0_dp)
call assert( sum( abs( mean(d8,3) - sum(d8,3)/real(size(d8,3), dp) )) == 0.0_dp)
call assert( sum( abs( mean(d8,4) - sum(d8,4)/real(size(d8,4), dp) )) == 0.0_dp)
call assert( sum( abs( mean(d8,5) - sum(d8,5)/real(size(d8,5), dp) )) == 0.0_dp)
call assert( sum( abs( mean(d8,6) - sum(d8,6)/real(size(d8,6), dp) )) == 0.0_dp)
call assert( sum( abs( mean(d8,7) - sum(d8,7)/real(size(d8,7), dp) )) == 0.0_dp)
call assert( sum( abs( mean(d8,8) - sum(d8,8)/real(size(d8,8), dp) )) == 0.0_dp)

contains

end program

0 comments on commit 17e3d16

Please sign in to comment.