Skip to content

Commit

Permalink
Merge pull request #10 from jdegoes/ready/cleanup
Browse files Browse the repository at this point in the history
misc cleanup
  • Loading branch information
paf31 committed Oct 12, 2014
2 parents dcdf9ae + cac372c commit 7cefd32
Show file tree
Hide file tree
Showing 5 changed files with 80 additions and 16 deletions.
7 changes: 7 additions & 0 deletions README.md
Original file line number Diff line number Diff line change
Expand Up @@ -22,6 +22,9 @@
Success :: Result
Failed :: String -> Result

newtype Signum where
Signum :: Number -> Signum


### Type Classes

Expand Down Expand Up @@ -57,6 +60,8 @@

instance arbPositive :: Arbitrary Positive

instance arbSignum :: Arbitrary Signum

instance arbString :: Arbitrary String

instance arbTuple :: (Arbitrary a, Arbitrary b) => Arbitrary (Tuple a b)
Expand All @@ -81,6 +86,8 @@

instance coarbPositive :: CoArbitrary Positive

instance coarbSignum :: CoArbitrary Signum

instance coarbString :: CoArbitrary String

instance coarbTuple :: (CoArbitrary a, CoArbitrary b) => CoArbitrary (Tuple a b)
Expand Down
25 changes: 13 additions & 12 deletions bower.json
Original file line number Diff line number Diff line change
Expand Up @@ -18,17 +18,18 @@
"package.json"
],
"dependencies": {
"purescript-random": "*",
"purescript-exceptions": "*",
"purescript-transformers": "*",
"purescript-free": "0.1.3",
"purescript-machines": "0.1.5",
"purescript-arrays": "*",
"purescript-strings": "*",
"purescript-math": "*",
"purescript-tuples": "*",
"purescript-either": "*",
"purescript-maybe": "*",
"purescript-foldable-traversable": "*"
"purescript-random": "~0.1.1",
"purescript-enums": "~0.2.0",
"purescript-exceptions": "~0.2.1",
"purescript-transformers": "~0.2.1",
"purescript-free": "~0.1.3",
"purescript-machines": "~0.1.5",
"purescript-arrays": "~0.2.1",
"purescript-strings": "~0.2.1",
"purescript-math": "~0.1.0",
"purescript-tuples": "~0.2.1",
"purescript-either": "~0.1.3",
"purescript-maybe": "~0.2.1",
"purescript-foldable-traversable": "~0.1.3"
}
}
34 changes: 31 additions & 3 deletions src/Test/QuickCheck.purs
Original file line number Diff line number Diff line change
Expand Up @@ -7,14 +7,23 @@ module Test.QuickCheck
, NonZero(..)
, Positive(..)
, QC(..)
, arbitrary
, coarbitrary
, quickCheck
, quickCheck'
, quickCheckPure
, Result(..)
, runAlphaNumString
, runNegative
, runNonZero
, runPositive
, runSignum
, Signum(..)
, smallCheck
, smallCheckPure
, statCheck
, statCheckPure
, test
, Testable
) where

Expand Down Expand Up @@ -53,6 +62,8 @@ newtype Negative = Negative Number

newtype NonZero = NonZero Number

newtype Signum = Signum Number

type QC a = forall eff. Eff (trace :: Trace, random :: Random, err :: Exception | eff) a

data Result = Success | Failed String
Expand Down Expand Up @@ -127,8 +138,18 @@ countSuccesses = countSuccesses' 0
countSuccesses' acc (Success : rest) = countSuccesses' (acc + 1) rest
countSuccesses' acc (_ : rest) = countSuccesses' acc rest

foreign import maxNumber "var maxNumber = Number.MAX_VALUE;" :: Number
foreign import minNumber "var minNumber = Number.MIN_VALUE;" :: Number
maxNumber :: Number
maxNumber = 9007199254740992

runAlphaNumString (AlphaNumString s) = s

runSignum (Signum n) = n

runPositive (Positive n) = n

runNegative (Negative n) = n

runNonZero (NonZero n) = n

instance showResult :: Show Result where
show Success = "Success"
Expand Down Expand Up @@ -156,7 +177,7 @@ instance coarbPositive :: CoArbitrary Positive where
coarbitrary (Positive n) = coarbitrary n

instance arbNegative :: Arbitrary Negative where
arbitrary = Negative <$> ((*) minNumber) <$> uniform
arbitrary = Negative <$> ((*) (-maxNumber)) <$> uniform

instance coarbNegative :: CoArbitrary Negative where
coarbitrary (Negative n) = coarbitrary n
Expand All @@ -170,6 +191,13 @@ instance arbNonZero :: Arbitrary NonZero where
instance coarbNonZero :: CoArbitrary NonZero where
coarbitrary (NonZero n) = coarbitrary n

instance arbSignum :: Arbitrary Signum where
arbitrary = do b <- arbitrary
return $ Signum (if b then 1 else -1)

instance coarbSignum :: CoArbitrary Signum where
coarbitrary (Signum n) = coarbitrary n

instance arbBoolean :: Arbitrary Boolean where
arbitrary = do
n <- uniform
Expand Down
7 changes: 6 additions & 1 deletion src/Test/QuickCheck/LCG.purs
Original file line number Diff line number Diff line change
Expand Up @@ -19,6 +19,7 @@ module Test.QuickCheck.LCG
, foldGen'
, frequency
, infinite
, interleave
, oneOf
, perms
, perturbGen
Expand Down Expand Up @@ -249,6 +250,10 @@ extend n (GenT m) = GenT $ loop 0 m

in Mealy.stepMealy st m >>= f

-- | Fairly interleaves two generators.
interleave :: forall f a. (Monad f) => GenT f a -> GenT f a -> GenT f a
interleave (GenT g1) (GenT g2) = GenT $ Mealy.interleave g1 g2

-- | Ensures that a given generator can produce an infinite number of values,
-- | assuming it can produce at least one.
infinite :: forall f a. (Monad f) => GenT f a -> GenT f a
Expand Down Expand Up @@ -399,4 +404,4 @@ instance plusGenT :: (Monad f) => Plus (GenT f) where

instance alternativeGenT :: (Monad f) => Alternative (GenT f)

instance monadPlusGenT :: (Monad f) => MonadPlus (GenT f)
instance monadPlusGenT :: (Monad f) => MonadPlus (GenT f)
23 changes: 23 additions & 0 deletions src/Test/QuickCheck/README.md
Original file line number Diff line number Diff line change
Expand Up @@ -87,6 +87,8 @@

infinite :: forall f a. (Monad f) => GenT f a -> GenT f a

interleave :: forall f a. (Monad f) => GenT f a -> GenT f a -> GenT f a

oneOf :: forall f a. (Monad f) => GenT f a -> [GenT f a] -> GenT f a

perms :: forall f a. (Monad f) => [a] -> GenT f [a]
Expand Down Expand Up @@ -126,4 +128,25 @@
vectorOf :: forall f a. (Monad f) => Number -> GenT f a -> GenT f [a]


## Module Test.QuickCheck.Perturb

### Type Classes

class Perturb a where
perturb :: Number -> a -> Gen a
dist :: a -> a -> Number


### Type Class Instances

instance perturbArray :: (Perturb a) => Perturb [a]

instance perturbNumber :: Perturb Number

instance perturbTuple :: (Perturb a, Perturb b) => Perturb (Tuple a b)


### Values



0 comments on commit 7cefd32

Please sign in to comment.