| Safe Haskell | None | 
|---|---|
| Language | Haskell98 | 
Hedgehog.Gen
Contents
Synopsis
- shrink :: MonadGen m => (a -> [a]) -> m a -> m a
- prune :: MonadGen m => m a -> m a
- small :: MonadGen m => m a -> m a
- scale :: MonadGen m => (Size -> Size) -> m a -> m a
- resize :: MonadGen m => Size -> m a -> m a
- sized :: MonadGen m => (Size -> m a) -> m a
- integral :: (MonadGen m, Integral a) => Range a -> m a
- integral_ :: (MonadGen m, Integral a) => Range a -> m a
- int :: MonadGen m => Range Int -> m Int
- int8 :: MonadGen m => Range Int8 -> m Int8
- int16 :: MonadGen m => Range Int16 -> m Int16
- int32 :: MonadGen m => Range Int32 -> m Int32
- int64 :: MonadGen m => Range Int64 -> m Int64
- word :: MonadGen m => Range Word -> m Word
- word8 :: MonadGen m => Range Word8 -> m Word8
- word16 :: MonadGen m => Range Word16 -> m Word16
- word32 :: MonadGen m => Range Word32 -> m Word32
- word64 :: MonadGen m => Range Word64 -> m Word64
- realFloat :: (MonadGen m, RealFloat a) => Range a -> m a
- realFrac_ :: (MonadGen m, RealFrac a) => Range a -> m a
- float :: MonadGen m => Range Float -> m Float
- double :: MonadGen m => Range Double -> m Double
- enum :: (MonadGen m, Enum a) => a -> a -> m a
- enumBounded :: (MonadGen m, Enum a, Bounded a) => m a
- bool :: MonadGen m => m Bool
- bool_ :: MonadGen m => m Bool
- binit :: MonadGen m => m Char
- octit :: MonadGen m => m Char
- digit :: MonadGen m => m Char
- hexit :: MonadGen m => m Char
- lower :: MonadGen m => m Char
- upper :: MonadGen m => m Char
- alpha :: MonadGen m => m Char
- alphaNum :: MonadGen m => m Char
- ascii :: MonadGen m => m Char
- latin1 :: MonadGen m => m Char
- unicode :: MonadGen m => m Char
- unicodeAll :: MonadGen m => m Char
- string :: MonadGen m => Range Int -> m Char -> m String
- text :: MonadGen m => Range Int -> m Char -> m Text
- utf8 :: MonadGen m => Range Int -> m Char -> m ByteString
- bytes :: MonadGen m => Range Int -> m ByteString
- constant :: MonadGen m => a -> m a
- element :: MonadGen m => [a] -> m a
- choice :: MonadGen m => [m a] -> m a
- frequency :: MonadGen m => [(Int, m a)] -> m a
- recursive :: MonadGen m => ([m a] -> m a) -> [m a] -> [m a] -> m a
- discard :: MonadGen m => m a
- filter :: (MonadGen m, GenBase m ~ Identity) => (a -> Bool) -> m a -> m a
- mapMaybe :: (MonadGen m, GenBase m ~ Identity) => (a -> Maybe b) -> m a -> m b
- just :: (MonadGen m, GenBase m ~ Identity) => m (Maybe a) -> m a
- maybe :: MonadGen m => m a -> m (Maybe a)
- list :: MonadGen m => Range Int -> m a -> m [a]
- seq :: MonadGen m => Range Int -> m a -> m (Seq a)
- nonEmpty :: MonadGen m => Range Int -> m a -> m (NonEmpty a)
- set :: (MonadGen m, Ord a) => Range Int -> m a -> m (Set a)
- map :: (MonadGen m, Ord k) => Range Int -> m (k, v) -> m (Map k v)
- freeze :: MonadGen m => m a -> m (a, m a)
- subterm :: MonadGen m => m a -> (a -> a) -> m a
- subtermM :: MonadGen m => m a -> (a -> m a) -> m a
- subterm2 :: MonadGen m => m a -> m a -> (a -> a -> a) -> m a
- subtermM2 :: MonadGen m => m a -> m a -> (a -> a -> m a) -> m a
- subterm3 :: MonadGen m => m a -> m a -> m a -> (a -> a -> a -> a) -> m a
- subtermM3 :: MonadGen m => m a -> m a -> m a -> (a -> a -> a -> m a) -> m a
- subsequence :: MonadGen m => [a] -> m [a]
- shuffle :: MonadGen m => [a] -> m [a]
- sequential :: (MonadGen gen, MonadTest m) => Range Int -> (forall v. state v) -> [Command gen m state] -> gen (Sequential m state)
- parallel :: (MonadGen gen, MonadTest m) => Range Int -> Range Int -> (forall v. state v) -> [Command gen m state] -> gen (Parallel m state)
- sample :: MonadIO m => Gen a -> m a
- print :: (MonadIO m, Show a) => Gen a -> m ()
- printTree :: (MonadIO m, Show a) => Gen a -> m ()
- printWith :: (MonadIO m, Show a) => Size -> Seed -> Gen a -> m ()
- printTreeWith :: (MonadIO m, Show a) => Size -> Seed -> Gen a -> m ()
Shrinking
shrink :: MonadGen m => (a -> [a]) -> m a -> m a Source #
Apply a shrinking function to a generator.
This will give the generator additional shrinking options, while keeping the existing shrinks intact.
Size
scale :: MonadGen m => (Size -> Size) -> m a -> m a Source #
Adjust the size parameter by transforming it with the given function.
resize :: MonadGen m => Size -> m a -> m a Source #
Override the size parameter. Returns a generator which uses the given size instead of the runtime-size parameter.
sized :: MonadGen m => (Size -> m a) -> m a Source #
Construct a generator that depends on the size parameter.
Integral
integral :: (MonadGen m, Integral a) => Range a -> m a Source #
Generates a random integral number in the given [inclusive,inclusive] range.
When the generator tries to shrink, it will shrink towards the
   origin of the specified Range.
For example, the following generator will produce a number between 1970
   and 2100, but will shrink towards 2000:
integral (Range.constantFrom2000 1970 2100) ::GenInt
Some sample outputs from this generator might look like:
=== Outcome === 1973 === Shrinks === 2000 1987 1980 1976 1974
=== Outcome === 2061 === Shrinks === 2000 2031 2046 2054 2058 2060
integral_ :: (MonadGen m, Integral a) => Range a -> m a Source #
Generates a random integral number in the [inclusive,inclusive] range.
This generator does not shrink.
int :: MonadGen m => Range Int -> m Int Source #
Generates a random machine integer in the given [inclusive,inclusive] range.
This is a specialization of integral, offered for convenience.
int8 :: MonadGen m => Range Int8 -> m Int8 Source #
Generates a random 8-bit integer in the given [inclusive,inclusive] range.
This is a specialization of integral, offered for convenience.
int16 :: MonadGen m => Range Int16 -> m Int16 Source #
Generates a random 16-bit integer in the given [inclusive,inclusive] range.
This is a specialization of integral, offered for convenience.
int32 :: MonadGen m => Range Int32 -> m Int32 Source #
Generates a random 32-bit integer in the given [inclusive,inclusive] range.
This is a specialization of integral, offered for convenience.
int64 :: MonadGen m => Range Int64 -> m Int64 Source #
Generates a random 64-bit integer in the given [inclusive,inclusive] range.
This is a specialization of integral, offered for convenience.
word :: MonadGen m => Range Word -> m Word Source #
Generates a random machine word in the given [inclusive,inclusive] range.
This is a specialization of integral, offered for convenience.
word8 :: MonadGen m => Range Word8 -> m Word8 Source #
Generates a random byte in the given [inclusive,inclusive] range.
This is a specialization of integral, offered for convenience.
word16 :: MonadGen m => Range Word16 -> m Word16 Source #
Generates a random 16-bit word in the given [inclusive,inclusive] range.
This is a specialization of integral, offered for convenience.
word32 :: MonadGen m => Range Word32 -> m Word32 Source #
Generates a random 32-bit word in the given [inclusive,inclusive] range.
This is a specialization of integral, offered for convenience.
word64 :: MonadGen m => Range Word64 -> m Word64 Source #
Generates a random 64-bit word in the given [inclusive,inclusive] range.
This is a specialization of integral, offered for convenience.
Floating-point
realFloat :: (MonadGen m, RealFloat a) => Range a -> m a Source #
Generates a random floating-point number in the [inclusive,exclusive) range.
This generator works the same as integral, but for floating point numbers.
realFrac_ :: (MonadGen m, RealFrac a) => Range a -> m a Source #
Generates a random fractional number in the [inclusive,exclusive) range.
This generator does not shrink.
float :: MonadGen m => Range Float -> m Float Source #
Generates a random floating-point number in the [inclusive,exclusive) range.
This is a specialization of realFloat, offered for convenience.
double :: MonadGen m => Range Double -> m Double Source #
Generates a random floating-point number in the [inclusive,exclusive) range.
This is a specialization of realFloat, offered for convenience.
Enumeration
bool :: MonadGen m => m Bool Source #
Generates a random boolean.
This generator shrinks to False.
This is a specialization of enumBounded, offered for convenience.
Characters
alphaNum :: MonadGen m => m Char Source #
Generates an ASCII letter or digit: 'a'..'z', 'A'..'Z', '0'..'9'
unicode :: MonadGen m => m Char Source #
Generates a Unicode character, excluding noncharacters and invalid standalone surrogates:
   '\0'..'\1114111' (excluding '\55296'..'\57343', '\65534', '\65535')
unicodeAll :: MonadGen m => m Char Source #
Generates a Unicode character, including noncharacters and invalid standalone surrogates:
   '\0'..'\1114111'
Strings
text :: MonadGen m => Range Int -> m Char -> m Text Source #
Generates a string using Range to determine the length.
utf8 :: MonadGen m => Range Int -> m Char -> m ByteString Source #
Generates a UTF-8 encoded string, using Range to determine the length.
bytes :: MonadGen m => Range Int -> m ByteString Source #
Generates a random ByteString, using Range to determine the
   length.
Choice
element :: MonadGen m => [a] -> m a Source #
Randomly selects one of the elements in the list.
This generator shrinks towards the first element in the list.
The input list must be non-empty.
choice :: MonadGen m => [m a] -> m a Source #
Randomly selects one of the generators in the list.
This generator shrinks towards the first generator in the list.
The input list must be non-empty.
frequency :: MonadGen m => [(Int, m a)] -> m a Source #
Uses a weighted distribution to randomly select one of the generators in the list.
This generator shrinks towards the first generator in the list.
The input list must be non-empty.
recursive :: MonadGen m => ([m a] -> m a) -> [m a] -> [m a] -> m a Source #
Modifies combinators which choose from a list of generators, like choice
   or frequency, so that they can be used in recursive scenarios.
This combinator modifies its target to select one of the generators in
   either the non-recursive or the recursive list. When a selection is made
   from the recursive list, the Size is halved. When the Size gets to one
   or less, selections are no longer made from the recursive list, this
   ensures termination.
A good example of where this might be useful is abstract syntax trees:
data Expr =
    Var String
  | Lam String Expr
  | App Expr Expr
-- Assuming we have a name generator
genName :: MonadGen m => m String
-- We can write a generator for expressions
genExpr :: MonadGen m => m Expr
genExpr =
  Gen.recursive Gen.choice [
      -- non-recursive generators
      Var <$> genName
    ] [
      -- recursive generators
      Gen.subtermM genExpr (x -> Lam <$> genName <*> pure x)
    , Gen.subterm2 genExpr genExpr App
    ]
If we wrote the above example using only choice, it is likely that it
   would fail to terminate. This is because for every call to genExpr,
   there is a 2 in 3 chance that we will recurse again.
Conditional
filter :: (MonadGen m, GenBase m ~ Identity) => (a -> Bool) -> m a -> m a Source #
Generates a value that satisfies a predicate.
This is essentially:
filter p gen =mfilterp gen<|>filter p gen
It differs from the above in that we keep some state to avoid looping forever. If we trigger these limits then the whole generator is discarded.
Collections
list :: MonadGen m => Range Int -> m a -> m [a] Source #
Generates a list using a Range to determine the length.
seq :: MonadGen m => Range Int -> m a -> m (Seq a) Source #
Generates a seq using a Range to determine the length.
nonEmpty :: MonadGen m => Range Int -> m a -> m (NonEmpty a) Source #
Generates a non-empty list using a Range to determine the length.
set :: (MonadGen m, Ord a) => Range Int -> m a -> m (Set a) Source #
Generates a set using a Range to determine the length.
This may fail to generate anything if the element generator cannot produce a large enough number of unique items to satify the required set size.
map :: (MonadGen m, Ord k) => Range Int -> m (k, v) -> m (Map k v) Source #
Generates a map using a Range to determine the length.
This may fail to generate anything if the keys produced by the generator do not account for a large enough number of unique items to satify the required map size.
Subterms
freeze :: MonadGen m => m a -> m (a, m a) Source #
Freeze the size and seed used by a generator, so we can inspect the value which it will produce.
This is used for implementing list and subtermMVec. It allows us to
   shrink the list itself before trying to shrink the values inside the list.
subterm :: MonadGen m => m a -> (a -> a) -> m a Source #
Constructs a generator from a sub-term generator.
Shrinks to the sub-term if possible.
subtermM :: MonadGen m => m a -> (a -> m a) -> m a Source #
Constructs a generator from a sub-term generator.
Shrinks to the sub-term if possible.
subterm2 :: MonadGen m => m a -> m a -> (a -> a -> a) -> m a Source #
Constructs a generator from two sub-term generators.
Shrinks to one of the sub-terms if possible.
subtermM2 :: MonadGen m => m a -> m a -> (a -> a -> m a) -> m a Source #
Constructs a generator from two sub-term generators.
Shrinks to one of the sub-terms if possible.
subterm3 :: MonadGen m => m a -> m a -> m a -> (a -> a -> a -> a) -> m a Source #
Constructs a generator from three sub-term generators.
Shrinks to one of the sub-terms if possible.
subtermM3 :: MonadGen m => m a -> m a -> m a -> (a -> a -> a -> m a) -> m a Source #
Constructs a generator from three sub-term generators.
Shrinks to one of the sub-terms if possible.
Combinations & Permutations
subsequence :: MonadGen m => [a] -> m [a] Source #
Generates a random subsequence of a list.
shuffle :: MonadGen m => [a] -> m [a] Source #
Generates a random permutation of a list.
This shrinks towards the order of the list being identical to the input list.
Abstract State Machine
sequential :: (MonadGen gen, MonadTest m) => Range Int -> (forall v. state v) -> [Command gen m state] -> gen (Sequential m state) Source #
Generates a sequence of actions from an initial model state and set of commands.
parallel :: (MonadGen gen, MonadTest m) => Range Int -> Range Int -> (forall v. state v) -> [Command gen m state] -> gen (Parallel m state) Source #
Given the initial model state and set of commands, generates prefix actions to be run sequentially, followed by two branches to be run in parallel.
Sampling Generators
print :: (MonadIO m, Show a) => Gen a -> m () Source #
Run a generator with a random seed and print the outcome, and the first level of shrinks.
Gen.print (Gen.enum 'a' 'f')
=== Outcome === 'd' === Shrinks === 'a' 'b' 'c'
printTree :: (MonadIO m, Show a) => Gen a -> m () Source #
Run a generator with a random seed and print the resulting shrink tree.
Gen.printTree (Gen.enum 'a' 'f')
'd'
 ├╼'a'
 ├╼'b'
 │  └╼'a'
 └╼'c'
    ├╼'a'
    └╼'b'
       └╼'a'This may not terminate when the tree is very large.