rerefined-0.2.0: Refinement types, again
Safe HaskellSafe-Inferred
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

Refine Succeed a Source # 
Instance details

Defined in Rerefined.Predicate.Succeed

data Fail Source #

Always fails.

Instances

Instances details
Predicate Fail Source # 
Instance details

Defined in Rerefined.Predicate.Fail

Refine Fail a Source # 
Instance details

Defined in Rerefined.Predicate.Fail

Logical

data Not p Source #

Instances

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

Defined in Rerefined.Predicate.Logical

Methods

predicateName :: Proxy# (Not p) -> Int -> ShowS Source #

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

Defined in Rerefined.Predicate.Logical

data Logical (op :: LogicOp) l r Source #

A logical binary operation on two predicates.

Instances

Instances details
(Predicate l, Predicate r, ReifyLogicOp op) => Predicate (Logical op l r :: Type) Source # 
Instance details

Defined in Rerefined.Predicate.Logical

Methods

predicateName :: Proxy# (Logical op l r) -> Int -> ShowS Source #

(Refine l a, Refine r a, ReifyLogicOp op) => Refine (Logical op l r :: Type) a Source # 
Instance details

Defined in Rerefined.Predicate.Logical

Methods

validate :: Proxy# (Logical op l r) -> a -> Maybe (RefineFailure String) Source #

Relational

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

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

Instances

Instances details
(Typeable op, Typeable sign, KnownNat n) => Predicate (CompareValue op sign n :: Type) Source # 
Instance details

Defined in Rerefined.Predicate.Relational.Value

Methods

predicateName :: Proxy# (CompareValue op sign n) -> Int -> ShowS Source #

(KnownNat n, Num a, Ord a, ReifyRelOp op, ReifySignedNat sign n, ReifySign sign) => 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 String) Source #

data Sign Source #

Constructors

Pos 
Neg 

data RelOp Source #

Relational operator.

There are three possible outcomes from compareing two terms, defined in Ordering. However, we may instead compare terms using relational operators such as >=, which are more specific comparisons that return a Bool.

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

Constructors

LT'

< less than

LTE

<= less than or equal to

EQ'

== equal to

NEQ

/= less than or greater than

GTE

>= equal to or greater than

GT'

> greater than

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) => 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

Methods

validate1 :: forall (a :: k1). Proxy# (CompareLength op n) -> f a -> Maybe (RefineFailure String) Source #

(Typeable op, KnownNat n) => Predicate (CompareLength op n :: Type) Source # 
Instance details

Defined in Rerefined.Predicate.Relational.Length

(KnownNat n, MonoFoldable a, ReifyRelOp op) => 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