Skip to content
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
5 changes: 4 additions & 1 deletion arrayfire.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -144,6 +144,8 @@ test-suite test
exitcode-stdio-1.0
main-is:
Main.hs
other-modules:
Test.Hspec.ApproxExpect
hs-source-dirs:
test
build-depends:
Expand All @@ -154,7 +156,8 @@ test-suite test
HUnit,
QuickCheck,
quickcheck-classes,
vector
vector,
call-stack >=0.4 && <0.5
if !flag(disable-build-tool-depends)
build-tool-depends:
hspec-discover:hspec-discover
Expand Down
5 changes: 3 additions & 2 deletions test/ArrayFire/LAPACKSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,6 +4,7 @@ module ArrayFire.LAPACKSpec where
import qualified ArrayFire as A
import Prelude
import Test.Hspec
import Test.Hspec.ApproxExpect

spec :: Spec
spec =
Expand Down Expand Up @@ -33,9 +34,9 @@ spec =
it "Should get determinant of Double" $ do
let eles = [[3 A.:+ 1, 8 A.:+ 1], [4 A.:+ 1, 6 A.:+ 1]]
(x,y) = A.det (A.matrix @(A.Complex Double) (2,2) eles)
x `shouldBe` (-14)
x `shouldBeApprox` (-14)
let (x,y) = A.det $ A.matrix @Double (2,2) [[3,8],[4,6]]
x `shouldBe` (-14)
x `shouldBeApprox` (-14)
-- it "Should calculate inverse" $ do
-- let x = flip A.inverse A.None $ A.matrix @Double (2,2) [[4.0,7.0],[2.0,6.0]]
-- x `shouldBe` A.matrix (2,2) [[0.6,-0.7],[-0.2,0.4]]
Expand Down
3 changes: 2 additions & 1 deletion test/ArrayFire/StatisticsSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,6 +5,7 @@ import ArrayFire hiding (not)

import Data.Complex
import Test.Hspec
import Test.Hspec.ApproxExpect

spec :: Spec
spec =
Expand All @@ -15,7 +16,7 @@ spec =
5.5
it "Should find the weighted-mean" $ do
meanWeighted (vector @Double 10 [1..]) (vector @Double 10 [1..]) 0
`shouldBe`
`shouldBeApprox`
7.0
it "Should find the variance" $ do
var (vector @Double 8 [1..8]) False 0
Expand Down
19 changes: 19 additions & 0 deletions test/Test/Hspec/ApproxExpect.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,19 @@
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Test.Hspec.ApproxExpect where

import Data.CallStack (HasCallStack)

import Test.Hspec (shouldSatisfy, Expectation)

infix 1 `shouldBeApprox`

shouldBeApprox :: (HasCallStack, Show a, Fractional a, Eq a)
=> a -> a -> Expectation
shouldBeApprox actual tgt
-- This is a hackish way of checking, without requiring a specific
-- type or an 'Ord' instance, whether two floating-point values
-- are only some epsilons apart: when the difference is small enough
-- so scaling it down some more makes it a no-op for addition.
= actual `shouldSatisfy` \x -> (x-tgt) * 1e-4 + tgt == tgt