Skip to content

Commit

Permalink
Add cabal test support.
Browse files Browse the repository at this point in the history
  • Loading branch information
bos committed Nov 21, 2011
1 parent 8e4cf6d commit 90e0f74
Show file tree
Hide file tree
Showing 3 changed files with 19 additions and 25 deletions.
19 changes: 18 additions & 1 deletion attoparsec.cabal
Expand Up @@ -8,7 +8,7 @@ maintainer: Bryan O'Sullivan <bos@serpentine.com>
stability: experimental
tested-with: GHC == 6.10.4, GHC == 6.12.3, GHC == 7.0.3
synopsis: Fast combinator parsing for bytestrings
cabal-version: >= 1.6
cabal-version: >= 1.8
homepage: https://github.com/bos/attoparsec
bug-reports: https://github.com/bos/attoparsec/issues
build-type: Simple
Expand Down Expand Up @@ -56,6 +56,23 @@ library
if flag(developer)
ghc-prof-options: -auto-all

test-suite tests
type: exitcode-stdio-1.0
hs-source-dirs: tests
main-is: QC.hs

ghc-options:
-Wall -threaded -rtsopts

build-depends:
attoparsec,
base >= 4 && < 5,
bytestring,
QuickCheck >= 2.4,
test-framework >= 0.4,
test-framework-quickcheck2 >= 0.2,
text

source-repository head
type: git
location: https://github.com/bos/attoparsec
Expand Down
12 changes: 1 addition & 11 deletions tests/QC.hs
@@ -1,17 +1,13 @@
{-# LANGUAGE OverloadedStrings #-}
module Main (main) where

import Control.Monad (forM_)
import Data.Maybe (isJust)
import Data.Word (Word8)
import Prelude hiding (takeWhile)
import QCSupport
import Test.Framework (defaultMain, testGroup)
import Test.Framework.Providers.QuickCheck2 (testProperty)
import Test.QuickCheck hiding (NonEmpty)
import qualified Data.Attoparsec as P
import qualified Data.ByteString as B
import qualified Data.ByteString.Char8 as C

-- Make sure that structures whose types claim they are non-empty
-- really are.
Expand Down Expand Up @@ -81,11 +77,6 @@ takeTill w s =
P.Done t' h' -> t == t' && h == h'
_ -> False

ensure n s = case defP (P.ensure m) s of
P.Done _ () -> B.length s >= m
_ -> B.length s < m
where m = (n `mod` 220) - 20

takeWhile1_empty = maybeP (P.takeWhile1 undefined) B.empty == Nothing

endOfInput s = maybeP P.endOfInput s == if B.null s
Expand All @@ -109,8 +100,7 @@ tests = [
testProperty "takeWhile1" takeWhile1,
testProperty "takeWhile1_empty" takeWhile1_empty,
testProperty "takeTill" takeTill,
testProperty "endOfInput" endOfInput,
testProperty "ensure" ensure
testProperty "endOfInput" endOfInput
]

]
13 changes: 0 additions & 13 deletions tests/QCSupport.hs
Expand Up @@ -7,16 +7,10 @@ module QCSupport
import Control.Applicative
import Data.Attoparsec
import Data.Word (Word8)
import System.Random (RandomGen, Random(..))
import Test.QuickCheck hiding (NonEmpty)
import qualified Data.ByteString as S
import qualified Data.ByteString.Lazy as L

integralRandomR :: (Integral a, RandomGen g) => (a,a) -> g -> (a,g)
integralRandomR (a,b) g = case randomR (fromIntegral a :: Integer,
fromIntegral b :: Integer) g of
(x,g') -> (fromIntegral x, g')

newtype NonEmpty a = NonEmpty { nonEmpty :: a }
deriving (Eq, Ord, Read, Show)

Expand All @@ -43,10 +37,3 @@ instance Arbitrary L.ByteString where
instance Arbitrary (NonEmpty L.ByteString) where
arbitrary = sized $ \n -> resize (round (sqrt (toEnum n :: Double)))
(fmap (L.fromChunks . map nonEmpty) <$> arbitrary)

instance Random Word8 where
randomR = integralRandomR
random = randomR (minBound,maxBound)

instance Arbitrary Word8 where
arbitrary = choose (minBound, maxBound)

0 comments on commit 90e0f74

Please sign in to comment.