-
-
Save vertexcite/d714910c2533d546768f to your computer and use it in GitHub Desktop.
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Using cabal to install quickcheck: | |
Make a directory to work in. | |
Inside the directory: “cabal sandbox init” | |
Then: “cabal install quickcheck” | |
You can open the GHCI repl in the sandbox: | |
"cabal repl" | |
And use normal commands like ":load filename.hs" | |
To install hspec: | |
cabal install hspec | |
To install tasty: | |
cabal install tasty | |
cabal install tasty-quickcheck | |
cabal install tasty-hunit |
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
{-# LANGUAGE InstanceSigs #-} | |
import Test.QuickCheck | |
-- you can run any of the 'sample' functions in GHCi | |
-- to print a list of examples | |
data Height = Height Int deriving (Show, Eq) | |
instance Arbitrary Height where | |
arbitrary :: Gen Height | |
arbitrary = do | |
height <- choose (100, 250) | |
return (Height height) | |
sampleHeights :: IO [Height] | |
sampleHeights = sample' arbitrary | |
data Color = R | G | B deriving (Eq, Show) | |
instance Arbitrary Color where | |
arbitrary = do | |
color <- frequency | |
[(1, return R), | |
(1, return G), | |
(2, return B)] | |
return color | |
sampleColors :: IO [Color] | |
sampleColors = sample' arbitrary | |
data Point = Point Int Int deriving (Eq, Show) | |
instance Arbitrary Point where | |
arbitrary = do | |
x <- arbitrary | |
y <- arbitrary | |
return (Point x y) | |
samplePoints :: IO [Point] | |
samplePoints = sample' arbitrary |
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
import Test.Hspec | |
import Test.QuickCheck | |
-- https://hspec.github.io/ | |
main = hspec $ do | |
describe "Tests" $ do | |
properties | |
unitTests | |
properties = describe "List properties" $ do | |
it "reverse . reverse == id" $ | |
property (\xs -> reverse (reverse xs) == (xs :: [Int])) | |
unitTests = describe "List tests" $ do | |
it "List with one element is not empty" $ do | |
not (null [1]) `shouldBe` True | |
it "List with no elements is empty" $ do | |
null [] `shouldBe` True |
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
import Test.QuickCheck | |
-- Operations on a queue: | |
class Queue q where | |
push :: a -> q a -> q a | |
pop :: q a -> q a | |
-- Implementation of a queue: | |
instance Queue [] where | |
push x xs = | |
-- bug! | |
if length xs == 12 | |
then (x:x:xs) | |
else (x:xs) | |
pop [] = [] | |
pop (x:xs) = xs | |
-- Our simplified model: | |
data QCount a = QCount { count :: Int } deriving Show | |
instance Queue QCount where | |
push _ (QCount n) = QCount (n+1) | |
pop (QCount 0) = QCount 0 | |
pop (QCount n) = QCount (n-1) | |
-- Actions on a queue: | |
data QueueAction a | |
= Push a | |
| Pop | |
deriving (Show, Eq) | |
-- And we can generate arbitrary actions: | |
instance Arbitrary a => Arbitrary (QueueAction a) where | |
arbitrary = do | |
value <- arbitrary | |
elements [Push value, Pop] | |
-- Apply an action to a queue: | |
act :: (Queue q) => QueueAction a -> q a -> q a | |
act (Push item) queue = push item queue | |
act (Pop) queue = pop queue | |
-- Apply a list of actions to the queue: | |
applyActions :: (Queue q) => q a -> [QueueAction a] -> q a | |
applyActions actions queue = foldr act actions queue | |
-- run "quickcheck checkAgainstModel" | |
checkAgainstModel :: [QueueAction Int] -> Property | |
checkAgainstModel actions = | |
length realQueue === count counterQueue | |
where | |
realQueue = applyActions [] actions | |
counterQueue = applyActions (QCount 0) actions |
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
module Types (Name, toName) where | |
import Test.QuickCheck | |
newtype Name = Name String deriving (Eq, Ord, Show) | |
toName "" = Nothing | |
toName s = Just (Name s) | |
instance Arbitrary Name where | |
arbitrary = do | |
s <- listOf1 arbitrary | |
case toName s of | |
Nothing -> arbitrary | |
Just name -> return name |
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
import Test.Tasty | |
import Test.Tasty.QuickCheck | |
import Test.Tasty.HUnit | |
-- http://documentup.com/feuerbach/tasty | |
main = defaultMain tests | |
tests = testGroup "Tests" [properties, unitTests] | |
properties = testGroup "Properties" [ | |
testProperty "reverse . reverse == id" $ | |
\xs -> reverse (reverse xs) == (xs :: [Int]) | |
] | |
unitTests = testGroup "UnitTests" [ | |
testCase "List with one element is not empty" $ | |
True @=? not (null [1]), | |
testCase "List with no elements is empty" $ | |
True @=? null [] | |
] |
Sign up for free
to join this conversation on GitHub.
Already have an account?
Sign in to comment