{-# LANGUAGE TemplateHaskell, FlexibleInstances #-} module Main where import Data.Maybe import Data.Ratio import Math.ContinuedFraction import Math.ContinuedFraction.Interval import Test.QuickCheck import Test.QuickCheck.Function import Test.Framework.TH import Test.Framework.Providers.QuickCheck2 instance Arbitrary (Extended Rational) where arbitrary = do b <- arbitrary :: Gen Bool if b then return Infinity else do n <- choose (-10, 10) return $ Finite (n % 1) instance Arbitrary (Interval Rational) where arbitrary = do (i, s) <- suchThat arbitrary (\(i,s) -> i /= s) :: Gen (Extended Rational, Extended Rational) return $ Interval i s prop_sensiblePrimitiveBound x = fromInteger x `elementOf` primitiveBound x where types = x :: Integer prop_sensibleMergeInterval a b = a `subset` ab && b `subset` ab where types = (a :: Interval Rational, b :: Interval Rational) ab = a `mergeInterval` b finitePrimitiveBounds (CF cf) = zipWith boundHom homs (map primitiveBound cf) where homs = scanl homAbsorb (1,0,0,1) cf prop_primitiveBoundsContain a b = all ((Finite $ a + b) `elementOf`) $ finitePrimitiveBounds (valueToCF a + valueToCF b) where types = (a :: Rational, b :: Rational) prop_sensibleEuclidean i = case existsEmittable i of Just n -> i `subset` primitiveBound n Nothing -> True where types = i :: Interval Rational main :: IO () main = $defaultMainGenerator