Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
Rerefined.Predicates
Contents
Description
Predicate re-exports, for when you're heavily using refinement types.
Synopsis
- data Succeed
- data Fail
- data Via pVia p
- validateVia :: forall pVia p a. (Refine pVia a, Predicate p, KnownPredicateName p) => Proxy# p -> a -> Maybe RefineFailure
- data And l r
- data Iff l r
- data If l r
- data Nand l r
- data Nor l r
- data Not p
- data Or l r
- data Xor l r
- data CompareValue op (sign :: Sign) (n :: Natural)
- data Sign
- data CompareLength op (n :: Natural)
- type LTE = LT `Or` EQ
- type GTE = GT `Or` EQ
Base
The unit predicate. Always succeeds.
Instances
Predicate Succeed Source # | |
Defined in Rerefined.Predicate.Succeed Associated Types type PredicateName d Succeed :: Symbol Source # | |
Refine Succeed a Source # | |
Defined in Rerefined.Predicate.Succeed | |
type PredicateName d Succeed Source # | |
Defined in Rerefined.Predicate.Succeed |
Always fails.
Instances
Predicate Fail Source # | |
Defined in Rerefined.Predicate.Fail Associated Types type PredicateName d Fail :: Symbol Source # | |
Refine Fail a Source # | |
Defined in Rerefined.Predicate.Fail | |
type PredicateName d Fail Source # | |
Defined in Rerefined.Predicate.Fail |
Predicate p
is implemented via predicate 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.
Via
assists in doing this. Implement your Predicate
instance as normal, then
implement Refine
with:
validate
= validateVia
@pVia
Now when this predicate fails, it will print the pVia
failure with a wrapper
stating the name of the original predicate.
Note that you may not use DerivingVia
because it only works on the last
parameter of a multi-parameter type class, and I don't want to switch the order
of the Refine
parameters. Even if I did, DerivingVia
isn't much different to
or easier than this.
Instances
(Predicate p, Predicate pVia) => Predicate (Via pVia p :: Type) Source # | |
Defined in Rerefined.Predicate.Via Associated Types type PredicateName d (Via pVia p) :: Symbol Source # | |
(Refine pVia a, Predicate p, KnownPredicateName p) => Refine (Via pVia p :: Type) a Source # | |
Defined in Rerefined.Predicate.Via | |
type PredicateName d (Via pVia p :: Type) Source # | |
Defined in Rerefined.Predicate.Via type PredicateName d (Via pVia p :: Type) = ShowParen (d > 9) ((("Via " ++ PredicateName 10 p) ++ " ") ++ PredicateName 10 pVia) |
validateVia :: forall pVia p a. (Refine pVia a, Predicate p, KnownPredicateName p) => Proxy# p -> a -> Maybe RefineFailure Source #
Logical
Logical conjunction. Also AND logic gate.
Instances
(Predicate l, Predicate r) => Predicate (And l r :: Type) Source # | Precedence of 3 (matching |
Defined in Rerefined.Predicate.Logical.And Associated Types type PredicateName d (And l r) :: Symbol Source # | |
(Refine l a, Refine r a, KnownPredicateName (And l r)) => Refine (And l r :: Type) a Source # | |
Defined in Rerefined.Predicate.Logical.And | |
type PredicateName d (And l r :: Type) Source # | |
Defined in Rerefined.Predicate.Logical.And |
Logical biconditional ("if and only if"). Also the XNOR logic gate, or equivalence (loosely).
Instances
(Predicate l, Predicate r) => Predicate (Iff l r :: Type) Source # | Precedence of 4 (matching |
Defined in Rerefined.Predicate.Logical.Iff Associated Types type PredicateName d (Iff l r) :: Symbol Source # | |
(Refine l a, Refine r a, KnownPredicateName (Iff l r)) => Refine (Iff l r :: Type) a Source # | |
Defined in Rerefined.Predicate.Logical.Iff | |
type PredicateName d (Iff l r :: Type) Source # | |
Defined in Rerefined.Predicate.Logical.Iff |
Logical implication. "If l then r".
Instances
(Predicate l, Predicate r) => Predicate (If l r :: Type) Source # | Precedence of 4 (matching |
Defined in Rerefined.Predicate.Logical.If Associated Types type PredicateName d (If l r) :: Symbol Source # | |
(Refine l a, Refine r a, KnownPredicateName (If l r)) => Refine (If l r :: Type) a Source # | |
Defined in Rerefined.Predicate.Logical.If | |
type PredicateName d (If l r :: Type) Source # | |
Defined in Rerefined.Predicate.Logical.If |
NAND logic gate. Also called the Sheffer stroke, or non-conjunction.
Instances
(Predicate l, Predicate r) => Predicate (Nand l r :: Type) Source # | Precedence of 3 (matching |
Defined in Rerefined.Predicate.Logical.Nand Associated Types type PredicateName d (Nand l r) :: Symbol Source # | |
(Refine l a, Refine r a, KnownPredicateName (Nand l r)) => Refine (Nand l r :: Type) a Source # | |
Defined in Rerefined.Predicate.Logical.Nand | |
type PredicateName d (Nand l r :: Type) Source # | |
Defined in Rerefined.Predicate.Logical.Nand |
NOR logic gate. Also called non-disjunction, or joint denial.
Instances
(Predicate l, Predicate r) => Predicate (Nor l r :: Type) Source # | Precedence of 2 (matching |
Defined in Rerefined.Predicate.Logical.Nor Associated Types type PredicateName d (Nor l r) :: Symbol Source # | |
(Refine l a, Refine r a, KnownPredicateName (Nor l r)) => Refine (Nor l r :: Type) a Source # | |
Defined in Rerefined.Predicate.Logical.Nor | |
type PredicateName d (Nor l r :: Type) Source # | |
Defined in Rerefined.Predicate.Logical.Nor |
Logical negation. Also NOT logic gate, or logical complement.
Instances
Predicate p => Predicate (Not p :: Type) Source # | Precedence of 9 (one below function application). |
Defined in Rerefined.Predicate.Logical.Not Associated Types type PredicateName d (Not p) :: Symbol Source # | |
(Refine p a, KnownPredicateName (Not p)) => Refine (Not p :: Type) a Source # | |
Defined in Rerefined.Predicate.Logical.Not | |
type PredicateName d (Not p :: Type) Source # | |
Defined in Rerefined.Predicate.Logical.Not |
Logical disjunction. Also OR logic gate.
Instances
Logical exclusive disjunction. Also XOR logic gate.
Instances
(Predicate l, Predicate r) => Predicate (Xor l r :: Type) Source # | Precedence of 4 (matching |
Defined in Rerefined.Predicate.Logical.Xor Associated Types type PredicateName d (Xor l r) :: Symbol Source # | |
(Refine l a, Refine r a, KnownPredicateName (Xor l r)) => Refine (Xor l r :: Type) a Source # | |
Defined in Rerefined.Predicate.Logical.Xor | |
type PredicateName d (Xor l r :: Type) Source # | |
Defined in Rerefined.Predicate.Logical.Xor |
Relational
data CompareValue op (sign :: Sign) (n :: Natural) Source #
Compare value to a type-level Natural
using the given RelOp
.
Instances
Predicate (CompareValue op sign n :: Type) Source # | Precedence of 4 (matching base relational operators e.g. |
Defined in Rerefined.Predicate.Relational.Value Associated Types type PredicateName d (CompareValue op sign n) :: Symbol Source # | |
(KnownNat n, Num a, Ord a, ReifyRelOp op, ReifySignedNat sign n, KnownPredicateName (CompareValue op sign n)) => Refine (CompareValue op sign n :: Type) a Source # | |
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 # | |
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 CompareLength op (n :: Natural) Source #
Compare length to a type-level Natural
using the given RelOp
.