File: QuickCheck.hs

package info (click to toggle)
haskell-trifecta 2.1.4-1
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid, trixie
  • size: 256 kB
  • sloc: haskell: 1,793; makefile: 3
file content (76 lines) | stat: -rw-r--r-- 1,970 bytes parent folder | download | duplicates (2)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
{-# LANGUAGE OverloadedStrings #-}

module Main
( main
) where

import Control.Applicative

import Data.Either

import qualified Test.QuickCheck as Q

import Text.Parser.Char
import Text.Parser.Combinators

import Text.Trifecta.Parser
import Text.Trifecta.Result

import System.Exit

-- -------------------------------------------------------------------------- --
-- Main

main :: IO ()
main = mapM Q.quickCheckResult tests >>= \x -> case filter (not . passed) x of
    [] -> exitSuccess
    _ -> exitFailure
  where
    passed Q.Success{} = True
    passed _ = False

-- -------------------------------------------------------------------------- --
-- Tests

tests :: [Q.Property]
tests =
    [ Q.property prop_fail
    , Q.property prop_succeed
    , Q.property prop_notFollowedBy0
    , Q.property prop_notFollowedBy1
    , Q.property prop_notFollowedBy2
    , Q.property prop_notFollowedBy3
    ]

-- -------------------------------------------------------------------------- --
-- Properties

prop_fail :: String -> Bool
prop_fail = isLeft . parse (fail "fail" :: Parser ())

prop_succeed :: String -> Bool
prop_succeed = isRight . parse (mempty :: Parser ())

prop_notFollowedBy0 :: Char -> Char -> Bool
prop_notFollowedBy0 x y = either (\_ -> x == y) (/= y)
    $ parse (notFollowedBy (char y) *> anyChar) [x]

prop_notFollowedBy1 :: Char -> Bool
prop_notFollowedBy1 x = either (\_ -> x == x) (/= x)
    $ parse (notFollowedBy (char x) *> anyChar) [x]

prop_notFollowedBy2 :: String -> Char -> Bool
prop_notFollowedBy2 x y = isLeft
    $ parse (anyChar *> notFollowedBy (char y) *> char y) x

prop_notFollowedBy3 :: Char -> Bool
prop_notFollowedBy3 x = isRight
    $ parse (notFollowedBy (char x) <|> char x *> pure ()) [x]

-- -------------------------------------------------------------------------- --
-- Utils

parse :: Parser a -> String -> Either String a
parse p s = case parseString p mempty s of
    Failure e -> Left (show e)
    Success a -> Right a