Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
Rerefined.Predicate
Description
Base definitions for refinement predicates.
Synopsis
- class Predicate p => Refine p a where
- validate :: Proxy# p -> a -> Maybe RefineFailure
- class Predicate p => Refine1 p f where
- validate1 :: Proxy# p -> f a -> Maybe RefineFailure
- data RefineFailure = RefineFailure {}
- class Predicate p where
- type PredicateName (d :: Natural) p :: Symbol
- predicateName :: forall p. (Predicate p, KnownSymbol (PredicateName 0 p)) => String
Documentation
class Predicate p => Refine p a where Source #
Refine a
with predicate p
.
Methods
Instances
class Predicate p => Refine1 p f where Source #
Refine functor type f
with functor predicate p
.
By not making the contained type accessible, we ensure refinements apply
forall a. f a
. That is, refinements here apply only to the functor
structure, and not the stored elements.
Methods
validate1 :: Proxy# p -> f a -> Maybe RefineFailure Source #
Validate predicate p
for the given f a
.
Instances
(KnownNat n, Foldable f, ReifyRelOp op, KnownPredicateName (CompareLength op n)) => Refine1 (CompareLength op n :: Type) (f :: Type -> Type) Source # | Compare the length of a |
Defined in Rerefined.Predicate.Relational.Length Methods validate1 :: forall (a :: k1). Proxy# (CompareLength op n) -> f a -> Maybe RefineFailure Source # |
data RefineFailure Source #
Predicate validation failure.
Constructors
RefineFailure | |
Fields
|
Instances
Show RefineFailure Source # | |
Defined in Rerefined.Predicate Methods showsPrec :: Int -> RefineFailure -> ShowS # show :: RefineFailure -> String # showList :: [RefineFailure] -> ShowS # |
Types which define refinements on other types.
Associated Types
type PredicateName (d :: Natural) p :: Symbol Source #
Predicate name.
Predicate names should aim to communicate the meaning of the predicate as clearly and concisely as possible.
Consider using type-level-show
to build this. However, note that GHC
cannot figure out KnownSymbol
when there are type families in play, so
you may need to put KnownSymbol
constraints in instance contexts.
Instances
predicateName :: forall p. (Predicate p, KnownSymbol (PredicateName 0 p)) => String Source #
Reify predicate name.