Skip to content

Commit

Permalink
add PBTs for arithmetic operators
Browse files Browse the repository at this point in the history
 - commutativity of addition
 - commutativity of multiplication
  • Loading branch information
nerdypepper committed Oct 14, 2020
1 parent 8b08ea9 commit 82a64ef
Show file tree
Hide file tree
Showing 4 changed files with 27 additions and 24 deletions.
6 changes: 3 additions & 3 deletions lisk.cabal
Expand Up @@ -18,11 +18,11 @@ extra-source-files: CHANGELOG.md

library
default-language: Haskell2010
hs-source-dirs: src
build-depends:
base == 4.*,
parsec == 3.*,
mtl >= 2.1
hs-source-dirs: src
exposed-modules:
Parser,
Evaluator,
Expand All @@ -33,22 +33,22 @@ library
executable lisk
default-language: Haskell2010
main-is: Main.hs
hs-source-dirs: bin
build-depends:
base == 4.*,
parsec == 3.*,
readline >= 1.0,
mtl >= 2.1,
lisk
hs-source-dirs: bin

test-suite properties
default-language: Haskell2010
type: exitcode-stdio-1.0
main-is: Main.hs
hs-source-dirs: tests
other-modules: Properties
build-depends:
base == 4.*,
parsec == 3.*,
QuickCheck >= 2.1 && < 3,
lisk
other-modules: Properties
3 changes: 0 additions & 3 deletions src/Error/Base.hs
Expand Up @@ -5,12 +5,9 @@ module Error.Base (
) where

import Control.Monad.Except
import Data.List (intercalate, nub)
import Parser
import Text.Parsec
import Text.Parsec.Error
import Text.Parsec.Pos
import Text.Parsec.String (Parser)
import Text.ParserCombinators.Parsec

data LispError = Parse ParseError
Expand Down
4 changes: 2 additions & 2 deletions tests/Main.hs
@@ -1,6 +1,6 @@
module Main where

import Properties
import Properties (runTests)
import Test.QuickCheck

main = tests
main = runTests
38 changes: 22 additions & 16 deletions tests/Properties.hs
@@ -1,25 +1,31 @@
{-# LANGUAGE TemplateHaskell #-}
module Properties where
module Properties (
runTests
) where

import Data.Maybe (fromJust)
import Error.Base (unwrap)
import Evaluator (eval)
import Operators (primitives)
import Parser (Expr (..), parseLispValue, parseQuote)

import Test.QuickCheck

-- some tests would go here hopefully
addition = fromJust $ lookup "+" primitives
multiplication = fromJust $ lookup "*" primitives

-- a filler test to test the test suite :^)
qsort :: (Ord a) => [a] -> [a]
qsort [] = []
qsort [x] = [x]
qsort (x:xs) = qsort left ++ [x] ++ qsort right
where left = filter (<= x) xs
right = filter (> x) xs
prop_commutativeAdd :: [Integer] -> Property
prop_commutativeAdd xs =
not (null xs) ==> rhs == lhs
where rhs = (unwrap . addition) exprs
lhs = (unwrap . addition . reverse) exprs
exprs = map IntLiteral xs

checkList :: (Ord a) => [a] -> Bool
checkList = ordered . qsort
where ordered [] = True
ordered [x] = True
ordered (x:y:xs) = x <= y && ordered (y:xs)
prop_commutativeMul :: [Integer] -> Property
prop_commutativeMul xs =
not (null xs) ==> rhs == lhs
where rhs = (unwrap . multiplication) exprs
lhs = (unwrap . multiplication . reverse) exprs
exprs = map IntLiteral xs

return []
tests = $quickCheckAll
runTests = $quickCheckAll

0 comments on commit 82a64ef

Please sign in to comment.