Navigation Menu

Skip to content

Commit

Permalink
Added unit test and travis-ci config.
Browse files Browse the repository at this point in the history
  • Loading branch information
acowley committed Dec 7, 2012
1 parent 3f8aa65 commit c0a7e38
Show file tree
Hide file tree
Showing 3 changed files with 61 additions and 3 deletions.
1 change: 1 addition & 0 deletions .travis.yml
@@ -0,0 +1 @@
language: haskell
16 changes: 13 additions & 3 deletions RANSAC.cabal
@@ -1,5 +1,5 @@
name: RANSAC
version: 0.1.0.0
version: 0.1.0.1
synopsis: The RANSAC algorithm for parameter estimation.
description: The RANdom SAmple Consensus (RANSAC) algorithm for
estimating the parameters of a mathematical model
Expand All @@ -25,9 +25,19 @@ source-repository head

library
exposed-modules: Numeric.Ransac
build-depends: base >= 4.6 && < 5,
build-depends: base >= 4.5 && < 5,
vector >= 0.10,
random >= 1.0
hs-source-dirs: src
default-language: Haskell2010
ghc-options: -Wall
ghc-options: -Wall

test-suite tests
type: exitcode-stdio-1.0
hs-source-dirs: tests
main-is: SmokeTest.hs
ghc-options: -Wall
default-language: Haskell2010
build-depends: base >= 4.5 && < 5,
test-framework, test-framework-hunit, HUnit,
linear, vector, lens, RANSAC
47 changes: 47 additions & 0 deletions tests/SmokeTest.hs
@@ -0,0 +1,47 @@
-- |Basic linear fit unit test. There is no noise in the data set, so
-- it is very unlikely that the correct model will not be found.
module Main where
import Control.Applicative
import Control.Lens (view)
import qualified Data.Foldable as F
import Data.Vector.Storable (Vector)
import qualified Data.Vector.Storable as V
import Linear
import Test.Framework (defaultMain)
import Test.Framework.Providers.HUnit (hUnitTestToTests)
import Test.HUnit (Test, (~?))
import Numeric.Ransac

type Point = V2 Float

sq :: Float -> Float
sq x = x * x

-- | Fit a 2D line to a collection of 'Point's.
fitLine :: Vector Point -> Maybe (V2 Float)
fitLine pts = (!* b) <$> inv22 a
where sx = V.sum $ V.map (view _x) pts
a = V2 (V2 (V.sum (V.map (sq . view _x) pts)) sx)
(V2 sx (fromIntegral (V.length pts)))
b = V2 (V.sum (V.map F.product pts))
(V.sum (V.map (view _y) pts))

-- | Compute the error of a 'Point' with respect to a hypothesized
-- linear model.
ptError :: V2 Float -> Point -> Float
ptError (V2 m b) (V2 x y) = sq $ y - (m*x+b)

test1 :: Test
test1 = tst ~? "noise-free linear fit"
where model = ransac 20 2 0.8 fitLine ptError (< 0.1) pts
pts :: Vector Point
pts = V.generate 100 mkPoint
mkPoint i = let x = fromIntegral i * 0.1
in V2 x (3 * x + 1)
tst = do mm <- model
return $ case mm of
Nothing -> False
Just (m,_) -> qd (V2 3 1) m < 0.1

main :: IO ()
main = defaultMain $ hUnitTestToTests test1

0 comments on commit c0a7e38

Please sign in to comment.