rerefined-0.1.0: Refinement types, again
Safe HaskellSafe-Inferred
LanguageGHC2021

Rerefined.Predicate

Description

Base definitions for refinement predicates.

Synopsis

Documentation

class Predicate p => Refine p a where Source #

Refine a with predicate p.

Methods

validate :: Proxy# p -> a -> Maybe (RefineFailure String) 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 => Refine (Not p :: Type) a Source # 
Instance details

Defined in Rerefined.Predicate.Logical

(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

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

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

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 String) Source #

Validate predicate p for the given f a.

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 #

data RefineFailure a Source #

Predicate validation failure.

Polymorphic over the message type because I want to use Text, but want it doesn't have the convenient Show internals that String does.

Constructors

RefineFailure 

Fields

class Predicate p where Source #

Types which define refinements on other types.

Methods

predicateName :: Proxy# p -> Int -> ShowS Source #

The predicate name, as a Show-like (for good bracketing).

Non-combinator predicates may derive this via Typeably. Combinator predicates must write a Show-like instance manually, in order to avoid incurring insidious Typeable contexts for the wrapped predicate(s). (TODO figure out some generics and/or TH to resolve that)

Instances

Instances details
Predicate Fail Source # 
Instance details

Defined in Rerefined.Predicate.Fail

Predicate Succeed Source # 
Instance details

Defined in Rerefined.Predicate.Succeed

Typeable a => Predicate (Typeably a :: Type) Source #

Fill out predicate metadata using its Typeable instance.

Do not use this for combinator predicates. Doing so will incur insidious Typeable contexts for the wrapped predicate(s).

Instance details

Defined in Rerefined.Predicate

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

Defined in Rerefined.Predicate.Logical

Methods

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

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

Defined in Rerefined.Predicate.Relational.Length

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

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