rerefined-0.8.0: Refinement types, again
Safe HaskellNone
LanguageGHC2021

Rerefined.Predicate

Description

Base definitions for refinement predicates.

Synopsis

Documentation

class Predicate p => Refine (p :: k) a where Source #

Refine a with predicate p.

Note that validate implementations decide what failure information is emitted. They don't even have to emit their own predicate name, even though Predicate is in the context. This is useful in certain cases such as Rerefined.Predicate.Via.

That does mean that the Predicate context may not be used occasionally. But it's very useful, since otherwise combinator predicates have to constantly state (Refine p a, Predicate p), and all predicates should have a pretty name even if it doesn't get printed under normal circumstances.

Methods

validate :: Proxy# p -> a -> Maybe RefineFailure Source #

Validate predicate p for the given a.

Nothing indicates success. Just contains a validation failure.

Instances

Instances details
Refine Fail a Source # 
Instance details

Defined in Rerefined.Predicate.Fail

Refine Succeed a Source # 
Instance details

Defined in Rerefined.Predicate.Succeed

(Refine p a, KnownPredicateName (Not p)) => Refine (Not p :: Type) a Source # 
Instance details

Defined in Rerefined.Predicate.Logical.Not

Methods

validate :: Proxy# (Not p) -> a -> Maybe RefineFailure Source #

(KnownNat n, MonoFoldable a, ReifyRelOp op, KnownPredicateName (CompareLength op n)) => Refine (CompareLength op n :: Type) a Source #

Compare the length of a MonoFoldable to a type-level Natural using the given RelOp.

Instance details

Defined in Rerefined.Predicate.Relational.Length

(KnownNat n, Num a, Ord a, ReifyRelOp op, ReifySignedNat sign n, KnownPredicateName (CompareValue op sign n)) => Refine (CompareValue op sign n :: Type) a Source # 
Instance details

Defined in Rerefined.Predicate.Relational.Value

Methods

validate :: Proxy# (CompareValue op sign n) -> a -> Maybe RefineFailure Source #

(Refine l a, Refine r a, KnownPredicateName (And l r)) => Refine (And l r :: Type) a Source # 
Instance details

Defined in Rerefined.Predicate.Logical.And

Methods

validate :: Proxy# (And l r) -> a -> Maybe RefineFailure Source #

(Refine l a, Refine r a, KnownPredicateName (If l r)) => Refine (If l r :: Type) a Source # 
Instance details

Defined in Rerefined.Predicate.Logical.If

Methods

validate :: Proxy# (If l r) -> a -> Maybe RefineFailure Source #

(Refine l a, Refine r a, KnownPredicateName (Iff l r)) => Refine (Iff l r :: Type) a Source # 
Instance details

Defined in Rerefined.Predicate.Logical.Iff

Methods

validate :: Proxy# (Iff l r) -> a -> Maybe RefineFailure Source #

(Refine l a, Refine r a, KnownPredicateName (Nand l r)) => Refine (Nand l r :: Type) a Source # 
Instance details

Defined in Rerefined.Predicate.Logical.Nand

Methods

validate :: Proxy# (Nand l r) -> a -> Maybe RefineFailure Source #

(Refine l a, Refine r a, KnownPredicateName (Nor l r)) => Refine (Nor l r :: Type) a Source # 
Instance details

Defined in Rerefined.Predicate.Logical.Nor

Methods

validate :: Proxy# (Nor l r) -> a -> Maybe RefineFailure Source #

(Refine l a, Refine r a, KnownPredicateName (Or l r)) => Refine (Or l r :: Type) a Source # 
Instance details

Defined in Rerefined.Predicate.Logical.Or

Methods

validate :: Proxy# (Or l r) -> a -> Maybe RefineFailure Source #

(Refine l a, Refine r a, KnownPredicateName (Xor l r)) => Refine (Xor l r :: Type) a Source # 
Instance details

Defined in Rerefined.Predicate.Logical.Xor

Methods

validate :: Proxy# (Xor l r) -> a -> Maybe RefineFailure Source #

class Predicate p => Refine1 (p :: k) (f :: k1 -> Type) 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 :: forall (a :: k1). Proxy# p -> f a -> Maybe RefineFailure Source #

Validate predicate p for the given f a.

Instances

Instances details
(KnownNat n, Foldable f, ReifyRelOp op, KnownPredicateName (CompareLength op n)) => Refine1 (CompareLength op n :: Type) (f :: Type -> Type) Source #

Compare the length of a Foldable to a type-level Natural using the given RelOp.

Instance details

Defined in Rerefined.Predicate.Relational.Length

data RefineFailure Source #

Predicate validation failure.

Constructors

RefineFailure 

Fields

Instances

Instances details
Show RefineFailure Source # 
Instance details

Defined in Rerefined.Predicate

class Predicate (p :: k) Source #

Types which define refinements on other types.

Associated Types

type PredicateName (d :: Natural) (p :: k) :: Symbol Source #

Predicate name.

Predicate names should aim to communicate the meaning of the predicate as clearly and concisely as possible.

Consider using the package type-level-show to build this.

Instances

Instances details
Predicate Fail Source # 
Instance details

Defined in Rerefined.Predicate.Fail

Associated Types

type PredicateName d Fail 
Instance details

Defined in Rerefined.Predicate.Fail

type PredicateName d Fail = "\8869"
Predicate Succeed Source # 
Instance details

Defined in Rerefined.Predicate.Succeed

Associated Types

type PredicateName d Succeed 
Instance details

Defined in Rerefined.Predicate.Succeed

type PredicateName d Succeed = "\8868"
Predicate p => Predicate (Not p :: Type) Source #

Precedence of 9 (one below function application).

Instance details

Defined in Rerefined.Predicate.Logical.Not

Predicate (CompareLength op n :: Type) Source #

Precedence of 4 (matching base relational operators e.g. >=).

Instance details

Defined in Rerefined.Predicate.Relational.Length

Predicate (CompareValue op sign n :: Type) Source #

Precedence of 4 (matching base relational operators e.g. >=).

Instance details

Defined in Rerefined.Predicate.Relational.Value

(Predicate l, Predicate r) => Predicate (And l r :: Type) Source #

Precedence of 3 (matching &&).

Instance details

Defined in Rerefined.Predicate.Logical.And

(Predicate l, Predicate r) => Predicate (If l r :: Type) Source #

Precedence of 4 (matching ==).

Instance details

Defined in Rerefined.Predicate.Logical.If

(Predicate l, Predicate r) => Predicate (Iff l r :: Type) Source #

Precedence of 4 (matching ==).

Instance details

Defined in Rerefined.Predicate.Logical.Iff

(Predicate l, Predicate r) => Predicate (Nand l r :: Type) Source #

Precedence of 3 (matching &&).

Instance details

Defined in Rerefined.Predicate.Logical.Nand

(Predicate l, Predicate r) => Predicate (Nor l r :: Type) Source #

Precedence of 2 (matching ||).

Instance details

Defined in Rerefined.Predicate.Logical.Nor

(Predicate l, Predicate r) => Predicate (Or l r :: Type) Source #

Precedence of 2 (matching ||).

Instance details

Defined in Rerefined.Predicate.Logical.Or

(Predicate l, Predicate r) => Predicate (Xor l r :: Type) Source #

Precedence of 4 (matching ==).

Instance details

Defined in Rerefined.Predicate.Logical.Xor

type KnownPredicateName (p :: k) = KnownSymbol (PredicateName 0 p) Source #

Constraint for reifying a predicate name.

predicateName :: forall {k} (p :: k). KnownPredicateName p => String Source #

Reify predicate name to a String.

Using this regrettably necessitates UndecidableInstances, due to the type family in the constraint. It sucks, but that's life.