module Main where import Calculator.Evaluator (eval) import Calculator.Primitives (Number) import Model.Arithmetic import Data.Function (on) import Control.Monad import Control.Applicative ((<$>)) import System.Exit (exitSuccess, exitFailure) import Test.QuickCheck newtype ExprString = ExprString { unwrapExprString :: String } instance Show ExprString where show (ExprString s) = s instance Arbitrary ExprString where arbitrary = ExprString <$> genExprString operators :: [Char] operators = "+-*/^" genOp :: Gen Char genOp = elements operators genArg :: Gen String genArg = show . abs <$> (arbitrary :: Gen Number) genExprString :: Gen String genExprString = liftM concat . liftM2 (:) genArg . listOf $ liftM2 (:) genOp genArg -- Converts to string so that NaN == NaN evaluates to true equal :: Either a Number -> Either a Number -> Bool equal (Right x) (Right y) = on (==) show x y equal (Left _) (Left _) = True equal _ _ = False prop_model :: ExprString -> Bool prop_model xs = (calcResult `equal` modelResult) where expr = unwrapExprString xs calcResult = eval expr modelResult = modelEval expr main :: IO () main = do status <- quickCheckWithResult stdArgs { maxSuccess = 2500 } prop_model case status of (Success _ _ _) -> exitSuccess _ -> exitFailure