predicate-typed-0.7.4.5: Predicates, Refinement types and Dsl
Safe HaskellNone
LanguageHaskell2010

Predicate.Core

Description

a dsl for evaluating and displaying type level expressions

Synopsis

basic types

data Id Source #

identity function

>>> pz @Id 23
Val 23

Instances

Instances details
Show Id Source # 
Instance details

Defined in Predicate.Core

Methods

showsPrec :: Int -> Id -> ShowS #

show :: Id -> String #

showList :: [Id] -> ShowS #

Show a => P Id a Source # 
Instance details

Defined in Predicate.Core

Associated Types

type PP Id a 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
Val 23

Instances

Instances details
Show IdT Source # 
Instance details

Defined in Predicate.Core

Methods

showsPrec :: Int -> IdT -> ShowS #

show :: IdT -> String #

showList :: [IdT] -> ShowS #

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

Defined in Predicate.Core

Associated Types

type PP IdT a 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 wrapper to turn kind k into kind Type eg useful for putting in a promoted list (cant mix kinds) see Do

>>> pz @'[W 123, Id] 99
Val [123,99]
>>> pz @'[W "abc", W "def", Id, Id] "ghi"
Val ["abc","def","ghi","ghi"]

Instances

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

Defined in Predicate.Core

Associated Types

type PP (W p) a Source #

Methods

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

Show (W p) Source # 
Instance details

Defined in Predicate.Core

Methods

showsPrec :: Int -> W p -> ShowS #

show :: W p -> String #

showList :: [W p] -> ShowS #

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

>>> pan @(Msg "[somemessage]" Id) 999
P [somemessage] Id 999
Val 999
>>> pan @(Msg Id 999) "info message:"
P info message: '999
Val 999

Instances

Instances details
(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 Source #

Methods

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

Show (Msg prt p) Source # 
Instance details

Defined in Predicate.Core

Methods

showsPrec :: Int -> Msg prt p -> ShowS #

show :: Msg prt p -> String #

showList :: [Msg prt p] -> ShowS #

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

Defined in Predicate.Core

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

data MsgI prt p Source #

add a message to give more context to the evaluation tree

>>> pan @(MsgI "[somemessage] " Id) 999
P [somemessage] Id 999
Val 999
>>> pan @(MsgI Id 999) "info message:"
P info message:'999
Val 999

Instances

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

Defined in Predicate.Core

Associated Types

type PP (MsgI prt p) a Source #

Methods

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

Show (MsgI prt p) Source # 
Instance details

Defined in Predicate.Core

Methods

showsPrec :: Int -> MsgI prt p -> ShowS #

show :: MsgI prt p -> String #

showList :: [MsgI prt p] -> ShowS #

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

Defined in Predicate.Core

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

data Hide p Source #

run the expression p but remove the subtrees

Instances

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

Defined in Predicate.Core

Associated Types

type PP (Hide p) x Source #

Methods

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

Show (Hide p) Source # 
Instance details

Defined in Predicate.Core

Methods

showsPrec :: Int -> Hide p -> ShowS #

show :: Hide p -> String #

showList :: [Hide p] -> ShowS #

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

Defined in Predicate.Core

type PP (Hide p :: Type) x = PP p x

data Width (n :: Nat) p Source #

override the display width for the expression p

Instances

Instances details
(KnownNat n, P p a) => P (Width n p :: Type) a Source # 
Instance details

Defined in Predicate.Core

Associated Types

type PP (Width n p) a Source #

Methods

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

Show (Width n p) Source # 
Instance details

Defined in Predicate.Core

Methods

showsPrec :: Int -> Width n p -> ShowS #

show :: Width n p -> String #

showList :: [Width n p] -> ShowS #

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

Defined in Predicate.Core

type PP (Width n p :: Type) a = PP p a

data Hole (t :: Type) Source #

Acts as a proxy for a Type.

Instances

Instances details
Show (Hole t) Source # 
Instance details

Defined in Predicate.Core

Methods

showsPrec :: Int -> Hole t -> ShowS #

show :: Hole t -> String #

showList :: [Hole t] -> ShowS #

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

Defined in Predicate.Core

Associated Types

type PP (Hole t) a Source #

Methods

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

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

Defined in Predicate.Core

type PP (Hole t :: Type) a = t

data UnproxyT Source #

used internally for type inference

>>> pz @(FromIntegral' (Proxy (SG.Sum _) >> UnproxyT) 23) ()
Val (Sum {getSum = 23})
>>> pz @(FromIntegral' (Hole (SG.Sum _)) 23) () -- equivalent to Proxy UnproxyT above
Val (Sum {getSum = 23})

Instances

Instances details
Show UnproxyT Source # 
Instance details

Defined in Predicate.Core

Typeable t => P UnproxyT (Proxy t) Source # 
Instance details

Defined in Predicate.Core

Associated Types

type PP UnproxyT (Proxy t) Source #

Methods

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

type PP UnproxyT (Proxy t) Source # 
Instance details

Defined in Predicate.Core

type PP UnproxyT (Proxy t) = t

data Len Source #

similar to Length but displays the input value and works only for lists

>>> pl @Len "abcd"
Present 4 (Len 4 | "abcd")
Val 4
>>> pl @Len [1..3000]
Present 3000 (Len 3000 | [1,2,3,4,5,6,7,8,9,10,11,12,13,14,15,16,17,18,19,20,21,22,23,24,25,26,27,28,29,30,31,32,33,34,35,36,37,38,39,40,41,42,43,44,45,46,47,48,49,50,51,52,53,54,55,56,57,58,59,60,61,62,63,64,65,66,67,68,69,7...)
Val 3000
>>> pz @Len [10,4,5,12,3,4]
Val 6
>>> pz @Len []
Val 0
>>> pz @(Pairs >> Len > 2) "abcdef"
Val True

Instances

Instances details
Show Len Source # 
Instance details

Defined in Predicate.Core

Methods

showsPrec :: Int -> Len -> ShowS #

show :: Len -> String #

showList :: [Len] -> ShowS #

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

Defined in Predicate.Core

Associated Types

type PP Len x Source #

Methods

eval :: MonadEval m => proxy Len -> POpts -> x -> m (TT (PP Len x)) Source #

type PP Len x Source # 
Instance details

Defined in Predicate.Core

type PP Len x = Int

data Length p Source #

similar to length for Foldable instances

>>> pz @(Length Snd) (123,"abcdefg") -- if this breaks then get rid of Show a!
Val 7
>>> pz @(Length Id) (Left "aa")
Val 0
>>> pz @(Length Id) (Right "aa")
Val 1
>>> pz @(Length Right') (Right "abcd")
Val 4
>>> pz @(Length L23) (True,(23,'x',[10,9,1,3,4,2]))
Val 6

Instances

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

Defined in Predicate.Core

Associated Types

type PP (Length p) x Source #

Methods

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

Show (Length p) Source # 
Instance details

Defined in Predicate.Core

Methods

showsPrec :: Int -> Length p -> ShowS #

show :: Length p -> String #

showList :: [Length p] -> ShowS #

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

Defined in Predicate.Core

type PP (Length p :: Type) x = Int

data Map' p q Source #

similar to map for Foldable types

>>> pz @(Map' Pred Id) [1..5]
Val [0,1,2,3,4]

Instances

Instances details
(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.Core

Associated Types

type PP (Map' p q) x Source #

Methods

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

Show (Map' p q) Source # 
Instance details

Defined in Predicate.Core

Methods

showsPrec :: Int -> Map' p q -> ShowS #

show :: Map' p q -> String #

showList :: [Map' p q] -> ShowS #

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

Defined in Predicate.Core

type PP (Map' p q :: Type) x = [PP p (ExtractAFromTA (PP q x))]

data Map p Source #

similar to map

>>> pz @(Map Pred) [1..5]
Val [0,1,2,3,4]

Instances

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

Defined in Predicate.Core

Associated Types

type PP (Map p) x Source #

Methods

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

Show (Map p) Source # 
Instance details

Defined in Predicate.Core

Methods

showsPrec :: Int -> Map p -> ShowS #

show :: Map p -> String #

showList :: [Map p] -> ShowS #

type PP (Map p :: Type) x Source # 
Instance details

Defined in Predicate.Core

type PP (Map p :: Type) x = [PP p (ExtractAFromTA x)]

data Do (ps :: [k]) Source #

processes a type level list predicates running each in sequence with infixr: see >>

>>> pz @(Do [Pred, ShowP Id, Id &&& Len]) 9876543
Val ("9876542",7)
>>> pz @(Do '[W 123, W "xyz", Len &&& Id, Pred *** Id<>Id]) ()
Val (2,"xyzxyz")
>>> pl @(Do '[Succ,Id,ShowP Id,Ones,Map (ReadBase Int 8)]) 1239
Present [1,2,4,0] ((>>) [1,2,4,0] | {Map [1,2,4,0] | ["1","2","4","0"]})
Val [1,2,4,0]
>>> pl @(Do '[Pred,Id,ShowP Id,Ones,Map (ReadBase Int 8)]) 1239
Error invalid base 8 (Map(i=3, a="8") excnt=1)
Fail "invalid base 8"
>>> pl @(Do '[4,5,6]) ()
Present 6 ((>>) 6 | {'6})
Val 6
>>> pl @(Do '["abc", "Def", "ggg", "hhhhh"]) ()
Present "hhhhh" ((>>) "hhhhh" | {'"hhhhh"})
Val "hhhhh"
>>> pl @(Do '[ 'LT, 'EQ, 'GT ]) ()
Present GT ((>>) GT | {'GT})
Val GT
>>> pl @(Do '[4 % 4,22 % 1 ,12 -% 4]) ()
Present (-3) % 1 ((>>) (-3) % 1 | {Negate (-3) % 1 | 3 % 1})
Val ((-3) % 1)
>>> pl @(Do '[1,2,3]) ()
Present 3 ((>>) 3 | {'3})
Val 3

Instances

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

Defined in Predicate.Core

Associated Types

type PP (Do ps) a Source #

Methods

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

Show (Do ps) Source # 
Instance details

Defined in Predicate.Core

Methods

showsPrec :: Int -> Do ps -> ShowS #

show :: Do ps -> String #

showList :: [Do ps] -> ShowS #

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

Defined in Predicate.Core

type PP (Do ps :: Type) a = PP (DoExpandT ps) a

data Swap Source #

swaps using SwapC

>>> pz @Swap (Left 123)
Val (Right 123)
>>> pz @Swap (Right 123)
Val (Left 123)
>>> pz @Swap (These 'x' 123)
Val (These 123 'x')
>>> pz @Swap (This 'x')
Val (That 'x')
>>> pz @Swap (That 123)
Val (This 123)
>>> pz @Swap (123,'x')
Val ('x',123)
>>> pz @Swap (Left "abc")
Val (Right "abc")
>>> pz @Swap (Right 123)
Val (Left 123)
>>> pl @Swap (Right "asfd")
Present Left "asfd" (Swap Left "asfd" | Right "asfd")
Val (Left "asfd")
>>> pl @Swap (12,"asfd")
Present ("asfd",12) (Swap ("asfd",12) | (12,"asfd"))
Val ("asfd",12)
>>> pz @Swap (True,12,"asfd")
Val (True,"asfd",12)

Instances

Instances details
Show Swap Source # 
Instance details

Defined in Predicate.Core

Methods

showsPrec :: Int -> Swap -> ShowS #

show :: Swap -> String #

showList :: [Swap] -> ShowS #

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

Defined in Predicate.Core

Associated Types

type PP Swap (p a b) Source #

Methods

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

type PP Swap (p a b) Source # 
Instance details

Defined in Predicate.Core

type PP Swap (p a b) = p b a

data Arg' Source #

extracts a tuple from Arg

>>> pz @('SG.Arg (C "S") 10 >> Arg') ()
Val ('S',10)
>>> pz @Arg' (SG.Arg 'S' 10)
Val ('S',10)

Instances

Instances details
Show Arg' Source # 
Instance details

Defined in Predicate.Core

Methods

showsPrec :: Int -> Arg' -> ShowS #

show :: Arg' -> String #

showList :: [Arg'] -> ShowS #

x ~ Arg a b => P Arg' x Source # 
Instance details

Defined in Predicate.Core

Associated Types

type PP Arg' x Source #

Methods

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

type PP Arg' x Source # 
Instance details

Defined in Predicate.Core

type PP Arg' x = ArgT x

impure evaluation

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

displays the evaluation tree in plain text without colors

evaluate the type level expression in IO

>>> pl @(Between 4 10 Id) 7 & mapped . _Val %~ not
True (4 <= 7 <= 10)
Val False
>>> eval (Proxy @'True) defOpts 7 & mapped . ttValBool . _Val %~ not
TT {_ttValP = FalseP, _ttVal = Val False, _ttString = "'True", _ttForest = []}

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

displays the evaluation tree in plain text without colors and verbose

evaluate the type level expression in IO

>>> pl @(Between 4 10 Id) 7 & mapped . _Val %~ not
True (4 <= 7 <= 10)
Val False
>>> eval (Proxy @'True) defOpts 7 & mapped . ttValBool . _Val %~ not
TT {_ttValP = FalseP, _ttVal = Val False, _ttString = "'True", _ttForest = []}

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

displays the evaluation tree using colors without background colors

evaluate the type level expression in IO

>>> pl @(Between 4 10 Id) 7 & mapped . _Val %~ not
True (4 <= 7 <= 10)
Val False
>>> eval (Proxy @'True) defOpts 7 & mapped . ttValBool . _Val %~ not
TT {_ttValP = FalseP, _ttVal = Val False, _ttString = "'True", _ttForest = []}

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

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

evaluate the type level expression in IO

>>> pl @(Between 4 10 Id) 7 & mapped . _Val %~ not
True (4 <= 7 <= 10)
Val False
>>> eval (Proxy @'True) defOpts 7 & mapped . ttValBool . _Val %~ not
TT {_ttValP = FalseP, _ttVal = Val False, _ttString = "'True", _ttForest = []}

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

displays the evaluation tree using background colors

evaluate the type level expression in IO

>>> pl @(Between 4 10 Id) 7 & mapped . _Val %~ not
True (4 <= 7 <= 10)
Val False
>>> eval (Proxy @'True) defOpts 7 & mapped . ttValBool . _Val %~ not
TT {_ttValP = FalseP, _ttVal = Val False, _ttString = "'True", _ttForest = []}

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

displays the evaluation tree using unicode and colors with background colors

evaluate the type level expression in IO

>>> pl @(Between 4 10 Id) 7 & mapped . _Val %~ not
True (4 <= 7 <= 10)
Val False
>>> eval (Proxy @'True) defOpts 7 & mapped . ttValBool . _Val %~ not
TT {_ttValP = FalseP, _ttVal = Val False, _ttString = "'True", _ttForest = []}

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

pa and verbose

evaluate the type level expression in IO

>>> pl @(Between 4 10 Id) 7 & mapped . _Val %~ not
True (4 <= 7 <= 10)
Val False
>>> eval (Proxy @'True) defOpts 7 & mapped . ttValBool . _Val %~ not
TT {_ttValP = FalseP, _ttVal = Val False, _ttString = "'True", _ttForest = []}

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

pu and verbose

evaluate the type level expression in IO

>>> pl @(Between 4 10 Id) 7 & mapped . _Val %~ not
True (4 <= 7 <= 10)
Val False
>>> eval (Proxy @'True) defOpts 7 & mapped . ttValBool . _Val %~ not
TT {_ttValP = FalseP, _ttVal = Val False, _ttString = "'True", _ttForest = []}

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

same as pz but adds context to the end result

evaluate the type level expression in IO

>>> pl @(Between 4 10 Id) 7 & mapped . _Val %~ not
True (4 <= 7 <= 10)
Val False
>>> eval (Proxy @'True) defOpts 7 & mapped . ttValBool . _Val %~ not
TT {_ttValP = FalseP, _ttVal = Val False, _ttString = "'True", _ttForest = []}

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

skips the evaluation tree and just displays the end result

evaluate the type level expression in IO

>>> pl @(Between 4 10 Id) 7 & mapped . _Val %~ not
True (4 <= 7 <= 10)
Val False
>>> eval (Proxy @'True) defOpts 7 & mapped . ttValBool . _Val %~ not
TT {_ttValP = FalseP, _ttVal = Val False, _ttString = "'True", _ttForest = []}

run :: forall opts p a. (OptC opts, Show (PP p a), P p a) => a -> IO (Val (PP p a)) Source #

evaluate a typelevel expression (use type applications to pass in the options and the expression)

>>> run @OZ @Id 123
Val 123
>>> run @('OMsg "field1" ':# OL) @('Left Id) (Right 123)
field1 >>> Error 'Left found Right
Fail "'Left found Right"
>>> run @(OptT '[ 'OMsg "test", OU, 'OEmpty, OL, 'OMsg "field2"]) @(FailT _ "oops") ()
test | field2 >>> Error oops
Fail "oops"

runs :: forall optss p a. (OptC (OptT optss), Show (PP p a), P p a) => a -> IO (Val (PP p a)) Source #

run expression with multiple options in a list

>>> runs @'[OL, 'OMsg "field2"] @'( 'True, 'False) ()
field2 >>> Present (True,False) ('(True,False))
Val (True,False)
>>> runs @'[ 'OMsg "test", OU, 'OEmpty, OL, 'OMsg "field2"] @(FailT _ "oops") ()
test | field2 >>> Error oops
Fail "oops"

unsafeEval :: forall opts p a. (HasCallStack, OptC opts, Show (PP p a), P p a) => a -> PP p a Source #

for use with TH.Lift in a splice. returns a pure value or fails with a tree

pure evaluation

runP :: (P p a, MonadEval m) => Inline -> String -> proxy p -> POpts -> a -> [Tree PE] -> m (Either (TT x) (PP p a, TT (PP p a))) Source #

convenience method to evaluate one expression

runPQ :: (P p a, P q a, MonadEval m) => Inline -> String -> proxy1 p -> proxy2 q -> POpts -> a -> [Tree PE] -> m (Either (TT x) (PP p a, PP q a, TT (PP p a), TT (PP q a))) Source #

convenience method to evaluate two expressions using the same input and return the results

runPQBool :: (P p a, PP p a ~ Bool, P q a, PP q a ~ Bool, MonadEval m) => Inline -> String -> proxy1 p -> proxy2 q -> POpts -> a -> [Tree PE] -> m (Either (TT x) (PP p a, PP q a, TT (PP p a), TT (PP q a))) Source #

convenience method to evaluate two boolean expressions using the same input and return the results

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

evalBoolHide :: forall p a m. (MonadEval m, P p a, PP p a ~ Bool) => POpts -> a -> m (TT (PP p a)) Source #

evaluate a boolean expressions but hide the results unless verbose

evalHide :: forall p a m. (MonadEval m, P p a) => POpts -> a -> m (TT (PP p a)) Source #

evaluate a expressions but hide the results unless verbose

evalQuick :: forall opts p i. (OptC opts, P p i) => i -> Either String (PP p i) Source #

A specialised form of eval that returns the result or the error string on failure

evalEither :: forall opts p a. (OptC opts, Show (PP p a), P p a) => a -> Either String (PP p a) Source #

run a type level computation and returns the value or a tree with the error

wrap, unwrap

data Wrap (t :: Type) p Source #

wraps a value (see _Wrapped' and _Unwrapped')

>>> pz @(Wrap (SG.Sum _) Id) (-13)
Val (Sum {getSum = -13})
>>> pz @(Wrap SG.Any (Ge 4)) 13
Val (Any {getAny = True})
>>> import Data.List.NonEmpty (NonEmpty(..))
>>> pz @(Wrap (NonEmpty _) (Uncons >> 'Just Id)) "abcd"
Val ('a' :| "bcd")
>>> pl @(Wrap (SG.Sum _) Id) 13
Present Sum {getSum = 13} (Wrap Sum {getSum = 13} | 13)
Val (Sum {getSum = 13})
>>> pl @(Wrap (SG.Sum _) Id >> STimes 4 Id) 13
Present Sum {getSum = 52} ((>>) Sum {getSum = 52} | {getSum = 13})
Val (Sum {getSum = 52})
>>> pl @(Wrap _ 13 <> Id) (SG.Sum @Int 12)
Present Sum {getSum = 25} (Sum {getSum = 13} <> Sum {getSum = 12} = Sum {getSum = 25})
Val (Sum {getSum = 25})

Instances

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

Defined in Predicate.Core

Associated Types

type PP (Wrap t p) x Source #

Methods

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

Show (Wrap t p) Source # 
Instance details

Defined in Predicate.Core

Methods

showsPrec :: Int -> Wrap t p -> ShowS #

show :: Wrap t p -> String #

showList :: [Wrap t p] -> ShowS #

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

Defined in Predicate.Core

type PP (Wrap t p :: Type) x

data Wrap' t p Source #

similar to Wrap where t points to the type

Instances

Instances details
(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.Core

Associated Types

type PP (Wrap' s p) x Source #

Methods

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

Show (Wrap' t p) Source # 
Instance details

Defined in Predicate.Core

Methods

showsPrec :: Int -> Wrap' t p -> ShowS #

show :: Wrap' t p -> String #

showList :: [Wrap' t p] -> ShowS #

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

Defined in Predicate.Core

type PP (Wrap' s p :: Type) x = PP s x

data Unwrap Source #

unwraps a value (see _Wrapped')

>>> pz @Unwrap (SG.Sum (-13))
Val (-13)
>>> pl @(Unwrap >> '(Id, 'True)) (SG.Sum 13)
Present (13,True) ((>>) (13,True) | {'(13,True)})
Val (13,True)

Instances

Instances details
Show Unwrap Source # 
Instance details

Defined in Predicate.Core

(Show x, Show (Unwrapped x), Wrapped x) => P Unwrap x Source # 
Instance details

Defined in Predicate.Core

Associated Types

type PP Unwrap x Source #

Methods

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

type PP Unwrap x Source # 
Instance details

Defined in Predicate.Core

type PP Unwrap x = Unwrapped x

failure

data Fail t prt Source #

Fails the computation with a message but allows you to set the output type

>>> pz @('False || (Fail 'True "failed")) (99,"somedata")
Fail "failed"
>>> pz @('False || (Fail (Hole Bool) "failed")) (99,"somedata")
Fail "failed"
>>> pz @('False || (Fail (Hole _) "failed")) (99,"somedata")
Fail "failed"

Instances

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

Defined in Predicate.Core

Associated Types

type PP (Fail t prt) a Source #

Methods

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

Show (Fail t prt) Source # 
Instance details

Defined in Predicate.Core

Methods

showsPrec :: Int -> Fail t prt -> ShowS #

show :: Fail t prt -> String #

showList :: [Fail t prt] -> ShowS #

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

Defined in Predicate.Core

type PP (Fail t prt :: Type) a = PP t a

data FailP p Source #

Fails the computation with a message where the input value is a Proxy

>>> pz @(Ix 3 (FailP "oops")) "abcd"
Val 'd'
>>> pz @(Ix 3 (FailP "oops")) "abc"
Fail "oops"

Instances

Instances details
P (Fail UnproxyT p) x => P (FailP p :: Type) x Source # 
Instance details

Defined in Predicate.Core

Associated Types

type PP (FailP p) x Source #

Methods

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

Show (FailP p) Source # 
Instance details

Defined in Predicate.Core

Methods

showsPrec :: Int -> FailP p -> ShowS #

show :: FailP p -> String #

showList :: [FailP p] -> ShowS #

type PP (FailP p :: Type) x Source # 
Instance details

Defined in Predicate.Core

type PP (FailP p :: Type) x = PP (Fail UnproxyT p) x

data FailT (t :: Type) p Source #

Fails the computation with a message (wraps the type in Hole)

>>> pz @(FailT Int (PrintF "value=%03d" Id)) 99
Fail "value=099"

Instances

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

Defined in Predicate.Core

Associated Types

type PP (FailT t p) x Source #

Methods

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

Show (FailT t p) Source # 
Instance details

Defined in Predicate.Core

Methods

showsPrec :: Int -> FailT t p -> ShowS #

show :: FailT t p -> String #

showList :: [FailT t p] -> ShowS #

type PP (FailT t p :: Type) x Source # 
Instance details

Defined in Predicate.Core

type PP (FailT t p :: Type) x = PP (Fail (Hole t) p) x

data FailS p Source #

Fails the computation with a message for simple failures: doesnt preserve types

>>> pz @(FailS (PrintT "value=%03d string=%s" Id)) (99,"somedata")
Fail "value=099 string=somedata"

Instances

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

Defined in Predicate.Core

Associated Types

type PP (FailS p) x Source #

Methods

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

Show (FailS p) Source # 
Instance details

Defined in Predicate.Core

Methods

showsPrec :: Int -> FailS p -> ShowS #

show :: FailS p -> String #

showList :: [FailS p] -> ShowS #

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

Defined in Predicate.Core

type PP (FailS p :: Type) x = PP (Fail Id p) x

tuple

data Fst Source #

similar to fst

>>> pz @Fst (10,"Abc")
Val 10
>>> pz @Fst (10,"Abc",'x')
Val 10
>>> pz @Fst (10,"Abc",'x',False)
Val 10
>>> pl @Fst (99,'a',False,1.3)
Present 99 (Fst 99 | (99,'a',False,1.3))
Val 99

Instances

Instances details
Show Fst Source # 
Instance details

Defined in Predicate.Core

Methods

showsPrec :: Int -> Fst -> ShowS #

show :: Fst -> String #

showList :: [Fst] -> ShowS #

P FstT x => P Fst x Source # 
Instance details

Defined in Predicate.Core

Associated Types

type PP Fst x Source #

Methods

eval :: MonadEval m => proxy Fst -> POpts -> x -> m (TT (PP Fst x)) Source #

type PP Fst x Source # 
Instance details

Defined in Predicate.Core

type PP Fst x

data Snd Source #

similar to snd

>>> pz @Snd (10,"Abc")
Val "Abc"
>>> pz @Snd (10,"Abc",True)
Val "Abc"
>>> pl @Snd (99,'a',False,1.3)
Present 'a' (Snd 'a' | (99,'a',False,1.3))
Val 'a'

Instances

Instances details
Show Snd Source # 
Instance details

Defined in Predicate.Core

Methods

showsPrec :: Int -> Snd -> ShowS #

show :: Snd -> String #

showList :: [Snd] -> ShowS #

P SndT x => P Snd x Source # 
Instance details

Defined in Predicate.Core

Associated Types

type PP Snd x Source #

Methods

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

type PP Snd x Source # 
Instance details

Defined in Predicate.Core

type PP Snd x

data Thd Source #

similar to 3rd element in a n-tuple

>>> pz @Thd (10,"Abc",133)
Val 133
>>> pz @Thd (10,"Abc",133,True)
Val 133
>>> pl @Thd (99,'a',False,1.3)
Present False (Thd False | (99,'a',False,1.3))
Val False

Instances

Instances details
Show Thd Source # 
Instance details

Defined in Predicate.Core

Methods

showsPrec :: Int -> Thd -> ShowS #

show :: Thd -> String #

showList :: [Thd] -> ShowS #

P ThdT x => P Thd x Source # 
Instance details

Defined in Predicate.Core

Associated Types

type PP Thd x Source #

Methods

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

type PP Thd x Source # 
Instance details

Defined in Predicate.Core

type PP Thd x

data L1 p Source #

similar to fst

Instances

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

Defined in Predicate.Core

Associated Types

type PP (L1 p) x Source #

Methods

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

Show (L1 p) Source # 
Instance details

Defined in Predicate.Core

Methods

showsPrec :: Int -> L1 p -> ShowS #

show :: L1 p -> String #

showList :: [L1 p] -> ShowS #

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

Defined in Predicate.Core

type PP (L1 p :: Type) x = ExtractL1T (PP p x)

data L2 p Source #

similar to snd

Instances

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

Defined in Predicate.Core

Associated Types

type PP (L2 p) x Source #

Methods

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

Show (L2 p) Source # 
Instance details

Defined in Predicate.Core

Methods

showsPrec :: Int -> L2 p -> ShowS #

show :: L2 p -> String #

showList :: [L2 p] -> ShowS #

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

Defined in Predicate.Core

type PP (L2 p :: Type) x = ExtractL2T (PP p x)

data L3 p Source #

similar to 3rd element in a n-tuple

Instances

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

Defined in Predicate.Core

Associated Types

type PP (L3 p) x Source #

Methods

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

Show (L3 p) Source # 
Instance details

Defined in Predicate.Core

Methods

showsPrec :: Int -> L3 p -> ShowS #

show :: L3 p -> String #

showList :: [L3 p] -> ShowS #

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

Defined in Predicate.Core

type PP (L3 p :: Type) x = ExtractL3T (PP p x)

data L4 p Source #

similar to 4th element in a n-tuple

>>> pz @(L4 Id) (10,"Abc",'x',True)
Val True
>>> pz @(L4 L21) ('x',((10,"Abc",'x',999),"aa",1),9)
Val 999
>>> pl @(L4 Id) (99,'a',False,"someval")
Present "someval" (L4 "someval" | (99,'a',False,"someval"))
Val "someval"

Instances

Instances details
(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.Core

Associated Types

type PP (L4 p) x Source #

Methods

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

Show (L4 p) Source # 
Instance details

Defined in Predicate.Core

Methods

showsPrec :: Int -> L4 p -> ShowS #

show :: L4 p -> String #

showList :: [L4 p] -> ShowS #

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

Defined in Predicate.Core

type PP (L4 p :: Type) x = ExtractL4T (PP p x)

data L5 p Source #

similar to 5th element in a n-tuple

>>> pz @(L5 Id) (10,"Abc",'x',True,1)
Val 1

Instances

Instances details
(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.Core

Associated Types

type PP (L5 p) x Source #

Methods

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

Show (L5 p) Source # 
Instance details

Defined in Predicate.Core

Methods

showsPrec :: Int -> L5 p -> ShowS #

show :: L5 p -> String #

showList :: [L5 p] -> ShowS #

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

Defined in Predicate.Core

type PP (L5 p :: Type) x = ExtractL5T (PP p x)

data L6 p Source #

similar to 6th element in a n-tuple

>>> pz @(L6 Id) (10,"Abc",'x',True,1,99)
Val 99

Instances

Instances details
(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.Core

Associated Types

type PP (L6 p) x Source #

Methods

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

Show (L6 p) Source # 
Instance details

Defined in Predicate.Core

Methods

showsPrec :: Int -> L6 p -> ShowS #

show :: L6 p -> String #

showList :: [L6 p] -> ShowS #

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

Defined in Predicate.Core

type PP (L6 p :: Type) x = ExtractL6T (PP p x)

data L7 p Source #

similar to 7th element in a n-tuple

>>> pz @(L7 Id) (10,"Abc",'x',True,1,99,'a')
Val 'a'

Instances

Instances details
(Show (ExtractL7T (PP p x)), ExtractL7C (PP p x), P p x, Show (PP p x)) => P (L7 p :: Type) x Source # 
Instance details

Defined in Predicate.Core

Associated Types

type PP (L7 p) x Source #

Methods

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

Show (L7 p) Source # 
Instance details

Defined in Predicate.Core

Methods

showsPrec :: Int -> L7 p -> ShowS #

show :: L7 p -> String #

showList :: [L7 p] -> ShowS #

type PP (L7 p :: Type) x Source # 
Instance details

Defined in Predicate.Core

type PP (L7 p :: Type) x = ExtractL7T (PP p x)

data L8 p Source #

similar to 8th element in a n-tuple

>>> pz @(L8 Id) (10,"Abc",'x',True,1,99,True,'a')
Val 'a'

Instances

Instances details
(Show (ExtractL8T (PP p x)), ExtractL8C (PP p x), P p x, Show (PP p x)) => P (L8 p :: Type) x Source # 
Instance details

Defined in Predicate.Core

Associated Types

type PP (L8 p) x Source #

Methods

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

Show (L8 p) Source # 
Instance details

Defined in Predicate.Core

Methods

showsPrec :: Int -> L8 p -> ShowS #

show :: L8 p -> String #

showList :: [L8 p] -> ShowS #

type PP (L8 p :: Type) x Source # 
Instance details

Defined in Predicate.Core

type PP (L8 p :: Type) x = ExtractL8T (PP p x)

data L11 Source #

first element in a tuple followed by the first element

>>> pz @L11 ((10,"ss"),2)
Val 10

Instances

Instances details
Show L11 Source # 
Instance details

Defined in Predicate.Core

Methods

showsPrec :: Int -> L11 -> ShowS #

show :: L11 -> String #

showList :: [L11] -> ShowS #

P L11T x => P L11 x Source # 
Instance details

Defined in Predicate.Core

Associated Types

type PP L11 x Source #

Methods

eval :: MonadEval m => proxy L11 -> POpts -> x -> m (TT (PP L11 x)) Source #

type PP L11 x Source # 
Instance details

Defined in Predicate.Core

type PP L11 x

data L12 Source #

first element in a tuple followed by the second element

>>> pz @L12 ((10,"ss"),2)
Val "ss"

Instances

Instances details
Show L12 Source # 
Instance details

Defined in Predicate.Core

Methods

showsPrec :: Int -> L12 -> ShowS #

show :: L12 -> String #

showList :: [L12] -> ShowS #

P L12T x => P L12 x Source # 
Instance details

Defined in Predicate.Core

Associated Types

type PP L12 x Source #

Methods

eval :: MonadEval m => proxy L12 -> POpts -> x -> m (TT (PP L12 x)) Source #

type PP L12 x Source # 
Instance details

Defined in Predicate.Core

type PP L12 x

data L13 Source #

first element in a tuple followed by the third element

>>> pz @L13 ((10,"ss",4.5),2)
Val 4.5

Instances

Instances details
Show L13 Source # 
Instance details

Defined in Predicate.Core

Methods

showsPrec :: Int -> L13 -> ShowS #

show :: L13 -> String #

showList :: [L13] -> ShowS #

P L13T x => P L13 x Source # 
Instance details

Defined in Predicate.Core

Associated Types

type PP L13 x Source #

Methods

eval :: MonadEval m => proxy L13 -> POpts -> x -> m (TT (PP L13 x)) Source #

type PP L13 x Source # 
Instance details

Defined in Predicate.Core

type PP L13 x

data L21 Source #

second element in a tuple followed by the first element

>>> pz @L21 ('x',(10,"ss",4.5),2)
Val 10

Instances

Instances details
Show L21 Source # 
Instance details

Defined in Predicate.Core

Methods

showsPrec :: Int -> L21 -> ShowS #

show :: L21 -> String #

showList :: [L21] -> ShowS #

P L21T x => P L21 x Source # 
Instance details

Defined in Predicate.Core

Associated Types

type PP L21 x Source #

Methods

eval :: MonadEval m => proxy L21 -> POpts -> x -> m (TT (PP L21 x)) Source #

type PP L21 x Source # 
Instance details

Defined in Predicate.Core

type PP L21 x

data L22 Source #

second element in a tuple followed by the second element

>>> pz @L22 ('z',(10,"ss",4.5),2)
Val "ss"

Instances

Instances details
Show L22 Source # 
Instance details

Defined in Predicate.Core

Methods

showsPrec :: Int -> L22 -> ShowS #

show :: L22 -> String #

showList :: [L22] -> ShowS #

P L22T x => P L22 x Source # 
Instance details

Defined in Predicate.Core

Associated Types

type PP L22 x Source #

Methods

eval :: MonadEval m => proxy L22 -> POpts -> x -> m (TT (PP L22 x)) Source #

type PP L22 x Source # 
Instance details

Defined in Predicate.Core

type PP L22 x

data L23 Source #

second element in a tuple followed by the third element

>>> pz @L23 ('x',(10,"ss",4.5),2)
Val 4.5

Instances

Instances details
Show L23 Source # 
Instance details

Defined in Predicate.Core

Methods

showsPrec :: Int -> L23 -> ShowS #

show :: L23 -> String #

showList :: [L23] -> ShowS #

P L23T x => P L23 x Source # 
Instance details

Defined in Predicate.Core

Associated Types

type PP L23 x Source #

Methods

eval :: MonadEval m => proxy L23 -> POpts -> x -> m (TT (PP L23 x)) Source #

type PP L23 x Source # 
Instance details

Defined in Predicate.Core

type PP L23 x

data L31 Source #

third element in a tuple followed by the first element

>>> pz @L31 (1,2,('c',4))
Val 'c'

Instances

Instances details
Show L31 Source # 
Instance details

Defined in Predicate.Core

Methods

showsPrec :: Int -> L31 -> ShowS #

show :: L31 -> String #

showList :: [L31] -> ShowS #

P L31T x => P L31 x Source # 
Instance details

Defined in Predicate.Core

Associated Types

type PP L31 x Source #

Methods

eval :: MonadEval m => proxy L31 -> POpts -> x -> m (TT (PP L31 x)) Source #

type PP L31 x Source # 
Instance details

Defined in Predicate.Core

type PP L31 x

data L32 Source #

third element in a tuple followed by the second element

>>> pz @L32 (1,2,('c',4))
Val 4

Instances

Instances details
Show L32 Source # 
Instance details

Defined in Predicate.Core

Methods

showsPrec :: Int -> L32 -> ShowS #

show :: L32 -> String #

showList :: [L32] -> ShowS #

P L32T x => P L32 x Source # 
Instance details

Defined in Predicate.Core

Associated Types

type PP L32 x Source #

Methods

eval :: MonadEval m => proxy L32 -> POpts -> x -> m (TT (PP L32 x)) Source #

type PP L32 x Source # 
Instance details

Defined in Predicate.Core

type PP L32 x

data L33 Source #

third element in a tuple followed by the third element

>>> pz @L33 (1,2,('c',4,False))
Val False

Instances

Instances details
Show L33 Source # 
Instance details

Defined in Predicate.Core

Methods

showsPrec :: Int -> L33 -> ShowS #

show :: L33 -> String #

showList :: [L33] -> ShowS #

P L33T x => P L33 x Source # 
Instance details

Defined in Predicate.Core

Associated Types

type PP L33 x Source #

Methods

eval :: MonadEval m => proxy L33 -> POpts -> x -> m (TT (PP L33 x)) Source #

type PP L33 x Source # 
Instance details

Defined in Predicate.Core

type PP L33 x

boolean

data p && q infixr 3 Source #

similar to &&

>>> pz @(Fst && Snd) (True, True)
Val True
>>> pz @(Id > 15 && Id < 17) 16
Val True
>>> pz @(Id > 15 && Id < 17) 30
Val False
>>> pz @(Fst && (Length Snd >= 4)) (True,[11,12,13,14])
Val True
>>> pz @(Fst && (Length Snd == 4)) (True,[12,11,12,13,14])
Val False
>>> pz @(Uncurry (+:)) ([2..5],1)
Val [2,3,4,5,1]
>>> pz @(Uncurry (==!)) ('x','y')
Val LT

Instances

Instances details
(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.Core

Associated Types

type PP (p && q) a Source #

Methods

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

Show (p && q) Source # 
Instance details

Defined in Predicate.Core

Methods

showsPrec :: Int -> (p && q) -> ShowS #

show :: (p && q) -> String #

showList :: [p && q] -> ShowS #

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

Defined in Predicate.Core

type PP (p && q :: Type) a = Bool

data p &&~ q infixr 3 Source #

short circuit version of boolean And

>>> pl @(Id > 10 &&~ FailT _ "ss") 9
False (False &&~ _ | (9 > 10))
Val False
>>> pl @(Id > 10 &&~ Id == 12) 11
False (True &&~ False | (11 == 12))
Val False
>>> pl @(Id > 10 &&~ Id == 11) 11
True (True &&~ True)
Val True

Instances

Instances details
(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.Core

Associated Types

type PP (p &&~ q) a Source #

Methods

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

Show (p &&~ q) Source # 
Instance details

Defined in Predicate.Core

Methods

showsPrec :: Int -> (p &&~ q) -> ShowS #

show :: (p &&~ q) -> String #

showList :: [p &&~ q] -> ShowS #

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

Defined in Predicate.Core

type PP (p &&~ q :: Type) a = Bool

data p || q infixr 2 Source #

similar to ||

>>> pz @(Fst || (Length Snd >= 4)) (False,[11,12,13,14])
Val True
>>> pz @(Not Fst || (Length Snd == 4)) (True,[12,11,12,13,14])
Val False

Instances

Instances details
(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.Core

Associated Types

type PP (p || q) a Source #

Methods

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

Show (p || q) Source # 
Instance details

Defined in Predicate.Core

Methods

showsPrec :: Int -> (p || q) -> ShowS #

show :: (p || q) -> String #

showList :: [p || q] -> ShowS #

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

Defined in Predicate.Core

type PP (p || q :: Type) a = Bool

data p ||~ q infixr 2 Source #

short circuit version of boolean Or

>>> pl @(Id > 10 ||~ FailT _ "ss") 11
True (True ||~ _ | (11 > 10))
Val True
>>> pz @(Id > 10 ||~ Id == 9) 9
Val True
>>> pl @(Id > 10 ||~ Id > 9) 9
False (False ||~ False | (9 > 10) ||~ (9 > 9))
Val False

Instances

Instances details
(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.Core

Associated Types

type PP (p ||~ q) a Source #

Methods

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

Show (p ||~ q) Source # 
Instance details

Defined in Predicate.Core

Methods

showsPrec :: Int -> (p ||~ q) -> ShowS #

show :: (p ||~ q) -> String #

showList :: [p ||~ q] -> ShowS #

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

Defined in Predicate.Core

type PP (p ||~ q :: Type) a = Bool

data p ~> q infixr 1 Source #

boolean implication

>>> pz @(Fst ~> (Length Snd >= 4)) (True,[11,12,13,14])
Val True
>>> pz @(Fst ~> (Length Snd == 4)) (True,[12,11,12,13,14])
Val False
>>> pz @(Fst ~> (Length Snd == 4)) (False,[12,11,12,13,14])
Val True
>>> pz @(Fst ~> (Length Snd >= 4)) (False,[11,12,13,14])
Val True

Instances

Instances details
(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.Core

Associated Types

type PP (p ~> q) a Source #

Methods

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

Show (p ~> q) Source # 
Instance details

Defined in Predicate.Core

Methods

showsPrec :: Int -> (p ~> q) -> ShowS #

show :: (p ~> q) -> String #

showList :: [p ~> q] -> ShowS #

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

Defined in Predicate.Core

type PP (p ~> q :: Type) a = Bool

data Not p Source #

not function

>>> pz @(Not Id) False
Val True
>>> pz @(Not Id) True
Val False
>>> pz @(Not Fst) (True,22)
Val False
>>> pl @(Not (Lt 3)) 13
True (Not (13 < 3))
Val True
>>> pl @(Not 'True) ()
False (Not ('True))
Val False

Instances

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

Defined in Predicate.Core

Associated Types

type PP (Not p) x Source #

Methods

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

Show (Not p) Source # 
Instance details

Defined in Predicate.Core

Methods

showsPrec :: Int -> Not p -> ShowS #

show :: Not p -> String #

showList :: [Not p] -> ShowS #

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

Defined in Predicate.Core

type PP (Not p :: Type) x = Bool

data Between p q r Source #

A predicate that determines if the value is between p and q

>>> pz @(Between 5 8 Len) [1,2,3,4,5,5,7]
Val True
>>> pl @(Between 5 8 Id) 9
False (9 <= 8)
Val False
>>> pl @(Between L11 L12 Snd) ((1,4),3)
True (1 <= 3 <= 4)
Val True
>>> pl @(Between L11 L12 Snd) ((1,4),10)
False (10 <= 4)
Val False

Instances

Instances details
(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.Core

Associated Types

type PP (Between p q r) x Source #

Methods

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

Show (Between p q r) Source # 
Instance details

Defined in Predicate.Core

Methods

showsPrec :: Int -> Between p q r -> ShowS #

show :: Between p q r -> String #

showList :: [Between p q r] -> ShowS #

type PP (Between p q r :: Type) x Source # 
Instance details

Defined in Predicate.Core

type PP (Between p q r :: Type) x = Bool

data p <..> q infix 4 Source #

A operator predicate that determines if the value is between p and q

>>> pz @(5 <..> 8) 6
Val True
>>> pz @(10 % 4 <..> 40 % 5) 4
Val True
>>> pz @(10 % 4 <..> 40 % 5) 33
Val False
>>> pl @(Negate 7 <..> 20) (-4)
True (-7 <= -4 <= 20)
Val True
>>> pl @(Negate 7 <..> 20) 21
False (21 <= 20)
Val False

Instances

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

Defined in Predicate.Core

Associated Types

type PP (p <..> q) x Source #

Methods

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

Show (p <..> q) Source # 
Instance details

Defined in Predicate.Core

Methods

showsPrec :: Int -> (p <..> q) -> ShowS #

show :: (p <..> q) -> String #

showList :: [p <..> q] -> ShowS #

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

Defined in Predicate.Core

type PP (p <..> q :: Type) x

data All p Source #

similar to all

>>> pl @(All (Between 1 8 Id)) [7,3,4,1,2,9,0,1]
False (All(8) i=5 (9 <= 8))
Val False
>>> pz @(All Odd) [1,5,11,5,3]
Val True
>>> pz @(All Odd) []
Val True
>>> run @OANV @(All Even) [1,5,11,5,3]
False All(5) i=0 (1 == 0)
|
+- False i=0: 1 == 0
|  |
|  +- P 1 `mod` 2 = 1
|  |  |
|  |  +- P Id 1
|  |  |
|  |  `- P '2
|  |
|  `- P '0
|
+- False i=1: 1 == 0
|  |
|  +- P 5 `mod` 2 = 1
|  |  |
|  |  +- P Id 5
|  |  |
|  |  `- P '2
|  |
|  `- P '0
|
+- False i=2: 1 == 0
|  |
|  +- P 11 `mod` 2 = 1
|  |  |
|  |  +- P Id 11
|  |  |
|  |  `- P '2
|  |
|  `- P '0
|
+- False i=3: 1 == 0
|  |
|  +- P 5 `mod` 2 = 1
|  |  |
|  |  +- P Id 5
|  |  |
|  |  `- P '2
|  |
|  `- P '0
|
`- False i=4: 1 == 0
   |
   +- P 3 `mod` 2 = 1
   |  |
   |  +- P Id 3
   |  |
   |  `- P '2
   |
   `- P '0
Val False
>>> pl @(Fst >> All (Gt 3)) ([10,12,3,5],"ss")
False ((>>) False | {All(4) i=2 (3 > 3)})
Val False
>>> pl @(All (Lt 3)) [1 .. 10]
False (All(10) i=2 (3 < 3))
Val False

Instances

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

Defined in Predicate.Core

Associated Types

type PP (All p) x Source #

Methods

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

Show (All p) Source # 
Instance details

Defined in Predicate.Core

Methods

showsPrec :: Int -> All p -> ShowS #

show :: All p -> String #

showList :: [All p] -> ShowS #

type PP (All p :: Type) x Source # 
Instance details

Defined in Predicate.Core

type PP (All p :: Type) x = Bool

data Any p Source #

similar to any

>>> pl @(Any Even) [1,5,11,5,3]
False (Any(5))
Val False
>>> pl @(Any Even) [1,5,112,5,3]
True (Any(5) i=2 (0 == 0))
Val True
>>> pz @(Any Even) []
Val False
>>> pl @(Fst >> Any (Gt 3)) ([10,12,3,5],"ss")
True ((>>) True | {Any(4) i=0 (10 > 3)})
Val True
>>> pl @(Any (Same 2)) [1,4,5]
False (Any(3))
Val False
>>> pl @(Any (Same 2)) [1,4,5,2,1]
True (Any(5) i=3 (2 == 2))
Val True

Instances

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

Defined in Predicate.Core

Associated Types

type PP (Any p) x Source #

Methods

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

Show (Any p) Source # 
Instance details

Defined in Predicate.Core

Methods

showsPrec :: Int -> Any p -> ShowS #

show :: Any p -> String #

showList :: [Any p] -> ShowS #

type PP (Any p :: Type) x Source # 
Instance details

Defined in Predicate.Core

type PP (Any p :: Type) x = Bool

data IdBool Source #

id function on a boolean

>>> pz @('[ 'True] >> Head >> IdBool) ()
Val True
>>> pz @(Fst >> IdBool) (False,22)
Val False
>>> pl @(Head >> IdBool) [True]
True ((>>) True | {IdBool})
Val True
>>> pan @(Head >> Id) [True]
P (>>) True
|
+- P Head True
|
`- P Id True
Val True
>>> pan @(Head >> IdBool) [True]
True (>>) True
|
+- P Head True
|
`- True IdBool
Val True

Instances

Instances details
Show IdBool Source # 
Instance details

Defined in Predicate.Core

x ~ Bool => P IdBool x Source # 
Instance details

Defined in Predicate.Core

Associated Types

type PP IdBool x Source #

Methods

eval :: MonadEval m => proxy IdBool -> POpts -> x -> m (TT (PP IdBool x)) Source #

type PP IdBool x Source # 
Instance details

Defined in Predicate.Core

type PP IdBool x = Bool

type application

data p >> q infixr 1 Source #

compose expressions

>>> pz @(L11 >> Not Id) ((True,12),'x')
Val False
>>> pz @(L12 >> Succ >> Dup) ((True,12),'x')
Val (13,13)
>>> pz @(10 >> '(Id,"abc") >> Second Len) ()
Val (10,3)

Instances

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

Defined in Predicate.Core

Associated Types

type PP (p >> q) a Source #

Methods

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

Show (p >> q) Source # 
Instance details

Defined in Predicate.Core

Methods

showsPrec :: Int -> (p >> q) -> ShowS #

show :: (p >> q) -> String #

showList :: [p >> q] -> ShowS #

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

Defined in Predicate.Core

type PP (p >> q :: Type) a = PP q (PP p a)

data p >>> q infixl 1 Source #

infixl version of >>

Instances

Instances details
P (RightArrowsLeftInfixT p q) x => P (p >>> q :: Type) x Source # 
Instance details

Defined in Predicate.Core

Associated Types

type PP (p >>> q) x Source #

Methods

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

Show (p >>> q) Source # 
Instance details

Defined in Predicate.Core

Methods

showsPrec :: Int -> (p >>> q) -> ShowS #

show :: (p >>> q) -> String #

showList :: [p >>> q] -> ShowS #

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

Defined in Predicate.Core

type PP (p >>> q :: Type) x

data p << q infixr 1 Source #

flipped version of >>

Instances

Instances details
P (LeftArrowsT p q) x => P (p << q :: Type) x Source # 
Instance details

Defined in Predicate.Core

Associated Types

type PP (p << q) x Source #

Methods

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

Show (p << q) Source # 
Instance details

Defined in Predicate.Core

Methods

showsPrec :: Int -> (p << q) -> ShowS #

show :: (p << q) -> String #

showList :: [p << q] -> ShowS #

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

Defined in Predicate.Core

type PP (p << q :: Type) x

data (p :: k -> k1) $ (q :: k) infixr 0 Source #

like $ for expressions taking exactly on argument (similar is %%) ie this doesnt work: pz @('(,) $ 4 $ 'True) ()

>>> pl @(L1 $ L2 $ Id) ((1,2),(3,4))
Present 3 (Fst 3 | (3,4))
Val 3
>>> pl @((<=) 4 $ L1 $ L2 $ Id) ((1,2),(3,4))
False (4 <= 3)
Val False
>>> pz @('(,) 4 $ 'True) ()
Val (4,True)
>>> pz @('(,) %% 'True %% 'False) () -- cant do this with $
Val (True,False)

Instances

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

Defined in Predicate.Core

Associated Types

type PP (p $ q) a Source #

Methods

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

Show (p $ q) Source # 
Instance details

Defined in Predicate.Core

Methods

showsPrec :: Int -> (p $ q) -> ShowS #

show :: (p $ q) -> String #

showList :: [p $ q] -> ShowS #

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

Defined in Predicate.Core

type PP (p $ q :: Type) a = PP (p q) a

data (q :: k) & (p :: k -> k1) infixl 1 Source #

similar to & for expressions taking exactly on argument

>>> pl @(Id & L1 & Singleton & Length) (13,"xyzw")
Present 1 (Length 1)
Val 1
>>> pl @(2 & (&&&) "abc") ()
Present ("abc",2) ('("abc",2))
Val ("abc",2)
>>> pl @(2 & '(,) "abc") ()
Present ("abc",2) ('("abc",2))
Val ("abc",2)
>>> pl @('(,) 4 $ '(,) 7 $ "aa") ()
Present (4,(7,"aa")) ('(4,(7,"aa")))
Val (4,(7,"aa"))
>>> pl @(L3 $ L2 $ Fst) ((1,("X",9,'a')),(3,4))
Present 'a' (Thd 'a' | ("X",9,'a'))
Val 'a'
>>> pz @('True %& 'False %& '(,)) ()
Val (False,True)

Instances

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

Defined in Predicate.Core

Associated Types

type PP (q & p) a Source #

Methods

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

Show (q & p) Source # 
Instance details

Defined in Predicate.Core

Methods

showsPrec :: Int -> (q & p) -> ShowS #

show :: (q & p) -> String #

showList :: [q & p] -> ShowS #

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

Defined in Predicate.Core

type PP (q & p :: Type) a = PP (p q) a

data DoL (ps :: [k]) Source #

processes a type level list predicates running each in sequence with infixl: see >>

>>> pz @(DoL [Pred, ShowP Id, Id &&& Len]) 9876543
Val ("9876542",7)
>>> pz @(DoL [2,3,4]) ()
Val 4
>>> pl @(DoL '[4,5,6]) ()
Present 6 ((>>) 6 | {'6})
Val 6

Instances

Instances details
P (DoExpandLT ps) a => P (DoL ps :: Type) a Source # 
Instance details

Defined in Predicate.Core

Associated Types

type PP (DoL ps) a Source #

Methods

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

Show (DoL ps) Source # 
Instance details

Defined in Predicate.Core

Methods

showsPrec :: Int -> DoL ps -> ShowS #

show :: DoL ps -> String #

showList :: [DoL ps] -> ShowS #

type PP (DoL ps :: Type) a Source # 
Instance details

Defined in Predicate.Core

type PP (DoL ps :: Type) a = PP (DoExpandLT ps) a

core 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

proxy for the expression

-> POpts

display options

-> a

value

-> m (TT (PP p a))

returns a tree of results

Instances

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

pulls the type level Bool to the value level

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

Defined in Predicate.Core

Associated Types

type PP b a 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"
Val LT
>>> pz @'EQ ()
Val EQ
Instance details

Defined in Predicate.Core

Associated Types

type PP cmp a 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 ()
Val 123
Instance details

Defined in Predicate.Core

Associated Types

type PP n a 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" ()
Val "hello world"
Instance details

Defined in Predicate.Core

Associated Types

type PP s a 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 @'() ()
Val ()
Instance details

Defined in Predicate.Core

Associated Types

type PP '() a Source #

Methods

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

P () a Source #

const () function

>>> pz @() "Asf"
Val ()
Instance details

Defined in Predicate.Core

Associated Types

type PP () a Source #

Methods

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

x ~ Arg a b => P Arg' x Source # 
Instance details

Defined in Predicate.Core

Associated Types

type PP Arg' x Source #

Methods

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

P L33T x => P L33 x Source # 
Instance details

Defined in Predicate.Core

Associated Types

type PP L33 x Source #

Methods

eval :: MonadEval m => proxy L33 -> POpts -> x -> m (TT (PP L33 x)) Source #

P L32T x => P L32 x Source # 
Instance details

Defined in Predicate.Core

Associated Types

type PP L32 x Source #

Methods

eval :: MonadEval m => proxy L32 -> POpts -> x -> m (TT (PP L32 x)) Source #

P L31T x => P L31 x Source # 
Instance details

Defined in Predicate.Core

Associated Types

type PP L31 x Source #

Methods

eval :: MonadEval m => proxy L31 -> POpts -> x -> m (TT (PP L31 x)) Source #

P L23T x => P L23 x Source # 
Instance details

Defined in Predicate.Core

Associated Types

type PP L23 x Source #

Methods

eval :: MonadEval m => proxy L23 -> POpts -> x -> m (TT (PP L23 x)) Source #

P L22T x => P L22 x Source # 
Instance details

Defined in Predicate.Core

Associated Types

type PP L22 x Source #

Methods

eval :: MonadEval m => proxy L22 -> POpts -> x -> m (TT (PP L22 x)) Source #

P L21T x => P L21 x Source # 
Instance details

Defined in Predicate.Core

Associated Types

type PP L21 x Source #

Methods

eval :: MonadEval m => proxy L21 -> POpts -> x -> m (TT (PP L21 x)) Source #

P L13T x => P L13 x Source # 
Instance details

Defined in Predicate.Core

Associated Types

type PP L13 x Source #

Methods

eval :: MonadEval m => proxy L13 -> POpts -> x -> m (TT (PP L13 x)) Source #

P L12T x => P L12 x Source # 
Instance details

Defined in Predicate.Core

Associated Types

type PP L12 x Source #

Methods

eval :: MonadEval m => proxy L12 -> POpts -> x -> m (TT (PP L12 x)) Source #

P L11T x => P L11 x Source # 
Instance details

Defined in Predicate.Core

Associated Types

type PP L11 x Source #

Methods

eval :: MonadEval m => proxy L11 -> POpts -> x -> m (TT (PP L11 x)) Source #

P ThdT x => P Thd x Source # 
Instance details

Defined in Predicate.Core

Associated Types

type PP Thd x Source #

Methods

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

P SndT x => P Snd x Source # 
Instance details

Defined in Predicate.Core

Associated Types

type PP Snd x Source #

Methods

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

P FstT x => P Fst x Source # 
Instance details

Defined in Predicate.Core

Associated Types

type PP Fst x Source #

Methods

eval :: MonadEval m => proxy Fst -> POpts -> x -> m (TT (PP Fst x)) Source #

x ~ Bool => P IdBool x Source # 
Instance details

Defined in Predicate.Core

Associated Types

type PP IdBool x Source #

Methods

eval :: MonadEval m => proxy IdBool -> POpts -> x -> m (TT (PP IdBool x)) Source #

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

Defined in Predicate.Core

Associated Types

type PP Len x Source #

Methods

eval :: MonadEval m => proxy Len -> POpts -> x -> m (TT (PP Len x)) Source #

(Show x, Show (Unwrapped x), Wrapped x) => P Unwrap x Source # 
Instance details

Defined in Predicate.Core

Associated Types

type PP Unwrap x Source #

Methods

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

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

Defined in Predicate.Core

Associated Types

type PP IdT a 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 Source #

Methods

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

P ReverseITuple () Source # 
Instance details

Defined in Predicate.Data.Tuple

Associated Types

type PP ReverseITuple () Source #

Methods

eval :: MonadEval m => proxy ReverseITuple -> POpts -> () -> m (TT (PP ReverseITuple ())) Source #

FromITupleC x => P FromITuple x Source # 
Instance details

Defined in Predicate.Data.Tuple

Associated Types

type PP FromITuple x Source #

Methods

eval :: MonadEval m => proxy FromITuple -> POpts -> x -> m (TT (PP FromITuple x)) Source #

ToITupleC x => P ToITuple x Source # 
Instance details

Defined in Predicate.Data.Tuple

Associated Types

type PP ToITuple x Source #

Methods

eval :: MonadEval m => proxy ToITuple -> POpts -> x -> m (TT (PP ToITuple x)) Source #

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

Defined in Predicate.Data.Tuple

Associated Types

type PP Pairs x Source #

Methods

eval :: MonadEval m => proxy Pairs -> POpts -> x -> m (TT (PP Pairs x)) Source #

Show x => P Dup x Source # 
Instance details

Defined in Predicate.Data.Tuple

Associated Types

type PP Dup x Source #

Methods

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

P IsTheseT x => P IsThese x Source # 
Instance details

Defined in Predicate.Data.These

Associated Types

type PP IsThese x Source #

Methods

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

P IsThatT x => P IsThat x Source # 
Instance details

Defined in Predicate.Data.These

Associated Types

type PP IsThat x Source #

Methods

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

P IsThisT x => P IsThis x Source # 
Instance details

Defined in Predicate.Data.These

Associated Types

type PP IsThis x Source #

Methods

eval :: MonadEval m => proxy IsThis -> POpts -> x -> m (TT (PP IsThis x)) Source #

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

Defined in Predicate.Data.These

Associated Types

type PP Theses x 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.Data.These

Associated Types

type PP Thats x 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.Data.These

Associated Types

type PP Thiss x Source #

Methods

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

ToStringC x => P ToString x Source # 
Instance details

Defined in Predicate.Data.String

Associated Types

type PP ToString x Source #

Methods

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

P TrimBothT x => P TrimBoth x Source # 
Instance details

Defined in Predicate.Data.String

Associated Types

type PP TrimBoth x Source #

Methods

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

P TrimRT x => P TrimR x Source # 
Instance details

Defined in Predicate.Data.String

Associated Types

type PP TrimR x Source #

Methods

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

P TrimLT x => P TrimL x Source # 
Instance details

Defined in Predicate.Data.String

Associated Types

type PP TrimL x Source #

Methods

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

P Proxy2T x Source # 
Instance details

Defined in Predicate.Data.Proxy

Associated Types

type PP Proxy2T x Source #

Methods

eval :: MonadEval m => proxy Proxy2T -> POpts -> x -> m (TT (PP Proxy2T x)) Source #

P Proxy1T x Source # 
Instance details

Defined in Predicate.Data.Proxy

Associated Types

type PP Proxy1T x Source #

Methods

eval :: MonadEval m => proxy Proxy1T -> POpts -> x -> m (TT (PP Proxy1T x)) Source #

Show x => P ProxyT x Source # 
Instance details

Defined in Predicate.Data.Proxy

Associated Types

type PP ProxyT x Source #

Methods

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

P NegativeT x => P Negative x Source # 
Instance details

Defined in Predicate.Data.Ordering

Associated Types

type PP Negative x Source #

Methods

eval :: MonadEval m => proxy Negative -> POpts -> x -> m (TT (PP Negative x)) Source #

P PositiveT x => P Positive x Source # 
Instance details

Defined in Predicate.Data.Ordering

Associated Types

type PP Positive x Source #

Methods

eval :: MonadEval m => proxy Positive -> POpts -> x -> m (TT (PP Positive x)) Source #

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

Defined in Predicate.Data.Ordering

Associated Types

type PP AllNegative x 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.Data.Ordering

Associated Types

type PP AllPositive x 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.Data.Ordering

Associated Types

type PP Desc' x 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.Data.Ordering

Associated Types

type PP Desc x 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.Data.Ordering

Associated Types

type PP Asc' x 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.Data.Ordering

Associated Types

type PP Asc x Source #

Methods

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

P (Comparing Id) x => P Compare x Source # 
Instance details

Defined in Predicate.Data.Ordering

Associated Types

type PP Compare x Source #

Methods

eval :: MonadEval m => proxy Compare -> POpts -> x -> m (TT (PP Compare x)) Source #

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

Defined in Predicate.Data.Numeric

Associated Types

type PP Odd x 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.Data.Numeric

Associated Types

type PP Even x Source #

Methods

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

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

Defined in Predicate.Data.Monoid

Associated Types

type PP MEmptyP x Source #

Methods

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

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

Defined in Predicate.Data.Monoid

Associated Types

type PP MConcat x Source #

Methods

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

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

Defined in Predicate.Data.Foldable

Associated Types

type PP OneP x Source #

Methods

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

(x ~ t a, Foldable t, a ~ Bool) => P Ors x Source # 
Instance details

Defined in Predicate.Data.Foldable

Associated Types

type PP Ors x Source #

Methods

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

(x ~ t a, Foldable t, a ~ Bool) => P Ands x Source # 
Instance details

Defined in Predicate.Data.Foldable

Associated Types

type PP Ands x Source #

Methods

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

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

Defined in Predicate.Data.Foldable

Associated Types

type PP Null a Source #

Methods

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

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

Defined in Predicate.Data.Foldable

Associated Types

type PP Concat x Source #

Methods

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

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

Defined in Predicate.Data.Foldable

Associated Types

type PP ToListExt l Source #

Methods

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

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

Defined in Predicate.Data.Foldable

Associated Types

type PP IsEmpty as Source #

Methods

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

P CatMaybesT x => P CatMaybes x Source # 
Instance details

Defined in Predicate.Data.Maybe

Associated Types

type PP CatMaybes x Source #

Methods

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

x ~ Maybe a => P IsNothing x Source # 
Instance details

Defined in Predicate.Data.Maybe

Associated Types

type PP IsNothing x Source #

Methods

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

x ~ Maybe a => P IsJust x Source # 
Instance details

Defined in Predicate.Data.Maybe

Associated Types

type PP IsJust x Source #

Methods

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

P Stdin x Source # 
Instance details

Defined in Predicate.Data.IO

Associated Types

type PP Stdin x Source #

Methods

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

P TimeZt a Source # 
Instance details

Defined in Predicate.Data.IO

Associated Types

type PP TimeZt a Source #

Methods

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

P TimeUtc a Source # 
Instance details

Defined in Predicate.Data.IO

Associated Types

type PP TimeUtc a Source #

Methods

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

P ReadEnvAll a Source # 
Instance details

Defined in Predicate.Data.IO

Associated Types

type PP ReadEnvAll a Source #

Methods

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

(Show x, Enum x) => P FromEnum x Source # 
Instance details

Defined in Predicate.Data.Enum

Associated Types

type PP FromEnum x Source #

Methods

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

(Show x, Enum x) => P Pred x Source # 
Instance details

Defined in Predicate.Data.Enum

Associated Types

type PP Pred x Source #

Methods

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

(Show x, Enum x) => P Succ x Source # 
Instance details

Defined in Predicate.Data.Enum

Associated Types

type PP Succ x Source #

Methods

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

P IListT x => P IList x Source # 
Instance details

Defined in Predicate.Data.List

Associated Types

type PP IList x Source #

Methods

eval :: MonadEval m => proxy IList -> POpts -> x -> m (TT (PP IList x)) Source #

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

Defined in Predicate.Data.List

Associated Types

type PP Nub x Source #

Methods

eval :: MonadEval m => proxy Nub -> POpts -> x -> m (TT (PP Nub x)) Source #

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

Defined in Predicate.Data.List

Associated Types

type PP Max x Source #

Methods

eval :: MonadEval m => proxy Max -> POpts -> x -> m (TT (PP Max x)) Source #

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

Defined in Predicate.Data.List

Associated Types

type PP Min x Source #

Methods

eval :: MonadEval m => proxy Min -> POpts -> x -> m (TT (PP Min x)) Source #

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

Defined in Predicate.Data.List

Associated Types

type PP Product x Source #

Methods

eval :: MonadEval m => proxy Product -> POpts -> x -> m (TT (PP Product x)) Source #

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

Defined in Predicate.Data.List

Associated Types

type PP Sum x Source #

Methods

eval :: MonadEval m => proxy Sum -> POpts -> x -> m (TT (PP Sum x)) Source #

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

Defined in Predicate.Data.List

Associated Types

type PP ReverseL t Source #

Methods

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

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

Defined in Predicate.Data.List

Associated Types

type PP Reverse x Source #

Methods

eval :: MonadEval m => proxy Reverse -> POpts -> x -> m (TT (PP Reverse x)) Source #

P SortT x => P Sort x Source # 
Instance details

Defined in Predicate.Data.List

Associated Types

type PP Sort x Source #

Methods

eval :: MonadEval m => proxy Sort -> POpts -> x -> m (TT (PP Sort x)) Source #

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

Defined in Predicate.Data.List

Associated Types

type PP Unzip3 x 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.Data.List

Associated Types

type PP Unzip x Source #

Methods

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

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

Defined in Predicate.Data.List

Associated Types

type PP Init x Source #

Methods

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

(Snoc x x (ConsT x) (ConsT x), Show (ConsT x), Show x) => P Last x Source # 
Instance details

Defined in Predicate.Data.List

Associated Types

type PP Last x Source #

Methods

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

(Cons x x (ConsT x) (ConsT x), Show x) => P Tail x Source # 
Instance details

Defined in Predicate.Data.List

Associated Types

type PP Tail x Source #

Methods

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

(Cons x x (ConsT x) (ConsT x), Show (ConsT x), Show x) => P Head x Source # 
Instance details

Defined in Predicate.Data.List

Associated Types

type PP Head x Source #

Methods

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

x ~ [a] => P Ones x Source # 
Instance details

Defined in Predicate.Data.List

Associated Types

type PP Ones x Source #

Methods

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

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

Defined in Predicate.Data.List

Associated Types

type PP Tails x 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.Data.List

Associated Types

type PP Inits x Source #

Methods

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

P GroupCntT x => P GroupCnt x Source # 
Instance details

Defined in Predicate.Data.List

Associated Types

type PP GroupCnt x Source #

Methods

eval :: MonadEval m => proxy GroupCnt -> POpts -> x -> m (TT (PP GroupCnt x)) Source #

P GroupT x => P Group x Source # 
Instance details

Defined in Predicate.Data.List

Associated Types

type PP Group x Source #

Methods

eval :: MonadEval m => proxy Group -> POpts -> x -> m (TT (PP Group x)) Source #

(a ~ [x], Ord x) => P GroupCntStable a Source # 
Instance details

Defined in Predicate.Data.List

Associated Types

type PP GroupCntStable a Source #

Methods

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

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

Defined in Predicate.Data.List

Associated Types

type PP Unsnoc s 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.Data.List

Associated Types

type PP Uncons s Source #

Methods

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

x ~ [Int] => P LuhnDigit x Source # 
Instance details

Defined in Predicate.Data.Extra

Associated Types

type PP LuhnDigit x Source #

Methods

eval :: MonadEval m => proxy LuhnDigit -> POpts -> x -> m (TT (PP LuhnDigit x)) Source #

x ~ [Int] => P IsLuhn x Source # 
Instance details

Defined in Predicate.Data.Extra

Associated Types

type PP IsLuhn x Source #

Methods

eval :: MonadEval m => proxy IsLuhn -> POpts -> x -> m (TT (PP IsLuhn x)) Source #

(Show x, Integral x) => P PrimePrev x Source # 
Instance details

Defined in Predicate.Data.Extra

Associated Types

type PP PrimePrev x Source #

Methods

eval :: MonadEval m => proxy PrimePrev -> POpts -> x -> m (TT (PP PrimePrev x)) Source #

(Show x, Integral x) => P PrimeNext x Source # 
Instance details

Defined in Predicate.Data.Extra

Associated Types

type PP PrimeNext x Source #

Methods

eval :: MonadEval m => proxy PrimeNext -> POpts -> x -> m (TT (PP PrimeNext x)) Source #

(x ~ a, Show a, Integral a) => P IsPrime x Source # 
Instance details

Defined in Predicate.Data.Extra

Associated Types

type PP IsPrime x Source #

Methods

eval :: MonadEval m => proxy IsPrime -> POpts -> x -> m (TT (PP IsPrime x)) Source #

P InitMayT x => P InitMay x Source # 
Instance details

Defined in Predicate.Data.Extra

Associated Types

type PP InitMay x Source #

Methods

eval :: MonadEval m => proxy InitMay -> POpts -> x -> m (TT (PP InitMay x)) Source #

P TailMayT x => P TailMay x Source # 
Instance details

Defined in Predicate.Data.Extra

Associated Types

type PP TailMay x Source #

Methods

eval :: MonadEval m => proxy TailMay -> POpts -> x -> m (TT (PP TailMay x)) Source #

P LastMayT x => P LastMay x Source # 
Instance details

Defined in Predicate.Data.Extra

Associated Types

type PP LastMay x Source #

Methods

eval :: MonadEval m => proxy LastMay -> POpts -> x -> m (TT (PP LastMay x)) Source #

P HeadMayT x => P HeadMay x Source # 
Instance details

Defined in Predicate.Data.Extra

Associated Types

type PP HeadMay x Source #

Methods

eval :: MonadEval m => proxy HeadMay -> POpts -> x -> m (TT (PP HeadMay x)) Source #

P IsEBothT x => P IsEBoth x Source # 
Instance details

Defined in Predicate.Data.Elr

Associated Types

type PP IsEBoth x Source #

Methods

eval :: MonadEval m => proxy IsEBoth -> POpts -> x -> m (TT (PP IsEBoth x)) Source #

P IsERightT x => P IsERight x Source # 
Instance details

Defined in Predicate.Data.Elr

Associated Types

type PP IsERight x Source #

Methods

eval :: MonadEval m => proxy IsERight -> POpts -> x -> m (TT (PP IsERight x)) Source #

P IsELeftT x => P IsELeft x Source # 
Instance details

Defined in Predicate.Data.Elr

Associated Types

type PP IsELeft x Source #

Methods

eval :: MonadEval m => proxy IsELeft -> POpts -> x -> m (TT (PP IsELeft x)) Source #

P IsENoneT x => P IsENone x Source # 
Instance details

Defined in Predicate.Data.Elr

Associated Types

type PP IsENone x Source #

Methods

eval :: MonadEval m => proxy IsENone -> POpts -> x -> m (TT (PP IsENone x)) Source #

x ~ Either a b => P IsRight x Source # 
Instance details

Defined in Predicate.Data.Either

Associated Types

type PP IsRight x Source #

Methods

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

x ~ Either a b => P IsLeft x Source # 
Instance details

Defined in Predicate.Data.Either

Associated Types

type PP IsLeft x Source #

Methods

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

(ToTimeC x, Show x) => P ToTime x Source # 
Instance details

Defined in Predicate.Data.DateTime

Associated Types

type PP ToTime x Source #

Methods

eval :: MonadEval m => proxy ToTime -> POpts -> x -> m (TT (PP ToTime x)) Source #

(ToDayC x, Show x) => P ToDay x Source # 
Instance details

Defined in Predicate.Data.DateTime

Associated Types

type PP ToDay x Source #

Methods

eval :: MonadEval m => proxy ToDay -> POpts -> x -> m (TT (PP ToDay x)) Source #

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

Defined in Predicate.Data.Char

Associated Types

type PP ToTitle a Source #

Methods

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

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

Defined in Predicate.Data.Char

Associated Types

type PP ToUpper a 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.Data.Char

Associated Types

type PP ToLower a 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.Data.Char

Associated Types

type PP IsLatin1All x 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.Data.Char

Associated Types

type PP IsSeparatorAll x 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.Data.Char

Associated Types

type PP IsOctDigitAll x 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.Data.Char

Associated Types

type PP IsHexDigitAll x 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.Data.Char

Associated Types

type PP IsControlAll x 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.Data.Char

Associated Types

type PP IsPunctuationAll x Source #

Methods

eval :: MonadEval m => proxy IsPunctuationAll -> POpts -> x -> m (TT (PP IsPunctuationAll x)) Source #

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

Defined in Predicate.Data.Char

Associated Types

type PP IsSpaceAll x Source #

Methods

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

P IsDigitAllT x => P IsDigitAll x Source # 
Instance details

Defined in Predicate.Data.Char

Associated Types

type PP IsDigitAll x Source #

Methods

eval :: MonadEval m => proxy IsDigitAll -> POpts -> x -> m (TT (PP IsDigitAll x)) Source #

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

Defined in Predicate.Data.Char

Associated Types

type PP IsUpperAll x 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.Data.Char

Associated Types

type PP IsLowerAll x 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.Data.Char

Associated Types

type PP IsLatin1 x 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.Data.Char

Associated Types

type PP IsSeparator x 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.Data.Char

Associated Types

type PP IsOctDigit x 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.Data.Char

Associated Types

type PP IsHexDigit x 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.Data.Char

Associated Types

type PP IsControl x 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.Data.Char

Associated Types

type PP IsPunctuation x 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.Data.Char

Associated Types

type PP IsSpace x Source #

Methods

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

P IsDigitT x => P IsDigit x Source # 
Instance details

Defined in Predicate.Data.Char

Associated Types

type PP IsDigit x Source #

Methods

eval :: MonadEval m => proxy IsDigit -> POpts -> x -> m (TT (PP IsDigit x)) Source #

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

Defined in Predicate.Data.Char

Associated Types

type PP IsUpper x 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.Data.Char

Associated Types

type PP IsLower x Source #

Methods

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

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

Defined in Predicate.Data.These

Associated Types

type PP Theres [These a b] Source #

Methods

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

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

Defined in Predicate.Data.These

Associated Types

type PP Heres [These a b] Source #

Methods

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

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

Defined in Predicate.Data.These

Associated Types

type PP PartitionThese [These a b] Source #

Methods

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

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

Defined in Predicate.Data.Lifted

Associated Types

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

Methods

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

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

Defined in Predicate.Data.Lifted

Associated Types

type PP Join (t (t a)) 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.Data.Lifted

Associated Types

type PP Duplicate (t a) 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.Data.Lifted

Associated Types

type PP Extract (t a) Source #

Methods

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

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

Defined in Predicate.Data.Foldable

Associated Types

type PP ToList (t a) Source #

Methods

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

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

Defined in Predicate.Data.Foldable

Associated Types

type PP ToNEList (t a) Source #

Methods

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

Show a => P Just' (Maybe a) Source # 
Instance details

Defined in Predicate.Data.Maybe

Associated Types

type PP Just' (Maybe a) Source #

Methods

eval :: MonadEval m => proxy Just' -> POpts -> Maybe a -> m (TT (PP Just' (Maybe a))) Source #

(Show a, Show b) => P PartitionElr [Elr a b] Source # 
Instance details

Defined in Predicate.Data.Elr

Associated Types

type PP PartitionElr [Elr a b] Source #

Methods

eval :: MonadEval m => proxy PartitionElr -> POpts -> [Elr a b] -> m (TT (PP PartitionElr [Elr a b])) Source #

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

Defined in Predicate.Data.Either

Associated Types

type PP PartitionEithers [Either a b] Source #

Methods

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

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

Defined in Predicate.Core

Associated Types

type PP Swap (p a b) Source #

Methods

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

Typeable t => P UnproxyT (Proxy t) Source # 
Instance details

Defined in Predicate.Core

Associated Types

type PP UnproxyT (Proxy t) Source #

Methods

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

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

Defined in Predicate.Data.Tuple

Associated Types

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

Methods

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

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

Defined in Predicate.Data.Tuple

Associated Types

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

Methods

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

ReverseITupleC x xs () => P ReverseITuple (x, xs) Source # 
Instance details

Defined in Predicate.Data.Tuple

Associated Types

type PP ReverseITuple (x, xs) Source #

Methods

eval :: MonadEval m => proxy ReverseITuple -> POpts -> (x, xs) -> m (TT (PP ReverseITuple (x, xs))) Source #

(Show a, Show b) => P These' (These a b) Source # 
Instance details

Defined in Predicate.Data.These

Associated Types

type PP These' (These a b) Source #

Methods

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

Show a => P That' (These x a) Source # 
Instance details

Defined in Predicate.Data.These

Associated Types

type PP That' (These x a) Source #

Methods

eval :: MonadEval m => proxy That' -> POpts -> These x a -> m (TT (PP That' (These x a))) Source #

Show a => P This' (These a x) Source # 
Instance details

Defined in Predicate.Data.These

Associated Types

type PP This' (These a x) Source #

Methods

eval :: MonadEval m => proxy This' -> POpts -> These a x -> m (TT (PP This' (These a x))) Source #

P Elr2Maybe (Elr a b) Source # 
Instance details

Defined in Predicate.Data.Elr

Associated Types

type PP Elr2Maybe (Elr a b) Source #

Methods

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

P These2Elr (These a b) Source # 
Instance details

Defined in Predicate.Data.Elr

Associated Types

type PP These2Elr (These a b) Source #

Methods

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

P Elr2These (Elr a b) Source # 
Instance details

Defined in Predicate.Data.Elr

Associated Types

type PP Elr2These (Elr a b) Source #

Methods

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

(Show a, Show b) => P EBoth' (Elr a b) Source # 
Instance details

Defined in Predicate.Data.Elr

Associated Types

type PP EBoth' (Elr a b) Source #

Methods

eval :: MonadEval m => proxy EBoth' -> POpts -> Elr a b -> m (TT (PP EBoth' (Elr a b))) Source #

Show a => P ERight' (Elr x a) Source # 
Instance details

Defined in Predicate.Data.Elr

Associated Types

type PP ERight' (Elr x a) Source #

Methods

eval :: MonadEval m => proxy ERight' -> POpts -> Elr x a -> m (TT (PP ERight' (Elr x a))) Source #

Show a => P ELeft' (Elr a x) Source # 
Instance details

Defined in Predicate.Data.Elr

Associated Types

type PP ELeft' (Elr a x) Source #

Methods

eval :: MonadEval m => proxy ELeft' -> POpts -> Elr a x -> m (TT (PP ELeft' (Elr a x))) Source #

P ENone' (Elr x y) Source # 
Instance details

Defined in Predicate.Data.Elr

Associated Types

type PP ENone' (Elr x y) Source #

Methods

eval :: MonadEval m => proxy ENone' -> POpts -> Elr x y -> m (TT (PP ENone' (Elr x y))) Source #

Show a => P Right' (Either x a) Source # 
Instance details

Defined in Predicate.Data.Either

Associated Types

type PP Right' (Either x a) Source #

Methods

eval :: MonadEval m => proxy Right' -> POpts -> Either x a -> m (TT (PP Right' (Either x a))) Source #

Show a => P Left' (Either a x) Source # 
Instance details

Defined in Predicate.Data.Either

Associated Types

type PP Left' (Either a x) Source #

Methods

eval :: MonadEval m => proxy Left' -> POpts -> Either a x -> m (TT (PP Left' (Either a x))) Source #

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

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

>>> pz @'[] False
Val []
Instance details

Defined in Predicate.Core

Associated Types

type PP '[] a Source #

Methods

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

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

Defined in Predicate.Core

Associated Types

type PP (Hole t) a Source #

Methods

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

(KnownNat n, FailWhenT (n <=? 0) ('Text "ToITupleList:n cannot be 0"), ToITupleListC n a, xs ~ [a]) => P (ToITupleList n :: Type) xs Source # 
Instance details

Defined in Predicate.Data.Tuple

Associated Types

type PP (ToITupleList n) xs Source #

Methods

eval :: MonadEval m => proxy (ToITupleList n) -> POpts -> xs -> m (TT (PP (ToITupleList n) xs)) Source #

(KnownNat n, FailWhenT (n <=? 1) ('Text "Tuple':n cannot be less than two but found n=" :<>: 'ShowType n), TupleC n a, x ~ [a]) => P (Tuple' n :: Type) x Source # 
Instance details

Defined in Predicate.Data.Tuple

Associated Types

type PP (Tuple' n) x Source #

Methods

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

(KnownNat n, FailWhenT (n <=? 1) ('Text "Tuple:n cannot be less than two but found n=" :<>: 'ShowType n), TupleC n a, x ~ [a], Show a) => P (Tuple n :: Type) x Source # 
Instance details

Defined in Predicate.Data.Tuple

Associated Types

type PP (Tuple n) x Source #

Methods

eval :: MonadEval m => proxy (Tuple n) -> POpts -> x -> m (TT (PP (Tuple n) x)) Source #

(BetweenT "ShowBase" 2 36 n, KnownNat n, Integral x) => P (ShowBase n :: Type) x Source # 
Instance details

Defined in Predicate.Data.Numeric

Associated Types

type PP (ShowBase n) x Source #

Methods

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

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

Defined in Predicate.Data.Numeric

Associated Types

type PP (Floor t) x Source #

Methods

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

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

Defined in Predicate.Data.Numeric

Associated Types

type PP (Ceiling t) x Source #

Methods

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

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

Defined in Predicate.Data.Numeric

Associated Types

type PP (Truncate t) x Source #

Methods

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

P (FromRationalT t) x => P (FromRational t :: Type) x Source # 
Instance details

Defined in Predicate.Data.Numeric

Associated Types

type PP (FromRational t) x Source #

Methods

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

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

Defined in Predicate.Data.Numeric

Associated Types

type PP (FromIntegral t) x Source #

Methods

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

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

Defined in Predicate.Data.Numeric

Associated Types

type PP (FromInteger t) x Source #

Methods

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

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

Defined in Predicate.Data.Monoid

Associated Types

type PP (MEmptyT t) x Source #

Methods

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

P (SapT t) x => P (Sap t :: Type) x Source # 
Instance details

Defined in Predicate.Data.Monoid

Associated Types

type PP (Sap t) x Source #

Methods

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

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

Defined in Predicate.Data.Lifted

Associated Types

type PP (Coerce t) a Source #

Methods

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

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

Defined in Predicate.Data.Lifted

Associated Types

type PP (EmptyList t) x Source #

Methods

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

P (FoldAlaT t) x => P (FoldAla t :: Type) x Source # 
Instance details

Defined in Predicate.Data.Foldable

Associated Types

type PP (FoldAla t) x Source #

Methods

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

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

Defined in Predicate.Data.Foldable

Associated Types

type PP (FromListExt l') l 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.Data.Foldable

Associated Types

type PP (FromList t) x Source #

Methods

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

P (IToListT t) x => P (IToList t :: Type) x Source # 
Instance details

Defined in Predicate.Data.Foldable

Associated Types

type PP (IToList t) x Source #

Methods

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

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

Defined in Predicate.Data.Maybe

Associated Types

type PP (MkNothing t) x Source #

Methods

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

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

Defined in Predicate.Data.Index

Associated Types

type PP (Ix' n) x Source #

Methods

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

P (UniverseT t) x => P (Universe t :: Type) x Source # 
Instance details

Defined in Predicate.Data.Enum

Associated Types

type PP (Universe t) x Source #

Methods

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

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

Defined in Predicate.Data.Enum

Associated Types

type PP (ToEnumBFail t) x Source #

Methods

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

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

Defined in Predicate.Data.Enum

Associated Types

type PP (ToEnum t) x Source #

Methods

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

(KnownSymbol s, FailUnlessT (CmpSymbol s "" == 'GT) ('Text "C symbol cannot be empty")) => P (C s :: Type) a Source # 
Instance details

Defined in Predicate.Data.Char

Associated Types

type PP (C s) a Source #

Methods

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

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

expects Nothing otherwise it fails if the value is Nothing then it returns Proxy a as this provides type information

>>> pz @'Nothing Nothing
Val Proxy
>>> pz @'Nothing (Just True)
Fail "'Nothing found Just"
Instance details

Defined in Predicate.Core

Associated Types

type PP 'Nothing (Maybe a2) Source #

Methods

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

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

tries to extract a from Maybe a otherwise it fails: similar to fromJust

>>> pz @('Just Id) (Just "abc")
Val "abc"
>>> pl @('Just Id >> Id) (Just 123)
Present 123 ((>>) 123 | {Id 123})
Val 123
>>> pl @('Just Id) (Just [1,2,3])
Present [1,2,3] ('Just [1,2,3] | Just [1,2,3])
Val [1,2,3]
>>> pl @('Just Id) (Just 10)
Present 10 ('Just 10 | Just 10)
Val 10
>>> pl @('Just Id) Nothing
Error 'Just(empty)
Fail "'Just(empty)"
>>> pz @('Just Fst) (Just 123,'x')
Val 123
Instance details

Defined in Predicate.Core

Associated Types

type PP ('Just p) x Source #

Methods

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

P (Proxy t :: Type) a Source #

create a Proxy for a kind t

>>> pz @(Proxy 4) ()
Val Proxy
>>> pz @(Proxy Int) ()
Val Proxy
>>> pz @(Proxy "abc" >> Pop0 Id ()) ()
Val "abc"
Instance details

Defined in Predicate.Core

Associated Types

type PP (Proxy t) a Source #

Methods

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

P (DoExpandLT ps) a => P (DoL ps :: Type) a Source # 
Instance details

Defined in Predicate.Core

Associated Types

type PP (DoL ps) a Source #

Methods

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

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

Defined in Predicate.Core

Associated Types

type PP (Do ps) a Source #

Methods

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

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

Defined in Predicate.Core

Associated Types

type PP (Map p) x Source #

Methods

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

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

Defined in Predicate.Core

Associated Types

type PP (L8 p) x Source #

Methods

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

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

Defined in Predicate.Core

Associated Types

type PP (L7 p) x Source #

Methods

eval :: MonadEval m => proxy (L7 p) -> POpts -> x -> m (TT (PP (L7 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.Core

Associated Types

type PP (L6 p) x 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.Core

Associated Types

type PP (L5 p) x 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.Core

Associated Types

type PP (L4 p) x Source #

Methods

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

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

Defined in Predicate.Core

Associated Types

type PP (L3 p) x Source #

Methods

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

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

Defined in Predicate.Core

Associated Types

type PP (L2 p) x Source #

Methods

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

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

Defined in Predicate.Core

Associated Types

type PP (L1 p) x Source #

Methods

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

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

Defined in Predicate.Core

Associated Types

type PP (Any p) x Source #

Methods

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

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

Defined in Predicate.Core

Associated Types

type PP (All p) x Source #

Methods

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

P (Fail UnproxyT p) x => P (FailP p :: Type) x Source # 
Instance details

Defined in Predicate.Core

Associated Types

type PP (FailP p) x Source #

Methods

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

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

Defined in Predicate.Core

Associated Types

type PP (FailS p) x Source #

Methods

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

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

Defined in Predicate.Core

Associated Types

type PP (Not p) x Source #

Methods

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

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

Defined in Predicate.Core

Associated Types

type PP (Length p) x Source #

Methods

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

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

Defined in Predicate.Core

Associated Types

type PP (Hide p) x Source #

Methods

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

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

Defined in Predicate.Core

Associated Types

type PP (W p) a Source #

Methods

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

P (EachITuple p :: Type) () Source # 
Instance details

Defined in Predicate.Data.Tuple

Associated Types

type PP (EachITuple p) () Source #

Methods

eval :: MonadEval m => proxy (EachITuple p) -> POpts -> () -> m (TT (PP (EachITuple p) ())) Source #

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

Defined in Predicate.Data.Tuple

Associated Types

type PP (Uncurry p) x Source #

Methods

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

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

Defined in Predicate.Data.Tuple

Associated Types

type PP (Second q) x 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.Data.Tuple

Associated Types

type PP (First p) x Source #

Methods

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

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

Defined in Predicate.Data.Regex

Associated Types

type PP (ReplaceFn3 p) x 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.Data.Regex

Associated Types

type PP (ReplaceFn2 p) x 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.Data.Regex

Associated Types

type PP (ReplaceFn1 p) x Source #

Methods

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

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

Defined in Predicate.Data.Regex

Associated Types

type PP (Resplit p) x Source #

Methods

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

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

Defined in Predicate.Data.Regex

Associated Types

type PP (Rescan p) x Source #

Methods

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

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

Defined in Predicate.Data.Regex

Associated Types

type PP (Re p) x Source #

Methods

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

(PrintC bs, (b, bs) ~ x, PrintfArg b, PP s x ~ String, P s x) => P (PrintI s :: Type) x Source # 
Instance details

Defined in Predicate.Data.ReadShow

Associated Types

type PP (PrintI s) x Source #

Methods

eval :: MonadEval m => proxy (PrintI s) -> POpts -> x -> m (TT (PP (PrintI s) x)) Source #

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

Defined in Predicate.Data.ReadShow

Associated Types

type PP (ShowP p) x Source #

Methods

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

PP p x ~ proxy z => P (Proxify p :: Type) x Source # 
Instance details

Defined in Predicate.Data.Proxy

Associated Types

type PP (Proxify p) x Source #

Methods

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

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

Defined in Predicate.Data.Ordering

Associated Types

type PP (Comparing p) x Source #

Methods

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

P (NeT n) x => P (Ne n :: Type) x Source # 
Instance details

Defined in Predicate.Data.Ordering

Associated Types

type PP (Ne n) x Source #

Methods

eval :: MonadEval m => proxy (Ne n) -> POpts -> x -> m (TT (PP (Ne n) x)) Source #

P (LtT n) x => P (Lt n :: Type) x Source # 
Instance details

Defined in Predicate.Data.Ordering

Associated Types

type PP (Lt n) x Source #

Methods

eval :: MonadEval m => proxy (Lt n) -> POpts -> x -> m (TT (PP (Lt n) x)) Source #

P (LeT n) x => P (Le n :: Type) x Source # 
Instance details

Defined in Predicate.Data.Ordering

Associated Types

type PP (Le n) x Source #

Methods

eval :: MonadEval m => proxy (Le n) -> POpts -> x -> m (TT (PP (Le n) x)) Source #

P (SameT n) x => P (Same n :: Type) x Source # 
Instance details

Defined in Predicate.Data.Ordering

Associated Types

type PP (Same n) x Source #

Methods

eval :: MonadEval m => proxy (Same n) -> POpts -> x -> m (TT (PP (Same n) x)) Source #

P (GeT n) x => P (Ge n :: Type) x Source # 
Instance details

Defined in Predicate.Data.Ordering

Associated Types

type PP (Ge n) x Source #

Methods

eval :: MonadEval m => proxy (Ge n) -> POpts -> x -> m (TT (PP (Ge n) x)) Source #

P (GtT n) x => P (Gt n :: Type) x Source # 
Instance details

Defined in Predicate.Data.Ordering

Associated Types

type PP (Gt n) x Source #

Methods

eval :: MonadEval m => proxy (Gt n) -> POpts -> x -> m (TT (PP (Gt n) x)) Source #

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

Defined in Predicate.Data.Numeric

Associated Types

type PP (ToBits p) x Source #

Methods

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

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

Defined in Predicate.Data.Numeric

Associated Types

type PP (ReadBase t n) x Source #

Methods

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

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

Defined in Predicate.Data.Numeric

Associated Types

type PP (Signum p) x Source #

Methods

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

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

Defined in Predicate.Data.Numeric

Associated Types

type PP (Abs p) x Source #

Methods

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

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

Defined in Predicate.Data.Numeric

Associated Types

type PP (Negate p) x Source #

Methods

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

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

Defined in Predicate.Data.Numeric

Associated Types

type PP (ToRational p) x Source #

Methods

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

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

Defined in Predicate.Data.Monoid

Associated Types

type PP (MEmptyT' t) a Source #

Methods

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

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

Defined in Predicate.Data.Monoid

Associated Types

type PP (SConcat p) x Source #

Methods

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

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

Defined in Predicate.Data.Lifted

Associated Types

type PP (RDot ps q) a 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.Data.Lifted

Associated Types

type PP (Dot ps q) a Source #

Methods

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

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

Defined in Predicate.Data.Lifted

Associated Types

type PP (Skip p) a Source #

Methods

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

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

Defined in Predicate.Data.Lifted

Associated Types

type PP (Traverse p) x Source #

Methods

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

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

Defined in Predicate.Data.Lifted

Associated Types

type PP (EmptyList' t) x Source #

Methods

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

Alternative t => P (EmptyT t t1 :: Type) x Source # 
Instance details

Defined in Predicate.Data.Lifted

Associated Types

type PP (EmptyT t t1) x Source #

Methods

eval :: MonadEval m => proxy (EmptyT t t1) -> POpts -> x -> m (TT (PP (EmptyT t t1) 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.Data.Foldable

Associated Types

type PP (Null' p) x Source #

Methods

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

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

Defined in Predicate.Data.Maybe

Associated Types

type PP (MkJust p) x 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.Data.Maybe

Associated Types

type PP (MkNothing' t) a Source #

Methods

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

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

Defined in Predicate.Data.IO

Associated Types

type PP (Stderr p) x 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.Data.IO

Associated Types

type PP (Stdout p) x 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.Data.IO

Associated Types

type PP (ReadEnv p) x Source #

Methods

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

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

Defined in Predicate.Data.IO

Associated Types

type PP (ReadDir p) x Source #

Methods

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

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

Defined in Predicate.Data.IO

Associated Types

type PP (DirExists p) x Source #

Methods

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

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

Defined in Predicate.Data.IO

Associated Types

type PP (FileExists p) x 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 (ReadFileBinary p :: Type) x Source # 
Instance details

Defined in Predicate.Data.IO

Associated Types

type PP (ReadFileBinary p) x Source #

Methods

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

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

Defined in Predicate.Data.IO

Associated Types

type PP (ReadFile p) x Source #

Methods

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

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

Defined in Predicate.Data.Enum

Associated Types

type PP (Universe' p) x Source #

Methods

eval :: MonadEval m => proxy (Universe' p) -> POpts -> x -> m (TT (PP (Universe' 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.Data.Enum

Associated Types

type PP (FromEnum' p) x Source #

Methods

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

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

Defined in Predicate.Data.Enum

Associated Types

type PP (PredB' q) x 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.Data.Enum

Associated Types

type PP (SuccB' q) x Source #

Methods

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

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

Defined in Predicate.Data.List

Associated Types

type PP (Singleton p) x Source #

Methods

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

P (ChunksOfT n) x => P (ChunksOf n :: Type) x Source # 
Instance details

Defined in Predicate.Data.List

Associated Types

type PP (ChunksOf n) x Source #

Methods

eval :: MonadEval m => proxy (ChunksOf n) -> POpts -> x -> m (TT (PP (ChunksOf n) x)) Source #

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

Defined in Predicate.Data.List

Associated Types

type PP (All1 p) x Source #

Methods

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

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

Defined in Predicate.Data.List

Associated Types

type PP (Quant p) x Source #

Methods

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

(Integral (PP n x), P n x) => P (PrimeFactors n :: Type) x Source # 
Instance details

Defined in Predicate.Data.Extra

Associated Types

type PP (PrimeFactors n) x Source #

Methods

eval :: MonadEval m => proxy (PrimeFactors n) -> POpts -> x -> m (TT (PP (PrimeFactors n) x)) Source #

(Integral (PP n x), P n x) => P (Primes n :: Type) x Source # 
Instance details

Defined in Predicate.Data.Extra

Associated Types

type PP (Primes n) x Source #

Methods

eval :: MonadEval m => proxy (Primes n) -> POpts -> x -> m (TT (PP (Primes n) x)) Source #

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

Defined in Predicate.Data.Iterator

Associated Types

type PP (Para ps) x Source #

Methods

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

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

Defined in Predicate.Data.Iterator

Associated Types

type PP (ScanNA q) x Source #

Methods

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

P (MkENone t t1 :: Type) x Source # 
Instance details

Defined in Predicate.Data.Elr

Associated Types

type PP (MkENone t t1) x Source #

Methods

eval :: MonadEval m => proxy (MkENone t t1) -> POpts -> x -> m (TT (PP (MkENone t t1) x)) Source #

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

Defined in Predicate.Data.DateTime

Associated Types

type PP (LocalTimeToUTC p) x Source #

Methods

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

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

Defined in Predicate.Data.DateTime

Associated Types

type PP (UTCTimeToPosix p) x Source #

Methods

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

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

Defined in Predicate.Data.DateTime

Associated Types

type PP (PosixToUTCTime p) x Source #

Methods

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

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

Defined in Predicate.Data.DateTime

Associated Types

type PP (UnMkTime p) x Source #

Methods

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

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

Defined in Predicate.Data.DateTime

Associated Types

type PP (MkTime p) x Source #

Methods

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

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

Defined in Predicate.Data.DateTime

Associated Types

type PP (ToWeekYear p) x Source #

Methods

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

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

Defined in Predicate.Data.DateTime

Associated Types

type PP (ToWeekDate p) x Source #

Methods

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

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

Defined in Predicate.Data.DateTime

Associated Types

type PP (MkDayExtra p) x Source #

Methods

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

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

Defined in Predicate.Data.DateTime

Associated Types

type PP (UnMkDay p) x Source #

Methods

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

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

Defined in Predicate.Data.DateTime

Associated Types

type PP (MkDay p) x Source #

Methods

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

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

Defined in Predicate.Data.DateTime

Associated Types

type PP (FormatTimeP p) x Source #

Methods

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

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

Defined in Predicate.Data.Condition

Associated Types

type PP (GuardSimple p) a Source #

Methods

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

(Show t, Bits t) => P (ZeroBits t :: Type) a Source # 
Instance details

Defined in Predicate.Data.Bits

Associated Types

type PP (ZeroBits t) a Source #

Methods

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

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

Defined in Predicate.Data.Bits

Associated Types

type PP (PopCount p) a Source #

Methods

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

(Traversable n, P p a) => P (FMap p :: Type) (n a) Source # 
Instance details

Defined in Predicate.Data.Lifted

Associated Types

type PP (FMap p) (n a) Source #

Methods

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

(Traversable n, Monoid t, PP p a ~ t, P p a) => P (FoldMap p :: Type) (n a) Source # 
Instance details

Defined in Predicate.Data.Foldable

Associated Types

type PP (FoldMap p) (n a) Source #

Methods

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

(P p b, P (EachITuple p) bs) => P (EachITuple p :: Type) (b, bs) Source # 
Instance details

Defined in Predicate.Data.Tuple

Associated Types

type PP (EachITuple p) (b, bs) Source #

Methods

eval :: MonadEval m => proxy (EachITuple p) -> POpts -> (b, bs) -> m (TT (PP (EachITuple p) (b, bs))) Source #

(P p a, P p a') => P (Both p :: Type) (a, a') Source # 
Instance details

Defined in Predicate.Data.Tuple

Associated Types

type PP (Both p) (a, a') Source #

Methods

eval :: MonadEval m => proxy (Both p) -> POpts -> (a, a') -> m (TT (PP (Both p) (a, 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 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]) a Source #

runs each predicate in turn from the promoted list

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

Defined in Predicate.Core

Associated Types

type PP '[p] a Source #

Methods

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

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

Defined in Predicate.Core

Associated Types

type PP (FailT t p) x Source #

Methods

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

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

Defined in Predicate.Core

Associated Types

type PP (Wrap t p) x Source #

Methods

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

(KnownNat n, P p a) => P (Width n p :: Type) a Source # 
Instance details

Defined in Predicate.Core

Associated Types

type PP (Width n p) a Source #

Methods

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

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

Defined in Predicate.Data.These

Associated Types

type PP (MkThat t p) x 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.Data.These

Associated Types

type PP (MkThis t p) x Source #

Methods

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

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

Defined in Predicate.Data.String

Associated Types

type PP (FromString t p) x Source #

Methods

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

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

Defined in Predicate.Data.Regex

Associated Types

type PP (ReplaceFn r p) x Source #

Methods

eval :: MonadEval m => proxy (ReplaceFn r p) -> POpts -> x -> m (TT (PP (ReplaceFn r p) x)) Source #

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

Defined in Predicate.Data.ReadShow

Associated Types

type PP (ReadMaybe t p) x 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.Data.ReadShow

Associated Types

type PP (ReadP t p) x Source #

Methods

eval :: MonadEval m => proxy (ReadP t p) -> POpts -> x -> m (TT (PP (ReadP 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.Data.Lifted

Associated Types

type PP (Pure t p) x Source #

Methods

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

Alternative t => P (EmptyT' t p :: Type) x Source # 
Instance details

Defined in Predicate.Data.Lifted

Associated Types

type PP (EmptyT' t p) x Source #

Methods

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

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

Defined in Predicate.Data.Json

Associated Types

type PP (EncodeJson pretty p) x Source #

Methods

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

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

Defined in Predicate.Data.Json

Associated Types

type PP (ParseJsonFile t p) x 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.Data.Json

Associated Types

type PP (ParseJson t p) x Source #

Methods

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

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

Defined in Predicate.Data.Index

Associated Types

type PP (Ix n def) x Source #

Methods

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

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

Defined in Predicate.Data.IO

Associated Types

type PP (WriteFile s p) x 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.Data.IO

Associated Types

type PP (WriteFile' s p) x 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.Data.IO

Associated Types

type PP (AppendFile s p) x Source #

Methods

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

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

Defined in Predicate.Data.Enum

Associated Types

type PP (ToEnumBDef t def) x Source #

Methods

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

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

Defined in Predicate.Data.Iterator

Associated Types

type PP (DoN n p) a 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.Data.Iterator

Associated Types

type PP (Repeat n p) a Source #

Methods

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

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

Defined in Predicate.Data.Iterator

Associated Types

type PP (ParaN n p) x Source #

Methods

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

P (MkERightT t p) x => P (MkERight t p :: Type) x Source # 
Instance details

Defined in Predicate.Data.Elr

Associated Types

type PP (MkERight t p) x Source #

Methods

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

P (MkELeftT t p) x => P (MkELeft t p :: Type) x Source # 
Instance details

Defined in Predicate.Data.Elr

Associated Types

type PP (MkELeft t p) x Source #

Methods

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

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

Defined in Predicate.Data.Either

Associated Types

type PP (MkRight t p) x 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.Data.Either

Associated Types

type PP (MkLeft t p) x Source #

Methods

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

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

Defined in Predicate.Data.DateTime

Associated Types

type PP (ParseTimeP t p) x Source #

Methods

eval :: MonadEval m => proxy (ParseTimeP t p) -> POpts -> x -> m (TT (PP (ParseTimeP 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.Data.Condition

Associated Types

type PP (Bools ps) x 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.Data.Condition

Associated Types

type PP (Guards ps) x Source #

Methods

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

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

Defined in Predicate.Core

Associated Types

type PP (q & p) a 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.Core

Associated Types

type PP (p $ q) a 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.Core

Associated Types

type PP (p ~> q) a 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.Core

Associated Types

type PP (p ||~ q) a 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.Core

Associated Types

type PP (p || q) a 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.Core

Associated Types

type PP (p &&~ q) a 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.Core

Associated Types

type PP (p && q) a Source #

Methods

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

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

Defined in Predicate.Core

Associated Types

type PP (Map' p q) x Source #

Methods

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

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

Defined in Predicate.Core

Associated Types

type PP (p <..> q) x Source #

Methods

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

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

Defined in Predicate.Core

Associated Types

type PP (Fail t prt) a Source #

Methods

eval :: MonadEval m => proxy (Fail t prt) -> POpts -> a -> m (TT (PP (Fail t prt) a)) 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.Core

Associated Types

type PP (Wrap' s p) x Source #

Methods

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

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

Defined in Predicate.Core

Associated Types

type PP (p << q) x Source #

Methods

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

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

Defined in Predicate.Core

Associated Types

type PP (p >>> q) x Source #

Methods

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

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

Defined in Predicate.Core

Associated Types

type PP (p >> q) a Source #

Methods

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

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

Defined in Predicate.Core

Associated Types

type PP (MsgI prt p) a Source #

Methods

eval :: MonadEval m => proxy (MsgI prt p) -> POpts -> a -> m (TT (PP (MsgI prt p) 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 Source #

Methods

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

P (OnT p q) x => P (On p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.Tuple

Associated Types

type PP (On p q) x Source #

Methods

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

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

Defined in Predicate.Data.Tuple

Associated Types

type PP (p |+ q) x 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.Data.Tuple

Associated Types

type PP (p &* q) x 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.Data.Tuple

Associated Types

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

Methods

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

P (ThesePairT s t) x => P (ThesePair s t :: Type) x Source # 
Instance details

Defined in Predicate.Data.These

Associated Types

type PP (ThesePair s t) x Source #

Methods

eval :: MonadEval m => proxy (ThesePair s t) -> POpts -> x -> m (TT (PP (ThesePair s t) x)) 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.Data.These

Associated Types

type PP (TheseFail p q) x 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.Data.These

Associated Types

type PP (ThatFail p q) x 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.Data.These

Associated Types

type PP (ThisFail p q) x 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.Data.These

Associated Types

type PP (TheseDef p q) x 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.Data.These

Associated Types

type PP (ThatDef p q) x 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.Data.These

Associated Types

type PP (ThisDef p q) x Source #

Methods

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

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

Defined in Predicate.Data.These

Associated Types

type PP (ZipThese p q) a Source #

Methods

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

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

Defined in Predicate.Data.These

Associated Types

type PP (MkThese p q) a 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.Data.These

Associated Types

type PP (MkThat' t p) x Source #

Methods

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

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

Defined in Predicate.Data.These

Associated Types

type PP (MkThis' t p) x Source #

Methods

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

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

Defined in Predicate.Data.String

Associated Types

type PP (FromString' t p) a Source #

Methods

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

P (IsSuffixCIT p q) x => P (IsSuffixCI p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.String

Associated Types

type PP (IsSuffixCI p q) x Source #

Methods

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

P (IsInfixCIT p q) x => P (IsInfixCI p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.String

Associated Types

type PP (IsInfixCI p q) x Source #

Methods

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

P (IsPrefixCIT p q) x => P (IsPrefixCI p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.String

Associated Types

type PP (IsPrefixCI p q) x Source #

Methods

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

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

Defined in Predicate.Data.String

Associated Types

type PP (StripR p q) x 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.Data.String

Associated Types

type PP (StripL p q) x Source #

Methods

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

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

Defined in Predicate.Data.Regex

Associated Types

type PP (RescanRanges p q) x Source #

Methods

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

P (PrintTT s p) x => P (PrintT s p :: Type) x Source # 
Instance details

Defined in Predicate.Data.ReadShow

Associated Types

type PP (PrintT s p) x Source #

Methods

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

Associated Types

type PP (PrintF s p) x Source #

Methods

eval :: MonadEval m => proxy (PrintF s p) -> POpts -> x -> m (TT (PP (PrintF s 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.Data.ReadShow

Associated Types

type PP (ReadMaybe' t p) x 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.Data.ReadShow

Associated Types

type PP (ReadP' t p) x Source #

Methods

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

(PP p x ~ Proxy z, PP q x ~ Proxy w) => P (PApp p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.Proxy

Associated Types

type PP (PApp p q) x Source #

Methods

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

(P q x, PP p x ~ proxy z, P z (PP q x)) => P (Pop0 p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.Proxy

Associated Types

type PP (Pop0 p q) x Source #

Methods

eval :: MonadEval m => proxy (Pop0 p q) -> POpts -> x -> m (TT (PP (Pop0 p q) 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.Data.Ordering

Associated Types

type PP (p ===~ q) a Source #

Methods

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

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

Defined in Predicate.Data.Ordering

Associated Types

type PP (p ==! q) a 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.Data.Ordering

Associated Types

type PP (p /=~ q) x 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.Data.Ordering

Associated Types

type PP (p <~ q) x 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.Data.Ordering

Associated Types

type PP (p <=~ q) x 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.Data.Ordering

Associated Types

type PP (p ==~ q) x 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.Data.Ordering

Associated Types

type PP (p >=~ q) x 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.Data.Ordering

Associated Types

type PP (p >~ q) x 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.Data.Ordering

Associated Types

type PP (p /= q) x 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.Data.Ordering

Associated Types

type PP (p < q) x 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.Data.Ordering

Associated Types

type PP (p <= q) x 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.Data.Ordering

Associated Types

type PP (p == q) x 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.Data.Ordering

Associated Types

type PP (p >= q) x 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.Data.Ordering

Associated Types

type PP (p > q) x Source #

Methods

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

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

Defined in Predicate.Data.Numeric

Associated Types

type PP (RoundUp n p) x Source #

Methods

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

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

Defined in Predicate.Data.Numeric

Associated Types

type PP (UnShowBaseN n p) x Source #

Methods

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

(PP p x ~ a, P p x, PP n x ~ b, P n x, Integral a, Integral b) => P (ShowBaseN n p :: Type) x Source # 
Instance details

Defined in Predicate.Data.Numeric

Associated Types

type PP (ShowBaseN n p) x Source #

Methods

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

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

Defined in Predicate.Data.Numeric

Associated Types

type PP (Rem p q) x 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.Data.Numeric

Associated Types

type PP (Quot p q) x 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.Data.Numeric

Associated Types

type PP (QuotRem p q) a 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.Data.Numeric

Associated Types

type PP (DivMod p q) a 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.Data.Numeric

Associated Types

type PP (Mod p q) a 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.Data.Numeric

Associated Types

type PP (Div p q) a Source #

Methods

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

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

Defined in Predicate.Data.Numeric

Associated Types

type PP (p -% q) x 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.Data.Numeric

Associated Types

type PP (p % q) x 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.Data.Numeric

Associated Types

type PP (p / q) a Source #

Methods

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

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

Defined in Predicate.Data.Numeric

Associated Types

type PP (LogBase p q) a Source #

Methods

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

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

Defined in Predicate.Data.Numeric

Associated Types

type PP (p ** q) a Source #

Methods

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

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

Defined in Predicate.Data.Numeric

Associated Types

type PP (p ^ q) a Source #

Methods

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

P (MultT p q) x => P (p * q :: Type) x Source # 
Instance details

Defined in Predicate.Data.Numeric

Associated Types

type PP (p * q) x 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.Data.Numeric

Associated Types

type PP (p - q) x 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.Data.Numeric

Associated Types

type PP (p + q) x Source #

Methods

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

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

Defined in Predicate.Data.Numeric

Associated Types

type PP (Floor' t p) x Source #

Methods

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

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

Defined in Predicate.Data.Numeric

Associated Types

type PP (Ceiling' t p) x Source #

Methods

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

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

Defined in Predicate.Data.Numeric

Associated Types

type PP (Truncate' t p) x Source #

Methods

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

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

Defined in Predicate.Data.Numeric

Associated Types

type PP (FromRational' t p) a Source #

Methods

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

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

Defined in Predicate.Data.Numeric

Associated Types

type PP (FromIntegral' t p) a Source #

Methods

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

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

Defined in Predicate.Data.Numeric

Associated Types

type PP (FromInteger' t p) a Source #

Methods

eval :: MonadEval m => proxy (FromInteger' t p) -> POpts -> a -> m (TT (PP (FromInteger' t p) a)) 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.Data.Monoid

Associated Types

type PP (STimes n p) a Source #

Methods

eval :: MonadEval m => proxy (STimes n p) -> POpts -> a -> m (TT (PP (STimes n p) a)) 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.Data.Monoid

Associated Types

type PP (p <> q) x Source #

Methods

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

P (AppT p q) x => P (p <*> q :: Type) x Source # 
Instance details

Defined in Predicate.Data.Lifted

Associated Types

type PP (p <*> q) x Source #

Methods

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

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

Defined in Predicate.Data.Lifted

Associated Types

type PP (p >>= q) x Source #

Methods

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

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

Defined in Predicate.Data.Lifted

Associated Types

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

Methods

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

(Applicative n, PP p a ~ n x, PP q a ~ n y, JoinT (PP p a) (PP q a) ~ n (x, y), P p a, P q a) => P (FPair p q :: Type) a Source # 
Instance details

Defined in Predicate.Data.Lifted

Associated Types

type PP (FPair p q) a Source #

Methods

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

P (FMapFlipT p q) x => P (p <&> q :: Type) x Source # 
Instance details

Defined in Predicate.Data.Lifted

Associated Types

type PP (p <&> q) x Source #

Methods

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

(Traversable n, P q a, P p b, PP q a ~ n b, PP p b ~ c) => P (p <$> q :: Type) a Source # 
Instance details

Defined in Predicate.Data.Lifted

Associated Types

type PP (p <$> q) a Source #

Methods

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

P (LiftT p q) x => P (Lift p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.Lifted

Associated Types

type PP (Lift p q) x Source #

Methods

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

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

Defined in Predicate.Data.Lifted

Associated Types

type PP (K p q) a Source #

Methods

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

P (CatchT' p s) x => P (Catch' p s :: Type) x Source # 
Instance details

Defined in Predicate.Data.Lifted

Associated Types

type PP (Catch' p s) x 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.Data.Lifted

Associated Types

type PP (Catch p q) x Source #

Methods

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

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

Defined in Predicate.Data.Lifted

Associated Types

type PP (p >|> q) x 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.Data.Lifted

Associated Types

type PP (p >| q) x 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.Data.Lifted

Associated Types

type PP (p |> q) x Source #

Methods

eval :: MonadEval m => proxy (p |> q) -> POpts -> x -> m (TT (PP (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.Data.Lifted

Associated Types

type PP (q $& p) x 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.Data.Lifted

Associated Types

type PP (p $$ q) x Source #

Methods

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

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

Defined in Predicate.Data.Lifted

Associated Types

type PP (EmptyBool' b p) a Source #

Methods

eval :: MonadEval m => proxy (EmptyBool' b p) -> POpts -> a -> m (TT (PP (EmptyBool' b p) a)) 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.Data.Lifted

Associated Types

type PP (p <|> q) x 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), Show (t c), Applicative t, PP p x ~ t b, PP q x ~ t c) => P (p *> q :: Type) x Source # 
Instance details

Defined in Predicate.Data.Lifted

Associated Types

type PP (p *> q) x 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), Show (t c), Applicative t, PP p x ~ t b, PP q x ~ t c) => P (p <* q :: Type) x Source # 
Instance details

Defined in Predicate.Data.Lifted

Associated Types

type PP (p <* q) x 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.Data.Lifted

Associated Types

type PP (p <$ q) x Source #

Methods

eval :: MonadEval m => proxy (p <$ q) -> POpts -> x -> m (TT (PP (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.Data.Json

Associated Types

type PP (ParseJsonFile' t p) x 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.Data.Json

Associated Types

type PP (ParseJson' t p) x Source #

Methods

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

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

Defined in Predicate.Data.Foldable

Associated Types

type PP (Cycle n p) x Source #

Methods

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

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

Defined in Predicate.Data.Foldable

Associated Types

type PP (ConcatMap p q) x Source #

Methods

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

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

Defined in Predicate.Data.Foldable

Associated Types

type PP (IToList' t p) x Source #

Methods

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

P (MaybeIdT n p) x => P (MaybeId n p :: Type) x Source # 
Instance details

Defined in Predicate.Data.Maybe

Associated Types

type PP (MaybeId n p) x Source #

Methods

eval :: MonadEval m => proxy (MaybeId n p) -> POpts -> x -> m (TT (PP (MaybeId n p) 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.Data.Maybe

Associated Types

type PP (JustFail p q) x 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.Data.Maybe

Associated Types

type PP (JustDef p q) x Source #

Methods

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

P (MaybeBoolT b p) x => P (MaybeBool b p :: Type) x Source # 
Instance details

Defined in Predicate.Data.Maybe

Associated Types

type PP (MaybeBool b p) x Source #

Methods

eval :: MonadEval m => proxy (MaybeBool b p) -> POpts -> x -> m (TT (PP (MaybeBool b p) x)) Source #

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

Defined in Predicate.Data.Maybe

Associated Types

type PP (MapMaybe p q) x Source #

Methods

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

P (BangBangQT p q) a => P (p !!? q :: Type) a Source # 
Instance details

Defined in Predicate.Data.Index

Associated Types

type PP (p !!? q) a Source #

Methods

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

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

Defined in Predicate.Data.Index

Associated Types

type PP (Lookup p q) a 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.Data.Index

Associated Types

type PP (p !! q) a Source #

Methods

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

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

Defined in Predicate.Data.Enum

Associated Types

type PP (p ... q) x Source #

Methods

eval :: MonadEval m => proxy (p ... q) -> POpts -> x -> m (TT (PP (p ... q) x)) 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.Data.Enum

Associated Types

type PP (EnumFromTo p q) x Source #

Methods

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

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

Defined in Predicate.Data.Enum

Associated Types

type PP (ToEnum' t p) x 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.Data.Enum

Associated Types

type PP (PredB p q) x Source #

Methods

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

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

Defined in Predicate.Data.Enum

Associated Types

type PP (SuccN n p) x Source #

Methods

eval :: MonadEval m => proxy (SuccN n p) -> POpts -> x -> m (TT (PP (SuccN n 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 (SuccB p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.Enum

Associated Types

type PP (SuccB p q) x Source #

Methods

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

P (IMapT p q) x => P (IMap p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.List

Associated Types

type PP (IMap p q) x Source #

Methods

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

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

Defined in Predicate.Data.List

Associated Types

type PP (IsSuffix p q) x 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.Data.List

Associated Types

type PP (IsInfix p q) x 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.Data.List

Associated Types

type PP (IsPrefix p q) x Source #

Methods

eval :: MonadEval m => proxy (IsPrefix p q) -> POpts -> x -> m (TT (PP (IsPrefix p q) 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.Data.List

Associated Types

type PP (Zip p q) a Source #

Methods

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

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

Defined in Predicate.Data.List

Associated Types

type PP (SortOnDesc p q) x 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.Data.List

Associated Types

type PP (SortOn p q) x 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.Data.List

Associated Types

type PP (SortBy p q) x Source #

Methods

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

P (RemoveT p q) x => P (Remove p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.List

Associated Types

type PP (Remove p q) x 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.Data.List

Associated Types

type PP (Keep p q) x Source #

Methods

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

P (DropT n p) x => P (Drop n p :: Type) x Source # 
Instance details

Defined in Predicate.Data.List

Associated Types

type PP (Drop n p) x 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.Data.List

Associated Types

type PP (Take n p) x 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.Data.List

Associated Types

type PP (SplitAt n p) a 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.Data.List

Associated Types

type PP (SplitAts ns p) x Source #

Methods

eval :: MonadEval m => proxy (SplitAts ns p) -> POpts -> x -> m (TT (PP (SplitAts ns p) 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.Data.List

Associated Types

type PP (Elem p q) a Source #

Methods

eval :: MonadEval m => proxy (Elem p q) -> POpts -> a -> m (TT (PP (Elem p q) a)) 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.Data.List

Associated Types

type PP (Intercalate p q) x Source #

Methods

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

P (SpanT p q) x => P (Span p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.List

Associated Types

type PP (Span p q) x 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.Data.List

Associated Types

type PP (Break p q) a 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.Data.List

Associated Types

type PP (Filter p q) x Source #

Methods

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

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

Defined in Predicate.Data.List

Associated Types

type PP (GroupBy p q) a Source #

Methods

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

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

Defined in Predicate.Data.List

Associated Types

type PP (Partition p q) a Source #

Methods

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

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

Defined in Predicate.Data.List

Associated Types

type PP (Rotate n p) x Source #

Methods

eval :: MonadEval m => proxy (Rotate n p) -> POpts -> x -> m (TT (PP (Rotate n p) 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.Data.List

Associated Types

type PP (p +: q) x 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.Data.List

Associated Types

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

Defined in Predicate.Data.List

Associated Types

type PP (p ++ q) x Source #

Methods

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

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

Defined in Predicate.Data.Extra

Associated Types

type PP (InitFail msg q) x 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.Data.Extra

Associated Types

type PP (InitDef p q) x 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.Data.Extra

Associated Types

type PP (LastFail msg q) x 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.Data.Extra

Associated Types

type PP (LastDef p q) x 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.Data.Extra

Associated Types

type PP (TailFail msg q) x 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.Data.Extra

Associated Types

type PP (TailDef p q) x 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.Data.Extra

Associated Types

type PP (HeadFail msg q) x 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.Data.Extra

Associated Types

type PP (HeadDef p q) x Source #

Methods

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

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

Defined in Predicate.Data.Iterator

Associated Types

type PP (IterateWhile p f) x 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.Data.Iterator

Associated Types

type PP (IterateUntil p f) x Source #

Methods

eval :: MonadEval m => proxy (IterateUntil p f) -> POpts -> x -> m (TT (PP (IterateUntil p 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.Data.Iterator

Associated Types

type PP (Unfoldr p q) a Source #

Methods

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

P (ElrPairT s t) x => P (ElrPair s t :: Type) x Source # 
Instance details

Defined in Predicate.Data.Elr

Associated Types

type PP (ElrPair s t) x Source #

Methods

eval :: MonadEval m => proxy (ElrPair s t) -> POpts -> x -> m (TT (PP (ElrPair s t) x)) Source #

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

Defined in Predicate.Data.Elr

Associated Types

type PP (MkEBoth p q) a Source #

Methods

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

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

Defined in Predicate.Data.Elr

Associated Types

type PP (MkERight' t p) x Source #

Methods

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

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

Defined in Predicate.Data.Elr

Associated Types

type PP (MkELeft' t p) x Source #

Methods

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

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

Defined in Predicate.Data.Elr

Associated Types

type PP (MkENone' t t1) x Source #

Methods

eval :: MonadEval m => proxy (MkENone' t t1) -> POpts -> x -> m (TT (PP (MkENone' t t1) x)) Source #

P (EitherIdT p q) x => P (EitherId p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.Either

Associated Types

type PP (EitherId p q) x Source #

Methods

eval :: MonadEval m => proxy (EitherId p q) -> POpts -> x -> m (TT (PP (EitherId 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.Data.Either

Associated Types

type PP (RightFail p q) x 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.Data.Either

Associated Types

type PP (LeftFail p q) x 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.Data.Either

Associated Types

type PP (RightDef p q) x 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.Data.Either

Associated Types

type PP (LeftDef p q) x Source #

Methods

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

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

Defined in Predicate.Data.Either

Associated Types

type PP (MkRight' t p) x 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.Data.Either

Associated Types

type PP (MkLeft' t p) x Source #

Methods

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

P (DiffLocalTimeT p q) x => P (DiffLocalTime p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.DateTime

Associated Types

type PP (DiffLocalTime p q) x Source #

Methods

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

(PP p x ~ UTCTime, PP q x ~ UTCTime, P p x, P q x) => P (DiffUTCTime p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.DateTime

Associated Types

type PP (DiffUTCTime p q) x Source #

Methods

eval :: MonadEval m => proxy (DiffUTCTime p q) -> POpts -> x -> m (TT (PP (DiffUTCTime p q) 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.Data.DateTime

Associated Types

type PP (FormatTimeP' p q) x Source #

Methods

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

P (ExitWhenT prt p) x => P (ExitWhen prt p :: Type) x Source # 
Instance details

Defined in Predicate.Data.Condition

Associated Types

type PP (ExitWhen prt p) x Source #

Methods

eval :: MonadEval m => proxy (ExitWhen prt p) -> POpts -> x -> m (TT (PP (ExitWhen prt p) x)) Source #

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

Defined in Predicate.Data.Condition

Associated Types

type PP (GuardBool prt p) a Source #

Methods

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

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

Defined in Predicate.Data.Condition

Associated Types

type PP (Guard prt p) a 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.Data.Condition

Associated Types

type PP (BoolsQuick prt ps) x 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.Data.Condition

Associated Types

type PP (GuardsQuick prt ps) x Source #

Methods

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

(P p a, Show t, Bits t, Integral (PP p a)) => P (Bit t p :: Type) a Source # 
Instance details

Defined in Predicate.Data.Bits

Associated Types

type PP (Bit t p) a Source #

Methods

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

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

Defined in Predicate.Data.Bits

Associated Types

type PP (TestBit p q) a Source #

Methods

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

P (BitComplementT p q) x => P (BitComplement p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.Bits

Associated Types

type PP (BitComplement p q) x Source #

Methods

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

P (BitClearT p q) x => P (BitClear p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.Bits

Associated Types

type PP (BitClear p q) x Source #

Methods

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

P (BitSetT p q) x => P (BitSet p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.Bits

Associated Types

type PP (BitSet p q) x Source #

Methods

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

P (BitRotateRT p q) x => P (BitRotateR p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.Bits

Associated Types

type PP (BitRotateR p q) x Source #

Methods

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

P (BitRotateLT p q) x => P (BitRotateL p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.Bits

Associated Types

type PP (BitRotateL p q) x Source #

Methods

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

P (BitRotateT p q) x => P (BitRotate p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.Bits

Associated Types

type PP (BitRotate p q) x Source #

Methods

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

P (BitShiftRT p q) x => P (BitShiftR p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.Bits

Associated Types

type PP (BitShiftR p q) x Source #

Methods

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

P (BitShiftLT p q) x => P (BitShiftL p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.Bits

Associated Types

type PP (BitShiftL p q) x Source #

Methods

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

P (BitShiftT p q) x => P (BitShift p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.Bits

Associated Types

type PP (BitShift p q) x Source #

Methods

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

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

Defined in Predicate.Data.Bits

Associated Types

type PP (p .^. q) a Source #

Methods

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

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

Defined in Predicate.Data.Bits

Associated Types

type PP (p .|. q) a Source #

Methods

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

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

Defined in Predicate.Data.Bits

Associated Types

type PP (p .&. q) a Source #

Methods

eval :: MonadEval m => proxy (p .&. q) -> POpts -> a -> m (TT (PP (p .&. q) a)) 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.Data.Tuple

Associated Types

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

Methods

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

(Bitraversable n, Monoid t, PP p a ~ t, PP q b ~ t, P p a, P q b) => P (BiFoldMap p q :: Type) (n a b) Source # 
Instance details

Defined in Predicate.Data.Lifted

Associated Types

type PP (BiFoldMap p q) (n a b) Source #

Methods

eval :: MonadEval m => proxy (BiFoldMap p q) -> POpts -> n a b -> m (TT (PP (BiFoldMap p q) (n a b))) Source #

(Bitraversable n, P p a, P q b) => P (BiMap p q :: Type) (n a b) Source # 
Instance details

Defined in Predicate.Data.Lifted

Associated Types

type PP (BiMap p q) (n a b) Source #

Methods

eval :: MonadEval m => proxy (BiMap p q) -> POpts -> n a b -> m (TT (PP (BiMap p q) (n 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) (Either a b) Source # 
Instance details

Defined in Predicate.Data.Either

Associated Types

type PP (p +++ q) (Either a b) 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.Data.Either

Associated Types

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

Methods

eval :: MonadEval m => proxy (p ||| q) -> POpts -> Either a b -> m (TT (PP (p ||| q) (Either a b))) 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.Data.Regex

Associated Types

type PP (Resplit' rs p q) x 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.Data.Regex

Associated Types

type PP (RescanRanges' rs p q) x 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.Data.Regex

Associated Types

type PP (Rescan' rs p q) x 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.Data.Regex

Associated Types

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

Methods

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

P (PrintLT n s p) x => P (PrintL n s p :: Type) x Source # 
Instance details

Defined in Predicate.Data.ReadShow

Associated Types

type PP (PrintL n s p) x 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), BetweenT "ReadBase'" 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.Data.Numeric

Associated Types

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

Methods

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

(GetBool pretty, PP p x ~ String, P p x, ToJSON (PP q x), P q x) => P (EncodeJsonFile pretty p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.Json

Associated Types

type PP (EncodeJsonFile pretty p q) x Source #

Methods

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

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

Defined in Predicate.Data.DateTime

Associated Types

type PP (ParseTimes t p q) x Source #

Methods

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

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

Defined in Predicate.Data.Condition

Associated Types

type PP (GuardsN prt n p) x 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.Data.Condition

Associated Types

type PP (GuardsDetail prt ps) x 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.Data.Condition

Associated Types

type PP (BoolsN prt n p) x Source #

Methods

eval :: MonadEval m => proxy (BoolsN prt n p) -> POpts -> x -> m (TT (PP (BoolsN prt n p) 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.Core

Associated Types

type PP (Between p q r) x Source #

Methods

eval :: MonadEval m => proxy (Between p q r) -> POpts -> x -> m (TT (PP (Between 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 (OrA p q r :: Type) x Source # 
Instance details

Defined in Predicate.Data.Tuple

Associated Types

type PP (OrA p q r) x 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.Data.Tuple

Associated Types

type PP (AndA p q r) x Source #

Methods

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

P (TheseDefT' p q r) x => P (TheseDef' p q r :: Type) x Source # 
Instance details

Defined in Predicate.Data.These

Associated Types

type PP (TheseDef' p q r) x Source #

Methods

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

P (ThatDefT' p q r) x => P (ThatDef' p q r :: Type) x Source # 
Instance details

Defined in Predicate.Data.These

Associated Types

type PP (ThatDef' p q r) x Source #

Methods

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

P (ThisDefT' p q r) x => P (ThisDef' p q r :: Type) x Source # 
Instance details

Defined in Predicate.Data.These

Associated Types

type PP (ThisDef' p q r) x Source #

Methods

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

P (TheseInSimpleT p q r) x => P (TheseInSimple p q r :: Type) x Source # 
Instance details

Defined in Predicate.Data.These

Associated Types

type PP (TheseInSimple p q r) x Source #

Methods

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

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

Defined in Predicate.Data.These

Associated Types

type PP (TheseId p q r) x Source #

Methods

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

P (ReplaceOneT p q r) x => P (ReplaceOne p q r :: Type) x Source # 
Instance details

Defined in Predicate.Data.Regex

Associated Types

type PP (ReplaceOne p q r) x 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.Data.Regex

Associated Types

type PP (ReplaceAll p q r) x Source #

Methods

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

(PP p x ~ Proxy z, PP q x ~ Proxy w, PP r x ~ Proxy v) => P (PApp2 p q r :: Type) x Source # 
Instance details

Defined in Predicate.Data.Proxy

Associated Types

type PP (PApp2 p q r) x Source #

Methods

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

(P r x, PP p x ~ Proxy z, PP q x ~ Proxy w, P (z w) (PP r x)) => P (Pop1' p q r :: Type) x Source # 
Instance details

Defined in Predicate.Data.Proxy

Associated Types

type PP (Pop1' p q r) x Source #

Methods

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

(P r x, PP p x ~ Proxy z, P (z q) (PP r x)) => P (Pop1 p q r :: Type) x Source # 
Instance details

Defined in Predicate.Data.Proxy

Associated Types

type PP (Pop1 p q r) x Source #

Methods

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

P (DivIT t p q) x => P (DivI t p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.Numeric

Associated Types

type PP (DivI t p q) x Source #

Methods

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

(Traversable n, Applicative n, P p (a, b), P q x, P r x, PP p (a, b) ~ c, PP q x ~ n a, PP r x ~ n b) => P (LiftA2 p q r :: Type) x Source # 
Instance details

Defined in Predicate.Data.Lifted

Associated Types

type PP (LiftA2 p q r) x Source #

Methods

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

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

Defined in Predicate.Data.Lifted

Associated Types

type PP (Flip p q r) x Source #

Methods

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

P (FFishT p q r) x => P (FFish p q r :: Type) x Source # 
Instance details

Defined in Predicate.Data.Lifted

Associated Types

type PP (FFish p q r) x Source #

Methods

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

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

Defined in Predicate.Data.Lifted

Associated Types

type PP (EmptyBool t b p) a Source #

Methods

eval :: MonadEval m => proxy (EmptyBool t b p) -> POpts -> a -> m (TT (PP (EmptyBool t b p) a)) 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.Data.Index

Associated Types

type PP (IxL p q r) a 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.Data.Index

Associated Types

type PP (LookupFail msg v w) x 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.Data.Index

Associated Types

type PP (LookupDef v w p) x Source #

Methods

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

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

Defined in Predicate.Data.Enum

Associated Types

type PP (EnumFromThenTo p q r) x Source #

Methods

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

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

Defined in Predicate.Data.Enum

Associated Types

type PP (ToEnumBDef' t def p) a Source #

Methods

eval :: MonadEval m => proxy (ToEnumBDef' t def p) -> POpts -> a -> m (TT (PP (ToEnumBDef' t def p) a)) Source #

P (PartitionsByT p q r) x => P (PartitionsBy p q r :: Type) x Source # 
Instance details

Defined in Predicate.Data.List

Associated Types

type PP (PartitionsBy p q r) x Source #

Methods

eval :: MonadEval m => proxy (PartitionsBy p q r) -> POpts -> x -> m (TT (PP (PartitionsBy p q 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.Data.List

Associated Types

type PP (ZipR r p q) a 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.Data.List

Associated Types

type PP (ZipL l p q) a Source #

Methods

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

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

Defined in Predicate.Data.List

Associated Types

type PP (ZipWith p q r) a Source #

Methods

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

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

Defined in Predicate.Data.List

Associated Types

type PP (ChunksOf' n i p) a Source #

Methods

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

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

Defined in Predicate.Data.List

Associated Types

type PP (PadR n p q) x 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.Data.List

Associated Types

type PP (PadL n p q) x Source #

Methods

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

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

Defined in Predicate.Data.List

Associated Types

type PP (PartitionBy t p q) a Source #

Methods

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

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

Defined in Predicate.Data.Iterator

Associated Types

type PP (IterateNUntil n p f) x 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.Data.Iterator

Associated Types

type PP (IterateNWhile n p f) x Source #

Methods

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

P (IterateNT n p s) x => P (UnfoldN n p s :: Type) x Source # 
Instance details

Defined in Predicate.Data.Iterator

Associated Types

type PP (UnfoldN n p s) x Source #

Methods

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

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

Defined in Predicate.Data.Iterator

Associated Types

type PP (Foldl p q r) x 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.Data.Iterator

Associated Types

type PP (FoldN n p q) x 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.Data.Iterator

Associated Types

type PP (ScanN n p q) x 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.Data.Iterator

Associated Types

type PP (Scanl p q r) x Source #

Methods

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

P (EBothDefT p q r) x => P (EBothDef p q r :: Type) x Source # 
Instance details

Defined in Predicate.Data.Elr

Associated Types

type PP (EBothDef p q r) x Source #

Methods

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

P (ERightDefT p q r) x => P (ERightDef p q r :: Type) x Source # 
Instance details

Defined in Predicate.Data.Elr

Associated Types

type PP (ERightDef p q r) x Source #

Methods

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

P (ELeftDefT p q r) x => P (ELeftDef p q r :: Type) x Source # 
Instance details

Defined in Predicate.Data.Elr

Associated Types

type PP (ELeftDef p q r) x Source #

Methods

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

P (ENoneDefT p q r) x => P (ENoneDef p q r :: Type) x Source # 
Instance details

Defined in Predicate.Data.Elr

Associated Types

type PP (ENoneDef p q r) x Source #

Methods

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

P (RightDefT' p q r) x => P (RightDef' p q r :: Type) x Source # 
Instance details

Defined in Predicate.Data.Either

Associated Types

type PP (RightDef' p q r) x Source #

Methods

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

P (LeftDefT' p q r) x => P (LeftDef' p q r :: Type) x Source # 
Instance details

Defined in Predicate.Data.Either

Associated Types

type PP (LeftDef' p q r) x Source #

Methods

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

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

Defined in Predicate.Data.Either

Associated Types

type PP (EitherBool b p q) a 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 ~ Rational) => P (MkTime' p q r :: Type) x Source # 
Instance details

Defined in Predicate.Data.DateTime

Associated Types

type PP (MkTime' p q r) x Source #

Methods

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

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

Defined in Predicate.Data.DateTime

Associated Types

type PP (MkDayExtra' p q r) x Source #

Methods

eval :: MonadEval m => proxy (MkDayExtra' p q r) -> POpts -> x -> m (TT (PP (MkDayExtra' p q r) x)) 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.Data.DateTime

Associated Types

type PP (MkDay' p q r) x 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.Data.DateTime

Associated Types

type PP (ParseTimes' t p q) a 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.Data.DateTime

Associated Types

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

Methods

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

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

Defined in Predicate.Data.Condition

Associated Types

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

Methods

eval :: MonadEval m => proxy (Case' ps qs r) -> POpts -> x -> m (TT (PP (Case' ps qs r) x)) 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.Data.Condition

Associated Types

type PP (If p q r) a Source #

Methods

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

P (ReplaceOneStringT o p q r) x => P (ReplaceOneString o p q r :: Type) x Source # 
Instance details

Defined in Predicate.Data.Regex

Associated Types

type PP (ReplaceOneString o p q r) x Source #

Methods

eval :: MonadEval m => proxy (ReplaceOneString o p q r) -> POpts -> x -> m (TT (PP (ReplaceOneString o 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.Data.Regex

Associated Types

type PP (ReplaceOne' rs p q r) x 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.Data.Regex

Associated Types

type PP (ReplaceAll' rs p q r) x Source #

Methods

eval :: MonadEval m => proxy (ReplaceAll' rs p q r) -> POpts -> x -> m (TT (PP (ReplaceAll' rs p q r) x)) Source #

(P q (PP r x), P q (PP s x), P r x, P s x, P (p Fst Snd) (PP q (PP r x), PP q (PP s x))) => P (On' p q r s :: Type) x Source # 
Instance details

Defined in Predicate.Data.Tuple

Associated Types

type PP (On' p q r s) x Source #

Methods

eval :: MonadEval m => proxy (On' p q r s) -> POpts -> x -> m (TT (PP (On' p q r s) x)) Source #

P (ReplaceOneStringT' rs o p q r) x => P (ReplaceOneString' rs o p q r :: Type) x Source # 
Instance details

Defined in Predicate.Data.Regex

Associated Types

type PP (ReplaceOneString' rs o p q r) x Source #

Methods

eval :: MonadEval m => proxy (ReplaceOneString' rs o p q r) -> POpts -> x -> m (TT (PP (ReplaceOneString' rs o p q r) x)) Source #

P (ReplaceAllStringT o p q r) x => P (ReplaceAllString o p q r :: Type) x Source # 
Instance details

Defined in Predicate.Data.Regex

Associated Types

type PP (ReplaceAllString o p q r) x Source #

Methods

eval :: MonadEval m => proxy (ReplaceAllString o p q r) -> POpts -> x -> m (TT (PP (ReplaceAllString o p q r) x)) Source #

P (ReplaceAllStringT' rs o p q r) x => P (ReplaceAllString' rs o p q r :: Type) x Source # 
Instance details

Defined in Predicate.Data.Regex

Associated Types

type PP (ReplaceAllString' rs o p q r) x Source #

Methods

eval :: MonadEval m => proxy (ReplaceAllString' rs o p q r) -> POpts -> x -> m (TT (PP (ReplaceAllString' rs o p q r) x)) Source #

(P s x, PP p x ~ Proxy z, PP q x ~ Proxy w, PP r x ~ Proxy v, P (z w v) (PP s x)) => P (Pop2' p q r s :: Type) x Source # 
Instance details

Defined in Predicate.Data.Proxy

Associated Types

type PP (Pop2' p q r s) x Source #

Methods

eval :: MonadEval m => proxy (Pop2' p q r s) -> POpts -> x -> m (TT (PP (Pop2' p q r s) x)) Source #

(P s x, PP p x ~ Proxy z, P (z q r) (PP s x)) => P (Pop2 p q r s :: Type) x Source # 
Instance details

Defined in Predicate.Data.Proxy

Associated Types

type PP (Pop2 p q r s) x Source #

Methods

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

(Show a, Show (PP p (y, a)), P n (y, Proxy z), P p (y, a), PP n (y, Proxy z) ~ PP p (y, a), z ~ PP p (y, a), P s x, P t x, PP t x ~ Maybe a, PP s x ~ y) => P (MaybeIn n p s t :: Type) x Source # 
Instance details

Defined in Predicate.Data.Maybe

Associated Types

type PP (MaybeIn n p s t) x Source #

Methods

eval :: MonadEval m => proxy (MaybeIn n p s t) -> POpts -> x -> m (TT (PP (MaybeIn n p s t) x)) Source #

P (LookupFailT' msg v w q) x => P (LookupFail' msg v w q :: Type) x Source # 
Instance details

Defined in Predicate.Data.Index

Associated Types

type PP (LookupFail' msg v w q) x 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.Data.Index

Associated Types

type PP (LookupDef' v w p q) x Source #

Methods

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

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

Defined in Predicate.Data.List

Associated Types

type PP (ZipPad l r p q) a Source #

Methods

eval :: MonadEval m => proxy (ZipPad l r p q) -> POpts -> a -> m (TT (PP (ZipPad l r p q) a)) Source #

P (ElrInSimpleT n p q r) x => P (ElrInSimple n p q r :: Type) x Source # 
Instance details

Defined in Predicate.Data.Elr

Associated Types

type PP (ElrInSimple n p q r) x Source #

Methods

eval :: MonadEval m => proxy (ElrInSimple n p q r) -> POpts -> x -> m (TT (PP (ElrInSimple n p q r) x)) Source #

P (ElrIdT n p q r) x => P (ElrId n p q r :: Type) x Source # 
Instance details

Defined in Predicate.Data.Elr

Associated Types

type PP (ElrId n p q r) x Source #

Methods

eval :: MonadEval m => proxy (ElrId n p q r) -> POpts -> x -> m (TT (PP (ElrId n p q r) x)) Source #

(Show a, Show b, Show (PP q (y, b)), P p (y, a), P q (y, b), PP p (y, a) ~ PP q (y, b), P s x, P t x, PP s x ~ y, PP t x ~ Either a b) => P (EitherIn p q s t :: Type) x Source # 
Instance details

Defined in Predicate.Data.Either

Associated Types

type PP (EitherIn p q s t) x Source #

Methods

eval :: MonadEval m => proxy (EitherIn p q s t) -> POpts -> x -> m (TT (PP (EitherIn p q s t) x)) Source #

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

Defined in Predicate.Data.Condition

Associated Types

type PP (Case'' s ps qs r) x 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.Data.Condition

Associated Types

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

Methods

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

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

Defined in Predicate.Data.These

Associated Types

type PP (TheseIn p q r s t) x Source #

Methods

eval :: MonadEval m => proxy (TheseIn p q r s t) -> POpts -> x -> m (TT (PP (TheseIn p q r s t) x)) Source #

(Show a, Show b, Show (PP r (y, (a, b))), P n y, P p (y, a), P q (y, b), P r (y, (a, b)), PP n y ~ PP p (y, a), PP p (y, a) ~ PP q (y, b), PP q (y, b) ~ PP r (y, (a, b)), P s x, P t x, PP t x ~ Elr a b, PP s x ~ y) => P (ElrIn n p q r s t :: Type) x Source # 
Instance details

Defined in Predicate.Data.Elr

Associated Types

type PP (ElrIn n p q r s t) x Source #

Methods

eval :: MonadEval m => proxy (ElrIn n p q r s t) -> POpts -> x -> m (TT (PP (ElrIn n p q r s t) x)) Source #

P [] a Source #

const [] function

>>> pz @[] "Asf"
Val []
Instance details

Defined in Predicate.Core

Associated Types

type PP [] a Source #

Methods

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

P ('Proxy :: Proxy t1) t2 Source #

converts the type to the corresponding Proxy

>>> pz @'Proxy 'x' ^!? acts . _Val . to typeRep
Just Char
>>> pz @'Proxy 'x' >>= return . preview (_Val . to typeRep)
Just Char
>>> pz @'Proxy 45 ^!? acts . _Val . to typeRep
Just Integer
>>> pz @'Proxy "abc" ^!? acts . _Val . to typeRep
Just [Char]
>>> pz @(Pop1' (Proxy ToEnum) 'Proxy 2) LT
Val GT
Instance details

Defined in Predicate.Core

Associated Types

type PP 'Proxy t2 Source #

Methods

eval :: MonadEval m => proxy 'Proxy0 -> POpts -> t2 -> m (TT (PP 'Proxy0 t2)) Source #

x ~ Elr a2 b2 => P ('ENone :: Elr a1 b1) x Source #

extracts the () from type level ENone if the value exists

>>> pl @'ENone ENone
Present () ('ENone)
Val ()
>>> pz @'ENone (ERight "aaa")
Fail "'ENone found ERight"
Instance details

Defined in Predicate.Core

Associated Types

type PP 'ENone x Source #

Methods

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

(PP p x ~ Either a2 b2, P p x) => P ('Right p :: Either a1 b1) x Source #

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

>>> pl @('Right Id) (Right 123)
Present 123 (Right)
Val 123
>>> pz @('Right Id >> Snd) (Right ('x',123))
Val 123
>>> pz @('Right Id) (Left "aaa")
Fail "'Right found Left"
>>> pl @('Right Id) (Left 123)
Error 'Right found Left
Fail "'Right found Left"
Instance details

Defined in Predicate.Core

Associated Types

type PP ('Right p) x Source #

Methods

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

(PP p x ~ Either a2 b2, P p x) => P ('Left p :: Either a1 b1) x Source #

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

>>> pz @('Left Id) (Left 123)
Val 123
>>> pz @('Left Snd) ('x', Left 123)
Val 123
>>> pz @('Left Id) (Right "aaa")
Fail "'Left found Right"
>>> pl @('Left Id) (Left 123)
Present 123 (Left)
Val 123
>>> pl @('Left Id) (Right 123)
Error 'Left found Right
Fail "'Left found Right"
Instance details

Defined in Predicate.Core

Associated Types

type PP ('Left p) x Source #

Methods

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

(PP p x ~ These a2 b2, P p x) => P ('That p :: These a1 b1) x Source #

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

>>> pz @('That Id) (That 123)
Val 123
>>> pz @('That Id) (This "aaa")
Fail "'That found This"
>>> pz @('That Id) (These 44 "aaa")
Fail "'That found These"
Instance details

Defined in Predicate.Core

Associated Types

type PP ('That p) x Source #

Methods

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

(PP p x ~ These a2 b2, P p x) => P ('This p :: These a1 b1) x Source #

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

>>> pl @('This Id) (This 12)
Present 12 (This)
Val 12
>>> pz @('This Id) (That "aaa")
Fail "'This found That"
>>> pz @('This Id) (These 999 "aaa")
Fail "'This found These"
>>> pl @('This Id) (That 12)
Error 'This found That
Fail "'This found That"
Instance details

Defined in Predicate.Core

Associated Types

type PP ('This p) x Source #

Methods

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

(PP p x ~ Elr a2 b2, P p x) => P ('ERight p :: Elr a1 b1) x Source #

extracts the b from type level ERight b if the value exists

>>> pz @('ERight Id) (ERight 123)
Val 123
>>> pz @('ERight Id) (ELeft "aaa")
Fail "'ERight found ELeft"
>>> pz @('ERight Id) (EBoth 44 "aaa")
Fail "'ERight found EBoth"
Instance details

Defined in Predicate.Core

Associated Types

type PP ('ERight p) x Source #

Methods

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

(PP p x ~ Elr a2 b2, P p x) => P ('ELeft p :: Elr a1 b1) x Source #

extracts the a from type level ELeft a if the value exists

>>> pl @('ELeft Id) (ELeft 12)
Present 12 ('ELeft)
Val 12
>>> pz @('ELeft Id) (ERight "aaa")
Fail "'ELeft found ERight"
>>> pz @('ELeft Id) (EBoth 999 "aaa")
Fail "'ELeft found EBoth"
>>> pl @('ELeft Id) (ERight 12)
Error 'ELeft found ERight
Fail "'ELeft found ERight"
Instance details

Defined in Predicate.Core

Associated Types

type PP ('ELeft p) x Source #

Methods

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

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

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

>>> pz @'(Id, 4) "hello"
Val ("hello",4)
Instance details

Defined in Predicate.Core

Associated Types

type PP '(p, q) a Source #

Methods

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

(P p x, P q x, Show (PP p x), Show (PP q x)) => P ('Arg p q :: Arg a b) x Source #

creates a Arg value using p and q

>>> pz @('SG.Arg (C "S") 10) ()
Val (Arg 'S' 10)
Instance details

Defined in Predicate.Core

Associated Types

type PP ('Arg p q) x Source #

Methods

eval :: MonadEval m => proxy ('Arg0 p q) -> POpts -> x -> m (TT (PP ('Arg0 p q) x)) 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")
Val (123,"abc")
>>> pz @('These Id 5) (These 123 "abcde")
Val (123,5)
>>> pz @('These Id Id) (This "aaa")
Fail "'These found This"
>>> pz @('These Id Id) (That "aaa")
Fail "'These found That"
Instance details

Defined in Predicate.Core

Associated Types

type PP ('These p q) (These a2 b2) Source #

Methods

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

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

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

>>> pz @('EBoth Id Id) (EBoth 123 "abc")
Val (123,"abc")
>>> pz @('EBoth Id 5) (EBoth 123 "abcde")
Val (123,5)
>>> pz @('EBoth Id Id) (ELeft "aaa")
Fail "'EBoth found ELeft"
>>> pz @('EBoth Id Id) (ERight "aaa")
Fail "'EBoth found ERight"
Instance details

Defined in Predicate.Core

Associated Types

type PP ('EBoth p q) (Elr a2 b2) Source #

Methods

eval :: MonadEval m => proxy ('EBoth p q) -> POpts -> Elr a2 b2 -> m (TT (PP ('EBoth p q) (Elr a2 b2))) Source #

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

run the predicates in a promoted 3-tuple

>>> pz @'(4, Id, "goodbye") "hello"
Val (4,"hello","goodbye")
>>> pan @'( 'True, 'False, 123) True
P '(,,)
|
+- True 'True
|
+- False 'False
|
`- P '123
Val (True,False,123)
Instance details

Defined in Predicate.Core

Associated Types

type PP '(p, q, r) a 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) :: (k1, k2, k3, k4)) a Source #

run the predicates in a promoted 4-tuple

>>> pz @'(4, Id, "inj", 999) "hello"
Val (4,"hello","inj",999)
Instance details

Defined in Predicate.Core

Associated Types

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

Methods

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

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

run the predicates in a promoted 5-tuple

>>> pz @'(4, Id, "inj", 999, 'LT) "hello"
Val (4,"hello","inj",999,LT)
Instance details

Defined in Predicate.Core

Associated Types

type PP '(p, q, r, s, t) a Source #

Methods

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

(P p a, P q a, P r a, P s a, P t a, P u a) => P ('(p, q, r, s, t, u) :: (k1, k2, k3, k4, k5, k6)) a Source #

run the predicates in a promoted 6-tuple

>>> pz @'(4, Id, "inj", 999, 'LT, 1) "hello"
Val (4,"hello","inj",999,LT,1)
Instance details

Defined in Predicate.Core

Associated Types

type PP '(p, q, r, s, t, u) a Source #

Methods

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

(P p a, P q a, P r a, P s a, P t a, P u a, P v a) => P ('(p, q, r, s, t, u, v) :: (k1, k2, k3, k4, k5, k6, k7)) a Source #

run the predicates in a promoted 7-tuple

>>> pz @'(4, Id, "inj", 999, 'LT, 1, 2) "hello"
Val (4,"hello","inj",999,LT,1,2)
Instance details

Defined in Predicate.Core

Associated Types

type PP '(p, q, r, s, t, u, v) a Source #

Methods

eval :: MonadEval m => proxy '(p, q, r, s, t, u, v) -> POpts -> a -> m (TT (PP '(p, q, r, s, t, u, v) a)) Source #

(P p a, P q a, P r a, P s a, P t a, P u a, P v a, P w a) => P ('(p, q, r, s, t, u, v, w) :: (k1, k2, k3, k4, k5, k6, k7, k8)) a Source #

run the predicates in a promoted 8-tuple

>>> pz @'(4, Id, "inj", 999, 'LT, 1, 2, 3) "hello"
Val (4,"hello","inj",999,LT,1,2,3)
Instance details

Defined in Predicate.Core

Associated Types

type PP '(p, q, r, s, t, u, v, w) a Source #

Methods

eval :: MonadEval m => proxy '(p, q, r, s, t, u, v, w) -> POpts -> a -> m (TT (PP '(p, q, r, s, t, u, v, w) a)) Source #

type families

type family DoExpandT (ps :: [k]) :: Type where ... Source #

expand out a type level list of commands using >> (associates to the right)

Equations

DoExpandT '[] = TypeError ('Text "DoExpandT '[] invalid: requires at least one predicate in the list") 
DoExpandT '[p] = W p 
DoExpandT (p ': (p1 ': ps)) = p >> DoExpandT (p1 ': ps) 

type family DoExpandLT (ps :: [k]) :: Type where ... Source #

like DoExpandT but associates to the left

Equations

DoExpandLT '[] = TypeError ('Text "DoExpandT '[] invalid: requires at least one predicate in the list") 
DoExpandLT '[p] = W p 
DoExpandLT (p ': (p1 ': '[])) = p >> p1 
DoExpandLT (p ': (p1 ': (p2 ': ps))) = (p >> p1) >> DoExpandLT (p2 ': ps) 

type family ArgT (x :: Type) where ... Source #

calculates the return type for Arg'

Equations

ArgT (Arg a b) = (a, b) 
ArgT o = TypeError ('Text "ArgT: expected 'SG.Arg a b' " :$$: ('Text "o = " :<>: 'ShowType o))