Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Representation of (higher-order) functions.
Warning
This is an internal module: it is not subject to any versioning policy, breaking changes can happen at any time. It is made available only for debugging. Otherwise, use Test.Fun.
If something here seems useful, please open an issue to export it from an external module.
Synopsis
- type FunName = String
- type TypeName = String
- type ConName = String
- type ShowsPrec r = Int -> r -> String -> String
- data Concrete r = Concrete {
- shrinkC :: r -> [r]
- showsPrecC :: ShowsPrec r
- hardConcrete :: Show r => Concrete r
- data a :-> r where
- Const :: r -> a :-> r
- CoApply :: Concrete w -> w -> (w -> a) -> (b :-> ((a -> b) :-> r)) -> (a -> b) :-> r
- Apply :: FunName -> (a -> b) -> (b :-> r) -> a :-> r
- Case :: TypeName -> (a -> x) -> Branches x r -> r -> a :-> r
- CaseInteger :: TypeName -> (a -> Integer) -> Bin r -> r -> a :-> r
- Absurd :: (a -> Void) -> a :-> r
- ToShrink :: (a :-> r) -> a :-> r
- data Branches x r where
- data Fields x r where
- data Bin r
- coapply :: Concrete w -> w -> (w -> a) -> (b :-> ((a -> b) :-> r)) -> (a -> b) :-> r
- apply :: FunName -> (a -> b) -> (b :-> r) -> a :-> r
- case_ :: TypeName -> (a -> x) -> Branches x r -> r -> a :-> r
- caseInteger :: TypeName -> (a -> Integer) -> Bin r -> r -> a :-> r
- alt :: Branches x r -> Branches y r -> Branches (Either x y) r
- binAlt :: r -> Bin r -> Bin r -> Bin r
- applyFun :: (a :-> r) -> a -> r
- applyFun2 :: (a :-> (b :-> r)) -> a -> b -> r
- applyFun3 :: (a :-> (b :-> (c :-> r))) -> a -> b -> c -> r
- applyBranches :: r -> Branches x r -> x -> r
- applyFields :: Fields x r -> x -> r
- applyBin :: r -> Bin r -> Integer -> r
- applyBin' :: r -> Bin r -> Integer -> r
- clearFun :: (r -> r) -> a -> (a :-> r) -> a :-> r
- clearBranches :: forall x r. (r -> r) -> Branches x r -> x -> Maybe (Branches x r)
- clearFields :: (r -> r) -> Fields x r -> x -> Fields x r
- clearBin :: (r -> r) -> Bin r -> Integer -> Maybe (Bin r)
- clearBin' :: (r -> r) -> Integer -> Bin r -> Maybe (Bin r)
- truncateFun :: Int -> (r -> t) -> t -> (a :-> r) -> a :-> t
- truncateBin :: Int -> (r -> s) -> Bin r -> Bin s
Documentation
Dictionary with shrinker and printer.
Used as part of the representation of higher-order functions with (
.:->
)
Concrete | |
|
hardConcrete :: Show r => Concrete r Source #
Trivial shrinker and default printer.
data a :-> r where infixr 1 Source #
Testable representation of functions (a -> r)
.
This representation supports random generation, shrinking, and printing, for property testing with QuickCheck or Hedgehog.
Higher-order functions can be represented.
Const :: r -> a :-> r | Constant function, ignore the argument. |
CoApply :: Concrete w -> w -> (w -> a) -> (b :-> ((a -> b) :-> r)) -> (a -> b) :-> r | Apply the argument |
Apply :: FunName -> (a -> b) -> (b :-> r) -> a :-> r | Apply some function to the argument |
Case :: TypeName -> (a -> x) -> Branches x r -> r -> a :-> r | Pattern-match on the argument (in some ADT).
The branches may be incomplete, in which case a default value |
CaseInteger :: TypeName -> (a -> Integer) -> Bin r -> r -> a :-> r | Pattern-match on the argument (of some integral type). |
Absurd :: (a -> Void) -> a :-> r | There is no value for the argument, so we're done. |
ToShrink :: (a :-> r) -> a :-> r | Marker for truncating infinite representations. |
Instances
Functor ((:->) a) Source # | |
Foldable ((:->) a) Source # | |
Defined in Test.Fun.Internal.Types fold :: Monoid m => (a :-> m) -> m # foldMap :: Monoid m => (a0 -> m) -> (a :-> a0) -> m # foldr :: (a0 -> b -> b) -> b -> (a :-> a0) -> b # foldr' :: (a0 -> b -> b) -> b -> (a :-> a0) -> b # foldl :: (b -> a0 -> b) -> b -> (a :-> a0) -> b # foldl' :: (b -> a0 -> b) -> b -> (a :-> a0) -> b # foldr1 :: (a0 -> a0 -> a0) -> (a :-> a0) -> a0 # foldl1 :: (a0 -> a0 -> a0) -> (a :-> a0) -> a0 # toList :: (a :-> a0) -> [a0] # elem :: Eq a0 => a0 -> (a :-> a0) -> Bool # maximum :: Ord a0 => (a :-> a0) -> a0 # minimum :: Ord a0 => (a :-> a0) -> a0 # | |
Traversable ((:->) a) Source # | |
Show r => Show (a :-> r) Source # | Pretty-printed |
data Branches x r where Source #
Representation of the branches of a Case
.
Fail :: Branches x r | |
Alt :: !(Branches x r) -> !(Branches y r) -> Branches (Either x y) r | |
Pat :: ConName -> !(Fields x r) -> Branches x r |
Instances
Functor (Branches x) Source # | |
Foldable (Branches x) Source # | |
Defined in Test.Fun.Internal.Types fold :: Monoid m => Branches x m -> m # foldMap :: Monoid m => (a -> m) -> Branches x a -> m # foldr :: (a -> b -> b) -> b -> Branches x a -> b # foldr' :: (a -> b -> b) -> b -> Branches x a -> b # foldl :: (b -> a -> b) -> b -> Branches x a -> b # foldl' :: (b -> a -> b) -> b -> Branches x a -> b # foldr1 :: (a -> a -> a) -> Branches x a -> a # foldl1 :: (a -> a -> a) -> Branches x a -> a # toList :: Branches x a -> [a] # null :: Branches x a -> Bool # length :: Branches x a -> Int # elem :: Eq a => a -> Branches x a -> Bool # maximum :: Ord a => Branches x a -> a # minimum :: Ord a => Branches x a -> a # | |
Traversable (Branches x) Source # | |
Defined in Test.Fun.Internal.Types |
data Fields x r where Source #
Representation of one branch of a Case
.
Instances
Functor (Fields x) Source # | |
Foldable (Fields x) Source # | |
Defined in Test.Fun.Internal.Types fold :: Monoid m => Fields x m -> m # foldMap :: Monoid m => (a -> m) -> Fields x a -> m # foldr :: (a -> b -> b) -> b -> Fields x a -> b # foldr' :: (a -> b -> b) -> b -> Fields x a -> b # foldl :: (b -> a -> b) -> b -> Fields x a -> b # foldl' :: (b -> a -> b) -> b -> Fields x a -> b # foldr1 :: (a -> a -> a) -> Fields x a -> a # foldl1 :: (a -> a -> a) -> Fields x a -> a # elem :: Eq a => a -> Fields x a -> Bool # maximum :: Ord a => Fields x a -> a # minimum :: Ord a => Fields x a -> a # | |
Traversable (Fields x) Source # | |
Representation of branches of a CaseInteger
.
Instances
Functor Bin Source # | |
Foldable Bin Source # | |
Defined in Test.Fun.Internal.Types fold :: Monoid m => Bin m -> m # foldMap :: Monoid m => (a -> m) -> Bin a -> m # foldr :: (a -> b -> b) -> b -> Bin a -> b # foldr' :: (a -> b -> b) -> b -> Bin a -> b # foldl :: (b -> a -> b) -> b -> Bin a -> b # foldl' :: (b -> a -> b) -> b -> Bin a -> b # foldr1 :: (a -> a -> a) -> Bin a -> a # foldl1 :: (a -> a -> a) -> Bin a -> a # elem :: Eq a => a -> Bin a -> Bool # maximum :: Ord a => Bin a -> a # | |
Traversable Bin Source # | |
Eq r => Eq (Bin r) Source # | |
Ord r => Ord (Bin r) Source # | |
Show r => Show (Bin r) Source # | |
applyFun3 :: (a :-> (b :-> (c :-> r))) -> a -> b -> c -> r Source #
Apply a ternary function representation.
applyBranches :: r -> Branches x r -> x -> r Source #
applyFields :: Fields x r -> x -> r Source #
clearFun :: (r -> r) -> a -> (a :-> r) -> a :-> r Source #
Remove ToShrink
nodes from evaluating a given argument a
.
clearFields :: (r -> r) -> Fields x r -> x -> Fields x r Source #