module Main where -------------------------------------------------------------------------------- import Calculator.Evaluator.Base (evalTest) import Model.Arithmetic -------------------------------------------------------------------------------- import Control.Applicative ((<$>)) import Control.Monad import System.Exit (exitFailure, exitSuccess) import Test.QuickCheck -------------------------------------------------------------------------------- newtype ExprString = ExprString { unwrapExprString :: String } instance Show ExprString where show (ExprString s) = s instance Arbitrary ExprString where arbitrary = ExprString <$> genExprString -------------------------------------------------------------------------------- operators :: String operators = "+-*/^" genOp :: Gen Char genOp = elements operators genArg :: Gen String genArg = show . abs <$> (arbitrary :: Gen Double) genExprString :: Gen String genExprString = liftM concat . liftM2 (:) (listOf (elements " ")) . liftM2 (:) genArg . liftM2 (:) (listOf (elements " ")) . listOf . liftM2 (:) genOp . liftM2 (++) (listOf (elements " ")) $ genArg -------------------------------------------------------------------------------- prop_model :: ExprString -> Bool prop_model xs = calcResult == modelResult where expr = unwrapExprString xs calcResult = evalTest expr modelResult = modelEval expr -------------------------------------------------------------------------------- main :: IO () main = do status <- quickCheckWithResult stdArgs { maxSuccess = 2500 } prop_model case status of Success{} -> exitSuccess _ -> exitFailure --------------------------------------------------------------------------------