Skip to content

Commit

Permalink
stat_dev_1: update test_mean
Browse files Browse the repository at this point in the history
  • Loading branch information
jvdp1 committed Jan 21, 2020
1 parent 5a1adcb commit 922e523
Showing 1 changed file with 31 additions and 44 deletions.
75 changes: 31 additions & 44 deletions src/tests/stat/test_mean.f90
Original file line number Diff line number Diff line change
Expand Up @@ -11,37 +11,37 @@ program test_mean
real(dp), allocatable :: d3(:, :, :)
real(dp), allocatable :: d4(:, :, :, :)


!sp
call loadtxt("array1.dat", s)
call loadtxt("array3.dat", s)

call assert( mean(s) - 4.5_sp == 0.0_sp)
call assert(sum( mean(s, dim = 1) - [4.0_sp, 5.0_sp] ) == 0.0_sp)
call assert(sum( mean(s, dim = 2) - [1.5_sp, 3.5_sp, 5.5_sp, 7.5_sp] ) == 0.0_sp)
call assert( mean(s) - sum(s)/real(size(s), sp) == 0.0_sp)
call assert( sum( abs( mean(s,1) - sum(s,1)/real(size(s,1), sp) )) == 0.0_sp)
call assert( sum( abs( mean(s,2) - sum(s,2)/real(size(s,2), sp) )) == 0.0_sp)

call assert( size(mean(s, dim = 1))- size(sum(s, dim = 1)) == 0)
call assert( size(mean(s, dim = 2))- size(sum(s, dim = 2)) == 0)

!dp
call loadtxt("array1.dat", d)
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)

call assert(mean(d) - 4.5_dp == 0.0_dp)
call assert(sum( mean(d, dim = 1) - [4.0_dp, 5.0_dp] ) == 0.0_dp)
call assert(sum( mean(d, dim = 2) - [1.5_dp, 3.5_dp, 5.5_dp, 7.5_dp] ) == 0.0_dp)

!int32
call loadtxt("array1.dat", s)
call loadtxt("array3.dat", d)

call assert( mean(int(s, int32)) - 4.5_dp == 0.0_dp)
call assert(sum( mean(int(s, int32), dim = 1) - [4.0_dp, 5.0_dp] ) == 0.0_dp)
call assert(sum( mean(int(s, int32), dim = 2) - [1.5_dp, 3.5_dp, 5.5_dp, 7.5_dp] ) == 0.0_dp)
call assert( mean(int(d, int32)) - sum(real(int(d, int32),dp))/real(size(d), dp) == 0.0_dp)
call assert( sum(abs( mean(int(d, int32),1) - sum(real(int(d, int32),dp),1)/real(size(d,1), dp) )) == 0.0_dp)
call assert( sum(abs( mean(int(d, int32),2) - sum(real(int(d, int32),dp),2)/real(size(d,2), dp) )) == 0.0_dp)

!int64
call loadtxt("array1.dat", s)

call assert( mean(int(s, int64)) - 4.5_dp == 0.0_dp)
call assert(sum( mean(int(s, int64), dim = 1) - [4.0_dp, 5.0_dp] ) == 0.0_dp)
call assert(sum( mean(int(s, int64), dim = 2) - [1.5_dp, 3.5_dp, 5.5_dp, 7.5_dp] ) == 0.0_dp)
!int64
call loadtxt("array3.dat", d)

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


!dp rank 3
Expand All @@ -50,38 +50,25 @@ program test_mean
d3(:,:,2)=d*1.5_dp;
d3(:,:,3)=d*4._dp;

call assert( sum( shape(mean(d3,1))-shape(sum(d3,1)) ) == 0)
call assert( sum( shape(mean(d3,2))-shape(sum(d3,2)) ) == 0)
call assert( sum( shape(mean(d3,3))-shape(sum(d3,3)) ) == 0)

call assert( mean(d3) - sum(d3)/size(d3) == 0.0_dp)
call assert( sum(abs( mean(d3,1) - &
reshape([4.0_dp, 5.0_dp, 6.0_dp, 7.5_dp, 16.0_dp, 20.0_dp], shape(sum(d3,1))) ) ) &
== 0.0_dp)
call assert( sum(abs( mean(d3,2) - &
reshape([ 1.5_dp, 3.5_dp, 5.5_dp, 7.5_dp, &
2.25_dp, 5.25_dp, 8.25_dp, 11.25_dp, &
6._dp, 14._dp, 22._dp, 30._dp &
], shape(sum(d3,2))) ) ) &
== 0.0_dp)
call assert( sum(abs( mean(d3,3) - &
reshape([2.1666666666666665_dp, 6.5_dp, 10.833333333333334_dp,&
15.166666666666666_dp, 4.333333333333333_dp, &
8.6666666666666661_dp, 13.0_dp, 17.333333333333332_dp &
], shape(sum(d3,3))) ) ) &
== 0.0_dp)
call assert( mean(d3) - sum(d3)/real(size(d3), dp) == 0.0_dp)
call assert( sum( abs( mean(d3,1) - sum(d3,1)/real(size(d3,1), dp) )) == 0.0_dp)
call assert( sum( abs( mean(d3,2) - sum(d3,2)/real(size(d3,2), dp) )) == 0.0_dp)
call assert( sum( abs( mean(d3,3) - sum(d3,3)/real(size(d3,3), dp) )) == 0.0_dp)


!dp rank 4
allocate(d4(size(d,1),size(d,2),3,9))
d4 = 1.
d4(:,:,1,1)=d;
d4(:,:,2,1)=d*1.5_dp;
d4(:,:,3,1)=d*4._dp;
d4(:,:,3,9)=d*4._dp;

call assert( sum( shape(mean(d4,1))-shape(sum(d4,1)) ) == 0)
call assert( sum( shape(mean(d4,2))-shape(sum(d4,2)) ) == 0)
call assert( sum( shape(mean(d4,3))-shape(sum(d4,3)) ) == 0)
call assert( sum( shape(mean(d4,4))-shape(sum(d4,4)) ) == 0)

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

contains

Expand Down

0 comments on commit 922e523

Please sign in to comment.