predicate-typed-0.1.0.4: Predicates, Refinement types and Dsl

Copyright(c) Grant Weyburne 2019
LicenseBSD-3
Maintainergbwey9@gmail.com
Safe HaskellNone
LanguageHaskell2010

PredicateCore

Description

class P is the main class. Contains a minimal set of instances of P to prevent orphans

Synopsis

Documentation

class P p a where Source #

This is the core class. Each instance of this class can be combined into a dsl using >>

Associated Types

type PP (p :: k) a :: Type Source #

Methods

eval Source #

Arguments

:: MonadEval m 
=> Proxy p 
-> POpts 
-> a 
-> m (TT (PP p a))

returns a tree of results

Instances
GetBool b => P (b :: Bool) a Source #

pulls the type level Bool to the value level

>>> pl @'True "ignore this"
True
TrueT
>>> pl @'False ()
False
FalseT
Instance details

Defined in PredicateCore

Associated Types

type PP b a :: Type Source #

Methods

eval :: MonadEval m => Proxy b -> POpts -> a -> m (TT (PP b a)) Source #

GetOrdering cmp => P (cmp :: Ordering) a Source #

extracts the value level representation of the promoted Ordering

>>> pl @'LT "not used"
Present LT
PresentT LT
>>> pl @'EQ ()
Present EQ
PresentT EQ
Instance details

Defined in PredicateCore

Associated Types

type PP cmp a :: Type Source #

Methods

eval :: MonadEval m => Proxy cmp -> POpts -> a -> m (TT (PP cmp a)) Source #

KnownNat n => P (n :: Nat) a Source #

extracts the value level representation of the type level Nat

>>> pl @123 ()
Present 123
PresentT 123
Instance details

Defined in PredicateCore

Associated Types

type PP n a :: Type Source #

Methods

eval :: MonadEval m => Proxy n -> POpts -> a -> m (TT (PP n a)) Source #

KnownSymbol s => P (s :: Symbol) a Source #

pulls the type level Symbol to the value level

>>> pl @"hello world" ()
Present "hello world"
PresentT "hello world"
Instance details

Defined in PredicateCore

Associated Types

type PP s a :: Type Source #

Methods

eval :: MonadEval m => Proxy s -> POpts -> a -> m (TT (PP s a)) Source #

P () a Source #

extracts the value level representation of the type level '()

>>> pl @'() ()
Present ()
PresentT ()
Instance details

Defined in PredicateCore

Associated Types

type PP () a :: Type Source #

Methods

eval :: MonadEval m => Proxy () -> POpts -> a -> m (TT (PP () a)) Source #

Show a => P () a Source #

const () function

>>> pl @() "Asf"
Present ()
PresentT ()
Instance details

Defined in PredicateCore

Associated Types

type PP () a :: Type Source #

Methods

eval :: MonadEval m => Proxy () -> POpts -> a -> m (TT (PP () a)) Source #

(Typeable a, Show a) => P IdT a Source # 
Instance details

Defined in PredicateCore

Associated Types

type PP IdT a :: Type Source #

Methods

eval :: MonadEval m => Proxy IdT -> POpts -> a -> m (TT (PP IdT a)) Source #

Show a => P Id a Source # 
Instance details

Defined in PredicateCore

Associated Types

type PP Id a :: Type Source #

Methods

eval :: MonadEval m => Proxy Id -> POpts -> a -> m (TT (PP Id a)) Source #

P I a Source # 
Instance details

Defined in PredicateCore

Associated Types

type PP I a :: Type Source #

Methods

eval :: MonadEval m => Proxy I -> POpts -> a -> m (TT (PP I a)) Source #

(ReverseTupleC tp, Show (ReverseTupleP tp), Show tp) => P ReverseTupleN tp Source # 
Instance details

Defined in Predicate

Associated Types

type PP ReverseTupleN tp :: Type Source #

Methods

eval :: MonadEval m => Proxy ReverseTupleN -> POpts -> tp -> m (TT (PP ReverseTupleN tp)) Source #

P Stdin a Source # 
Instance details

Defined in Predicate

Associated Types

type PP Stdin a :: Type Source #

Methods

eval :: MonadEval m => Proxy Stdin -> POpts -> a -> m (TT (PP Stdin a)) Source #

P TimeZ a Source # 
Instance details

Defined in Predicate

Associated Types

type PP TimeZ a :: Type Source #

Methods

eval :: MonadEval m => Proxy TimeZ -> POpts -> a -> m (TT (PP TimeZ a)) Source #

P TimeU a Source # 
Instance details

Defined in Predicate

Associated Types

type PP TimeU a :: Type Source #

Methods

eval :: MonadEval m => Proxy TimeU -> POpts -> a -> m (TT (PP TimeU a)) Source #

P ReadEnvAll a Source # 
Instance details

Defined in Predicate

Associated Types

type PP ReadEnvAll a :: Type Source #

Methods

eval :: MonadEval m => Proxy ReadEnvAll -> POpts -> a -> m (TT (PP ReadEnvAll a)) Source #

(Show l, IsList l, Show (Item l)) => P ToListExt l Source # 
Instance details

Defined in Predicate

Associated Types

type PP ToListExt l :: Type Source #

Methods

eval :: MonadEval m => Proxy ToListExt -> POpts -> l -> m (TT (PP ToListExt l)) Source #

(Show (t a), Foldable t, t a ~ as) => P Null as Source # 
Instance details

Defined in Predicate

Associated Types

type PP Null as :: Type Source #

Methods

eval :: MonadEval m => Proxy Null -> POpts -> as -> m (TT (PP Null as)) Source #

(Show as, AsEmpty as) => P IsEmpty as Source # 
Instance details

Defined in Predicate

Associated Types

type PP IsEmpty as :: Type Source #

Methods

eval :: MonadEval m => Proxy IsEmpty -> POpts -> as -> m (TT (PP IsEmpty as)) Source #

(Show (ConsT s), Show s, Snoc s s (ConsT s) (ConsT s)) => P Unsnoc s Source # 
Instance details

Defined in Predicate

Associated Types

type PP Unsnoc s :: Type Source #

Methods

eval :: MonadEval m => Proxy Unsnoc -> POpts -> s -> m (TT (PP Unsnoc s)) Source #

(Show (ConsT s), Show s, Cons s s (ConsT s) (ConsT s)) => P Uncons s Source # 
Instance details

Defined in Predicate

Associated Types

type PP Uncons s :: Type Source #

Methods

eval :: MonadEval m => Proxy Uncons -> POpts -> s -> m (TT (PP Uncons s)) Source #

(Show t, Reversing t) => P ReverseL t Source # 
Instance details

Defined in Predicate

Associated Types

type PP ReverseL t :: Type Source #

Methods

eval :: MonadEval m => Proxy ReverseL -> POpts -> t -> m (TT (PP ReverseL t)) Source #

(Show a, as ~ [a]) => P Reverse as Source # 
Instance details

Defined in Predicate

Associated Types

type PP Reverse as :: Type Source #

Methods

eval :: MonadEval m => Proxy Reverse -> POpts -> as -> m (TT (PP Reverse as)) Source #

Show a => P MkProxy a Source # 
Instance details

Defined in Predicate

Associated Types

type PP MkProxy a :: Type Source #

Methods

eval :: MonadEval m => Proxy MkProxy -> POpts -> a -> m (TT (PP MkProxy a)) Source #

(Show a, as ~ [a]) => P Len as Source # 
Instance details

Defined in Predicate

Associated Types

type PP Len as :: Type Source #

Methods

eval :: MonadEval m => Proxy Len -> POpts -> as -> m (TT (PP Len as)) Source #

(Show a, IsText a) => P ToUpper a Source # 
Instance details

Defined in Predicate

Associated Types

type PP ToUpper a :: Type Source #

Methods

eval :: MonadEval m => Proxy ToUpper -> POpts -> a -> m (TT (PP ToUpper a)) Source #

(Show a, IsText a) => P ToLower a Source # 
Instance details

Defined in Predicate

Associated Types

type PP ToLower a :: Type Source #

Methods

eval :: MonadEval m => Proxy ToLower -> POpts -> a -> m (TT (PP ToLower a)) Source #

(Show (t (t a)), Show (t a), Monad t) => P Join (t (t a)) Source # 
Instance details

Defined in Predicate

Associated Types

type PP Join (t (t a)) :: Type Source #

Methods

eval :: MonadEval m => Proxy Join -> POpts -> t (t a) -> m (TT (PP Join (t (t a)))) Source #

(Show (t a), Show (t (t a)), Comonad t) => P Duplicate (t a) Source # 
Instance details

Defined in Predicate

Associated Types

type PP Duplicate (t a) :: Type Source #

Methods

eval :: MonadEval m => Proxy Duplicate -> POpts -> t a -> m (TT (PP Duplicate (t a))) Source #

(Show (t a), Show a, Comonad t) => P Extract (t a) Source # 
Instance details

Defined in Predicate

Associated Types

type PP Extract (t a) :: Type Source #

Methods

eval :: MonadEval m => Proxy Extract -> POpts -> t a -> m (TT (PP Extract (t a))) Source #

(Show (f (t a)), Show (t (f a)), Traversable t, Applicative f) => P Sequence (t (f a)) Source # 
Instance details

Defined in Predicate

Associated Types

type PP Sequence (t (f a)) :: Type Source #

Methods

eval :: MonadEval m => Proxy Sequence -> POpts -> t (f a) -> m (TT (PP Sequence (t (f a)))) Source #

(Show (t a), Foldable t, Show a) => P ToList (t a) Source # 
Instance details

Defined in Predicate

Associated Types

type PP ToList (t a) :: Type Source #

Methods

eval :: MonadEval m => Proxy ToList -> POpts -> t a -> m (TT (PP ToList (t a))) Source #

Show a => P Pairs [a] Source # 
Instance details

Defined in Predicate

Associated Types

type PP Pairs [a] :: Type Source #

Methods

eval :: MonadEval m => Proxy Pairs -> POpts -> [a] -> m (TT (PP Pairs [a])) Source #

(Show a, Show b) => P PartitionThese [These a b] Source # 
Instance details

Defined in Predicate

Associated Types

type PP PartitionThese [These a b] :: Type Source #

Methods

eval :: MonadEval m => Proxy PartitionThese -> POpts -> [These a b] -> m (TT (PP PartitionThese [These a b])) Source #

(Show a, Show b) => P PartitionEithers [Either a b] Source # 
Instance details

Defined in Predicate

Associated Types

type PP PartitionEithers [Either a b] :: Type Source #

Methods

eval :: MonadEval m => Proxy PartitionEithers -> POpts -> [Either a b] -> m (TT (PP PartitionEithers [Either a b])) Source #

Functor f => P Fmap_2 (f (x, a)) Source # 
Instance details

Defined in Predicate

Associated Types

type PP Fmap_2 (f (x, a)) :: Type Source #

Methods

eval :: MonadEval m => Proxy Fmap_2 -> POpts -> f (x, a) -> m (TT (PP Fmap_2 (f (x, a)))) Source #

Functor f => P Fmap_1 (f (a, x)) Source # 
Instance details

Defined in Predicate

Associated Types

type PP Fmap_1 (f (a, x)) :: Type Source #

Methods

eval :: MonadEval m => Proxy Fmap_1 -> POpts -> f (a, x) -> m (TT (PP Fmap_1 (f (a, x)))) Source #

(Ord a, Show a) => P Max [a] Source # 
Instance details

Defined in Predicate

Associated Types

type PP Max [a] :: Type Source #

Methods

eval :: MonadEval m => Proxy Max -> POpts -> [a] -> m (TT (PP Max [a])) Source #

(Ord a, Show a) => P Min [a] Source # 
Instance details

Defined in Predicate

Associated Types

type PP Min [a] :: Type Source #

Methods

eval :: MonadEval m => Proxy Min -> POpts -> [a] -> m (TT (PP Min [a])) Source #

Show a => P Tails [a] Source # 
Instance details

Defined in Predicate

Associated Types

type PP Tails [a] :: Type Source #

Methods

eval :: MonadEval m => Proxy Tails -> POpts -> [a] -> m (TT (PP Tails [a])) Source #

Show a => P Inits [a] Source # 
Instance details

Defined in Predicate

Associated Types

type PP Inits [a] :: Type Source #

Methods

eval :: MonadEval m => Proxy Inits -> POpts -> [a] -> m (TT (PP Inits [a])) Source #

Typeable a => P Unproxy (Proxy a) Source # 
Instance details

Defined in Predicate

Associated Types

type PP Unproxy (Proxy a) :: Type Source #

Methods

eval :: MonadEval m => Proxy Unproxy -> POpts -> Proxy a -> m (TT (PP Unproxy (Proxy a))) Source #

Monoid a => P MEmptyProxy (Proxy a) Source # 
Instance details

Defined in Predicate

Associated Types

type PP MEmptyProxy (Proxy a) :: Type Source #

Methods

eval :: MonadEval m => Proxy MEmptyProxy -> POpts -> Proxy a -> m (TT (PP MEmptyProxy (Proxy a))) Source #

P TheseToMaybe (These a b) Source # 
Instance details

Defined in Predicate

Associated Types

type PP TheseToMaybe (These a b) :: Type Source #

Methods

eval :: MonadEval m => Proxy TheseToMaybe -> POpts -> These a b -> m (TT (PP TheseToMaybe (These a b))) Source #

P ThatToMaybe (These x a) Source # 
Instance details

Defined in Predicate

Associated Types

type PP ThatToMaybe (These x a) :: Type Source #

Methods

eval :: MonadEval m => Proxy ThatToMaybe -> POpts -> These x a -> m (TT (PP ThatToMaybe (These x a))) Source #

P ThisToMaybe (These a x) Source # 
Instance details

Defined in Predicate

Associated Types

type PP ThisToMaybe (These a x) :: Type Source #

Methods

eval :: MonadEval m => Proxy ThisToMaybe -> POpts -> These a x -> m (TT (PP ThisToMaybe (These a x))) Source #

P RightToMaybe (Either x a) Source # 
Instance details

Defined in Predicate

Associated Types

type PP RightToMaybe (Either x a) :: Type Source #

Methods

eval :: MonadEval m => Proxy RightToMaybe -> POpts -> Either x a -> m (TT (PP RightToMaybe (Either x a))) Source #

P LeftToMaybe (Either a x) Source # 
Instance details

Defined in Predicate

Associated Types

type PP LeftToMaybe (Either a x) :: Type Source #

Methods

eval :: MonadEval m => Proxy LeftToMaybe -> POpts -> Either a x -> m (TT (PP LeftToMaybe (Either a x))) Source #

(Show (p (p a b) c), Show (p a (p b c)), Assoc p) => P Unassoc (p a (p b c)) Source # 
Instance details

Defined in Predicate

Associated Types

type PP Unassoc (p a (p b c)) :: Type Source #

Methods

eval :: MonadEval m => Proxy Unassoc -> POpts -> p a (p b c) -> m (TT (PP Unassoc (p a (p b c)))) Source #

(Show (p (p a b) c), Show (p a (p b c)), Assoc p) => P Assoc (p (p a b) c) Source # 
Instance details

Defined in Predicate

Associated Types

type PP Assoc (p (p a b) c) :: Type Source #

Methods

eval :: MonadEval m => Proxy Assoc -> POpts -> p (p a b) c -> m (TT (PP Assoc (p (p a b) c))) Source #

(Show (p a b), Swap p, Show (p b a)) => P Swap (p a b) Source # 
Instance details

Defined in Predicate

Associated Types

type PP Swap (p a b) :: Type Source #

Methods

eval :: MonadEval m => Proxy Swap -> POpts -> p a b -> m (TT (PP Swap (p a b))) Source #

P ([] :: [k]) a Source #

extracts the value level representation of the type level '[]

>>> pl @'[] False
Present []
PresentT []
Instance details

Defined in PredicateCore

Associated Types

type PP [] a :: Type Source #

Methods

eval :: MonadEval m => Proxy [] -> POpts -> a -> m (TT (PP [] a)) Source #

(KnownSymbol s, NullT s ~ False) => P (Char1 s :: Type) a Source # 
Instance details

Defined in Predicate

Associated Types

type PP (Char1 s) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (Char1 s) -> POpts -> a -> m (TT (PP (Char1 s) a)) Source #

(Show l, IsList l, l ~ l') => P (FromListF l' :: Type) l Source # 
Instance details

Defined in Predicate

Associated Types

type PP (FromListF l') l :: Type Source #

Methods

eval :: MonadEval m => Proxy (FromListF l') -> POpts -> l -> m (TT (PP (FromListF l') l)) Source #

Typeable t => P (Hole t :: Type) a Source #

Acts as a proxy in this dsl where you can explicitly set the Type.

It is passed around as an argument to help the type checker when needed. see ReadP, ParseTimeP, ShowP

Instance details

Defined in Predicate

Associated Types

type PP (Hole t) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (Hole t) -> POpts -> a -> m (TT (PP (Hole t) a)) Source #

(GetCharSet cs, Show a, IsText a) => P (IsCharSet cs :: Type) a Source # 
Instance details

Defined in Predicate

Associated Types

type PP (IsCharSet cs) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (IsCharSet cs) -> POpts -> a -> m (TT (PP (IsCharSet cs) a)) Source #

P (Nothing :: Maybe a1) (Maybe a2) Source #

expects Nothing otherwise it fails if the value is Nothing then it returns 'Proxy a' as this provides more information than '()'

>>> pl @'Nothing Nothing
Present Proxy
PresentT Proxy
>>> pl @'Nothing (Just True)
Error 'Nothing found Just
FailT "'Nothing found Just"
Instance details

Defined in PredicateCore

Associated Types

type PP Nothing (Maybe a2) :: Type Source #

Methods

eval :: MonadEval m => Proxy Nothing -> POpts -> Maybe a2 -> m (TT (PP Nothing (Maybe a2))) Source #

(a ~ Item t, Show t, IsList t) => P (FromList t :: Type) [a] Source # 
Instance details

Defined in Predicate

Associated Types

type PP (FromList t) [a] :: Type Source #

Methods

eval :: MonadEval m => Proxy (FromList t) -> POpts -> [a] -> m (TT (PP (FromList t) [a])) Source #

(Show (f (t a)), Show (f a), Applicative t, Functor f) => P (Pure2 t :: Type) (f a) Source # 
Instance details

Defined in Predicate

Associated Types

type PP (Pure2 t) (f a) :: Type Source #

Methods

eval :: MonadEval m => Proxy (Pure2 t) -> POpts -> f a -> m (TT (PP (Pure2 t) (f a))) Source #

P (Proxy t :: Type) a Source # 
Instance details

Defined in PredicateCore

Associated Types

type PP (Proxy t) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (Proxy t) -> POpts -> a -> m (TT (PP (Proxy t) a)) Source #

P p a => P (W p :: Type) a Source # 
Instance details

Defined in PredicateCore

Associated Types

type PP (W p) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (W p) -> POpts -> a -> m (TT (PP (W p) a)) Source #

(PP p x ~ String, P p x) => P (ReadEnv p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

type PP (ReadEnv p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (ReadEnv p) -> POpts -> x -> m (TT (PP (ReadEnv p) x)) Source #

(PP p x ~ String, P p x) => P (ReadDir p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

type PP (ReadDir p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (ReadDir p) -> POpts -> x -> m (TT (PP (ReadDir p) x)) Source #

(PP p x ~ String, P p x) => P (ReadFile p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

type PP (ReadFile p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (ReadFile p) -> POpts -> x -> m (TT (PP (ReadFile p) x)) Source #

P p x => P (Hide p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

type PP (Hide p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (Hide p) -> POpts -> x -> m (TT (PP (Hide p) x)) Source #

(PP p x ~ [Int], P p x) => P (Luhn p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

type PP (Luhn p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (Luhn p) -> POpts -> x -> m (TT (PP (Luhn p) x)) Source #

P (EmptyList' t :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

type PP (EmptyList' t) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (EmptyList' t) -> POpts -> x -> m (TT (PP (EmptyList' t) x)) Source #

(PP p x ~ t a, P p x, Show (t a), Foldable t, Show a) => P (ToList' p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

type PP (ToList' p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (ToList' p) -> POpts -> x -> m (TT (PP (ToList' p) x)) Source #

(Show (PP p a), P p a) => P (Skip p :: Type) a Source # 
Instance details

Defined in Predicate

Associated Types

type PP (Skip p) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (Skip p) -> POpts -> a -> m (TT (PP (Skip p) a)) Source #

(Show a, P p a, PP p a ~ Bool) => P (GuardSimple p :: Type) a Source # 
Instance details

Defined in Predicate

Associated Types

type PP (GuardSimple p) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (GuardSimple p) -> POpts -> a -> m (TT (PP (GuardSimple p) a)) Source #

(PP p x ~ t a, P p x, Show (t a), Foldable t, a ~ Bool) => P (Ors p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

type PP (Ors p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (Ors p) -> POpts -> x -> m (TT (PP (Ors p) x)) Source #

(PP p x ~ t a, P p x, Show (t a), Foldable t, a ~ Bool) => P (Ands p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

type PP (Ands p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (Ands p) -> POpts -> x -> m (TT (PP (Ands p) x)) Source #

Typeable t => P (ProxyT' t :: Type) a Source # 
Instance details

Defined in Predicate

Associated Types

type PP (ProxyT' t) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (ProxyT' t) -> POpts -> a -> m (TT (PP (ProxyT' t) a)) Source #

(Show a, Show (t [a]), PP p x ~ t [a], P p x, Foldable t) => P (Concat p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

type PP (Concat p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (Concat p) -> POpts -> x -> m (TT (PP (Concat p) x)) Source #

(PP p x ~ [a], P p x, Show a, Monoid a) => P (MConcat p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

type PP (MConcat p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (MConcat p) -> POpts -> x -> m (TT (PP (MConcat p) x)) Source #

(PP p x ~ a, P p x, Show a) => P (MkJust p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

type PP (MkJust p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (MkJust p) -> POpts -> x -> m (TT (PP (MkJust p) x)) Source #

P (MkNothing' t :: Type) a Source # 
Instance details

Defined in Predicate

Associated Types

type PP (MkNothing' t) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (MkNothing' t) -> POpts -> a -> m (TT (PP (MkNothing' t) a)) Source #

(Show (PP t a), Monoid (PP t a)) => P (MEmptyT' t :: Type) a Source # 
Instance details

Defined in Predicate

Associated Types

type PP (MEmptyT' t) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (MEmptyT' t) -> POpts -> a -> m (TT (PP (MEmptyT' t) a)) Source #

(PP p x ~ Bool, P p x) => P (Not p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

type PP (Not p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (Not p) -> POpts -> x -> m (TT (PP (Not p) x)) Source #

(PP p x ~ a, P p x, Show a, Integral a) => P (Prime p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

type PP (Prime p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (Prime p) -> POpts -> x -> m (TT (PP (Prime p) x)) Source #

(Show a, Enum a, PP p x ~ a, P p x) => P (FromEnum p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

type PP (FromEnum p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (FromEnum p) -> POpts -> x -> m (TT (PP (FromEnum p) x)) Source #

(Show a, Enum a, PP p x ~ a, P p x) => P (Pred p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

type PP (Pred p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (Pred p) -> POpts -> x -> m (TT (PP (Pred p) x)) Source #

(Show a, Enum a, PP p x ~ a, P p x) => P (Succ p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

type PP (Succ p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (Succ p) -> POpts -> x -> m (TT (PP (Succ p) x)) Source #

(Show a, Show t, Coercible t a) => P (Coerce t :: Type) a Source # 
Instance details

Defined in Predicate

Associated Types

type PP (Coerce t) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (Coerce t) -> POpts -> a -> m (TT (PP (Coerce t) a)) Source #

(PP p x ~ s, P p x, Show s, Show (Unwrapped s), Wrapped s) => P (Unwrap p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

type PP (Unwrap p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (Unwrap p) -> POpts -> x -> m (TT (PP (Unwrap p) x)) Source #

(Show (PP p x), Num (PP p x), P p x) => P (Signum p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

type PP (Signum p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (Signum p) -> POpts -> x -> m (TT (PP (Signum p) x)) Source #

(Show (PP p x), Num (PP p x), P p x) => P (Abs p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

type PP (Abs p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (Abs p) -> POpts -> x -> m (TT (PP (Abs p) x)) Source #

(Show (PP p x), Num (PP p x), P p x) => P (Negate p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

type PP (Negate p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (Negate p) -> POpts -> x -> m (TT (PP (Negate p) x)) Source #

P (TupleI ([] :: [k]) :: Type) a Source # 
Instance details

Defined in Predicate

Associated Types

type PP (TupleI []) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (TupleI []) -> POpts -> a -> m (TT (PP (TupleI []) a)) Source #

(P p a, P (TupleI ps) a, Show a) => P (TupleI (p ': ps) :: Type) a Source # 
Instance details

Defined in Predicate

Associated Types

type PP (TupleI (p ': ps)) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (TupleI (p ': ps)) -> POpts -> a -> m (TT (PP (TupleI (p ': ps)) a)) Source #

P (DoExpandT ps) a => P (Do ps :: Type) a Source # 
Instance details

Defined in Predicate

Associated Types

type PP (Do ps) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (Do ps) -> POpts -> a -> m (TT (PP (Do ps) a)) Source #

(a ~ PP p x, Show a, Real a, P p x) => P (ToRational p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

type PP (ToRational p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (ToRational p) -> POpts -> x -> m (TT (PP (ToRational p) x)) Source #

(Show (ExtractL6T (PP p x)), ExtractL6C (PP p x), P p x, Show (PP p x)) => P (L6 p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

type PP (L6 p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (L6 p) -> POpts -> x -> m (TT (PP (L6 p) x)) Source #

(Show (ExtractL5T (PP p x)), ExtractL5C (PP p x), P p x, Show (PP p x)) => P (L5 p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

type PP (L5 p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (L5 p) -> POpts -> x -> m (TT (PP (L5 p) x)) Source #

(Show (ExtractL4T (PP p x)), ExtractL4C (PP p x), P p x, Show (PP p x)) => P (L4 p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

type PP (L4 p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (L4 p) -> POpts -> x -> m (TT (PP (L4 p) x)) Source #

(Show (ExtractL3T (PP p x)), ExtractL3C (PP p x), P p x, Show (PP p x)) => P (L3 p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

type PP (L3 p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (L3 p) -> POpts -> x -> m (TT (PP (L3 p) x)) Source #

(Show (ExtractL2T (PP p x)), ExtractL2C (PP p x), P p x, Show (PP p x)) => P (L2 p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

type PP (L2 p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (L2 p) -> POpts -> x -> m (TT (PP (L2 p) x)) Source #

(Show (ExtractL1T (PP p x)), ExtractL1C (PP p x), P p x, Show (PP p x)) => P (L1 p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

type PP (L1 p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (L1 p) -> POpts -> x -> m (TT (PP (L1 p) x)) Source #

(PP p x ~ t a, P p x, Show (t a), Foldable t) => P (Length p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

type PP (Length p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (Length p) -> POpts -> x -> m (TT (PP (Length p) x)) Source #

(PP p x ~ Day, P p x) => P (UnMkDay p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

type PP (UnMkDay p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (UnMkDay p) -> POpts -> x -> m (TT (PP (UnMkDay p) x)) Source #

(Show (PP p x), P p x) => P (ShowP p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

type PP (ShowP p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (ShowP p) -> POpts -> x -> m (TT (PP (ShowP p) x)) Source #

(PP p x ~ [a], P p x, Show a) => P (Ones p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

type PP (Ones p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (Ones p) -> POpts -> x -> m (TT (PP (Ones p) x)) Source #

(PP p x ~ ([String] -> String), P p x) => P (MakeRR3 p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

type PP (MakeRR3 p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (MakeRR3 p) -> POpts -> x -> m (TT (PP (MakeRR3 p) x)) Source #

(PP p x ~ (String -> String), P p x) => P (MakeRR2 p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

type PP (MakeRR2 p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (MakeRR2 p) -> POpts -> x -> m (TT (PP (MakeRR2 p) x)) Source #

(PP p x ~ (String -> [String] -> String), P p x) => P (MakeRR1 p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

type PP (MakeRR1 p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (MakeRR1 p) -> POpts -> x -> m (TT (PP (MakeRR1 p) x)) Source #

(PP p x ~ String, P p x) => P (MakeRR p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

type PP (MakeRR p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (MakeRR p) -> POpts -> x -> m (TT (PP (MakeRR p) x)) Source #

(Show (PP p a2), P p a2, Show a2) => P (Just p :: Maybe a1) (Maybe a2) Source #

extracts the 'a' from type level 'Maybe a' if the value exists

>>> pl @('Just Id) (Just 123)
Present 123
PresentT 123
>>> pl @('Just Id) (Just True)
Present True
PresentT True
>>> pl @('Just Id) Nothing
Error 'Just found Nothing
FailT "'Just found Nothing"
Instance details

Defined in PredicateCore

Associated Types

type PP (Just p) (Maybe a2) :: Type Source #

Methods

eval :: MonadEval m => Proxy (Just p) -> POpts -> Maybe a2 -> m (TT (PP (Just p) (Maybe a2))) Source #

(Show a, KnownNat n, GetBool strict, TupleListD (ToN n) a, Show (TupleListT (ToN n) a)) => P (TupleListImpl strict n :: Type) [a] Source # 
Instance details

Defined in Predicate

Associated Types

type PP (TupleListImpl strict n) [a] :: Type Source #

Methods

eval :: MonadEval m => Proxy (TupleListImpl strict n) -> POpts -> [a] -> m (TT (PP (TupleListImpl strict n) [a])) Source #

(Show (f a), Show (f (PP t (f a))), Functor f, Monoid (PP t (f a))) => P (MEmptyT2' t :: Type) (f a) Source # 
Instance details

Defined in Predicate

Associated Types

type PP (MEmptyT2' t) (f a) :: Type Source #

Methods

eval :: MonadEval m => Proxy (MEmptyT2' t) -> POpts -> f a -> m (TT (PP (MEmptyT2' t) (f a))) Source #

(Show (f a), Show (f t), Coercible t a, Functor f) => P (Coerce2 t :: Type) (f a) Source # 
Instance details

Defined in Predicate

Associated Types

type PP (Coerce2 t) (f a) :: Type Source #

Methods

eval :: MonadEval m => Proxy (Coerce2 t) -> POpts -> f a -> m (TT (PP (Coerce2 t) (f a))) Source #

(Show (PP p a2), Show a2, P (p1 ': ps) a2, PP (p1 ': ps) a2 ~ [PP p1 a2], P p a2, PP p a2 ~ PP p1 a2) => P (p ': (p1 ': ps) :: [a1]) a2 Source # 
Instance details

Defined in PredicateCore

Associated Types

type PP (p ': (p1 ': ps)) a2 :: Type Source #

Methods

eval :: MonadEval m => Proxy (p ': (p1 ': ps)) -> POpts -> a2 -> m (TT (PP (p ': (p1 ': ps)) a2)) Source #

(Show (PP p a), Show a, P p a) => P (p ': ([] :: [k]) :: [k]) a Source #

runs each predicate in turn from the promoted list

>>> pl @'[1, 2, 3] 999
Present [1,2,3]
PresentT [1,2,3]
>>> pl @'[W 1, W 2, W 3, Id] 999
Present [1,2,3,999]
PresentT [1,2,3,999]
Instance details

Defined in PredicateCore

Associated Types

type PP (p ': []) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (p ': []) -> POpts -> a -> m (TT (PP (p ': []) a)) Source #

P (DoExpandT (RepeatT n p)) a => P (DoN n p :: Type) a Source # 
Instance details

Defined in Predicate

Associated Types

type PP (DoN n p) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (DoN n p) -> POpts -> a -> m (TT (PP (DoN n p) a)) Source #

P (RepeatT n p) a => P (Repeat n p :: Type) a Source # 
Instance details

Defined in Predicate

Associated Types

type PP (Repeat n p) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (Repeat n p) -> POpts -> a -> m (TT (PP (Repeat n p) a)) Source #

(GetFHandle fh, P p a, PP p a ~ String) => P (WritefileImpl fh p :: Type) a Source # 
Instance details

Defined in Predicate

Associated Types

type PP (WritefileImpl fh p) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (WritefileImpl fh p) -> POpts -> a -> m (TT (PP (WritefileImpl fh p) a)) Source #

(PP p x ~ a, P p x, Show a, 2 <= n, n <= 36, KnownNat n, Integral a) => P (ShowBase' n p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

type PP (ShowBase' n p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (ShowBase' n p) -> POpts -> x -> m (TT (PP (ShowBase' n p) x)) Source #

(P p x, PP p x ~ a, Show (t a), Show a, Alternative t) => P (EmptyT t p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

type PP (EmptyT t p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (EmptyT t p) -> POpts -> x -> m (TT (PP (EmptyT t p) x)) Source #

(P p x, Show (PP p x), Show (t (PP p x)), Applicative t) => P (Pure t p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

type PP (Pure t p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (Pure t p) -> POpts -> x -> m (TT (PP (Pure t p) x)) Source #

(GetBool strict, GetLen ps, P (ParaImpl (LenT ps) strict ps) [a]) => P (ParaImplW strict ps :: Type) [a] Source # 
Instance details

Defined in Predicate

Associated Types

type PP (ParaImplW strict ps) [a] :: Type Source #

Methods

eval :: MonadEval m => Proxy (ParaImplW strict ps) -> POpts -> [a] -> m (TT (PP (ParaImplW strict ps) [a])) Source #

(P def (Proxy a), PP def (Proxy a) ~ a, KnownNat n, Show a) => P (Ix n def :: Type) [a] Source # 
Instance details

Defined in Predicate

Associated Types

type PP (Ix n def) [a] :: Type Source #

Methods

eval :: MonadEval m => Proxy (Ix n def) -> POpts -> [a] -> m (TT (PP (Ix n def) [a])) Source #

(P prt a, PP prt a ~ String, P p a) => P (Msg prt p :: Type) a Source # 
Instance details

Defined in PredicateCore

Associated Types

type PP (Msg prt p) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (Msg prt p) -> POpts -> a -> m (TT (PP (Msg prt p) a)) Source #

(FailIfT (NotT (OrT l r)) (Text "Trim': left and right cannot both be False"), GetBool l, GetBool r, IsText (PP p x), P p x) => P (Trim' l r p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

type PP (Trim' l r p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (Trim' l r p) -> POpts -> x -> m (TT (PP (Trim' l r p) x)) Source #

(P p x, P q x, PP p x ~ (a -> b), FnT (PP p x) ~ b, PP q x ~ a, Show a, Show b) => P (q & p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

type PP (q & p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (q & p) -> POpts -> x -> m (TT (PP (q & p) x)) Source #

(P p x, P q x, PP p x ~ (a -> b), FnT (PP p x) ~ b, PP q x ~ a, Show a, Show b) => P (p $ q :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

type PP (p $ q) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (p $ q) -> POpts -> x -> m (TT (PP (p $ q) x)) Source #

(P p x, P q x, Show (t b), Alternative t, t b ~ PP p x, PP q x ~ t b) => P (p <|> q :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

type PP (p <|> q) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (p <|> q) -> POpts -> x -> m (TT (PP (p <|> q) x)) Source #

(Show (t c), P p x, P q x, Show (t b), Applicative t, t b ~ PP p x, PP q x ~ t c) => P (p <* q :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

type PP (p <* q) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (p <* q) -> POpts -> x -> m (TT (PP (p <* q) x)) Source #

(P p x, P q x, Show (PP p x), Functor t, PP q x ~ t c, ApplyConstT (PP q x) (PP p x) ~ t (PP p x)) => P (p <$ q :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

type PP (p <$ q) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (p <$ q) -> POpts -> x -> m (TT (PP (p <$ q) x)) Source #

(KnownNat (TupleLenT as), PrintC bs, (b, bs) ~ ReverseTupleP (a, as), ReverseTupleC (a, as), Show a, Show as, PrintfArg b, PP s x ~ String, PP p x ~ (a, as), P s x, P p x, CheckT (PP p x) ~ True) => P (Printfn s p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

type PP (Printfn s p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (Printfn s p) -> POpts -> x -> m (TT (PP (Printfn s p) x)) Source #

(Semigroup (PP p x), PP p x ~ PP q x, P p x, Show (PP q x), P q x) => P (p <> q :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

type PP (p <> q) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (p <> q) -> POpts -> x -> m (TT (PP (p <> q) x)) Source #

(PrintfArg (PP p x), Show (PP p x), PP s x ~ String, P s x, P p x) => P (Printf s p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

type PP (Printf s p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (Printf s p) -> POpts -> x -> m (TT (PP (Printf s p) x)) Source #

(PP p x ~ [a], PP q x ~ PP p x, P p x, P q x, Show a) => P (Intercalate p q :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

type PP (Intercalate p q) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (Intercalate p q) -> POpts -> x -> m (TT (PP (Intercalate p q) x)) Source #

(PP p a ~ [x], PP q a ~ [y], P p a, P q a, Show x, Show y) => P (ZipThese p q :: Type) a Source # 
Instance details

Defined in Predicate

Associated Types

type PP (ZipThese p q) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (ZipThese p q) -> POpts -> a -> m (TT (PP (ZipThese p q) a)) Source #

(Show x, P p x, Typeable (PP t (PP p x)), Show (PP t (PP p x)), FoldableWithIndex (PP t (PP p x)) f, PP p x ~ f a, Show a) => P (IToList' t p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

type PP (IToList' t p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (IToList' t p) -> POpts -> x -> m (TT (PP (IToList' t p) x)) Source #

(PP p a ~ String, PP p a ~ PP q a, P p a, P q a) => P (OrdI p q :: Type) a Source # 
Instance details

Defined in Predicate

Associated Types

type PP (OrdI p q) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (OrdI p q) -> POpts -> a -> m (TT (PP (OrdI p q) a)) Source #

(Ord (PP p a), PP p a ~ PP q a, P p a, Show (PP q a), P q a) => P (OrdP p q :: Type) a Source # 
Instance details

Defined in Predicate

Associated Types

type PP (OrdP p q) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (OrdP p q) -> POpts -> a -> m (TT (PP (OrdP p q) a)) Source #

(P p a, P q a, PP p a ~ Bool, PP q a ~ Bool) => P (p ~> q :: Type) a Source # 
Instance details

Defined in Predicate

Associated Types

type PP (p ~> q) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (p ~> q) -> POpts -> a -> m (TT (PP (p ~> q) a)) Source #

(P p a, P q a, PP p a ~ Bool, PP q a ~ Bool) => P (p || q :: Type) a Source # 
Instance details

Defined in Predicate

Associated Types

type PP (p || q) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (p || q) -> POpts -> a -> m (TT (PP (p || q) a)) Source #

(P p a, P q a, PP p a ~ Bool, PP q a ~ Bool) => P (p && q :: Type) a Source # 
Instance details

Defined in Predicate

Associated Types

type PP (p && q) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (p && q) -> POpts -> a -> m (TT (PP (p && q) a)) Source #

(Show (PP p a), Show (PP q (PP p a)), P p a, P q (PP p a)) => P (p >> q :: Type) a Source # 
Instance details

Defined in Predicate

Associated Types

type PP (p >> q) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (p >> q) -> POpts -> a -> m (TT (PP (p >> q) a)) Source #

(Show a, P prt a, PP prt a ~ String, P p a, PP p a ~ Bool) => P (Guard prt p :: Type) a Source # 
Instance details

Defined in Predicate

Associated Types

type PP (Guard prt p) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (Guard prt p) -> POpts -> a -> m (TT (PP (Guard prt p) a)) Source #

(PP p a ~ PP q a, P p a, P q a, Show (PP p a), Integral (PP p a)) => P (QuotRem p q :: Type) a Source # 
Instance details

Defined in Predicate

Associated Types

type PP (QuotRem p q) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (QuotRem p q) -> POpts -> a -> m (TT (PP (QuotRem p q) a)) Source #

(PP p a ~ PP q a, P p a, P q a, Show (PP p a), Integral (PP p a)) => P (DivMod p q :: Type) a Source # 
Instance details

Defined in Predicate

Associated Types

type PP (DivMod p q) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (DivMod p q) -> POpts -> a -> m (TT (PP (DivMod p q) a)) Source #

(PP p a ~ PP q a, P p a, P q a, Show (PP p a), Integral (PP p a)) => P (Mod p q :: Type) a Source # 
Instance details

Defined in Predicate

Associated Types

type PP (Mod p q) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (Mod p q) -> POpts -> a -> m (TT (PP (Mod p q) a)) Source #

(PP p a ~ PP q a, P p a, P q a, Show (PP p a), Integral (PP p a)) => P (Div p q :: Type) a Source # 
Instance details

Defined in Predicate

Associated Types

type PP (Div p q) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (Div p q) -> POpts -> a -> m (TT (PP (Div p q) a)) Source #

(P p x, P q ((String, x), Proxy (PP p x)), PP p x ~ PP q ((String, x), Proxy (PP p x))) => P (Catch p q :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

type PP (Catch p q) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (Catch p q) -> POpts -> x -> m (TT (PP (Catch p q) x)) Source #

(P prt a, PP prt a ~ String) => P (Fail t prt :: Type) a Source # 
Instance details

Defined in Predicate

Associated Types

type PP (Fail t prt) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (Fail t prt) -> POpts -> a -> m (TT (PP (Fail t prt) a)) Source #

(P p x, PP q a ~ [x], PP p x ~ Bool, P q a) => P (Break p q :: Type) a Source # 
Instance details

Defined in Predicate

Associated Types

type PP (Break p q) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (Break p q) -> POpts -> a -> m (TT (PP (Break p q) a)) Source #

(P p x, Show x, PP q a ~ [x], PP p x ~ Bool, P q a) => P (Partition p q :: Type) a Source # 
Instance details

Defined in Predicate

Associated Types

type PP (Partition p q) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (Partition p q) -> POpts -> a -> m (TT (PP (Partition p q) a)) Source #

(Show (PP p a), P p a, PP q x ~ f a, P q x, Show a, Show (f a), Foldable f) => P (Map p q :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

type PP (Map p q) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (Map p q) -> POpts -> x -> m (TT (PP (Map p q) x)) Source #

(PP q a ~ s, PP p s ~ Maybe (b, s), P q a, P p s, Show s, Show b) => P (Unfoldr p q :: Type) a Source # 
Instance details

Defined in Predicate

Associated Types

type PP (Unfoldr p q) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (Unfoldr p q) -> POpts -> a -> m (TT (PP (Unfoldr p q) a)) Source #

(P p x, P q x, PP p x ~ a, Show a, PP q x ~ a, Enum a) => P (EnumFromTo p q :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

type PP (EnumFromTo p q) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (EnumFromTo p q) -> POpts -> x -> m (TT (PP (EnumFromTo p q) x)) Source #

(P p x, P q x, Show (PP q x), Show (PP p x), Snoc (PP p x) (PP p x) (PP q x) (PP q x)) => P (p +: q :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

type PP (p +: q) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (p +: q) -> POpts -> x -> m (TT (PP (p +: q) x)) Source #

(P p x, P q x, Show (PP p x), Show (PP q x), Cons (PP q x) (PP q x) (PP p x) (PP p x)) => P (p :+ q :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

type PP (p :+ q) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (p :+ q) -> POpts -> x -> m (TT (PP (p :+ q) x)) Source #

(P q a, P p a, Show (PP p a), Ixed (PP p a), PP q a ~ Index (PP p a), Show (Index (PP p a)), Show (IxValue (PP p a))) => P (Lookup p q :: Type) a Source # 
Instance details

Defined in Predicate

Associated Types

type PP (Lookup p q) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (Lookup p q) -> POpts -> a -> m (TT (PP (Lookup p q) a)) Source #

(P p a, P q a, Show (PP p a), Show (PP q a)) => P (MkThese p q :: Type) a Source # 
Instance details

Defined in Predicate

Associated Types

type PP (MkThese p q) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (MkThese p q) -> POpts -> a -> m (TT (PP (MkThese p q) a)) Source #

(Show (PP p x), P p x) => P (MkThat' t p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

type PP (MkThat' t p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (MkThat' t p) -> POpts -> x -> m (TT (PP (MkThat' t p) x)) Source #

(Show (PP p x), P p x) => P (MkThis' t p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

type PP (MkThis' t p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (MkThis' t p) -> POpts -> x -> m (TT (PP (MkThis' t p) x)) Source #

(Show (PP p x), P p x) => P (MkRight' t p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

type PP (MkRight' t p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (MkRight' t p) -> POpts -> x -> m (TT (PP (MkRight' t p) x)) Source #

(Show (PP p x), P p x) => P (MkLeft' t p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

type PP (MkLeft' t p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (MkLeft' t p) -> POpts -> x -> m (TT (PP (MkLeft' t p) x)) Source #

(P n a, Integral (PP n a), Semigroup (PP p a), P p a, Show (PP p a)) => P (STimes n p :: Type) a Source # 
Instance details

Defined in Predicate

Associated Types

type PP (STimes n p) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (STimes n p) -> POpts -> a -> m (TT (PP (STimes n p) a)) Source #

([PP p a] ~ PP q a, P p a, P q a, Show (PP p a), Eq (PP p a)) => P (Elem p q :: Type) a Source # 
Instance details

Defined in Predicate

Associated Types

type PP (Elem p q) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (Elem p q) -> POpts -> a -> m (TT (PP (Elem p q) a)) Source #

(P def (Proxy (PP t a)), PP def (Proxy (PP t a)) ~ PP t a, Show a, Show (PP t a), Bounded (PP t a), Enum (PP t a), Integral a) => P (ToEnumB' t def :: Type) a Source # 
Instance details

Defined in Predicate

Associated Types

type PP (ToEnumB' t def) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (ToEnumB' t def) -> POpts -> a -> m (TT (PP (ToEnumB' t def) a)) Source #

(PP p x ~ a, P p x, Show a, Enum (PP t x), Show (PP t x), Integral a) => P (ToEnum' t p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

type PP (ToEnum' t p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (ToEnum' t p) -> POpts -> x -> m (TT (PP (ToEnum' t p) x)) Source #

(PP q x ~ a, P q x, P p (Proxy a), PP p (Proxy a) ~ a, Show a, Eq a, Bounded a, Enum a) => P (PredB p q :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

type PP (PredB p q) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (PredB p q) -> POpts -> x -> m (TT (PP (PredB p q) x)) Source #

(PP q x ~ a, P q x, P p (Proxy a), PP p (Proxy a) ~ a, Show a, Eq a, Bounded a, Enum a) => P (SuccB p q :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

type PP (SuccB p q) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (SuccB p q) -> POpts -> x -> m (TT (PP (SuccB p q) x)) Source #

(Show (PP p x), P p x, Unwrapped (PP s x) ~ PP p x, Wrapped (PP s x), Show (PP s x)) => P (Wrap' s p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

type PP (Wrap' s p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (Wrap' s p) -> POpts -> x -> m (TT (PP (Wrap' s p) x)) Source #

(Integral (PP p x), Integral (PP q x), Eq (PP q x), P p x, P q x, Show (PP p x), Show (PP q x)) => P (p % q :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

type PP (p % q) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (p % q) -> POpts -> x -> m (TT (PP (p % q) x)) Source #

(PP p a ~ PP q a, Eq (PP q a), P p a, P q a, Show (PP p a), Fractional (PP p a)) => P (DivF p q :: Type) a Source # 
Instance details

Defined in Predicate

Associated Types

type PP (DivF p q) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (DivF p q) -> POpts -> a -> m (TT (PP (DivF p q) a)) Source #

(PP p a ~ [b], P n a, P p a, Show b, Integral (PP n a)) => P (SplitAt n p :: Type) a Source # 
Instance details

Defined in Predicate

Associated Types

type PP (SplitAt n p) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (SplitAt n p) -> POpts -> a -> m (TT (PP (SplitAt n p) a)) Source #

(P ns x, P p x, PP p x ~ [a], Show n, Show a, PP ns x ~ [n], Integral n) => P (SplitAts ns p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

type PP (SplitAts ns p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (SplitAts ns p) -> POpts -> x -> m (TT (PP (SplitAts ns p) x)) Source #

(Show (PP p a), P b a, P p a, PP b a ~ Bool) => P (MaybeB b p :: Type) a Source # 
Instance details

Defined in Predicate

Associated Types

type PP (MaybeB b p) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (MaybeB b p) -> POpts -> a -> m (TT (PP (MaybeB b p) a)) Source #

(Show (PP p x), P p x, Show (PP t x), RealFrac (PP p x), Integral (PP t x)) => P (Floor' t p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

type PP (Floor' t p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (Floor' t p) -> POpts -> x -> m (TT (PP (Floor' t p) x)) Source #

(Show (PP p x), P p x, Show (PP t x), RealFrac (PP p x), Integral (PP t x)) => P (Ceiling' t p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

type PP (Ceiling' t p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (Ceiling' t p) -> POpts -> x -> m (TT (PP (Ceiling' t p) x)) Source #

(Show (PP p x), P p x, Show (PP t x), RealFrac (PP p x), Integral (PP t x)) => P (Truncate' t p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

type PP (Truncate' t p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (Truncate' t p) -> POpts -> x -> m (TT (PP (Truncate' t p) x)) Source #

(P r a, PP r a ~ Rational, Show (PP t a), Fractional (PP t a)) => P (FromRational' t r :: Type) a Source # 
Instance details

Defined in Predicate

Associated Types

type PP (FromRational' t r) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (FromRational' t r) -> POpts -> a -> m (TT (PP (FromRational' t r) a)) Source #

(Num (PP t a), Integral (PP n a), P n a, Show (PP t a), Show (PP n a)) => P (FromIntegral' t n :: Type) a Source # 
Instance details

Defined in Predicate

Associated Types

type PP (FromIntegral' t n) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (FromIntegral' t n) -> POpts -> a -> m (TT (PP (FromIntegral' t n) a)) Source #

(Num (PP t a), Integral (PP n a), P n a, Show (PP t a)) => P (FromInteger' t n :: Type) a Source # 
Instance details

Defined in Predicate

Associated Types

type PP (FromInteger' t n) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (FromInteger' t n) -> POpts -> a -> m (TT (PP (FromInteger' t n) a)) Source #

(P s a, PP s a ~ String, Show (PP t a), IsString (PP t a)) => P (FromStringP' t s :: Type) a Source # 
Instance details

Defined in Predicate

Associated Types

type PP (FromStringP' t s) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (FromStringP' t s) -> POpts -> a -> m (TT (PP (FromStringP' t s) a)) Source #

(P p (a, a), P q x, Show a, PP q x ~ [a], PP p (a, a) ~ Ordering) => P (SortBy p q :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

type PP (SortBy p q) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (SortBy p q) -> POpts -> x -> m (TT (PP (SortBy p q) x)) Source #

(P p x, PP p x ~ String, Typeable (PP t x), Show (PP t x), Read (PP t x)) => P (ReadP'' t p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

type PP (ReadP'' t p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (ReadP'' t p) -> POpts -> x -> m (TT (PP (ReadP'' t p) x)) Source #

(PP p x ~ String, FormatTime (PP q x), P p x, Show (PP q x), P q x) => P (FormatTimeP p q :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

type PP (FormatTimeP p q) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (FormatTimeP p q) -> POpts -> x -> m (TT (PP (FormatTimeP p q) x)) Source #

(P (ParaImpl (LenT (RepeatT n p)) strict (RepeatT n p)) [a], GetLen (RepeatT n p), GetBool strict) => P (ParaNImpl strict n p :: Type) [a] Source # 
Instance details

Defined in Predicate

Associated Types

type PP (ParaNImpl strict n p) [a] :: Type Source #

Methods

eval :: MonadEval m => Proxy (ParaNImpl strict n p) -> POpts -> [a] -> m (TT (PP (ParaNImpl strict n p) [a])) Source #

(TypeError (Text "ParaImpl '[] invalid: requires at least one value in the list") :: Constraint) => P (ParaImpl n strict ([] :: [k]) :: Type) [a] Source # 
Instance details

Defined in Predicate

Associated Types

type PP (ParaImpl n strict []) [a] :: Type Source #

Methods

eval :: MonadEval m => Proxy (ParaImpl n strict []) -> POpts -> [a] -> m (TT (PP (ParaImpl n strict []) [a])) Source #

(KnownNat n, GetBool strict, GetLen ps, P p a, P (ParaImpl n strict (p1 ': ps)) [a], PP (ParaImpl n strict (p1 ': ps)) [a] ~ [PP p a], Show a, Show (PP p a)) => P (ParaImpl n strict (p ': (p1 ': ps)) :: Type) [a] Source # 
Instance details

Defined in Predicate

Associated Types

type PP (ParaImpl n strict (p ': (p1 ': ps))) [a] :: Type Source #

Methods

eval :: MonadEval m => Proxy (ParaImpl n strict (p ': (p1 ': ps))) -> POpts -> [a] -> m (TT (PP (ParaImpl n strict (p ': (p1 ': ps))) [a])) Source #

(Show (PP p a), KnownNat n, GetBool strict, Show a, P p a) => P (ParaImpl n strict (p ': ([] :: [k])) :: Type) [a] Source # 
Instance details

Defined in Predicate

Associated Types

type PP (ParaImpl n strict (p ': [])) [a] :: Type Source #

Methods

eval :: MonadEval m => Proxy (ParaImpl n strict (p ': [])) -> POpts -> [a] -> m (TT (PP (ParaImpl n strict (p ': [])) [a])) Source #

(GetBool strict, GetLen ps, P (GuardsImpl (LenT ps) strict ps) [a]) => P (GuardsImplW strict ps :: Type) [a] Source # 
Instance details

Defined in Predicate

Associated Types

type PP (GuardsImplW strict ps) [a] :: Type Source #

Methods

eval :: MonadEval m => Proxy (GuardsImplW strict ps) -> POpts -> [a] -> m (TT (PP (GuardsImplW strict ps) [a])) Source #

(P q a, Show a, Show (PP q a), PP p (Proxy (PP q a)) ~ PP q a, P p (Proxy (PP q a))) => P (MaybeIn p q :: Type) (Maybe a) Source # 
Instance details

Defined in Predicate

Associated Types

type PP (MaybeIn p q) (Maybe a) :: Type Source #

Methods

eval :: MonadEval m => Proxy (MaybeIn p q) -> POpts -> Maybe a -> m (TT (PP (MaybeIn p q) (Maybe a))) Source #

(Show (PP p a), Show (PP q b), P p a, P q b, Show a, Show b) => P (p +++ q :: Type) (Either a b) Source # 
Instance details

Defined in Predicate

Associated Types

type PP (p +++ q) (Either a b) :: Type Source #

Methods

eval :: MonadEval m => Proxy (p +++ q) -> POpts -> Either a b -> m (TT (PP (p +++ q) (Either a b))) Source #

(Show (PP p a), P p a, P q b, PP p a ~ PP q b, Show a, Show b) => P (p ||| q :: Type) (Either a b) Source # 
Instance details

Defined in Predicate

Associated Types

type PP (p ||| q) (Either a b) :: Type Source #

Methods

eval :: MonadEval m => Proxy (p ||| q) -> POpts -> Either a b -> m (TT (PP (p ||| q) (Either a b))) Source #

(Show (PP p a), Show (PP q b), P p a, P q b, Show a, Show b) => P (p *** q :: Type) (a, b) Source # 
Instance details

Defined in Predicate

Associated Types

type PP (p *** q) (a, b) :: Type Source #

Methods

eval :: MonadEval m => Proxy (p *** q) -> POpts -> (a, b) -> m (TT (PP (p *** q) (a, b))) Source #

(GetBool r, PP p x ~ String, P p x, IsText (PP q x), P q x) => P (StripLR r p q :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

type PP (StripLR r p q) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (StripLR r p q) -> POpts -> x -> m (TT (PP (StripLR r p q) x)) Source #

(Typeable (PP t x), BetweenT 2 36 n, Show (PP t x), Num (PP t x), KnownNat n, PP p x ~ String, P p x) => P (ReadBase' t n p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

type PP (ReadBase' t n p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (ReadBase' t n p) -> POpts -> x -> m (TT (PP (ReadBase' t n p) x)) Source #

(PP p x ~ These a b, P p x, Show a, Show b, GetThese th) => P (IsTh th p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

type PP (IsTh th p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (IsTh th p) -> POpts -> x -> m (TT (PP (IsTh th p) x)) Source #

(PP p a ~ String, GetOrd o, PP p a ~ PP q a, P p a, P q a) => P (CmpI o p q :: Type) a Source # 
Instance details

Defined in Predicate

Associated Types

type PP (CmpI o p q) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (CmpI o p q) -> POpts -> a -> m (TT (PP (CmpI o p q) a)) Source #

(GetOrd o, Ord (PP p a), Show (PP p a), PP p a ~ PP q a, P p a, P q a) => P (Cmp o p q :: Type) a Source # 
Instance details

Defined in Predicate

Associated Types

type PP (Cmp o p q) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (Cmp o p q) -> POpts -> a -> m (TT (PP (Cmp o p q) a)) Source #

(GetBool keep, Eq a, Show a, P p x, P q x, PP p x ~ PP q x, PP q x ~ [a]) => P (KeepImpl keep p q :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

type PP (KeepImpl keep p q) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (KeepImpl keep p q) -> POpts -> x -> m (TT (PP (KeepImpl keep p q) x)) Source #

(GetBinOp op, PP p a ~ PP q a, P p a, P q a, Show (PP p a), Num (PP p a)) => P (Bin op p q :: Type) a Source # 
Instance details

Defined in Predicate

Associated Types

type PP (Bin op p q) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (Bin op p q) -> POpts -> a -> m (TT (PP (Bin op p q) a)) Source #

(GetROpts rs, PP p x ~ String, PP q x ~ String, P p x, P q x) => P (Resplit' rs p q :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

type PP (Resplit' rs p q) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (Resplit' rs p q) -> POpts -> x -> m (TT (PP (Resplit' rs p q) x)) Source #

(GetROpts rs, PP p x ~ String, PP q x ~ String, P p x, P q x) => P (RescanRanges' rs p q :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

type PP (RescanRanges' rs p q) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (RescanRanges' rs p q) -> POpts -> x -> m (TT (PP (RescanRanges' rs p q) x)) Source #

(GetROpts rs, PP p x ~ String, PP q x ~ String, P p x, P q x) => P (Rescan' rs p q :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

type PP (Rescan' rs p q) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (Rescan' rs p q) -> POpts -> x -> m (TT (PP (Rescan' rs p q) x)) Source #

(GetROpts rs, PP p x ~ String, PP q x ~ String, P p x, P q x) => P (Re' rs p q :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

type PP (Re' rs p q) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (Re' rs p q) -> POpts -> x -> m (TT (PP (Re' rs p q) x)) Source #

(KnownNat n, GetBool strict, Show a) => P (GuardsImpl n strict ([] :: [(k, k1)]) :: Type) [a] Source # 
Instance details

Defined in Predicate

Associated Types

type PP (GuardsImpl n strict []) [a] :: Type Source #

Methods

eval :: MonadEval m => Proxy (GuardsImpl n strict []) -> POpts -> [a] -> m (TT (PP (GuardsImpl n strict []) [a])) Source #

(PP prt (Int, a) ~ String, P prt (Int, a), KnownNat n, GetBool strict, GetLen ps, P p a, PP p a ~ Bool, P (GuardsImpl n strict ps) [a], PP (GuardsImpl n strict ps) [a] ~ [a], Show a) => P (GuardsImpl n strict ((,) prt p ': ps) :: Type) [a] Source # 
Instance details

Defined in Predicate

Associated Types

type PP (GuardsImpl n strict ((prt, p) ': ps)) [a] :: Type Source #

Methods

eval :: MonadEval m => Proxy (GuardsImpl n strict ((prt, p) ': ps)) -> POpts -> [a] -> m (TT (PP (GuardsImpl n strict ((prt, p) ': ps)) [a])) Source #

(GetBool ignore, P p x, P q x, PP p x ~ String, PP q x ~ String, GetOrdering cmp) => P (IsFixImpl cmp ignore p q :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

type PP (IsFixImpl cmp ignore p q) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (IsFixImpl cmp ignore p q) -> POpts -> x -> m (TT (PP (IsFixImpl cmp ignore p q) x)) Source #

(GetBool lc, GetBool rc, PP p a ~ [x], PP q a ~ [y], P p a, P q a, Show x, Show y) => P (Zip lc rc p q :: Type) a Source # 
Instance details

Defined in Predicate

Associated Types

type PP (Zip lc rc p q) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (Zip lc rc p q) -> POpts -> a -> m (TT (PP (Zip lc rc p q) a)) Source #

(Show (PP r a), P p a, PP p a ~ Bool, P q a, P r a, PP q a ~ PP r a) => P (If p q r :: Type) a Source # 
Instance details

Defined in Predicate

Associated Types

type PP (If p q r) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (If p q r) -> POpts -> a -> m (TT (PP (If p q r) a)) Source #

(PP p (b, a) ~ b, PP q x ~ b, PP r x ~ [a], P p (b, a), P q x, P r x, Show b, Show a) => P (Scanl p q r :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

type PP (Scanl p q r) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (Scanl p q r) -> POpts -> x -> m (TT (PP (Scanl p q r) x)) Source #

(P q a, P p a, Show (PP p a), Ixed (PP p a), PP q a ~ Index (PP p a), Show (Index (PP p a)), Show (IxValue (PP p a)), P r (Proxy (IxValue (PP p a))), PP r (Proxy (IxValue (PP p a))) ~ IxValue (PP p a)) => P (IxL p q r :: Type) a Source # 
Instance details

Defined in Predicate

Associated Types

type PP (IxL p q r) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (IxL p q r) -> POpts -> a -> m (TT (PP (IxL p q r) a)) Source #

(P r x, P p (x, a), P q (x, b), PP r x ~ Either a b, PP p (x, a) ~ c, PP q (x, b) ~ c) => P (EitherX p q r :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

type PP (EitherX p q r) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (EitherX p q r) -> POpts -> x -> m (TT (PP (EitherX p q r) x)) Source #

(P r x, P p (x, Proxy a), P q (x, a), PP r x ~ Maybe a, PP p (x, Proxy a) ~ b, PP q (x, a) ~ b) => P (MaybeXP p q r :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

type PP (MaybeXP p q r) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (MaybeXP p q r) -> POpts -> x -> m (TT (PP (MaybeXP p q r) x)) Source #

(Show (PP p a), P p a, Show (PP q a), P q a, P b a, PP b a ~ Bool) => P (EitherB b p q :: Type) a Source # 
Instance details

Defined in Predicate

Associated Types

type PP (EitherB b p q) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (EitherB b p q) -> POpts -> a -> m (TT (PP (EitherB b p q) a)) Source #

(P p x, P q x, P r x, PP p x ~ Int, PP q x ~ Int, PP r x ~ Int) => P (MkDay' p q r :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

type PP (MkDay' p q r) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (MkDay' p q r) -> POpts -> x -> m (TT (PP (MkDay' p q r) x)) Source #

(ParseTime (PP t a), Typeable (PP t a), Show (PP t a), P p a, P q a, PP p a ~ [String], PP q a ~ String) => P (ParseTimes' t p q :: Type) a Source # 
Instance details

Defined in Predicate

Associated Types

type PP (ParseTimes' t p q) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (ParseTimes' t p q) -> POpts -> a -> m (TT (PP (ParseTimes' t p q) a)) Source #

(ParseTime (PP t a), Typeable (PP t a), Show (PP t a), P p a, P q a, PP p a ~ String, PP q a ~ String) => P (ParseTimeP' t p q :: Type) a Source # 
Instance details

Defined in Predicate

Associated Types

type PP (ParseTimeP' t p q) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (ParseTimeP' t p q) -> POpts -> a -> m (TT (PP (ParseTimeP' t p q) a)) Source #

(GetBool strict, GetLen (ToGuardsT prt (RepeatT n p)), P (GuardsImpl (LenT (ToGuardsT prt (RepeatT n p))) strict (ToGuardsT prt (RepeatT n p))) [a]) => P (GuardsNImpl strict prt n p :: Type) [a] Source # 
Instance details

Defined in Predicate

Associated Types

type PP (GuardsNImpl strict prt n p) [a] :: Type Source #

Methods

eval :: MonadEval m => Proxy (GuardsNImpl strict prt n p) -> POpts -> [a] -> m (TT (PP (GuardsNImpl strict prt n p) [a])) Source #

(Show a, Show b, Show (PP p a), P p a, P q b, P r (a, b), PP p a ~ PP q b, PP p a ~ PP r (a, b), PP q b ~ PP r (a, b)) => P (TheseIn p q r :: Type) (These a b) Source # 
Instance details

Defined in Predicate

Associated Types

type PP (TheseIn p q r) (These a b) :: Type Source #

Methods

eval :: MonadEval m => Proxy (TheseIn p q r) -> POpts -> These a b -> m (TT (PP (TheseIn p q r) (These a b))) Source #

(P n a, GetBool left, Integral (PP n a), [PP p a] ~ PP q a, P p a, P q a, Show (PP p a)) => P (Pad left n p q :: Type) a Source # 
Instance details

Defined in Predicate

Associated Types

type PP (Pad left n p q) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (Pad left n p q) -> POpts -> a -> m (TT (PP (Pad left n p q) a)) Source #

(FailIfT (NotT (LenT ps == LenT qs)) (((Text "lengths are not the same " :<>: ShowType (LenT ps)) :<>: Text " vs ") :<>: ShowType (LenT qs)), P (CaseImpl (LenT ps) e ps qs r) x) => P (Case e ps qs r :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

type PP (Case e ps qs r) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (Case e ps qs r) -> POpts -> x -> m (TT (PP (Case e ps qs r) x)) Source #

(P s x, P p (x, a), P q (x, b), P r (x, (a, b)), PP s x ~ These a b, PP p (x, a) ~ c, PP q (x, b) ~ c, PP r (x, (a, b)) ~ c) => P (TheseX p q r s :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

type PP (TheseX p q r s) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (TheseX p q r s) -> POpts -> x -> m (TT (PP (TheseX p q r s) x)) Source #

(GetBool b, GetROpts rs, PP p x ~ String, PP q x ~ RR, PP r x ~ String, P p x, P q x, P r x) => P (ReplaceImpl b rs p q r :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

type PP (ReplaceImpl b rs p q r) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (ReplaceImpl b rs p q r) -> POpts -> x -> m (TT (PP (ReplaceImpl b rs p q r) x)) Source #

(KnownNat n, GetLen ps, P r x, P p (PP r x), P q (PP r x), PP p (PP r x) ~ Bool, Show (PP q (PP r x)), Show (PP r x), P (CaseImpl n e (p1 ': ps) (q1 ': qs) r) x, PP (CaseImpl n e (p1 ': ps) (q1 ': qs) r) x ~ PP q (PP r x)) => P (CaseImpl n e (p ': (p1 ': ps)) (q ': (q1 ': qs)) r :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

type PP (CaseImpl n e (p ': (p1 ': ps)) (q ': (q1 ': qs)) r) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (CaseImpl n e (p ': (p1 ': ps)) (q ': (q1 ': qs)) r) -> POpts -> x -> m (TT (PP (CaseImpl n e (p ': (p1 ': ps)) (q ': (q1 ': qs)) r) x)) Source #

(P r x, P q (PP r x), Show (PP q (PP r x)), P p (PP r x), PP p (PP r x) ~ Bool, KnownNat n, Show (PP r x), P e (PP r x, Proxy (PP q (PP r x))), PP e (PP r x, Proxy (PP q (PP r x))) ~ PP q (PP r x)) => P (CaseImpl n e (p ': ([] :: [k])) (q ': ([] :: [k1])) r :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

type PP (CaseImpl n e (p ': []) (q ': []) r) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (CaseImpl n e (p ': []) (q ': []) r) -> POpts -> x -> m (TT (PP (CaseImpl n e (p ': []) (q ': []) r) x)) Source #

(TypeError (Text "CaseImpl '[] invalid: lists are both empty") :: Constraint) => P (CaseImpl n e ([] :: [k]) ([] :: [k1]) r :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

type PP (CaseImpl n e [] [] r) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (CaseImpl n e [] [] r) -> POpts -> x -> m (TT (PP (CaseImpl n e [] [] r) x)) Source #

(TypeError (Text "CaseImpl '[] invalid: rhs requires at least one value in the list") :: Constraint) => P (CaseImpl n e (p ': ps) ([] :: [k1]) r :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

type PP (CaseImpl n e (p ': ps) [] r) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (CaseImpl n e (p ': ps) [] r) -> POpts -> x -> m (TT (PP (CaseImpl n e (p ': ps) [] r) x)) Source #

(TypeError (Text "CaseImpl '[] invalid: lhs requires at least one value in the list") :: Constraint) => P (CaseImpl n e ([] :: [k]) (q ': qs) r :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

type PP (CaseImpl n e [] (q ': qs) r) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (CaseImpl n e [] (q ': qs) r) -> POpts -> x -> m (TT (PP (CaseImpl n e [] (q ': qs) r) x)) Source #

Show a => P (Proxy :: Proxy t) a Source #

converts the value to the corresponding Proxy

>>> pl @'Proxy 'x'
Present Proxy
PresentT Proxy
Instance details

Defined in PredicateCore

Associated Types

type PP Proxy a :: Type Source #

Methods

eval :: MonadEval m => Proxy Proxy0 -> POpts -> a -> m (TT (PP Proxy0 a)) Source #

(Show a2, Show (PP p a2), P p a2) => P (Right p :: Either a1 b) (Either x a2) Source #

extracts the 'b' from type level 'Either a b' if the value exists

>>> pl @('Right Id) (Right 123)
Present 123
PresentT 123
>>> pl @('Right Id) (Left "aaa")
Error 'Right found Left
FailT "'Right found Left"
Instance details

Defined in PredicateCore

Associated Types

type PP (Right p) (Either x a2) :: Type Source #

Methods

eval :: MonadEval m => Proxy (Right p) -> POpts -> Either x a2 -> m (TT (PP (Right p) (Either x a2))) Source #

(Show a2, Show (PP p a2), P p a2) => P (Left p :: Either a1 b) (Either a2 x) Source #

extracts the 'a' from type level 'Either a b' if the value exists

>>> pl @('Left Id) (Left 123)
Present 123
PresentT 123
>>> pl @('Left Id) (Right "aaa")
Error 'Left found Right
FailT "'Left found Right"
Instance details

Defined in PredicateCore

Associated Types

type PP (Left p) (Either a2 x) :: Type Source #

Methods

eval :: MonadEval m => Proxy (Left p) -> POpts -> Either a2 x -> m (TT (PP (Left p) (Either a2 x))) Source #

(Show a2, Show (PP p a2), P p a2) => P (That p :: These a1 b) (These x a2) Source #

extracts the 'b' from type level 'These a b' if the value exists

>>> pl @('That Id) (That 123)
Present 123
PresentT 123
>>> pl @('That Id) (This "aaa")
Error 'That found This
FailT "'That found This"
>>> pl @('That Id) (These 44 "aaa")
Error 'That found These
FailT "'That found These"
Instance details

Defined in PredicateCore

Associated Types

type PP (That p) (These x a2) :: Type Source #

Methods

eval :: MonadEval m => Proxy (That p) -> POpts -> These x a2 -> m (TT (PP (That p) (These x a2))) Source #

(Show a2, Show (PP p a2), P p a2) => P (This p :: These a1 b) (These a2 x) Source #

extracts the 'a' from type level 'These a b' if the value exists

>>> pl @('This Id) (This 123)
Present 123
PresentT 123
>>> pl @('This Id) (That "aaa")
Error 'This found That
FailT "'This found That"
>>> pl @('This Id) (These 999 "aaa")
Error 'This found These
FailT "'This found These"
Instance details

Defined in PredicateCore

Associated Types

type PP (This p) (These a2 x) :: Type Source #

Methods

eval :: MonadEval m => Proxy (This p) -> POpts -> These a2 x -> m (TT (PP (This p) (These a2 x))) Source #

(P p a, P q a) => P ((,) p q :: (k2, k1)) a Source #

run the predicates in a promoted 2-tuple; similar to &&&

>>> pl @'(Id, 4) "hello"
Present ("hello",4)
PresentT ("hello",4)
Instance details

Defined in PredicateCore

Associated Types

type PP (p, q) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (p, q) -> POpts -> a -> m (TT (PP (p, q) a)) Source #

(Show a2, Show b2, P p a2, P q b2, Show (PP p a2), Show (PP q b2)) => P (These p q :: These a1 b1) (These a2 b2) Source #

extracts the (a,b) from type level 'These a b' if the value exists

>>> pl @('These Id Id) (These 123 "abc")
Present (123,"abc")
PresentT (123,"abc")
>>> pl @('These Id 5) (These 123 "abcde")
Present (123,5)
PresentT (123,5)
>>> pl @('These Id Id) (This "aaa")
Error 'These found This
FailT "'These found This"
>>> pl @('These Id Id) (That "aaa")
Error 'These found That
FailT "'These found That"
Instance details

Defined in PredicateCore

Associated Types

type PP (These p q) (These a2 b2) :: Type Source #

Methods

eval :: MonadEval m => Proxy (These0 p q) -> POpts -> These a2 b2 -> m (TT (PP (These0 p q) (These a2 b2))) Source #

(P p a, P q a, P r a) => P ((,,) p q r :: (k3, k2, k1)) a Source #

run the predicates in a promoted 3-tuple

>>> pl @'(4, Id, "goodbye") "hello"
Present (4,"hello","goodbye")
PresentT (4,"hello","goodbye")
Instance details

Defined in PredicateCore

Associated Types

type PP (p, q, r) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (p, q, r) -> POpts -> a -> m (TT (PP (p, q, r) a)) Source #

(P p a, P q a, P r a, P s a) => P ((,,,) p q r s :: (k4, k3, k2, k1)) a Source #

run the predicates in a promoted 4-tuple

>>> pl @'(4, Id, "inj", 999) "hello"
Present (4,"hello","inj",999)
PresentT (4,"hello","inj",999)
Instance details

Defined in PredicateCore

Associated Types

type PP (p, q, r, s) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (p, q, r, s) -> POpts -> a -> m (TT (PP (p, q, r, s) a)) Source #

evalBool :: (MonadEval m, P p a, PP p a ~ Bool) => Proxy p -> POpts -> a -> m (TT (PP p a)) Source #

A specialised form of eval that works only on predicates

data I Source #

identity function

>>> pl @I 23
Present 23
PresentT 23
Instances
P I a Source # 
Instance details

Defined in PredicateCore

Associated Types

type PP I a :: Type Source #

Methods

eval :: MonadEval m => Proxy I -> POpts -> a -> m (TT (PP I a)) Source #

type PP I a Source # 
Instance details

Defined in PredicateCore

type PP I a = a

data Id Source #

identity function that displays the input unlike I

even more constraints than I so we might need to add explicit type signatures

>>> pl @Id 23
Present 23
PresentT 23
Instances
Show a => P Id a Source # 
Instance details

Defined in PredicateCore

Associated Types

type PP Id a :: Type Source #

Methods

eval :: MonadEval m => Proxy Id -> POpts -> a -> m (TT (PP Id a)) Source #

type PP Id a Source # 
Instance details

Defined in PredicateCore

type PP Id a = a

data IdT Source #

identity function that also displays the type information for debugging

>>> pl @IdT 23
Present 23
PresentT 23
Instances
(Typeable a, Show a) => P IdT a Source # 
Instance details

Defined in PredicateCore

Associated Types

type PP IdT a :: Type Source #

Methods

eval :: MonadEval m => Proxy IdT -> POpts -> a -> m (TT (PP IdT a)) Source #

type PP IdT a Source # 
Instance details

Defined in PredicateCore

type PP IdT a = a

data W (p :: k) Source #

transparent predicate wrapper to make k of kind Type so it can be in a promoted list (cant mix kinds) see Do

>>> pl @'[W 123, Id] 99
Present [123,99]
PresentT [123,99]
Instances
P p a => P (W p :: Type) a Source # 
Instance details

Defined in PredicateCore

Associated Types

type PP (W p) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (W p) -> POpts -> a -> m (TT (PP (W p) a)) Source #

type PP (W p :: Type) a Source # 
Instance details

Defined in PredicateCore

type PP (W p :: Type) a = PP p a

data Msg prt p Source #

add a message to give more context to the evaluation tree

>>> pe @(Msg "[somemessage] " Id) 999
P [somemessage] Id 999
PresentT 999
Instances
(P prt a, PP prt a ~ String, P p a) => P (Msg prt p :: Type) a Source # 
Instance details

Defined in PredicateCore

Associated Types

type PP (Msg prt p) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (Msg prt p) -> POpts -> a -> m (TT (PP (Msg prt p) a)) Source #

type PP (Msg prt p :: Type) a Source # 
Instance details

Defined in PredicateCore

type PP (Msg prt p :: Type) a = PP p a

pe :: forall p a. (Show (PP p a), P p a) => a -> IO (BoolT (PP p a)) Source #

displays the evaluation tree in plain text without colors

pe2 :: forall p a. (Show (PP p a), P p a) => a -> IO (BoolT (PP p a)) Source #

displays the evaluation tree using colors

pe2n :: forall p a. (Show (PP p a), P p a) => a -> IO (BoolT (PP p a)) Source #

same as pe2 but truncates the display tree horizontally: see o2n

pu :: forall p a. (Show (PP p a), P p a) => a -> IO (BoolT (PP p a)) Source #

display the evaluation tree using unicode and colors pu '(Id, "abc", 123) [1..4] @

pun :: forall p a. (Show (PP p a), P p a) => a -> IO (BoolT (PP p a)) Source #

same as pu but truncates the display tree horizontally: see ou

pe3 :: forall p a. (Show (PP p a), P p a) => a -> IO (BoolT (PP p a)) Source #

pl :: forall p a. (Show (PP p a), P p a) => a -> IO (BoolT (PP p a)) Source #

skips the evaluation tree and just displays the end result

plc :: forall p a. (Show (PP p a), P p a) => a -> IO (BoolT (PP p a)) Source #

same as pl but with colors

peWith :: forall p a. (Show (PP p a), P p a) => POpts -> a -> IO (BoolT (PP p a)) Source #

runPQ :: (P p a, P q a, MonadEval m) => String -> Proxy p -> Proxy q -> POpts -> a -> m (Either (TT x) (PP p a, PP q a, TT (PP p a), TT (PP q a))) Source #