rerefined-0.8.0: Refinement types, again
Safe HaskellNone
LanguageGHC2021

Rerefined.Predicates

Description

Predicate re-exports, for when you're heavily using refinement types.

Synopsis

Base

data Succeed Source #

The unit predicate. Always succeeds.

Instances

Instances details
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"
Refine Succeed a Source # 
Instance details

Defined in Rerefined.Predicate.Succeed

type PredicateName d Succeed Source # 
Instance details

Defined in Rerefined.Predicate.Succeed

type PredicateName d Succeed = "\8868"

data Fail Source #

Always fails.

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"
Refine Fail a Source # 
Instance details

Defined in Rerefined.Predicate.Fail

type PredicateName d Fail Source # 
Instance details

Defined in Rerefined.Predicate.Fail

type PredicateName d Fail = "\8869"

validateVia :: forall {k1} {k2} (pVia :: k1) (p :: k2) a. (Refine pVia a, Predicate p, KnownPredicateName p) => Proxy# p -> a -> Maybe RefineFailure Source #

Implement validate for predicate p via pVia.

This is useful when you need a unique data type for a predicate (e.g. for instances, clarity), but the predicate it tests already exists. In such cases, it would be nice to reuse the existing predicate, while printing both predicates in failures i.e. "predicate X, implemented via predicate Y, failed with Z".

Call using visible type applications:

validate = validateVia @pVia

Logical

data And (l :: k) (r :: k1) Source #

Logical conjunction. Also AND logic gate.

Instances

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

Precedence of 3 (matching &&).

Instance details

Defined in Rerefined.Predicate.Logical.And

(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 #

type PredicateName d (And l r :: Type) Source # 
Instance details

Defined in Rerefined.Predicate.Logical.And

type PredicateName d (And l r :: Type) = PredicateNameBOp " \8743 " 3 d l r

data Iff (l :: k) (r :: k1) Source #

Logical biconditional ("if and only if"). Also the XNOR logic gate, or equivalence (loosely).

Instances

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

Precedence of 4 (matching ==).

Instance details

Defined in Rerefined.Predicate.Logical.Iff

(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 #

type PredicateName d (Iff l r :: Type) Source # 
Instance details

Defined in Rerefined.Predicate.Logical.Iff

type PredicateName d (Iff l r :: Type) = PredicateNameBOp " \8596 " 4 d l r

data If (l :: k) (r :: k1) Source #

Logical implication. "If l then r".

Instances

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

Precedence of 4 (matching ==).

Instance details

Defined in Rerefined.Predicate.Logical.If

(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 #

type PredicateName d (If l r :: Type) Source # 
Instance details

Defined in Rerefined.Predicate.Logical.If

type PredicateName d (If l r :: Type) = PredicateNameBOp " \8594 " 4 d l r

data Nand (l :: k) (r :: k1) Source #

NAND logic gate. Also called the Sheffer stroke, or non-conjunction.

Instances

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

Precedence of 3 (matching &&).

Instance details

Defined in Rerefined.Predicate.Logical.Nand

(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 #

type PredicateName d (Nand l r :: Type) Source # 
Instance details

Defined in Rerefined.Predicate.Logical.Nand

type PredicateName d (Nand l r :: Type) = PredicateNameBOp " \8892 " 3 d l r

data Nor (l :: k) (r :: k1) Source #

NOR logic gate. Also called non-disjunction, or joint denial.

Instances

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

Precedence of 2 (matching ||).

Instance details

Defined in Rerefined.Predicate.Logical.Nor

(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 #

type PredicateName d (Nor l r :: Type) Source # 
Instance details

Defined in Rerefined.Predicate.Logical.Nor

type PredicateName d (Nor l r :: Type) = PredicateNameBOp " \8893 " 2 d l r

data Not (p :: k) Source #

Logical negation. Also NOT logic gate, or logical complement.

Instances

Instances details
Predicate p => Predicate (Not p :: Type) Source #

Precedence of 9 (one below function application).

Instance details

Defined in Rerefined.Predicate.Logical.Not

(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 #

type PredicateName d (Not p :: Type) Source # 
Instance details

Defined in Rerefined.Predicate.Logical.Not

type PredicateName d (Not p :: Type) = ShowParen (d > 9) ("\172 " ++ PredicateName 10 p)

data Or (l :: k) (r :: k1) Source #

Logical disjunction. Also OR logic gate.

Instances

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

Precedence of 2 (matching ||).

Instance details

Defined in Rerefined.Predicate.Logical.Or

(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 #

type PredicateName d (Or l r :: Type) Source # 
Instance details

Defined in Rerefined.Predicate.Logical.Or

type PredicateName d (Or l r :: Type) = PredicateNameBOp " \8744 " 2 d l r

data Xor (l :: k) (r :: k1) Source #

Logical exclusive disjunction. Also XOR logic gate.

Instances

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

Precedence of 4 (matching ==).

Instance details

Defined in Rerefined.Predicate.Logical.Xor

(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 #

type PredicateName d (Xor l r :: Type) Source # 
Instance details

Defined in Rerefined.Predicate.Logical.Xor

type PredicateName d (Xor l r :: Type) = PredicateNameBOp " \8853 " 4 d l r

Relational

data RelOp Source #

Relational operator.

Constructor order is arbitrary due to NEQ, which obstructs ordering in a meaningful way.

Note that these operators may be defined by combining Orderings in certain ways: for example LT OR EQ could be LTE, LT OR GT could be NEQ. This is convenient for user intuition, permitting the use of e.g. LT as a relational operator directly. However, it complicates type-level work, as now we can't restrict relational operators to a given kind, and we have to handle non-standard orderings like GT OR LT.

Constructors

RelOpEQ

== equal to

RelOpNEQ

/= less than or greater than (also not equal to)

RelOpLT

< less than

RelOpLTE

<= less than or equal to

RelOpGTE

>= equal to or greater than

RelOpGT

> greater than

data CompareValue (op :: RelOp) (sign :: Sign) (n :: Natural) Source #

Compare value to a type-level Natural using the given RelOp.

Instances

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

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

Instance details

Defined in Rerefined.Predicate.Relational.Value

(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 #

type PredicateName d (CompareValue op sign n :: Type) Source # 
Instance details

Defined in Rerefined.Predicate.Relational.Value

type PredicateName d (CompareValue op sign n :: Type) = ShowParen (d > 4) (((("Value " ++ ShowRelOp op) ++ ShowChar ' ') ++ ShowSign sign) ++ ShowNatDec n)

data Sign Source #

Constructors

Pos 
Neg 

data CompareLength (op :: RelOp) (n :: Natural) Source #

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

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

Predicate (CompareLength op n :: Type) Source #

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

Instance details

Defined in Rerefined.Predicate.Relational.Length

(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

type PredicateName d (CompareLength op n :: Type) Source # 
Instance details

Defined in Rerefined.Predicate.Relational.Length

type PredicateName d (CompareLength op n :: Type) = ShowParen (d > 4) ((("Length " ++ ShowRelOp op) ++ ShowChar ' ') ++ ShowNatDec n)