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

Safe HaskellNone
LanguageHaskell2010

Predicate.Core

Contents

Description

Dsl for evaluating and displaying type level expressions

Synopsis

basic types

data I Source #

identity function

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

Defined in Predicate.Core

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 Predicate.Core

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

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

Defined in Predicate.Core

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 Predicate.Core

type PP Id a = a

data IdT Source #

identity function that also displays the type information for debugging

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

Defined in Predicate.Core

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 Predicate.Core

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

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

Defined in Predicate.Core

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 Predicate.Core

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
>>> pe @(Msg Id 999) "info message:"
P info message:'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 Predicate.Core

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 Predicate.Core

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

display evaluation tree

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 width: 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 width: see ou

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

same as pe2 but allows for wider data

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

same as pz but adds context to the end result

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

same as pz but with colors

pz :: 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

P class

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

>>> pz @'True "not used"
True
TrueT
>>> pz @'False ()
False
FalseT
Instance details

Defined in Predicate.Core

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

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

Defined in Predicate.Core

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

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

Defined in Predicate.Core

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 as a String

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

Defined in Predicate.Core

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 '()

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

Defined in Predicate.Core

Associated Types

type PP () a :: Type Source #

Methods

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

P () a Source #

const () function

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

Defined in Predicate.Core

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 Predicate.Core

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 Predicate.Core

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 Predicate.Core

Associated Types

type PP I a :: Type Source #

Methods

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

P SapAT x => P SapA x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP SapA x :: Type Source #

Methods

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

P Stdin x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP Stdin x :: Type Source #

Methods

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

P TimeZt a Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP TimeZt a :: Type Source #

Methods

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

P TimeUtc a Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP TimeUtc a :: Type Source #

Methods

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

P ReadEnvAll a Source # 
Instance details

Defined in Predicate.Prelude

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.Prelude

Associated Types

type PP ToListExt l :: Type Source #

Methods

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

P OddT x => P Odd x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP Odd x :: Type Source #

Methods

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

P EvenT x => P Even x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP Even x :: Type Source #

Methods

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

P ThesesT x => P Theses x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP Theses x :: Type Source #

Methods

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

P ThatsT x => P Thats x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP Thats x :: Type Source #

Methods

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

P ThissT x => P Thiss x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP Thiss x :: Type Source #

Methods

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

P NullT a => P Null a Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP Null a :: Type Source #

Methods

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

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

Defined in Predicate.Prelude

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.Prelude

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.Prelude

Associated Types

type PP Uncons s :: Type Source #

Methods

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

P MEmptyPT x => P MEmptyP x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP MEmptyP x :: Type Source #

Methods

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

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

Defined in Predicate.Prelude

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.Prelude

Associated Types

type PP Reverse as :: Type Source #

Methods

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

Show x => P Dup x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP Dup x :: Type Source #

Methods

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

Show a => P MkProxy a Source # 
Instance details

Defined in Predicate.Prelude

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.Prelude

Associated Types

type PP Len as :: Type Source #

Methods

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

P MkDayT x => P MkDay x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP MkDay x :: Type Source #

Methods

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

([a] ~ x, Show a) => P Tails x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP Tails x :: Type Source #

Methods

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

([a] ~ x, Show a) => P Inits x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP Inits x :: Type Source #

Methods

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

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

Defined in Predicate.Prelude

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.Prelude

Associated Types

type PP ToLower a :: Type Source #

Methods

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

P IsLatin1AllT x => P IsLatin1All x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP IsLatin1All x :: Type Source #

Methods

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

P IsSeparatorAllT x => P IsSeparatorAll x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP IsSeparatorAll x :: Type Source #

Methods

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

P IsOctDigitAllT x => P IsOctDigitAll x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP IsOctDigitAll x :: Type Source #

Methods

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

P IsHexDigitAllT x => P IsHexDigitAll x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP IsHexDigitAll x :: Type Source #

Methods

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

P IsControlAllT x => P IsControlAll x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP IsControlAll x :: Type Source #

Methods

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

P IsPunctuationAllT x => P IsPunctuationAll x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP IsPunctuationAll x :: Type Source #

P IsSpaceAllT x => P IsSpaceAll x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP IsSpaceAll x :: Type Source #

Methods

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

P IsNumberAllT x => P IsNumberAll x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP IsNumberAll x :: Type Source #

Methods

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

P IsUpperAllT x => P IsUpperAll x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP IsUpperAll x :: Type Source #

Methods

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

P IsLowerAllT x => P IsLowerAll x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP IsLowerAll x :: Type Source #

Methods

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

P IsLatin1T x => P IsLatin1 x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP IsLatin1 x :: Type Source #

Methods

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

P IsSeparatorT x => P IsSeparator x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP IsSeparator x :: Type Source #

Methods

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

P IsOctDigitT x => P IsOctDigit x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP IsOctDigit x :: Type Source #

Methods

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

P IsHexDigitT x => P IsHexDigit x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP IsHexDigit x :: Type Source #

Methods

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

P IsControlT x => P IsControl x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP IsControl x :: Type Source #

Methods

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

P IsPunctuationT x => P IsPunctuation x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP IsPunctuation x :: Type Source #

Methods

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

P IsSpaceT x => P IsSpace x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP IsSpace x :: Type Source #

Methods

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

P IsNumberT x => P IsNumber x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP IsNumber x :: Type Source #

Methods

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

P IsUpperT x => P IsUpper x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP IsUpper x :: Type Source #

Methods

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

P IsLowerT x => P IsLower x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP IsLower x :: Type Source #

Methods

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

P Unzip3T x => P Unzip3 x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP Unzip3 x :: Type Source #

Methods

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

P UnzipT x => P Unzip x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP Unzip x :: Type Source #

Methods

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

P AllNegativeT x => P AllNegative x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP AllNegative x :: Type Source #

Methods

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

P AllPositiveT x => P AllPositive x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP AllPositive x :: Type Source #

Methods

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

P DescT' x => P Desc' x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP Desc' x :: Type Source #

Methods

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

P DescT x => P Desc x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP Desc x :: Type Source #

Methods

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

P AscT' x => P Asc' x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP Asc' x :: Type Source #

Methods

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

P AscT x => P Asc x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP Asc x :: Type Source #

Methods

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

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

Defined in Predicate.Prelude

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.Prelude

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.Prelude

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.Prelude

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.Prelude

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.Prelude

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.Prelude

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.Prelude

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 FMapSnd (f (x, a)) Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

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

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

Defined in Predicate.Prelude

Associated Types

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

Methods

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

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

Defined in Predicate.Prelude

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.Prelude

Associated Types

type PP Min [a] :: Type Source #

Methods

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

(Num a, Show a) => P Product [a] Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP Product [a] :: Type Source #

Methods

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

(Num a, Show a) => P Sum [a] Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP Sum [a] :: Type Source #

Methods

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

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

Defined in Predicate.Prelude

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 #

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

Defined in Predicate.Prelude

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)), AssocC p) => P Assoc (p (p a b) c) Source # 
Instance details

Defined in Predicate.Prelude

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), SwapC p, Show (p b a)) => P Swap (p a b) Source # 
Instance details

Defined in Predicate.Prelude

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 '[]

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

Defined in Predicate.Core

Associated Types

type PP [] a :: Type Source #

Methods

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

P (SapAT' t) x => P (SapA' t :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

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

(KnownSymbol s, CmpSymbol s "" ~ GT) => P (Char1 s :: Type) a Source # 
Instance details

Defined in Predicate.Prelude

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 #

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

Defined in Predicate.Prelude

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 #

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

Defined in Predicate.Prelude

Associated Types

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

Methods

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

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

Defined in Predicate.Prelude

Associated Types

type PP (FromList t) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (FromList t) -> POpts -> x -> m (TT (PP (FromList t) x)) 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 ParseTimeP, ReadBase

Instance details

Defined in Predicate.Prelude

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 #

P (IxT' n) x => P (Ix' n :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (Ix' n) x :: Type Source #

Methods

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

P (ProxyT t :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (ProxyT t) x :: Type Source #

Methods

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

P (MkNothing t :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (MkNothing t) x :: Type Source #

Methods

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

P (MEmptyTT t) x => P (MEmptyT t :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (MEmptyT t) x :: Type Source #

Methods

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

P (ToEnumBFailT t) x => P (ToEnumBFail t :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (ToEnumBFail t) x :: Type Source #

Methods

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

P (MEmpty2T t) x => P (MEmpty2 t :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (MEmpty2 t) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (MEmpty2 t) -> POpts -> x -> m (TT (PP (MEmpty2 t) x)) 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 '()'

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

Defined in Predicate.Core

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 #

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

Defined in Predicate.Prelude

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 Predicate.Core

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 Predicate.Core

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 #

(ToStringC (PP p x), P p x) => P (ToString p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

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

(ToJSON (PP p x), P p x) => P (EncodeJson p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

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

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

Defined in Predicate.Prelude

Associated Types

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

Methods

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

P (RDotExpandT ps q) a => P (RDot ps q :: Type) a Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (RDot ps q) a :: Type Source #

Methods

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

P (DotExpandT ps q) a => P (Dot ps q :: Type) a Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (Dot ps q) a :: Type Source #

Methods

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

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

Defined in Predicate.Prelude

Associated Types

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

Methods

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

(Show s, Snoc s s (ConsT s) (ConsT s), PP p x ~ s, P p x) => P (Init p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

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

(Show (ConsT s), Show s, Snoc s s (ConsT s) (ConsT s), PP p x ~ s, P p x) => P (Last p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

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

(Show s, Cons s s (ConsT s) (ConsT s), PP p x ~ s, P p x) => P (Tail p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

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

(Show (ConsT s), Show s, Cons s s (ConsT s) (ConsT s), PP p x ~ s, P p x) => P (Head p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

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

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

Defined in Predicate.Prelude

Associated Types

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

Methods

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

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

Defined in Predicate.Prelude

Associated Types

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

Methods

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

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

Defined in Predicate.Prelude

Associated Types

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

Methods

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

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

Defined in Predicate.Prelude

Associated Types

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

Methods

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

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

Defined in Predicate.Prelude

Associated Types

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

Methods

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

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

Defined in Predicate.Prelude

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 #

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

Defined in Predicate.Prelude

Associated Types

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

Methods

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

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

Defined in Predicate.Prelude

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 #

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

Defined in Predicate.Prelude

Associated Types

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

Methods

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

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

Defined in Predicate.Prelude

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.Prelude

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 #

([a] ~ x, GetLen ps, P (ParaImpl (LenT ps) ps) x) => P (Para ps :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (Para ps) x :: Type Source #

Methods

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

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

Defined in Predicate.Prelude

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 p x => P (Singleton p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

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

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

Defined in Predicate.Prelude

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 #

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

Defined in Predicate.Prelude

Associated Types

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

Methods

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

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

Defined in Predicate.Prelude

Associated Types

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

Methods

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

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

Defined in Predicate.Prelude

Associated Types

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

Methods

eval :: MonadEval m => Proxy (IsThis p) -> POpts -> x -> m (TT (PP (IsThis p) 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.Prelude

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 #

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

Defined in Predicate.Prelude

Associated Types

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

Methods

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

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

Defined in Predicate.Prelude

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 #

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

Defined in Predicate.Prelude

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.Prelude

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 #

P (Fail Unproxy p) x => P (Failp p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

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

P (Fail I p) x => P (FailS p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

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

P (ScanNAT q) x => P (ScanNA q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (ScanNA q) x :: Type Source #

Methods

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

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

Defined in Predicate.Prelude

Associated Types

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

Methods

eval :: MonadEval m => Proxy (Null' p) -> POpts -> x -> m (TT (PP (Null' p) x)) 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.Prelude

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.Prelude

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 #

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

Defined in Predicate.Prelude

Associated Types

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

Methods

eval :: MonadEval m => Proxy (ProxyT' t) -> POpts -> x -> m (TT (PP (ProxyT' t) x)) 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.Prelude

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.Prelude

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.Prelude

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.Prelude

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.Prelude

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 #

P (CatMaybesT q) x => P (CatMaybes q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (CatMaybes q) x :: Type Source #

Methods

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

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

Defined in Predicate.Prelude

Associated Types

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

Methods

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

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

Defined in Predicate.Prelude

Associated Types

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

Methods

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

P (TheseT' p) x => P (These' p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

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

P (ThatT' p) x => P (That' p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

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

P (ThisT' p) x => P (This' p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

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

P (RightT' p) x => P (Right' p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

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

P (LeftT' p) x => P (Left' p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

eval :: MonadEval m => Proxy (Left' p) -> POpts -> x -> m (TT (PP (Left' 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.Prelude

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.Prelude

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.Prelude

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.Prelude

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 #

P (PredBT' q) x => P (PredB' q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

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

P (SuccBT' q) x => P (SuccB' q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

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

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

Defined in Predicate.Prelude

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.Prelude

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.Prelude

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.Prelude

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.Prelude

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 p x, PP p x ~ Either a b) => P (IsRight p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

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

(P p x, PP p x ~ Either a b) => P (IsLeft p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

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

P (SecondT q) x => P (Second q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (Second q) x :: Type Source #

Methods

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

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

Defined in Predicate.Prelude

Associated Types

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

Methods

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

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

Defined in Predicate.Prelude

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.Prelude

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.Prelude

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.Prelude

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.Prelude

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 #

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

Defined in Predicate.Prelude

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 (ExtractL3T (PP p x)), ExtractL3C (PP p x), P p x, Show (PP p x)) => P (Thd p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

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

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

Defined in Predicate.Prelude

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 (ExtractL2T (PP p x)), ExtractL2C (PP p x), P p x, Show (PP p x)) => P (Snd p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

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

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

Defined in Predicate.Prelude

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 #

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

Defined in Predicate.Prelude

Associated Types

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

Methods

eval :: MonadEval m => Proxy (Fst p) -> POpts -> x -> m (TT (PP (Fst 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.Prelude

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.Prelude

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.Prelude

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.Prelude

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 (ReplaceFn3 p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

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

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

Defined in Predicate.Prelude

Associated Types

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

Methods

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

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

Defined in Predicate.Prelude

Associated Types

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

Methods

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

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

Defined in Predicate.Prelude

Associated Types

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

Methods

eval :: MonadEval m => Proxy (ReplaceFn p) -> POpts -> x -> m (TT (PP (ReplaceFn 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

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

Defined in Predicate.Core

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 (f a), Show (f (PP t (f a))), Functor f, Monoid (PP t (f a))) => P (MEmpty2' t :: Type) (f a) Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

eval :: MonadEval m => Proxy (MEmpty2' t) -> POpts -> f a -> m (TT (PP (MEmpty2' 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.Prelude

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 Predicate.Core

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

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

Defined in Predicate.Core

Associated Types

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

Methods

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

P (ParseJsonFileT t p) x => P (ParseJsonFile t p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

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

P (ParseJsonT t p) x => P (ParseJson t p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

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

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

Defined in Predicate.Prelude

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.Prelude

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 #

P (WriteFileT s p) x => P (WriteFile s p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

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

P (WriteFileT' s p) x => P (WriteFile' s p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

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

P (AppendFileT s p) x => P (AppendFile s p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

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

(P (ParaImpl (LenT (RepeatT n p)) (RepeatT n p)) x, GetLen (RepeatT n p), x ~ [a]) => P (ParaN n p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (ParaN n p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (ParaN n p) -> POpts -> x -> m (TT (PP (ParaN n p) x)) 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.Prelude

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 (IToListT t p) x => P (IToList t p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

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 #

([a] ~ x, GetLen ps, P (BoolsImpl (LenT ps) ps) x, PP (BoolsImpl (LenT ps) ps) x ~ Bool) => P (Bools ps :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (Bools ps) x :: Type Source #

Methods

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

([a] ~ x, GetLen ps, P (GuardsImpl (LenT ps) ps) x) => P (Guards ps :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (Guards ps) x :: Type Source #

Methods

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

P (Fail (Hole t) p) x => P (Failt t p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

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

P (FoldMapT t p) x => P (FoldMap t p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

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

P (MkThatT t p) x => P (MkThat t p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

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 #

P (MkThisT t p) x => P (MkThis t p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

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 #

P (MkRightT t p) x => P (MkRight t p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

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 #

P (MkLeftT t p) x => P (MkLeft t p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

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 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.Prelude

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.Prelude

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 #

P (ToEnumBDefT t def) x => P (ToEnumBDef t def :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (ToEnumBDef t def) x :: Type Source #

Methods

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

P (ToEnumT t p) x => P (ToEnum t p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

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 #

P (WrapT t p) x => P (Wrap t p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

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

P (FloorT t p) x => P (Floor t p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

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 #

P (CeilingT t p) x => P (Ceiling t p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

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 #

P (TruncateT t p) x => P (Truncate t p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

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 (FromRationalT t p) x => P (FromRational t p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

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

P (FromIntegralT t p) x => P (FromIntegral t p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

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

P (FromIntegerT t p) x => P (FromInteger t p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

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

P (FromStringPT t p) x => P (FromString t p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

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

P (ReadQT t p) x => P (ReadQ t p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

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

P (ReadMaybeT t p) x => P (ReadMaybe t p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

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

P (ReadPT t p) x => P (ReadP t p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

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 #

(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.Prelude

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 Predicate.Core

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 #

P (RotateT n p) x => P (Rotate n p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (Rotate n p) x :: Type Source #

Methods

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

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

Defined in Predicate.Prelude

Associated Types

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

Methods

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

P (OrAT p q) x => P (p |+ q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

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 (AndAT p q) x => P (p &* q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

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 x ~ String, P p x, ToJSON (PP q x), P q x) => P (EncodeJsonFile p q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

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

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

Defined in Predicate.Prelude

Associated Types

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

Methods

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

(P p x, PP p x ~ ByteString, Typeable (PP t x), Show (PP t x), FromJSON (PP t x)) => P (ParseJson' t p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

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

(ExtractL1C (PP q x), ExtractL2C (PP q x), P p (ExtractL1T (PP q x)), P p (ExtractL2T (PP q x)), P q x) => P (Both p q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

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

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

Defined in Predicate.Prelude

Associated Types

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

Methods

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

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

Defined in Predicate.Prelude

Associated Types

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

Methods

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

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

Defined in Predicate.Prelude

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 #

(PP p x ~ String, PP q x ~ These a b, P p x, P q x) => P (TheseFail p q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

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

(PP p x ~ String, PP q x ~ These a b, P p x, P q x) => P (ThatFail p q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

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

(PP p x ~ String, PP q x ~ These a b, P p x, P q x) => P (ThisFail p q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

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

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

Defined in Predicate.Prelude

Associated Types

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

Methods

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

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

Defined in Predicate.Prelude

Associated Types

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

Methods

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

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

Defined in Predicate.Prelude

Associated Types

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

Methods

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

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

Defined in Predicate.Prelude

Associated Types

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

Methods

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

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

Defined in Predicate.Prelude

Associated Types

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

Methods

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

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

Defined in Predicate.Prelude

Associated Types

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

Methods

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

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

Defined in Predicate.Prelude

Associated Types

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

Methods

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

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

Defined in Predicate.Prelude

Associated Types

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

Methods

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

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

Defined in Predicate.Prelude

Associated Types

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

Methods

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

P (StripRT p q) x => P (StripR p q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

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

P (StripLT p q) x => P (StripL p q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

eval :: MonadEval m => Proxy (StripL p q) -> POpts -> x -> m (TT (PP (StripL p q) 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.Prelude

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.Prelude

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.Prelude

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 (ArrowRT p q) x => P (p *> q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

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.Prelude

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.Prelude

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 #

(PrintC bs, (b, bs) ~ InductTupleP y, InductTupleC y, PrintfArg b, PP s x ~ String, PP p x ~ y, P s x, P p x, CheckT (PP p x) ~ True) => P (PrintT s p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

eval :: MonadEval m => Proxy (PrintT s p) -> POpts -> x -> m (TT (PP (PrintT 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.Prelude

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 (IsSuffixIT p q) x => P (IsSuffixI p q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

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

P (IsInfixIT p q) x => P (IsInfixI p q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

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

P (IsPrefixIT p q) x => P (IsPrefixI p q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

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

P (IsSuffixT p q) x => P (IsSuffix p q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

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

P (IsInfixT p q) x => P (IsInfix p q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

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

P (IsPrefixT p q) x => P (IsPrefix p q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

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

P (TraverseT p q) x => P (Traverse p q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

eval :: MonadEval m => Proxy (Traverse p q) -> POpts -> x -> m (TT (PP (Traverse 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.Prelude

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.Prelude

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 #

P (ReadBaseT t n p) x => P (ReadBase t n p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

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 a ~ [x], PP q a ~ [y], P p a, P q a, Show x, Show y) => P (Zip p q :: Type) a Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

eval :: MonadEval m => Proxy (Zip p q) -> POpts -> a -> m (TT (PP (Zip p q) a)) 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.Prelude

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 #

P (TheseIdT p q) x => P (TheseId p q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

eval :: MonadEval m => Proxy (TheseId p q) -> POpts -> x -> m (TT (PP (TheseId p q) x)) 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.Prelude

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 (p ===~ q :: Type) a Source # 
Instance details

Defined in Predicate.Prelude

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 (OrdAT' p q) x => P (OrdA' p q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

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

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

Defined in Predicate.Prelude

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.Prelude

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.Prelude

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.Prelude

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 (LeftArrowsT p q) x => P (p << q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

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 (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.Prelude

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 (SkipBothT p q) x => P (p >|> q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

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 (SkipRT p q) x => P (p >| q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

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 (SkipLT p q) x => P (p |> q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

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 (ExitWhenT prt p) x => P (ExitWhen prt p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (ExitWhen prt p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (ExitWhen prt p) -> POpts -> x -> m (TT (PP (ExitWhen prt p) x)) 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.Prelude

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 (Bools (ToGuardsT prt ps)) x ~ Bool, P (BoolsQuickT prt ps) x) => P (BoolsQuick prt ps :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (BoolsQuick prt ps) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (BoolsQuick prt ps) -> POpts -> x -> m (TT (PP (BoolsQuick prt ps) x)) Source #

P (GuardsQuickT prt ps) x => P (GuardsQuick prt ps :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (GuardsQuick prt ps) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (GuardsQuick prt ps) -> POpts -> x -> m (TT (PP (GuardsQuick prt ps) x)) Source #

P (RemT p q) x => P (Rem p q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

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

P (QuotT p q) x => P (Quot p q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

eval :: MonadEval m => Proxy (Quot p q) -> POpts -> x -> m (TT (PP (Quot p q) x)) 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.Prelude

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.Prelude

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.Prelude

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.Prelude

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 (CatchT' p s) x => P (Catch' p s :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

eval :: MonadEval m => Proxy (Catch' p s) -> POpts -> x -> m (TT (PP (Catch' p s) x)) 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.Prelude

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.Prelude

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 (SpanT p q) x => P (Span p q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

eval :: MonadEval m => Proxy (Span p q) -> POpts -> x -> m (TT (PP (Span p q) x)) 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.Prelude

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 (FilterT p q) x => P (Filter p q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

eval :: MonadEval m => Proxy (Filter p q) -> POpts -> x -> m (TT (PP (Filter p q) x)) 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.Prelude

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 #

P (ConcatMapT p q) x => P (ConcatMap p q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

eval :: MonadEval m => Proxy (ConcatMap p q) -> POpts -> x -> m (TT (PP (ConcatMap p q) x)) 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.Prelude

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 #

P (IterateWhileT p f) x => P (IterateWhile p f :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (IterateWhile p f) x :: Type Source #

Methods

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

P (IterateUntilT p f) x => P (IterateUntil p f :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (IterateUntil p f) x :: Type Source #

Methods

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

P (IterateNT n f) x => P (IterateN n f :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (IterateN n f) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (IterateN n f) -> POpts -> x -> m (TT (PP (IterateN n f) 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.Prelude

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.Prelude

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.Prelude

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.Prelude

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.Prelude

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 (BangBangT p q) a => P (p !! q :: Type) a Source # 
Instance details

Defined in Predicate.Prelude

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, Show (t a), PP p x ~ t a, P p x, Integral (PP n x), P n x, Foldable t) => P (Cycle n p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (Cycle n p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (Cycle n p) -> POpts -> x -> m (TT (PP (Cycle n p) x)) 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.Prelude

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.Prelude

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.Prelude

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.Prelude

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.Prelude

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.Prelude

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 #

P (MapMaybeT p q) x => P (MapMaybe p q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

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

P (InitFailT msg q) x => P (InitFail msg q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (InitFail msg q) x :: Type Source #

Methods

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

P (InitDefT p q) x => P (InitDef p q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

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

P (LastFailT msg q) x => P (LastFail msg q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (LastFail msg q) x :: Type Source #

Methods

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

P (LastDefT p q) x => P (LastDef p q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

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

P (TailFailT msg q) x => P (TailFail msg q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (TailFail msg q) x :: Type Source #

Methods

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

P (TailDefT p q) x => P (TailDef p q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

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

P (HeadFailT msg q) x => P (HeadFail msg q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (HeadFail msg q) x :: Type Source #

Methods

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

P (HeadDefT p q) x => P (HeadDef p q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

eval :: MonadEval m => Proxy (HeadDef p q) -> POpts -> x -> m (TT (PP (HeadDef p q) x)) 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.Prelude

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 (RemoveT p q) x => P (Remove p q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

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

P (KeepT p q) x => P (Keep p q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

eval :: MonadEval m => Proxy (Keep p q) -> POpts -> x -> m (TT (PP (Keep p q) x)) 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 (ToEnumBDef' t def :: Type) a Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

eval :: MonadEval m => Proxy (ToEnumBDef' t def) -> POpts -> a -> m (TT (PP (ToEnumBDef' 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.Prelude

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.Prelude

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 #

bounded succ function

>>> pz @(SuccB' Id) (13 :: Int)
Present 14
PresentT 14
>>> pz @(SuccB' Id) LT
Present EQ
PresentT EQ
>>> pz @(SuccB 'LT Id) GT
Present LT
PresentT LT
>>> pz @(SuccB' Id) GT
Error Succ bounded
FailT "Succ bounded"
Instance details

Defined in Predicate.Prelude

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.Prelude

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 #

P (NegateRatioT p q) x => P (p -% q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

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 #

(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.Prelude

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 (p / q :: Type) a Source # 
Instance details

Defined in Predicate.Prelude

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 (CmpI CNe p q) x => P (p /=~ q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

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 (CmpI CLt p q) x => P (p <~ q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

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 (CmpI CLe p q) x => P (p <=~ q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

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 (CmpI CEq p q) x => P (p ==~ q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

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 (CmpI CGe p q) x => P (p >=~ q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

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 (CmpI CGt p q) x => P (p >~ q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

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 (Cmp CNe p q) x => P (p /= q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

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 (Cmp CLt p q) x => P (p < q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

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 (Cmp CLe p q) x => P (p <= q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

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 (Cmp CEq p q) x => P (p == q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

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 (Cmp CGe p q) x => P (p >= q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

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 (Cmp CGt p q) x => P (p > q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

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 (MultT p q) x => P (p * q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

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 (SubT p q) x => P (p - q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

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 (AddT p q) x => P (p + q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

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 (WAmpT p q) x => P (p &&& q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

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 (DropT n p) x => P (Drop n p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (Drop n p) x :: Type Source #

Methods

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

P (TakeT n p) x => P (Take n p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (Take n p) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (Take n p) -> POpts -> x -> m (TT (PP (Take n p) x)) 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.Prelude

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.Prelude

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 (MaybeBool b p :: Type) a Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

eval :: MonadEval m => Proxy (MaybeBool b p) -> POpts -> a -> m (TT (PP (MaybeBool 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.Prelude

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.Prelude

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.Prelude

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.Prelude

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.Prelude

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.Prelude

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 (FromString' t s :: Type) a Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

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

P (SortOnDescT p q) x => P (SortOnDesc p q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

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

P (SortOnT p q) x => P (SortOn p q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

eval :: MonadEval m => Proxy (SortOn p q) -> POpts -> x -> m (TT (PP (SortOn p q) x)) 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.Prelude

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 (ReadQT' t p) x => P (ReadQ' t p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

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

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

Defined in Predicate.Prelude

Associated Types

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

Methods

eval :: MonadEval m => Proxy (ReadMaybe' t p) -> POpts -> x -> m (TT (PP (ReadMaybe' t p) 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.Prelude

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.Prelude

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 (ResplitT p q) x => P (Resplit p q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

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

P (RescanRangesT p q) x => P (RescanRanges p q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

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

P (RescanT p q) x => P (Rescan p q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

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

P (ReT p q) x => P (Re p q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

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

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

Defined in Predicate.Prelude

Associated Types

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

Methods

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

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

Defined in Predicate.Prelude

Associated Types

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

Methods

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

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

Defined in Predicate.Prelude

Associated Types

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

Methods

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

P (BetweenT p q) x => P (p <..> q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

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, 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.Prelude

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.Prelude

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.Prelude

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.Prelude

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 #

(PP q x ~ (a, b), PP (p a b (PP r x)) x ~ PP (p (Fst Id) (Snd Id) (Thd Id)) (a, b, PP r x), P q x, P r x, P (p (Fst Id) (Snd Id) (Thd Id)) (a, b, PP r x)) => P (Uncurry p q r :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

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

(KnownNat n, PrintC bs, (b, bs) ~ InductListP n a, InductListC n a, PrintfArg b, PP s x ~ String, PP p x ~ [a], P s x, P p x) => P (PrintL n s p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (PrintL n s p) x :: Type Source #

Methods

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

(Typeable (PP t x), ZwischenT 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.Prelude

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 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.Prelude

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.Prelude

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 #

(x ~ [a], P (GuardsNT prt n p) x) => P (GuardsN prt n p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (GuardsN prt n p) x :: Type Source #

Methods

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

P (GuardsDetailT prt ps) x => P (GuardsDetail prt ps :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (GuardsDetail prt ps) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (GuardsDetail prt ps) -> POpts -> x -> m (TT (PP (GuardsDetail prt ps) x)) Source #

(x ~ [a], P (BoolsNT prt n p) x) => P (BoolsN prt n p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (BoolsN prt n p) x :: Type Source #

Methods

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

P (ParseTimesT t p q) x => P (ParseTimes t p q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

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

P (ParseTimePT t p q) x => P (ParseTimeP t p q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

eval :: MonadEval m => Proxy (ParseTimeP t p q) -> POpts -> x -> m (TT (PP (ParseTimeP t p q) x)) 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.Prelude

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.Prelude

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.Prelude

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.Prelude

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 #

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

Defined in Predicate.Prelude

Associated Types

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

Methods

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

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

Defined in Predicate.Prelude

Associated Types

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

Methods

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

P (CaseT' ps qs r) x => P (Case' ps qs r :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

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

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

Defined in Predicate.Prelude

Associated Types

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

Methods

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

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

Defined in Predicate.Prelude

Associated Types

type PP (ZipL l p q) a :: Type Source #

Methods

eval :: MonadEval m => Proxy (ZipL l p q) -> POpts -> a -> m (TT (PP (ZipL l 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.Prelude

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 #

P (IterateNUntilT n p f) x => P (IterateNUntil n p f :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (IterateNUntil n p f) x :: Type Source #

Methods

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

P (IterateNWhileT n p f) x => P (IterateNWhile n p f :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (IterateNWhile n p f) x :: Type Source #

Methods

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

P (FoldLT p q r) x => P (FoldL p q r :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

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

P (FoldNT n p q) x => P (FoldN n p q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (FoldN n p q) x :: Type Source #

Methods

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

P (ScanNT n p q) x => P (ScanN n p q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (ScanN n p q) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (ScanN n p q) -> POpts -> x -> m (TT (PP (ScanN n p q) x)) 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.Prelude

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.Prelude

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 (LookupFailT msg v w) x => P (LookupFail msg v w :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (LookupFail msg v w) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (LookupFail msg v w) -> POpts -> x -> m (TT (PP (LookupFail msg v w) x)) Source #

P (LookupDefT v w p) x => P (LookupDef v w p :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (LookupDef v w p) x :: Type Source #

Methods

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

P (PadRT n p q) x => P (PadR n p q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (PadR n p q) x :: Type Source #

Methods

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

P (PadLT n p q) x => P (PadL n p q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (PadL n p q) x :: Type Source #

Methods

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

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

Defined in Predicate.Prelude

Associated Types

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

Methods

eval :: MonadEval m => Proxy (EitherBool b p q) -> POpts -> a -> m (TT (PP (EitherBool 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.Prelude

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.Prelude

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.Prelude

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 #

P (ReplaceOneStringT p q r) x => P (ReplaceOneString p q r :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

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

P (ReplaceAllStringT p q r) x => P (ReplaceAllString p q r :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

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

P (ReplaceOneT p q r) x => P (ReplaceOne p q r :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

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

P (ReplaceAllT p q r) x => P (ReplaceAll p q r :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

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

(Ord (PP p x), Show (PP p x), PP r x ~ PP p x, PP r x ~ PP q x, P p x, P q x, P r x) => P (Between p q r :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

eval :: MonadEval m => Proxy (Between p q r) -> POpts -> x -> m (TT (PP (Between p q r) x)) 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.Prelude

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 (ReplaceOneStringT' rs p q r) x => P (ReplaceOneString' rs p q r :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

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

P (ReplaceAllStringT' rs p q r) x => P (ReplaceAllString' rs p q r :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

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

P (ReplaceOneT' rs p q r) x => P (ReplaceOne' rs p q r :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

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

P (ReplaceAllT' rs p q r) x => P (ReplaceAll' rs p q r :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

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

P (CaseT'' s ps qs r) x => P (Case'' s ps qs r :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

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

Methods

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

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

Defined in Predicate.Prelude

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.Prelude

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 #

P (LookupFailT' msg v w q) x => P (LookupFail' msg v w q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (LookupFail' msg v w q) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (LookupFail' msg v w q) -> POpts -> x -> m (TT (PP (LookupFail' msg v w q) x)) Source #

P (LookupDefT' v w p q) x => P (LookupDef' v w p q :: Type) x Source # 
Instance details

Defined in Predicate.Prelude

Associated Types

type PP (LookupDef' v w p q) x :: Type Source #

Methods

eval :: MonadEval m => Proxy (LookupDef' v w p q) -> POpts -> x -> m (TT (PP (LookupDef' v w p q) x)) Source #

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

converts the value to the corresponding Proxy

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

Defined in Predicate.Core

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

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

Defined in Predicate.Core

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

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

Defined in Predicate.Core

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

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

Defined in Predicate.Core

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

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

Defined in Predicate.Core

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 &&&

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

Defined in Predicate.Core

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

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

Defined in Predicate.Core

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

>>> pz @'(4, Id, "goodbye") "hello"
Present (4,"hello","goodbye")
PresentT (4,"hello","goodbye")
>>> pe @'( 'True, 'False, 123) True
P '(,,)
|
+- True 'True
|
+- False 'False
|
`- P '123
PresentT (True,False,123)
Instance details

Defined in Predicate.Core

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

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

Defined in Predicate.Core

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 #

evaluation methods

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

runPQBool :: (P p a, PP p a ~ Bool, P q a, PP q a ~ Bool, MonadEval m) => String -> Proxy p -> Proxy q -> POpts -> a -> [Holder] -> m (Either (TT x) (PP p a, PP q a, TT (PP p a), TT (PP q 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

evalQuick :: forall p i. P p i => i -> Either String (PP p i) Source #