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

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

Predicate

Description

Most of this code contains instances of the class P enabling evaluation of expressions at the type level.

Synopsis

Documentation

module UtilP

data DoN (n :: Nat) p Source #

leverages Do for repeating predicates (passthrough method) same as 'DoN n p' == 'FoldN n p Id' but more efficient

>>> pl @(DoN 4 (Succ Id)) 'c'
Present 'g'
PresentT 'g'
>>> pl @(DoN 4 (Id <> " | ")) "abc"
Present "abc |  |  |  | "
PresentT "abc |  |  |  | "
>>> pl @(DoN 4 (Id <> "|" <> Id)) "abc"
Present "abc|abc|abc|abc|abc|abc|abc|abc|abc|abc|abc|abc|abc|abc|abc|abc"
PresentT "abc|abc|abc|abc|abc|abc|abc|abc|abc|abc|abc|abc|abc|abc|abc|abc"
Instances
P (DoExpandT (RepeatT n p)) a => P (DoN n p :: Type) a Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (DoN n p :: Type) a = PP (Do (RepeatT n p)) a

data Repeat (n :: Nat) p Source #

creates a promoted list of predicates and then evaluates them into a list. see PP instance for '[k]

>>> pl @(Repeat 4 (Succ Id)) 'c'
Present "dddd"
PresentT "dddd"
>>> pl @(Repeat 4 "abc") ()
Present ["abc","abc","abc","abc"]
PresentT ["abc","abc","abc","abc"]
Instances
P (RepeatT n p) a => P (Repeat n p :: Type) a Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (Repeat n p :: Type) a = PP (RepeatT n p) a

type GuardsNLax prt (n :: Nat) p = GuardsNImpl False prt n p Source #

type GuardsN prt (n :: Nat) p = GuardsNImpl True prt n p Source #

data GuardsNImpl (strict :: Bool) prt (n :: Nat) p Source #

leverages GuardsQuick for repeating predicates (passthrough method)

>>> pl @(GuardsN (Printf2 "id=%d must be between 0 and 255, found %d") 4 (Between 0 255)) [121,33,7,256]
Error id=4 must be between 0 and 255, found 256
FailT "id=4 must be between 0 and 255, found 256"
>>> pl @(GuardsN (Printf2 "id=%d must be between 0 and 255, found %d") 4 (Between 0 255)) [121,33,7,44]
Present [121,33,7,44]
PresentT [121,33,7,44]
Instances
(GetBool strict, GetLen (ToGuardsT prt (RepeatT n p)), P (GuardsImpl (LenT (ToGuardsT prt (RepeatT n p))) strict (ToGuardsT prt (RepeatT n p))) [a]) => P (GuardsNImpl strict prt n p :: Type) [a] Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (GuardsNImpl strict prt n p :: Type) [a] = PP (GuardsImplW strict (ToGuardsT prt (RepeatT n p))) [a]

type ParaNLax (n :: Nat) p = ParaNImpl False n p Source #

type ParaN (n :: Nat) p = ParaNImpl True n p Source #

data ParaNImpl (strict :: Bool) (n :: Nat) p Source #

leverages Para for repeating predicates (passthrough method)

>>> pl @(ParaNImpl 'True 4 (Succ Id)) [1..4]
Present [2,3,4,5]
PresentT [2,3,4,5]
>>> pl @(ParaNLax 4 (Succ Id)) "azwxm"
Present "b{xy"
PresentT "b{xy"
>>> pl @(ParaN 4 (Succ Id)) "azwxm"
Error Para: data elements(5) /= predicates(4)
FailT "Para: data elements(5) /= predicates(4)"
>>> pl @(ParaN 4 (Succ Id)) "azwx"
Present "b{xy"
PresentT "b{xy"
Instances
(P (ParaImpl (LenT (RepeatT n p)) strict (RepeatT n p)) [a], GetLen (RepeatT n p), GetBool strict) => P (ParaNImpl strict n p :: Type) [a] Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (ParaNImpl strict n p :: Type) [a] = PP (ParaImplW strict (RepeatT n p)) [a]

type StripLeft p q = StripLR False p q Source #

type StripRight p q = StripLR True p q Source #

data StripLR (right :: Bool) p q Source #

similar to stripLeft stripRight

>>> pl @(StripLeft "xyz" Id) ("xyzHello" :: String)
Present Just "Hello"
PresentT (Just "Hello")
>>> import Data.Text (Text)
>>> pl @(StripLeft "xyz" Id) ("xyzHello" :: Text)
Present Just "Hello"
PresentT (Just "Hello")
>>> pl @(StripLeft "xyz" Id) "xywHello"
Present Nothing
PresentT Nothing
>>> pl @(StripRight "xyz" Id) "Hello xyz"
Present Just "Hello "
PresentT (Just "Hello ")
>>> pl @(StripRight "xyz" Id) "xyzHelloxyw"
Present Nothing
PresentT Nothing
>>> pl @(StripRight "xyz" Id) ""
Present Nothing
PresentT Nothing
>>> pl @(StripRight "xyz" "xyz") ()
Present Just ""
PresentT (Just "")
Instances
(GetBool r, PP p x ~ String, P p x, IsText (PP q x), P q x) => P (StripLR r p q :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (StripLR r p q :: Type) x = Maybe (PP q x)

type Trim p = Trim' True True p Source #

data Trim' (left :: Bool) (right :: Bool) p Source #

similar to strip stripStart stripEnd

>>> pl @(Trim (Snd Id)) (20," abc   " :: String)
Present "abc"
PresentT "abc"
>>> import Data.Text (Text)
>>> pl @(Trim (Snd Id)) (20," abc   " :: Text)
Present "abc"
PresentT "abc"
>>> pl @(TrimStart (Snd Id)) (20," abc   ")
Present "abc   "
PresentT "abc   "
>>> pl @(TrimEnd (Snd Id)) (20," abc   ")
Present " abc"
PresentT " abc"
>>> pl @(TrimEnd "  abc ") ()
Present "  abc"
PresentT "  abc"
>>> pl @(TrimEnd "") ()
Present ""
PresentT ""
>>> pl @(Trim "         ") ()
Present ""
PresentT ""
>>> pl @(Trim "") ()
Present ""
PresentT ""
Instances
(FailIfT (NotT (OrT l r)) (Text "Trim': left and right cannot both be False"), GetBool l, GetBool r, IsText (PP p x), P p x) => P (Trim' l r p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

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

type family FnT ab :: Type where ... Source #

Equations

FnT (a -> b) = b 
FnT ab = TypeError (Text "FnT: expected Type -> Type but found a simple Type?" :$$: (Text "ab = " :<>: ShowType ab)) 

type (&) p q = q $ p infixr 1 Source #

data p $ q infixl 0 Source #

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

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (p $ q :: Type) x = FnT (PP p x)

data Join Source #

similar to join

>>> pl @Join  (Just (Just 20))
Present Just 20
PresentT (Just 20)
>>> pl @Join  ["ab","cd","","ef"]
Present "abcdef"
PresentT "abcdef"
Instances
(Show (t (t a)), Show (t a), Monad t) => P Join (t (t a)) Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

type PP Join (t (t a)) Source # 
Instance details

Defined in Predicate

type PP Join (t (t a)) = t a

data Duplicate Source #

similar to duplicate

>>> pl @Duplicate (20,"abc")
Present (20,(20,"abc"))
PresentT (20,(20,"abc"))
Instances
(Show (t a), Show (t (t a)), Comonad t) => P Duplicate (t a) Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

type PP Duplicate (t a) Source # 
Instance details

Defined in Predicate

type PP Duplicate (t a) = t (t a)

data Extract Source #

similar to extract

>>> pl @Extract (Nothing,Just 20)
Present Just 20
PresentT (Just 20)
>>> pl @Extract (Identity 20)
Present 20
PresentT 20
Instances
(Show (t a), Show a, Comonad t) => P Extract (t a) Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

type PP Extract (t a) Source # 
Instance details

Defined in Predicate

type PP Extract (t a) = a

data p <|> q infixl 3 Source #

similar to <|>

>>> pl @(Fst Id <|> Snd Id) (Nothing,Just 20)
Present Just 20
PresentT (Just 20)
>>> pl @(Fst Id <|> Snd Id) (Just 10,Just 20)
Present Just 10
PresentT (Just 10)
>>> pl @(Fst Id <|> Snd Id) (Nothing,Nothing)
Present Nothing
PresentT Nothing
Instances
(P p x, P q x, Show (t b), Alternative t, t b ~ PP p x, PP q x ~ t b) => P (p <|> q :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

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

type (*>) p q = q <* p infixl 4 Source #

similar to <*

>>> pl @(Fst Id <* Snd Id) (Just "abc",Just 20)
Present Just "abc"
PresentT (Just "abc")

data p <* q infixl 4 Source #

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

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

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

data p <$ q infixl 4 Source #

similar to <$

>>> pl @(Fst Id <$ Snd Id) ("abc",Just 20)
Present Just "abc"
PresentT (Just "abc")
Instances
(P p x, P q x, Show (PP p x), Functor t, PP q x ~ t c, ApplyConstT (PP q x) (PP p x) ~ t (PP p x)) => P (p <$ q :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (p <$ q :: Type) x = ApplyConstT (PP q x) (PP p x)

type family ApplyConstT (ta :: Type) (b :: Type) :: Type where ... Source #

Equations

ApplyConstT (t a) b = t b 
ApplyConstT ta b = TypeError ((Text "ApplyConstT: (t a) b but found something else" :$$: (Text "t a = " :<>: ShowType ta)) :$$: (Text "b = " :<>: ShowType b)) 

type family CheckT (tp :: Type) :: Bool where ... Source #

Equations

CheckT () = TypeError (Text "Printfn: inductive tuple cannot be empty") 
CheckT o = True 

type Printf3' (s :: Symbol) = Printfn s (TupleI '[Fst Id, Snd Id, Thd Id]) Source #

type Printf3 (s :: Symbol) = Printfn s '(Fst Id, '(Snd Id, '(Thd Id, ()))) Source #

print a 3-tuple

>>> pl @(Printf3 "fst=%s snd=%03d thd=%s") ("ab",123,"xx")
Present "fst=ab snd=123 thd=xx"
PresentT "fst=ab snd=123 thd=xx"

type Printf2 (s :: Symbol) = Printfn s '(Fst Id, '(Snd Id, ())) Source #

print a 2-tuple

>>> pl @(Printf2 "fst=%s snd=%03d") ("ab",123)
Present "fst=ab snd=123"
PresentT "fst=ab snd=123"

type PrintfntLax (n :: Nat) s = Printfn s (TupleListLax n) Source #

type Printfnt (n :: Nat) s = Printfn s (TupleList n) Source #

data Printfn s p Source #

Printfn prints an inductive tuple

>>> pl @(Printfn "%s %s" Id) ("123",("def",()))
Present "123 def"
PresentT "123 def"
>>> pl @(Printfn "s=%s d=%03d" Id) ("ab",(123,()))
Present "s=ab d=123"
PresentT "s=ab d=123"
Instances
(KnownNat (TupleLenT as), PrintC bs, (b, bs) ~ ReverseTupleP (a, as), ReverseTupleC (a, as), Show a, Show as, PrintfArg b, PP s x ~ String, PP p x ~ (a, as), P s x, P p x, CheckT (PP p x) ~ True) => P (Printfn s p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (Printfn s p :: Type) x = String

data ReverseTupleN Source #

reverses inductive tuples

>>> pl @ReverseTupleN (1,('a',(True,("def",()))))
Present ("def",(True,('a',(1,()))))
PresentT ("def",(True,('a',(1,()))))
>>> pl @ReverseTupleN (1,('a',()))
Present ('a',(1,()))
PresentT ('a',(1,()))
>>> pl @ReverseTupleN (999,())
Present (999,())
PresentT (999,())
Instances
(ReverseTupleC tp, Show (ReverseTupleP tp), Show tp) => P ReverseTupleN tp Source # 
Instance details

Defined in Predicate

Associated Types

type PP ReverseTupleN tp :: Type Source #

Methods

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

type PP ReverseTupleN tp Source # 
Instance details

Defined in Predicate

data TupleListImpl (strict :: Bool) (n :: Nat) Source #

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

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (TupleListImpl strict n :: Type) [a] = TupleListT (ToN n) a

class PrintC x where Source #

Methods

prtC :: (PrintfArg a, PrintfType r) => String -> (a, x) -> r Source #

Instances
PrintC () Source # 
Instance details

Defined in Predicate

Methods

prtC :: (PrintfArg a, PrintfType r) => String -> (a, ()) -> r Source #

(PrintfArg a, PrintC rs) => PrintC (a, rs) Source # 
Instance details

Defined in Predicate

Methods

prtC :: (PrintfArg a0, PrintfType r) => String -> (a0, (a, rs)) -> r Source #

type Sapa' (t :: Type) = Wrap t (Fst Id) <> Wrap t (Snd Id) Source #

data p <> q infixr 6 Source #

similar to <>

>>> pl @(Fst Id <> Snd Id) ("abc","def")
Present "abcdef"
PresentT "abcdef"
>>> pl @("abcd" <> "ef" <> Id) "ghi"
Present "abcdefghi"
PresentT "abcdefghi"
Instances
(Semigroup (PP p x), PP p x ~ PP q x, P p x, Show (PP q x), P q x) => P (p <> q :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

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

type IsInfixI p q = IsFixImpl EQ True p q Source #

type IsInfix p q = IsFixImpl EQ False p q Source #

data IsFixImpl (cmp :: Ordering) (ignore :: Bool) p q Source #

isInfixOf isPrefixOf isSuffixOf equivalents

>>> pl @(IsInfixI "abc" "axAbCd") ()
True
TrueT
>>> pl @(IsPrefixI "abc" "aBcbCd") ()
True
TrueT
>>> pl @(IsPrefix "abc" "aBcbCd") ()
False
FalseT
>>> pl @(IsSuffix "bCd" "aBcbCd") ()
True
TrueT

prefix infix suffix for strings

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

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (IsFixImpl cmp ignore p q :: Type) x = Bool

type Nothing' = Guard "expected Nothing" IsNothing Source #

data Stdin Source #

Instances
P Stdin a Source # 
Instance details

Defined in Predicate

Associated Types

type PP Stdin a :: Type Source #

Methods

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

type PP Stdin a Source # 
Instance details

Defined in Predicate

type PP Stdin a = String

data WritefileImpl (hh :: FHandle Symbol) p Source #

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

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (WritefileImpl fh p :: Type) a = ()

class GetMode (x :: WFMode) where Source #

Instances
GetMode WFAppend Source # 
Instance details

Defined in Predicate

GetMode WFWrite Source # 
Instance details

Defined in Predicate

GetMode WFWriteForce Source # 
Instance details

Defined in Predicate

data WFMode Source #

Constructors

WFAppend 
WFWrite 
WFWriteForce 
Instances
Eq WFMode Source # 
Instance details

Defined in Predicate

Methods

(==) :: WFMode -> WFMode -> Bool #

(/=) :: WFMode -> WFMode -> Bool #

Show WFMode Source # 
Instance details

Defined in Predicate

class GetFHandle (x :: FHandle Symbol) where Source #

Instances
GetFHandle (FStdout :: FHandle Symbol) Source # 
Instance details

Defined in Predicate

GetFHandle (FStderr :: FHandle Symbol) Source # 
Instance details

Defined in Predicate

(GetMode w, KnownSymbol s) => GetFHandle (FOther s w) Source # 
Instance details

Defined in Predicate

data FHandle s Source #

Constructors

FStdout 
FStderr 
FOther s WFMode 
Instances
Show s => Show (FHandle s) Source # 
Instance details

Defined in Predicate

Methods

showsPrec :: Int -> FHandle s -> ShowS #

show :: FHandle s -> String #

showList :: [FHandle s] -> ShowS #

data TimeZ Source #

Instances
P TimeZ a Source # 
Instance details

Defined in Predicate

Associated Types

type PP TimeZ a :: Type Source #

Methods

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

type PP TimeZ a Source # 
Instance details

Defined in Predicate

type PP TimeZ a = ZonedTime

data TimeU Source #

Instances
P TimeU a Source # 
Instance details

Defined in Predicate

Associated Types

type PP TimeU a :: Type Source #

Methods

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

type PP TimeU a Source # 
Instance details

Defined in Predicate

type PP TimeU a = UTCTime

data ReadEnvAll Source #

Instances
P ReadEnvAll a Source # 
Instance details

Defined in Predicate

Associated Types

type PP ReadEnvAll a :: Type Source #

Methods

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

type PP ReadEnvAll a Source # 
Instance details

Defined in Predicate

type PP ReadEnvAll a = [(String, String)]

data ReadEnv p Source #

does the directory exists

>>> pl @(DirExists ".") ()
True
TrueT
Instances
(PP p x ~ String, P p x) => P (ReadEnv p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (ReadEnv p :: Type) x = Maybe String

data ReadDir p Source #

does the directory exists

>>> pl @(DirExists ".") ()
True
TrueT
Instances
(PP p x ~ String, P p x) => P (ReadDir p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (ReadDir p :: Type) x = Maybe [FilePath]

data ReadFile p Source #

similar to readFile

>>> pl @(ReadFile ".ghci" >> 'Just Id >> Len >> Gt 0) ()
True
TrueT
>>> pl @(FileExists "xyzzy") ()
False
FalseT
Instances
(PP p x ~ String, P p x) => P (ReadFile p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (ReadFile p :: Type) x = Maybe String

type H = Hide Source #

data Hide p Source #

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

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

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

type Traverse p q = Map p q >> Sequence Source #

data Sequence Source #

similar to sequenceA

>>> pl @Sequence [Just 10, Just 20, Just 30]
Present Just [10,20,30]
PresentT (Just [10,20,30])
>>> pl @Sequence [Just 10, Just 20, Just 30, Nothing, Just 40]
Present Nothing
PresentT Nothing
Instances
(Show (f (t a)), Show (t (f a)), Traversable t, Applicative f) => P Sequence (t (f a)) Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP Sequence (t (f a)) = f (t a)

type Case'' s (ps :: [k]) (qs :: [k1]) (r :: k2) = Case (FailCase s) ps qs r Source #

type Case' (ps :: [k]) (qs :: [k1]) (r :: k2) = Case (Snd Id >> Failp "Case:no match") ps qs r Source #

data Case (e :: k0) (ps :: [k]) (qs :: [k1]) (r :: k2) Source #

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

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (Case e ps qs r :: Type) x = PP (CaseImpl (LenT ps) e ps qs r) x

data CaseImpl (n :: Nat) (e :: k0) (ps :: [k]) (qs :: [k1]) (r :: k2) Source #

tries each predicate ps and on the first match runs the corresponding qs but if there is no match on ps then runs the fail case e

>>> pl @(Case (FailS "asdf" >> Snd Id >> Unproxy ) '[Lt 4,Lt 10,Same 50] '[Printf "%d is lt4" Id, Printf "%d is lt10" Id, Printf "%d is same50" Id] Id) 50
Present "50 is same50"
PresentT "50 is same50"
>>> pl @(Case (FailS "asdf" >> Snd Id >> Unproxy ) '[Lt 4,Lt 10,Same 50] '[Printf "%d is lt4" Id, Printf "%d is lt10" Id, Printf "%d is same50" Id] Id) 9
Present "9 is lt10"
PresentT "9 is lt10"
>>> pl @(Case (FailS "asdf" >> Snd Id >> Unproxy ) '[Lt 4,Lt 10,Same 50] '[Printf "%d is lt4" Id, Printf "%d is lt10" Id, Printf "%d is same50" Id] Id) 3
Present "3 is lt4"
PresentT "3 is lt4"
>>> pl @(Case (FailS "asdf" >> Snd Id >> Unproxy ) '[Lt 4,Lt 10,Same 50] '[Printf "%d is lt4" Id, Printf "%d is lt10" Id, Printf "%d is same50" Id] Id) 99
Error asdf
FailT "asdf"
Instances
(KnownNat n, GetLen ps, P r x, P p (PP r x), P q (PP r x), PP p (PP r x) ~ Bool, Show (PP q (PP r x)), Show (PP r x), P (CaseImpl n e (p1 ': ps) (q1 ': qs) r) x, PP (CaseImpl n e (p1 ': ps) (q1 ': qs) r) x ~ PP q (PP r x)) => P (CaseImpl n e (p ': (p1 ': ps)) (q ': (q1 ': qs)) r :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (CaseImpl n e (p ': (p1 ': ps)) (q ': (q1 ': qs)) r :: Type) x = PP q (PP r x)
type PP (CaseImpl n e (p ': ([] :: [k])) (q ': ([] :: [k1])) r :: Type) x Source # 
Instance details

Defined in Predicate

type PP (CaseImpl n e (p ': ([] :: [k])) (q ': ([] :: [k1])) r :: Type) x = PP q (PP r x)
type PP (CaseImpl n e ([] :: [k]) ([] :: [k1]) r :: Type) x Source # 
Instance details

Defined in Predicate

type PP (CaseImpl n e ([] :: [k]) ([] :: [k1]) r :: Type) x = Void
type PP (CaseImpl n e (p ': ps) ([] :: [k1]) r :: Type) x Source # 
Instance details

Defined in Predicate

type PP (CaseImpl n e (p ': ps) ([] :: [k1]) r :: Type) x = Void
type PP (CaseImpl n e ([] :: [k]) (q ': qs) r :: Type) x Source # 
Instance details

Defined in Predicate

type PP (CaseImpl n e ([] :: [k]) (q ': qs) r :: Type) x = Void

type GuardsViaPara prt ps = Para (GuardsViaParaT prt ps) Source #

type family GuardsViaParaT prt ps where ... Source #

Equations

GuardsViaParaT prt '[] = '[] 
GuardsViaParaT prt (p ': ps) = Guard prt p ': GuardsViaParaT prt ps 

data ParaImplW (strict :: Bool) (ps :: [k]) Source #

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

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (ParaImplW strict ps :: Type) [a] = PP (ParaImpl (LenT ps) strict ps) [a]

type ParaLax (os :: [k]) = ParaImplW False os Source #

type Para (os :: [k]) = ParaImplW True os Source #

data ParaImpl (n :: Nat) (strict :: Bool) (os :: [k]) Source #

runs values in parallel unlike Do

>>> pl @(Para '[Id,Id + 1,Id * 4]) [10,20,30]
Present [10,21,120]
PresentT [10,21,120]
Instances
(TypeError (Text "ParaImpl '[] invalid: requires at least one value in the list") :: Constraint) => P (ParaImpl n strict ([] :: [k]) :: Type) [a] Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

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

Defined in Predicate

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

Defined in Predicate

type PP (ParaImpl n strict ([] :: [k]) :: Type) [a] = Void

type family ToGuardsT (prt :: k) (os :: [k1]) :: [(k, k1)] where ... Source #

Equations

ToGuardsT prt '[p] = '(prt, p) ': '[] 
ToGuardsT prt (p ': ps) = '(prt, p) ': ToGuardsT prt ps 

type ToGuards (prt :: k) (os :: [k1]) = Proxy (Guards (ToGuardsT prt os)) Source #

type ToPara (os :: [k]) = Proxy (ParaImplW True os) Source #

type Guards' (ps :: [k]) = Para (GuardsT ps) Source #

type family GuardsT (ps :: [k]) where ... Source #

Equations

GuardsT '[] = '[] 
GuardsT (p ': ps) = Guard' p ': GuardsT ps 

data Printf s p Source #

uses Printf to format output

>>> pl @(Printf "value=%03d" Id) 12
Present "value=012"
PresentT "value=012"

splits string into pieces before "%" that way we have a chance of catching any errors

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

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (Printf s p :: Type) x = String

data Intercalate p q Source #

Intercalate

>>> pl @(Intercalate '["aB"] '["xxxx","yz","z","www","xyz"]) ()
Present ["xxxx","aB","yz","aB","z","aB","www","aB","xyz"]
PresentT ["xxxx","aB","yz","aB","z","aB","www","aB","xyz"]
Instances
(PP p x ~ [a], PP q x ~ PP p x, P p x, P q x, Show a) => P (Intercalate p q :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (Intercalate p q :: Type) x = PP p x

type AssocR = '(Fst I >> Fst I, Snd I *** I) Source #

type AssocL = '(I *** Fst I, Snd I >> Snd I) Source #

change associativity of nested pairs

>>> pl @AssocL (99,('a',True))
Present ((99,'a'),True)
PresentT ((99,'a'),True)
>>> pl @AssocR ((99,'a'),True)
Present (99,('a',True))
PresentT (99,('a',True))

type ShowBase (n :: Nat) = ShowBase' n Id Source #

data ShowBase' (n :: Nat) p Source #

Display a number at base 2 to 36, similar to showIntAtBase but supports signed numbers

>>> pl @(ShowBase 16) 4077
Present "fed"
PresentT "fed"
>>> pl @(ShowBase 16) (-255)
Present "-ff"
PresentT "-ff"
>>> pl @(ShowBase 2) 147
Present "10010011"
PresentT "10010011"
>>> pl @(ShowBase' 2 (Negate 147)) "whatever"
Present "-10010011"
PresentT "-10010011"
Instances
(PP p x ~ a, P p x, Show a, 2 <= n, n <= 36, KnownNat n, Integral a) => P (ShowBase' n p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (ShowBase' n p :: Type) x = String

type ReadBase (t :: Type) (n :: Nat) = ReadBase' (Hole t) n Id Source #

data ReadBase' t (n :: Nat) p Source #

Read a number base 2 via 36

>>> pl @(ReadBase Int 16) "00feD"
Present 4077
PresentT 4077
>>> pl @(ReadBase Int 16) "-ff"
Present -255
PresentT (-255)
>>> pl @(ReadBase Int 2) "10010011"
Present 147
PresentT 147

supports negative numbers unlike readInt

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

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

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

data Luhn p Source #

Luhn predicate check on last digit

>>> pl @(Luhn Id) [1,2,3,0]
True
TrueT
>>> pl @(Luhn Id) [1,2,3,4]
False
FalseT
Instances
(PP p x ~ [Int], P p x) => P (Luhn p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

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

type Zipn p q = Zip False False p q Source #

type Ziprc p q = Zip False True p q Source #

type Ziplc p q = Zip True False p q Source #

data Zip (lc :: Bool) (rc :: Bool) p q Source #

Zip two lists optionally cycling the one of the lists to match the size

>>> pl @(Ziplc (Fst Id) (Snd Id)) ("abc", [1..5])
Present [('a',1),('b',2),('c',3),('a',4),('b',5)]
PresentT [('a',1),('b',2),('c',3),('a',4),('b',5)]
>>> pl @(Ziplc (Fst Id) (Snd Id)) ("abcdefg", [1..5])
Present [('a',1),('b',2),('c',3),('d',4),('e',5)]
PresentT [('a',1),('b',2),('c',3),('d',4),('e',5)]
>>> pl @(Ziprc (Fst Id) (Snd Id)) ("abcdefg", [1..5])
Present [('a',1),('b',2),('c',3),('d',4),('e',5),('f',1),('g',2)]
PresentT [('a',1),('b',2),('c',3),('d',4),('e',5),('f',1),('g',2)]
Instances
(GetBool lc, GetBool rc, PP p a ~ [x], PP q a ~ [y], P p a, P q a, Show x, Show y) => P (Zip lc rc p q :: Type) a Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (Zip lc rc p q :: Type) a = [(ArrT (PP p a), ArrT (PP q a))]

type family ExtractAFromTA (ta :: Type) :: Type where ... Source #

Equations

ExtractAFromTA (t a) = a 
ExtractAFromTA ta = TypeError (Text "ExtractAFromTA: expected (t a) but found something else" :$$: (Text "t a = " :<>: ShowType ta)) 

data ZipThese p q Source #

similar to align thats pads with This or That if one list is shorter than the other

the key is that all information about both lists are preserved

>>> pl @(ZipThese (Fst Id) (Snd Id)) ("aBc", [1..5])
Present [These 'a' 1,These 'B' 2,These 'c' 3,That 4,That 5]
PresentT [These 'a' 1,These 'B' 2,These 'c' 3,That 4,That 5]
>>> pl @(ZipThese (Fst Id) (Snd Id)) ("aBcDeF", [1..3])
Present [These 'a' 1,These 'B' 2,These 'c' 3,This 'D',This 'e',This 'F']
PresentT [These 'a' 1,These 'B' 2,These 'c' 3,This 'D',This 'e',This 'F']
Instances
(PP p a ~ [x], PP q a ~ [y], P p a, P q a, Show x, Show y) => P (ZipThese p q :: Type) a Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (ZipThese p q :: Type) a = [These (ArrT (PP p a)) (ArrT (PP q a))]

data Char1 (s :: Symbol) Source #

extracts the first character from a non empty Symbol

>>> pl @(Char1 "aBc") ()
Present 'a'
PresentT 'a'
Instances
(KnownSymbol s, NullT s ~ False) => P (Char1 s :: Type) a Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (Char1 s :: Type) a = Char

type Singleton p = p :+ EmptyT [] p Source #

creates a singleton from a value

>>> pl @(Singleton (Char1 "aBc")) ()
Present "a"
PresentT "a"
>>> pl @(Singleton Id) False
Present [False]
PresentT [False]
>>> pl @(Singleton (Snd Id)) (False,"hello")
Present ["hello"]
PresentT ["hello"]

type EmptyList (t :: Type) = EmptyList' (Hole t) Source #

data EmptyList' t Source #

creates an empty list of the given type

>>> pl @(Id :+ EmptyList _) 99
Present [99]
PresentT [99]
Instances
P (EmptyList' t :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (EmptyList' t :: Type) x = [PP t x]

type Theseid p q = TheseIn '(I, p) '(q, I) I Source #

data TheseIn p q r Source #

similar to these

>>> pl @(TheseIn Id Len (Fst Id + Length (Snd Id))) (This 13)
Present 13
PresentT 13
>>> pl @(TheseIn Id Len (Fst Id + Length (Snd Id))) (That "this is a long string")
Present 21
PresentT 21
>>> pl @(TheseIn Id Len (Fst Id + Length (Snd Id))) (These 20 "somedata")
Present 28
PresentT 28
>>> pl @(TheseIn (Left _) (Right _) (If (Fst Id > Length (Snd Id)) (MkLeft _ (Fst Id)) (MkRight _ (Snd Id)))) (That "this is a long string")
Present Right "this is a long string"
PresentT (Right "this is a long string")
>>> pl @(TheseIn (Left _) (Right _) (If (Fst Id > Length (Snd Id)) (MkLeft _ (Fst Id)) (MkRight _ (Snd Id)))) (These 1 "this is a long string")
Present Right "this is a long string"
PresentT (Right "this is a long string")
>>> pl @(TheseIn (Left _) (Right _) (If (Fst Id > Length (Snd Id)) (MkLeft _ (Fst Id)) (MkRight _ (Snd Id)))) (These 100 "this is a long string")
Present Left 100
PresentT (Left 100)
Instances
(Show a, Show b, Show (PP p a), P p a, P q b, P r (a, b), PP p a ~ PP q b, PP p a ~ PP r (a, b), PP q b ~ PP r (a, b)) => P (TheseIn p q r :: Type) (These a b) Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

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

type IsThese p = IsTh (These () ()) p Source #

type IsThat p = IsTh (That ()) p Source #

type IsThis p = IsTh (This ()) p Source #

data IsTh (th :: These x y) p Source #

predicate on These

>>> pl @(IsThis Id) (This "aBc")
True
TrueT
>>> pl @(IsThis Id) (These 1 'a')
False
FalseT
>>> pl @(IsThese Id) (These 1 'a')
True
TrueT
Instances
(PP p x ~ These a b, P p x, Show a, Show b, GetThese th) => P (IsTh th p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (IsTh th p :: Type) x = Bool

data FromListF (t :: Type) Source #

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

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (FromListF l' :: Type) l = l'

data FromList (t :: Type) Source #

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

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (FromList t :: Type) [a] = t

data ToListExt Source #

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

Defined in Predicate

Associated Types

type PP ToListExt l :: Type Source #

Methods

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

type PP ToListExt l Source # 
Instance details

Defined in Predicate

type PP ToListExt l = [Item l]

data ToList' p Source #

similar to toList

>>> pl @(ToList' Id) ("aBc" :: String)
Present "aBc"
PresentT "aBc"
>>> pl @(ToList' Id) (Just 14)
Present [14]
PresentT [14]
>>> pl @(ToList' Id) Nothing
Present []
PresentT []
>>> pl @(ToList' Id) (Left "xx")
Present []
PresentT []
>>> pl @(ToList' Id) (These 12 "xx")
Present ["xx"]
PresentT ["xx"]
Instances
(PP p x ~ t a, P p x, Show (t a), Foldable t, Show a) => P (ToList' p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

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

data ToList Source #

similar to toList

>>> pl @ToList ("aBc" :: String)
Present "aBc"
PresentT "aBc"
>>> pl @ToList (Just 14)
Present [14]
PresentT [14]
>>> pl @ToList Nothing
Present []
PresentT []
>>> pl @ToList (Left "xx")
Present []
PresentT []
>>> pl @ToList (These 12 "xx")
Present ["xx"]
PresentT ["xx"]
Instances
(Show (t a), Foldable t, Show a) => P ToList (t a) Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

type PP ToList (t a) Source # 
Instance details

Defined in Predicate

type PP ToList (t a) = [a]

type IToList (t :: Type) = IToList' (Hole t) Id Source #

data IToList' t p Source #

similar to itoList

>>> pl @(IToList _) ("aBc" :: String)
Present [(0,'a'),(1,'B'),(2,'c')]
PresentT [(0,'a'),(1,'B'),(2,'c')]
Instances
(Show x, P p x, Typeable (PP t (PP p x)), Show (PP t (PP p x)), FoldableWithIndex (PP t (PP p x)) f, PP p x ~ f a, Show a) => P (IToList' t p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (IToList' t p :: Type) x = [(PP t (PP p x), ExtractAFromTA (PP p x))]

type Ne n = Cmp Cne I n Source #

type Lt n = Cmp Clt I n Source #

type Le n = Cmp Cle I n Source #

type Same n = Cmp Ceq I n Source #

type Ge n = Cmp Cge I n Source #

type Gt n = Cmp Cgt I n Source #

data CmpI (o :: OrderingP) p q Source #

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

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (CmpI o p q :: Type) a = Bool

data Cmp (o :: OrderingP) p q Source #

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

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (Cmp o p q :: Type) a = Bool

type (===?) p q = OrdI p q infix 4 Source #

data OrdI p q Source #

compare two strings ignoring case

>>> pl @(Fst Id ===? Snd Id) ("abC","aBc")
Present EQ
PresentT EQ
>>> pl @(Fst Id ===? Snd Id) ("abC","DaBc")
Present LT
PresentT LT
Instances
(PP p a ~ String, PP p a ~ PP q a, P p a, P q a) => P (OrdI p q :: Type) a Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (OrdI p q :: Type) a = Ordering

type OrdA p = OrdA' p p Source #

type OrdA' p q = OrdP (Fst Id >> p) (Snd Id >> q) Source #

similar to compare

>>> pl @(Fst Id === Snd Id) (10,9)
Present GT
PresentT GT
>>> pl @(14 % 3 === Fst Id %- Snd Id) (-10,7)
Present GT
PresentT GT
>>> pl @(Fst Id === Snd Id) (10,11)
Present LT
PresentT LT
>>> pl @(Snd Id === (Fst Id >> Snd Id >> Head' Id)) (('x',[10,12,13]),10)
Present EQ
PresentT EQ
>>> pl @(Snd Id === Head' (Snd (Fst Id))) (('x',[10,12,13]),10)
Present EQ
PresentT EQ

type (===) p q = OrdP p q infix 4 Source #

data OrdP p q Source #

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

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (OrdP p q :: Type) a = Ordering

type Imply p q = p ~> q Source #

data (p :: k) ~> (q :: k1) infixr 1 Source #

implication

>>> pl @(Fst Id ~> (Snd Id >> Len >> Ge 4)) (True,[11,12,13,14])
True
TrueT
>>> pl @(Fst Id ~> (Snd Id >> Len >> Same 4)) (True,[12,11,12,13,14])
False
FalseT
>>> pl @(Fst Id ~> (Snd Id >> Len >> Same 4)) (False,[12,11,12,13,14])
True
TrueT
>>> pl @(Fst Id ~> (Snd Id >> Len >> Ge 4)) (False,[11,12,13,14])
True
TrueT
Instances
(P p a, P q a, PP p a ~ Bool, PP q a ~ Bool) => P (p ~> q :: Type) a Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

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

type OR p q = p || q Source #

data (p :: k) || (q :: k1) infixr 2 Source #

similar to ||

>>> pl @(Fst Id || (Snd Id >> Len >> Ge 4)) (False,[11,12,13,14])
True
TrueT
>>> pl @((Not (Fst Id)) || (Snd Id >> Len >> Same 4)) (True,[12,11,12,13,14])
False
FalseT
Instances
(P p a, P q a, PP p a ~ Bool, PP q a ~ Bool) => P (p || q :: Type) a Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

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

type And p q = p && q Source #

data (p :: k) && (q :: k1) infixr 3 Source #

similar to &&

>>> pl @(Fst Id && (Snd Id >> Len >> Ge 4)) (True,[11,12,13,14])
True
TrueT
>>> pl @(Fst Id && (Snd Id >> Len >> Same 4)) (True,[12,11,12,13,14])
False
FalseT
Instances
(P p a, P q a, PP p a ~ Bool, PP q a ~ Bool) => P (p && q :: Type) a Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

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

type (<<) p q = q >> p infixl 1 Source #

data (p :: k) >> (q :: k1) infixr 1 Source #

This is composition for predicates

>>> pl @(Fst Id >> Succ (Id !! 0)) ([11,12],'x')
Present 12
PresentT 12
>>> pl @(Len *** Succ Id >> ShowP (First (Pred Id))) ([11,12],'x')
Present "(1,'y')"
PresentT "(1,'y')"
Instances
(Show (PP p a), Show (PP q (PP p a)), P p a, P q (PP p a)) => P (p >> q :: Type) a Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

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

type (>|) p q = p >> Skip q infixr 1 Source #

type (|>) p q = Skip p >> q infixr 1 Source #

data Skip p Source #

just run the effect but skip the value for example for use with Stdout so it doesnt interfere with the 'a' on the rhs unless there is an error

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

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

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

data GuardSimple p Source #

similar to Guard but uses the root message of the False predicate case as the failure message

>>> pl @(GuardSimple (Luhn Id)) [1..4]
Error Luhn map=[4,6,2,2] sum=14 ret=4 | [1,2,3,4]
FailT "Luhn map=[4,6,2,2] sum=14 ret=4 | [1,2,3,4]"
>>> pl @(GuardSimple (Luhn Id)) [1,2,3,0]
Present [1,2,3,0]
PresentT [1,2,3,0]
>>> pl @(GuardSimple (Len > 30)) [1,2,3,0]
Error 4 > 30
FailT "4 > 30"
Instances
(Show a, P p a, PP p a ~ Bool) => P (GuardSimple p :: Type) a Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

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

type ExitWhen' p = ExitWhen "ExitWhen" p Source #

type ExitWhen prt p = Guard prt (Not p) Source #

type Guard' p = Guard "Guard" p Source #

data Guard prt p Source #

'p' is the predicate and on failure of the predicate runs 'prt'

>>> pl @(Guard "expected > 3" (Gt 3)) 17
Present 17
PresentT 17
>>> pl @(Guard "expected > 3" (Gt 3)) 1
Error expected > 3
FailT "expected > 3"
>>> pl @(Guard (Printf "%d not > 3" Id) (Gt 3)) (-99)
Error -99 not > 3
FailT "-99 not > 3"
Instances
(Show a, P prt a, PP prt a ~ String, P p a, PP p a ~ Bool) => P (Guard prt p :: Type) a Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

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

data GuardsImplW (strict :: Bool) (ps :: [(k, k1)]) Source #

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

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (GuardsImplW strict ps :: Type) [a] = PP (GuardsImpl (LenT ps) strict ps) [a]

type GuardsQuick (prt :: k) (os :: [k1]) = Guards (ToGuardsT prt os) Source #

type GuardsLax (os :: [(k, k1)]) = GuardsImplW False os Source #

type Guards (os :: [(k, k1)]) = GuardsImplW True os Source #

data GuardsImpl (n :: Nat) (strict :: Bool) (os :: [(k, k1)]) Source #

Guards contain a type level list of tuples the action to run on failure of the predicate and the predicate itself Each tuple validating against the corresponding value in a value list

>>> pl @(Guards '[ '("arg1 failed",Gt 4), '("arg2 failed", Same 4)]) [17,4]
Present [17,4]
PresentT [17,4]
>>> pl @(Guards '[ '("arg1 failed",Gt 4), '("arg2 failed", Same 5)]) [17,4]
Error arg2 failed
FailT "arg2 failed"
>>> pl @(Guards '[ '("arg1 failed",Gt 99), '("arg2 failed", Same 4)]) [17,4]
Error arg1 failed
FailT "arg1 failed"
>>> pl @(Guards '[ '(Printf2 "arg %d failed with value %d",Gt 4), '(Printf2 "%d %d", Same 4)]) [17,3]
Error 2 3
FailT "2 3"
>>> pl @(GuardsQuick (Printf2 "arg %d failed with value %d") '[Gt 4, Ge 3, Same 4]) [17,3,5]
Error arg 3 failed with value 5
FailT "arg 3 failed with value 5"
>>> pl @(GuardsQuick (Printf2 "arg %d failed with value %d") '[Gt 4, Ge 3, Same 4]) [17,3,5,99]
Error Guards: data elements(4) /= predicates(3)
FailT "Guards: data elements(4) /= predicates(3)"
Instances
(KnownNat n, GetBool strict, Show a) => P (GuardsImpl n strict ([] :: [(k, k1)]) :: Type) [a] Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (GuardsImpl n strict ((,) prt p ': ps) :: Type) [a] = [a]
type PP (GuardsImpl n strict ([] :: [(k, k1)]) :: Type) [a] Source # 
Instance details

Defined in Predicate

type PP (GuardsImpl n strict ([] :: [(k, k1)]) :: Type) [a] = [a]

type OneP = Guard (Printf "expected list of length 1 but found length=%d" Len) (Len >> Same 1) >> Head Source #

type Rem p q = Snd (QuotRem p q) Source #

type Quot p q = Fst (QuotRem p q) Source #

data QuotRem p q Source #

similar to quotRem

>>> pl @(QuotRem (Fst Id) (Snd Id)) (10,3)
Present (3,1)
PresentT (3,1)
>>> pl @(QuotRem (Fst Id) (Snd Id)) (10,-3)
Present (-3,1)
PresentT (-3,1)
>>> pl @(QuotRem (Fst Id) (Snd Id)) (-10,-3)
Present (3,-1)
PresentT (3,-1)
>>> pl @(QuotRem (Fst Id) (Snd Id)) (-10,3)
Present (-3,-1)
PresentT (-3,-1)
>>> pl @(QuotRem (Fst Id) (Snd Id)) (10,0)
Error QuotRem zero denominator
FailT "QuotRem zero denominator"
Instances
(PP p a ~ PP q a, P p a, P q a, Show (PP p a), Integral (PP p a)) => P (QuotRem p q :: Type) a Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (QuotRem p q :: Type) a = (PP p a, PP p a)

data DivMod p q Source #

similar to divMod

>>> pl @(DivMod (Fst Id) (Snd Id)) (10,3)
Present (3,1)
PresentT (3,1)
>>> pl @(DivMod (Fst Id) (Snd Id)) (10,-3)
Present (-4,-2)
PresentT (-4,-2)
>>> pl @(DivMod (Fst Id) (Snd Id)) (-10,3)
Present (-4,2)
PresentT (-4,2)
>>> pl @(DivMod (Fst Id) (Snd Id)) (-10,-3)
Present (3,-1)
PresentT (3,-1)
>>> pl @(DivMod (Fst Id) (Snd Id)) (10,0)
Error DivMod zero denominator
FailT "DivMod zero denominator"
Instances
(PP p a ~ PP q a, P p a, P q a, Show (PP p a), Integral (PP p a)) => P (DivMod p q :: Type) a Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (DivMod p q :: Type) a = (PP p a, PP p a)

data Mod p q Source #

similar to mod

>>> pl @(Mod (Fst Id) (Snd Id)) (10,3)
Present 1
PresentT 1
>>> pl @(Mod (Fst Id) (Snd Id)) (10,0)
Error Mod zero denominator
FailT "Mod zero denominator"
Instances
(PP p a ~ PP q a, P p a, P q a, Show (PP p a), Integral (PP p a)) => P (Mod p q :: Type) a Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

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

data Div p q Source #

similar to div

>>> pl @(Div (Fst Id) (Snd Id)) (10,4)
Present 2
PresentT 2
>>> pl @(Div (Fst Id) (Snd Id)) (10,0)
Error Div zero denominator
FailT "Div zero denominator"
Instances
(PP p a ~ PP q a, P p a, P q a, Show (PP p a), Integral (PP p a)) => P (Div p q :: Type) a Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

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

type Mod' p q = Snd (DivMod p q) Source #

type Div' p q = Fst (DivMod p q) Source #

type Odd = Mod I 2 == 1 Source #

type Even = Mod I 2 == 0 Source #

type Catch' p s = Catch p (FailCatch s) Source #

data Catch p q Source #

catch a failure

>>> pl @(Catch (Succ Id) (Fst Id >> Second (ShowP Id) >> Printf2 "%s %s" >> 'LT)) GT
Present LT
PresentT LT
>>> pl @(Catch' (Succ Id) (Second (ShowP Id) >> Printf2 "%s %s")) GT
Error Succ IO e=Prelude.Enum.Ordering.succ: bad argument GT
FailT "Succ IO e=Prelude.Enum.Ordering.succ: bad argument GT"
>>> pl @(Catch' (Succ Id) (Second (ShowP Id) >> Printf2 "%s %s")) LT
Present EQ
PresentT EQ

more flexible: takes a (String,x) and a proxy so we can still call 'False 'True now takes the FailT string and x so you can print more detail if you want need the proxy so we can fail without having to explicitly specify a type

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

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (Catch p q :: Type) x = PP p x

data Unproxy Source #

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

Defined in Predicate

Associated Types

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

Methods

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

type PP Unproxy (Proxy a) Source # 
Instance details

Defined in Predicate

type PP Unproxy (Proxy a) = a

type T (t :: Type) = Hole t Source #

data Hole (t :: Type) Source #

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

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

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

Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

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

type FailPrt2 (t :: Type) prt = Fail (Hole t) (Printf2 prt) Source #

type FailPrt (t :: Type) prt = Fail (Hole t) (Printf prt) Source #

type FailS s = Fail I s Source #

type Failt (t :: Type) prt = Fail (Hole t) prt Source #

data Fail t prt Source #

Fails the computation with a message

>>> pl @(Failt Int (Printf "value=%03d" Id)) 99
Error value=099
FailT "value=099"
>>> pl @(FailS (Printf2 "value=%03d string=%s")) (99,"somedata")
Error value=099 string=somedata
FailT "value=099 string=somedata"
Instances
(P prt a, PP prt a ~ String) => P (Fail t prt :: Type) a Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

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

type Span p q = Break (Not p) q Source #

data Break p q Source #

similar to break

>>> pl @(Break (Ge 3) Id) [10,4,1,7,3,1,3,5]
Present ([],[10,4,1,7,3,1,3,5])
PresentT ([],[10,4,1,7,3,1,3,5])
>>> pl @(Break (Lt 3) Id) [10,4,1,7,3,1,3,5]
Present ([10,4],[1,7,3,1,3,5])
PresentT ([10,4],[1,7,3,1,3,5])
Instances
(P p x, PP q a ~ [x], PP p x ~ Bool, P q a) => P (Break p q :: Type) a Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (Break p q :: Type) a = (PP q a, PP q a)

type FilterBy p q = Partition p q >> Fst Id Source #

data Partition p q Source #

similar to partition

>>> pl @(Partition (Ge 3) Id) [10,4,1,7,3,1,3,5]
Present ([10,4,7,3,3,5],[1,1])
PresentT ([10,4,7,3,3,5],[1,1])
>>> pl @(Partition (Prime Id) Id) [10,4,1,7,3,1,3,5]
Present ([7,3,3,5],[10,4,1,1])
PresentT ([7,3,3,5],[10,4,1,1])
>>> pl @(Partition (Ge 300) Id) [10,4,1,7,3,1,3,5]
Present ([],[10,4,1,7,3,1,3,5])
PresentT ([],[10,4,1,7,3,1,3,5])
>>> pl @(Partition (Id < 300) Id) [10,4,1,7,3,1,3,5]
Present ([10,4,1,7,3,1,3,5],[])
PresentT ([10,4,1,7,3,1,3,5],[])
Instances
(P p x, Show x, PP q a ~ [x], PP p x ~ Bool, P q a) => P (Partition p q :: Type) a Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (Partition p q :: Type) a = (PP q a, PP q a)

data Pairs Source #

creates a list of overlapping pairs of elements. requires two or more elements

>>> pl @Pairs [1,2,3,4]
Present [(1,2),(2,3),(3,4)]
PresentT [(1,2),(2,3),(3,4)]
>>> pl @Pairs []
Error Pairs no data found
FailT "Pairs no data found"
>>> pl @Pairs [1]
Error Pairs only one element found
FailT "Pairs only one element found"
Instances
Show a => P Pairs [a] Source # 
Instance details

Defined in Predicate

Associated Types

type PP Pairs [a] :: Type Source #

Methods

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

type PP Pairs [a] Source # 
Instance details

Defined in Predicate

type PP Pairs [a] = [(a, a)]

data If p q r Source #

if p then run q else run r

>>> pl @(If (Gt 4) "greater than 4" "less than or equal to 4" ) 10
Present "greater than 4"
PresentT "greater than 4"
>>> pl @(If (Gt 4) "greater than 4" "less than or equal to 4") 0
Present "less than or equal to 4"
PresentT "less than or equal to 4"
Instances
(Show (PP r a), P p a, PP p a ~ Bool, P q a, P r a, PP q a ~ PP r a) => P (If p q r :: Type) a Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (If p q r :: Type) a = PP q a

type ConcatMap p q = Concat (Map p q) Source #

data Map p q Source #

similar to map

>>> pl @(Map (Pred Id) Id) [1..5]
Present [0,1,2,3,4]
PresentT [0,1,2,3,4]
Instances
(Show (PP p a), P p a, PP q x ~ f a, P q x, Show a, Show (f a), Foldable f) => P (Map p q :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

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

type IterateNUntil n p f = IterateNWhile n (Not p) f Source #

type IterateNWhile n p f = '(n, Id) >> (IterateWhile ((Fst Id > 0) && (Snd Id >> p)) (Pred Id *** f) >> Map (Snd Id) Id) Source #

type IterateWhile p f = Unfoldr (MaybeB p '(Id, f)) Id Source #

type IterateN n f = Unfoldr (MaybeB (Fst Id > 0) '(Snd Id, Pred Id *** f)) '(n, Id) Source #

data Unfoldr p q Source #

similar to unfoldr

>>> pl @(Unfoldr (MaybeB (Not Null) (SplitAt 2 Id)) Id) [1..5]
Present [[1,2],[3,4],[5]]
PresentT [[1,2],[3,4],[5]]
>>> pl @(IterateN 4 (Succ Id)) 4
Present [4,5,6,7]
PresentT [4,5,6,7]
Instances
(PP q a ~ s, PP p s ~ Maybe (b, s), P q a, P p s, Show s, Show b) => P (Unfoldr p q :: Type) a Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (Unfoldr p q :: Type) a = [UnfoldT (PP p (PP q a))]

type family UnfoldT mbs where ... Source #

Equations

UnfoldT (Maybe (b, s)) = b 

type Foldl p q r = Last' (Scanl p q r) Source #

type FoldN n p q = Last' (ScanN n p q) Source #

type ScanNA q = ScanN (Fst Id) (Snd Id) q Source #

type ScanN n p q = Scanl (Fst Id >> q) p (EnumFromTo 1 n) Source #

data Scanl p q r Source #

similar to scanl

>>> pl @(Scanl (Snd Id :+ Fst Id) (Fst Id) (Snd Id)) ([99],[1..5])
Present [[99],[1,99],[2,1,99],[3,2,1,99],[4,3,2,1,99],[5,4,3,2,1,99]]
PresentT [[99],[1,99],[2,1,99],[3,2,1,99],[4,3,2,1,99],[5,4,3,2,1,99]]
>>> pl @(ScanN 4 Id (Succ Id)) 'c'
Present "cdefg"
PresentT "cdefg"
>>> pl @(FoldN 4 Id (Succ Id)) 'c'
Present 'g'
PresentT 'g'
Instances
(PP p (b, a) ~ b, PP q x ~ b, PP r x ~ [a], P p (b, a), P q x, P r x, Show b, Show a) => P (Scanl p q r :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (Scanl p q r :: Type) x = [PP q x]

data PartitionThese Source #

similar to partitionThese. returns a 3-tuple with the results so use Fst Snd Thd to extract

>>> pl @PartitionThese [This 'a', That 2, This 'c', These 'z' 1, That 4, These 'a' 2, That 99]
Present ("ac",[2,4,99],[('z',1),('a',2)])
PresentT ("ac",[2,4,99],[('z',1),('a',2)])
Instances
(Show a, Show b) => P PartitionThese [These a b] Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

type PP PartitionThese [These a b] Source # 
Instance details

Defined in Predicate

type PP PartitionThese [These a b] = ([a], [b], [(a, b)])

data PartitionEithers Source #

similar to partitionEithers

>>> pl @PartitionEithers [Left 'a',Right 2,Left 'c',Right 4,Right 99]
Present ("ac",[2,4,99])
PresentT ("ac",[2,4,99])
Instances
(Show a, Show b) => P PartitionEithers [Either a b] Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

type PP PartitionEithers [Either a b] Source # 
Instance details

Defined in Predicate

type PP PartitionEithers [Either a b] = ([a], [b])

data EnumFromTo p q Source #

similar to enumFromTo

>>> pl @(EnumFromTo 2 5) ()
Present [2,3,4,5]
PresentT [2,3,4,5]
>>> pl @(EnumFromTo LT GT) ()
Present [LT,EQ,GT]
PresentT [LT,EQ,GT]
Instances
(P p x, P q x, PP p x ~ a, Show a, PP q x ~ a, Enum a) => P (EnumFromTo p q :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (EnumFromTo p q :: Type) x = [PP p x]

data Null Source #

similar to null using Foldable

>>> pl @Null [1,2,3,4]
False
FalseT
>>> pl @Null []
True
TrueT
Instances
(Show (t a), Foldable t, t a ~ as) => P Null as Source # 
Instance details

Defined in Predicate

Associated Types

type PP Null as :: Type Source #

Methods

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

type PP Null as Source # 
Instance details

Defined in Predicate

type PP Null as = Bool

data IsEmpty Source #

similar to null using AsEmpty

>>> pl @IsEmpty [1,2,3,4]
False
FalseT
>>> pl @IsEmpty []
True
TrueT
>>> pl @IsEmpty LT
False
FalseT
>>> pl @IsEmpty EQ
True
TrueT
Instances
(Show as, AsEmpty as) => P IsEmpty as Source # 
Instance details

Defined in Predicate

Associated Types

type PP IsEmpty as :: Type Source #

Methods

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

type PP IsEmpty as Source # 
Instance details

Defined in Predicate

type PP IsEmpty as = Bool

data Unsnoc Source #

unsnoc

>>> pl @Unsnoc [1,2,3,4]
Present Just ([1,2,3],4)
PresentT (Just ([1,2,3],4))
>>> pl @Unsnoc []
Present Nothing
PresentT Nothing
Instances
(Show (ConsT s), Show s, Snoc s s (ConsT s) (ConsT s)) => P Unsnoc s Source # 
Instance details

Defined in Predicate

Associated Types

type PP Unsnoc s :: Type Source #

Methods

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

type PP Unsnoc s Source # 
Instance details

Defined in Predicate

type PP Unsnoc s = Maybe (s, ConsT s)

data Uncons Source #

uncons

>>> pl @Uncons [1,2,3,4]
Present Just (1,[2,3,4])
PresentT (Just (1,[2,3,4]))
>>> pl @Uncons []
Present Nothing
PresentT Nothing
Instances
(Show (ConsT s), Show s, Cons s s (ConsT s) (ConsT s)) => P Uncons s Source # 
Instance details

Defined in Predicate

Associated Types

type PP Uncons s :: Type Source #

Methods

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

type PP Uncons s Source # 
Instance details

Defined in Predicate

type PP Uncons s = Maybe (ConsT s, s)

data p +: q infixl 5 Source #

similar to snoc

>>> pl @(Snd Id +: Fst Id) (99,[1,2,3,4])
Present [1,2,3,4,99]
PresentT [1,2,3,4,99]
>>> pl @(Fst Id +: Snd Id) ([],5)
Present [5]
PresentT [5]
>>> pl @(EmptyT [] Id +: 5) 5
Present [5]
PresentT [5]
Instances
(P p x, P q x, Show (PP q x), Show (PP p x), Snoc (PP p x) (PP p x) (PP q x) (PP q x)) => P (p +: q :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (p +: q :: Type) x = PP p x

data p :+ q infixr 5 Source #

similar to cons

>>> pl @(Fst Id :+ Snd Id) (99,[1,2,3,4])
Present [99,1,2,3,4]
PresentT [99,1,2,3,4]
>>> pl @(Snd Id :+ Fst Id) ([],5)
Present [5]
PresentT [5]
>>> pl @(123 :+ EmptyList _) "somestuff"
Present [123]
PresentT [123]
Instances
(P p x, P q x, Show (PP p x), Show (PP q x), Cons (PP q x) (PP q x) (PP p x) (PP p x)) => P (p :+ q :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (p :+ q :: Type) x = PP q x

type Ors' p = FoldMap Any p Source #

data Ors p Source #

ors

>>> pl @(Ors Id) [False,False,False]
False
FalseT
>>> pl @(Ors Id) [True,True,True,False]
True
TrueT
>>> pl @(Ors Id) []
False
FalseT
Instances
(PP p x ~ t a, P p x, Show (t a), Foldable t, a ~ Bool) => P (Ors p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

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

type Ands' p = FoldMap All p Source #

data Ands p Source #

ands

>>> pl @(Ands Id) [True,True,True]
True
TrueT
>>> pl @(Ands Id) [True,True,True,False]
False
FalseT
>>> pl @(Ands Id) []
True
TrueT
Instances
(PP p x ~ t a, P p x, Show (t a), Foldable t, a ~ Bool) => P (Ands p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

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

type Lookup' (t :: Type) p q = (q &&& Lookup p q) >> If (Snd Id >> IsNothing) (ShowP (Fst Id) >> Fail (Hole t) (Printf "index(%s) not found" Id)) (Snd Id >> Just Id) Source #

type (!!!) p q = Lookup p q >> MaybeIn (Failp "index not found") Id Source #

data Lookup p q Source #

lookup leveraging Ixed

>>> import qualified Data.Map.Strict as M
>>> pl @(Id !!! 2) ["abc","D","eF","","G"]
Present "eF"
PresentT "eF"
>>> pl @(Id !!! 20) ["abc","D","eF","","G"]
Error index not found
FailT "index not found"
>>> pl @(Id !!! "eF") (M.fromList (flip zip [0..] ["abc","D","eF","","G"]))
Present 2
PresentT 2
>>> pl @(Lookup Id 2) ["abc","D","eF","","G"]
Present Just "eF"
PresentT (Just "eF")
>>> pl @(Lookup Id 20) ["abc","D","eF","","G"]
Present Nothing
PresentT Nothing
Instances
(P q a, P p a, Show (PP p a), Ixed (PP p a), PP q a ~ Index (PP p a), Show (Index (PP p a)), Show (IxValue (PP p a))) => P (Lookup p q :: Type) a Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (Lookup p q :: Type) a = Maybe (IxValue (PP p a))

type (!!) p q = IxL p q (Failp "(!!) index not found") Source #

data IxL p q def Source #

similar to !! leveraging Ixed

>>> import qualified Data.Map.Strict as M
>>> pl @(Id !! 2) ["abc","D","eF","","G"]
Present "eF"
PresentT "eF"
>>> pl @(Id !! 20) ["abc","D","eF","","G"]
Error (!!) index not found
FailT "(!!) index not found"
>>> pl @(Id !! "eF") (M.fromList (flip zip [0..] ["abc","D","eF","","G"]))
Present 2
PresentT 2
Instances
(P q a, P p a, Show (PP p a), Ixed (PP p a), PP q a ~ Index (PP p a), Show (Index (PP p a)), Show (IxValue (PP p a)), P r (Proxy (IxValue (PP p a))), PP r (Proxy (IxValue (PP p a))) ~ IxValue (PP p a)) => P (IxL p q r :: Type) a Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (IxL p q r :: Type) a = IxValue (PP p a)

type Ix' (n :: Nat) = Ix n (Failp "Ix index not found") Source #

data Ix (n :: Nat) def Source #

similar to !!

>>> pl @(Ix 4 "not found") ["abc","D","eF","","G"]
Present "G"
PresentT "G"
>>> pl @(Ix 40 "not found") ["abc","D","eF","","G"]
Present "not found"
PresentT "not found"
Instances
(P def (Proxy a), PP def (Proxy a) ~ a, KnownNat n, Show a) => P (Ix n def :: Type) [a] Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

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

type ProxyT (t :: Type) = ProxyT' (Hole t) Source #

data ProxyT' t Source #

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

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (ProxyT' t :: Type) a = Proxy (PP t a)

data Concat p Source #

similar to concat

>>> pl @(Concat Id) ["abc","D","eF","","G"]
Present "abcDeFG"
PresentT "abcDeFG"
>>> pl @(Concat (Snd Id)) ('x',["abc","D","eF","","G"])
Present "abcDeFG"
PresentT "abcDeFG"
Instances
(Show a, Show (t [a]), PP p x ~ t [a], P p x, Foldable t) => P (Concat p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (Concat p :: Type) x = ExtractAFromTA (PP p x)

type Min' (t :: Type) = FoldMap (Min t) Id Source #

type Sum (t :: Type) = FoldMap (Sum t) Id Source #

type FoldMap (t :: Type) p = Map (Wrap t Id) p >> Unwrap (MConcat Id) Source #

similar to a limited form of foldMap

>>> pl @(FoldMap (SG.Sum _) Id) [44, 12, 3]
Present 59
PresentT 59
>>> pl @(FoldMap (SG.Product _) Id) [44, 12, 3]
Present 1584
PresentT 1584

data MConcat p Source #

similar to mconcat

>>> pl @(MConcat Id) [SG.Sum 44, SG.Sum 12, SG.Sum 3]
Present Sum {getSum = 59}
PresentT (Sum {getSum = 59})
Instances
(PP p x ~ [a], P p x, Show a, Monoid a) => P (MConcat p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (MConcat p :: Type) x = ExtractAFromTA (PP p x)

data MkThese p q Source #

These constructor

>>> pl @(MkThese (Fst Id) (Snd Id)) (44,'x')
Present These 44 'x'
PresentT (These 44 'x')
Instances
(P p a, P q a, Show (PP p a), Show (PP q a)) => P (MkThese p q :: Type) a Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (MkThese p q :: Type) a = These (PP p a) (PP q a)

type MkThat (t :: Type) p = MkThat' (Hole t) p Source #

data MkThat' t p Source #

That constructor

>>> pl @(MkThat _ Id) 44
Present That 44
PresentT (That 44)
Instances
(Show (PP p x), P p x) => P (MkThat' t p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (MkThat' t p :: Type) x = These (PP t x) (PP p x)

type MkThis (t :: Type) p = MkThis' (Hole t) p Source #

data MkThis' t p Source #

This constructor

>>> pl @(MkThis _ Id) 44
Present This 44
PresentT (This 44)
Instances
(Show (PP p x), P p x) => P (MkThis' t p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (MkThis' t p :: Type) x = These (PP p x) (PP t x)

type MkRight (t :: Type) p = MkRight' (Hole t) p Source #

data MkRight' t p Source #

Right constructor

>>> pl @(MkRight _ Id) 44
Present Right 44
PresentT (Right 44)
Instances
(Show (PP p x), P p x) => P (MkRight' t p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (MkRight' t p :: Type) x = Either (PP t x) (PP p x)

type MkLeft (t :: Type) p = MkLeft' (Hole t) p Source #

data MkLeft' t p Source #

Left constructor

>>> pl @(MkLeft _ Id) 44
Present Left 44
PresentT (Left 44)
Instances
(Show (PP p x), P p x) => P (MkLeft' t p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (MkLeft' t p :: Type) x = Either (PP p x) (PP t x)

data MkJust p Source #

Just constructor

>>> pl @(MkJust Id) 44
Present Just 44
PresentT (Just 44)
Instances
(PP p x ~ a, P p x, Show a) => P (MkJust p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (MkJust p :: Type) x = Maybe (PP p x)

type MkNothing (t :: Type) = MkNothing' (Hole t) Source #

data MkNothing' t Source #

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

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (MkNothing' t :: Type) a = Maybe (PP t a)

data EmptyT (t :: Type -> Type) p Source #

similar to empty

>>> pl @(EmptyT Maybe Id) ()
Present Nothing
PresentT Nothing
>>> pl @(EmptyT [] Id) ()
Present []
PresentT []
>>> pl @(EmptyT [] (Char1 "x")) (13,True)
Present ""
PresentT ""
>>> pl @(EmptyT (Either String) (Fst Id)) (13,True)
Present Left ""
PresentT (Left "")
Instances
(P p x, PP p x ~ a, Show (t a), Show a, Alternative t) => P (EmptyT t p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (EmptyT t p :: Type) x = t (PP p x)

data MEmptyProxy Source #

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

Defined in Predicate

Associated Types

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

Methods

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

type PP MEmptyProxy (Proxy a) Source # 
Instance details

Defined in Predicate

type PP MEmptyProxy (Proxy a) = a

type MEmptyT (t :: Type) = MEmptyT' (Hole t) Source #

data MEmptyT' t Source #

similar to mempty

>>> pl @(MEmptyT (SG.Sum Int)) ()
Present Sum {getSum = 0}
PresentT (Sum {getSum = 0})

no Monoid for Maybe a unless a is also a monoid but can use empty!

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

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (MEmptyT' t :: Type) a = PP t a

data Pure (t :: Type -> Type) p Source #

similar to pure

>>> pl @(Pure Maybe Id) 4
Present Just 4
PresentT (Just 4)
>>> pl @(Pure [] Id) 4
Present [4]
PresentT [4]
>>> pl @(Pure (Either String) (Fst Id)) (13,True)
Present Right 13
PresentT (Right 13)
Instances
(P p x, Show (PP p x), Show (t (PP p x)), Applicative t) => P (Pure t p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (Pure t p :: Type) x = t (PP p x)

data STimes n p Source #

similar to stimes

>>> pl @(STimes 4 Id) (SG.Sum 3)
Present Sum {getSum = 12}
PresentT (Sum {getSum = 12})
>>> pl @(STimes 4 Id) "ab"
Present "abababab"
PresentT "abababab"
Instances
(P n a, Integral (PP n a), Semigroup (PP p a), P p a, Show (PP p a)) => P (STimes n p :: Type) a Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

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

data MaybeIn p q Source #

similar to maybe

similar to MaybeX but provides a Proxy to the result of 'q' and does not provide the surrounding context

>>> pl @(MaybeIn "foundnothing" (ShowP (Pred Id))) (Just 20)
Present "19"
PresentT "19"
>>> pl @(MaybeIn "found nothing" (ShowP (Pred Id))) Nothing
Present "found nothing"
PresentT "found nothing"
Instances
(P q a, Show a, Show (PP q a), PP p (Proxy (PP q a)) ~ PP q a, P p (Proxy (PP q a))) => P (MaybeIn p q :: Type) (Maybe a) Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (MaybeIn p q :: Type) (Maybe a) = PP q a

type family TheseXT lr x p where ... Source #

Equations

TheseXT (These a b) x p = PP p (x, a) 

data TheseX p q r s Source #

similar to mergeTheseWith but additionally provides 'p', '\q' and 'r' the original input as the first element in the tuple

>>> pl @(TheseX (((Fst Id >> Fst Id) + Snd Id) >> ShowP Id) (ShowP Id) (Snd (Snd Id)) (Snd Id)) (9,This 123)
Present "132"
PresentT "132"
>>> pl @(TheseX '(Snd Id,"fromthis") '(Negate 99,Snd Id) (Snd Id) Id) (This 123)
Present (123,"fromthis")
PresentT (123,"fromthis")
>>> pl @(TheseX '(Snd Id,"fromthis") '(Negate 99,Snd Id) (Snd Id) Id) (That "fromthat")
Present (-99,"fromthat")
PresentT (-99,"fromthat")
>>> pl @(TheseX '(Snd Id,"fromthis") '(Negate 99,Snd Id) (Snd Id) Id) (These 123 "fromthese")
Present (123,"fromthese")
PresentT (123,"fromthese")
Instances
(P s x, P p (x, a), P q (x, b), P r (x, (a, b)), PP s x ~ These a b, PP p (x, a) ~ c, PP q (x, b) ~ c, PP r (x, (a, b)) ~ c) => P (TheseX p q r s :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (TheseX p q r s :: Type) x = TheseXT (PP s x) x p

type family EitherXT lr x p where ... Source #

Equations

EitherXT (Either a b) x p = PP p (x, a) 

data EitherX p q r Source #

similar to ||| but additionally gives 'p' and 'q' the original input

>>> pl @(EitherX (ShowP (Fst (Fst Id) + Snd Id)) (ShowP Id) (Snd Id)) (9,Left 123)
Present "132"
PresentT "132"
>>> pl @(EitherX (ShowP (Fst (Fst Id) + Snd Id)) (ShowP Id) (Snd Id)) (9,Right 'x')
Present "((9,Right 'x'),'x')"
PresentT "((9,Right 'x'),'x')"
>>> pl @(EitherX (ShowP Id) (ShowP (Second (Succ Id))) (Snd Id)) (9,Right 'x')
Present "((9,Right 'x'),'y')"
PresentT "((9,Right 'x'),'y')"
Instances
(P r x, P p (x, a), P q (x, b), PP r x ~ Either a b, PP p (x, a) ~ c, PP q (x, b) ~ c) => P (EitherX p q r :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (EitherX p q r :: Type) x = EitherXT (PP r x) x p

data TheseToMaybe Source #

Instances
P TheseToMaybe (These a b) Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

type PP TheseToMaybe (These a b) Source # 
Instance details

Defined in Predicate

type PP TheseToMaybe (These a b) = Maybe (a, b)

data ThatToMaybe Source #

Instances
P ThatToMaybe (These x a) Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

type PP ThatToMaybe (These x a) Source # 
Instance details

Defined in Predicate

type PP ThatToMaybe (These x a) = Maybe a

data ThisToMaybe Source #

Instances
P ThisToMaybe (These a x) Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

type PP ThisToMaybe (These a x) Source # 
Instance details

Defined in Predicate

type PP ThisToMaybe (These a x) = Maybe a

data RightToMaybe Source #

similar to either (const Nothing) Just

>>> pl @RightToMaybe (Right 13)
Present Just 13
PresentT (Just 13)
>>> pl @RightToMaybe (Left 13)
Present Nothing
PresentT Nothing
Instances
P RightToMaybe (Either x a) Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

type PP RightToMaybe (Either x a) Source # 
Instance details

Defined in Predicate

type PP RightToMaybe (Either x a) = Maybe a

data LeftToMaybe Source #

similar to either Just (const Nothing)

>>> pl @LeftToMaybe (Left 13)
Present Just 13
PresentT (Just 13)
>>> pl @LeftToMaybe (Right 13)
Present Nothing
PresentT Nothing
Instances
P LeftToMaybe (Either a x) Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

type PP LeftToMaybe (Either a x) Source # 
Instance details

Defined in Predicate

type PP LeftToMaybe (Either a x) = Maybe a

type family MaybeXPT lr x q where ... Source #

Equations

MaybeXPT (Maybe a) x q = PP q (x, a) 

type MaybeX p q r = MaybeXP (Fst Id >> p) q r Source #

data MaybeXP p q r Source #

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

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (MaybeXP p q r :: Type) x = MaybeXPT (PP r x) x q

type TheseFail msg q = GFail TheseToMaybe msg q Source #

type ThatFail msg q = GFail ThatToMaybe msg q Source #

type ThisFail msg q = GFail ThisToMaybe msg q Source #

type RightFail msg q = GFail RightToMaybe msg q Source #

type LeftFail msg q = GFail LeftToMaybe msg q Source #

type JustFail msg q = GFail I msg q Source #

type JustP q = GProxy I q Source #

type JustDef p q = GDef I p q Source #

type TheseIn' p = TheseFail "expected These" p Source #

type That' p = ThatFail "expected That" p Source #

type This' p = ThisFail "expected This" p Source #

type Right' p = RightFail "expected Right" p Source #

type Left' p = LeftFail "expected Left" p Source #

type Just' p = JustFail "expected Just" p Source #

type LookupFail msg x y = LookupFail' msg x y I Source #

type LookupP x y = LookupP' x y I Source #

type LookupDef x y p = LookupDef' x y p I Source #

type LookupFail' msg x y q = GFail (Lookup x y) msg q Source #

type LookupP' x y q = GProxy (Lookup x y) q Source #

type LookupDef' x y p q = GDef (Lookup x y) p q Source #

type GFail z msg q = '(I, q >> z) >> MaybeXP (Fail (PA >> Unproxy) (X >> msg)) A A Source #

type GProxy z q = '(I, q >> z) >> MaybeXP (PA >> MEmptyP) A A Source #

type GDef z p q = '(I, q >> z) >> MaybeXP (X >> p) A A Source #

type GDef_PA z p q r = (Hide % '(I, r >> z)) >> MaybeXP (PA >> p) ('(X, A) >> q) A Source #

type JustDef''' p q r = GDef_X I p q r Source #

type GDef_X z p q r = '(I, r >> z) >> MaybeXP (X >> p) ('(X, A) >> q) A Source #

type XPA = I Source #

type XA = I Source #

type X = Fst (Fst I) Source #

type A = Snd I Source #

type PA = Snd I Source #

type JustDef'' p q r = GDef'' I p q r Source #

type GDef'' z p q r = '(I, r >> z) >> MaybeXP p q (Snd Id) Source #

type JustDef' p q r = GDef' I p q r Source #

type GDef' z p q r = '(I, r >> z) >> MaybeXP (X >> p) q (Snd Id) Source #

type InitFail msg q = GFail (Unsnoc >> Fmap_1) msg q Source #

type InitDef p q = GDef (Unsnoc >> Fmap_1) p q Source #

type LastFail msg q = GFail (Unsnoc >> Fmap_2) msg q Source #

type LastDef p q = GDef (Unsnoc >> Fmap_2) p q Source #

type TailFail msg q = GFail (Uncons >> Fmap_2) msg q Source #

type TailDef p q = GDef (Uncons >> Fmap_2) p q Source #

type HeadFail msg q = GFail (Uncons >> Fmap_1) msg q Source #

type HeadDef p q = GDef (Uncons >> Fmap_1) p q Source #

data Fmap_2 Source #

similar to fmap snd

>>> pl @Fmap_2 (Just ("asf",13))
Present Just 13
PresentT (Just 13)
Instances
Functor f => P Fmap_2 (f (x, a)) Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

type PP Fmap_2 (f (x, a)) Source # 
Instance details

Defined in Predicate

type PP Fmap_2 (f (x, a)) = f a

data Fmap_1 Source #

similar to fmap fst

>>> pl @Fmap_1 (Just (13,"Asf"))
Present Just 13
PresentT (Just 13)

to make this work we grab the fst or snd out of the Maybe so it is a head or not/ is a tail or not etc! we still have access to the whole original list so we dont lose anything!

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

Defined in Predicate

Associated Types

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

Methods

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

type PP Fmap_1 (f (a, x)) Source # 
Instance details

Defined in Predicate

type PP Fmap_1 (f (a, x)) = f a

type Init' p = InitFail "Init(empty)" p Source #

type Last' p = LastFail "Last(empty)" p Source #

type Tail' p = TailFail "Tail(empty)" p Source #

type Head' p = HeadFail "Head(empty)" p Source #

data Elem p q Source #

elem function

>>> pl @(Elem (Fst Id) (Snd Id)) ('x',"abcdxy")
True
TrueT
>>> pl @(Elem (Fst Id) (Snd Id)) ('z',"abcdxy")
False
FalseT
Instances
([PP p a] ~ PP q a, P p a, P q a, Show (PP p a), Eq (PP p a)) => P (Elem p q :: Type) a Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

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

type Keep p q = KeepImpl True p q Source #

type Remove p q = KeepImpl False p q Source #

data KeepImpl (keep :: Bool) p q Source #

filters a list 'q' keeping or removing those elements in 'p'

>>> pl @(Keep '[5] '[1,5,5,2,5,2]) ()
Present [5,5,5]
PresentT [5,5,5]
>>> pl @(Keep '[0,1,1,5] '[1,5,5,2,5,2]) ()
Present [1,5,5,5]
PresentT [1,5,5,5]
>>> pl @(Remove '[5] '[1,5,5,2,5,2]) ()
Present [1,2,2]
PresentT [1,2,2]
>>> pl @(Remove '[0,1,1,5] '[1,5,5,2,5,2]) ()
Present [2,2]
PresentT [2,2]
>>> pl @(Remove '[99] '[1,5,5,2,5,2]) ()
Present [1,5,5,2,5,2]
PresentT [1,5,5,2,5,2]
>>> pl @(Remove '[99,91] '[1,5,5,2,5,2]) ()
Present [1,5,5,2,5,2]
PresentT [1,5,5,2,5,2]
>>> pl @(Remove Id '[1,5,5,2,5,2]) []
Present [1,5,5,2,5,2]
PresentT [1,5,5,2,5,2]
>>> pl @(Remove '[] '[1,5,5,2,5,2]) 44 -- works if you make this a number!
Present [1,5,5,2,5,2]
PresentT [1,5,5,2,5,2]
Instances
(GetBool keep, Eq a, Show a, P p x, P q x, PP p x ~ PP q x, PP q x ~ [a]) => P (KeepImpl keep p q :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (KeepImpl keep p q :: Type) x = PP q x

data Not p Source #

not function

>>> pl @(Not Id) False
True
TrueT
>>> pl @(Not Id) True
False
FalseT
>>> pl @(Not (Fst Id)) (True,22)
False
FalseT
Instances
(PP p x ~ Bool, P p x) => P (Not p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

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

data Prime p Source #

a predicate on prime numbers

>>> pl @(Prime Id) 2
True
TrueT
>>> pl @(Map '(Id,Prime Id) Id) [0..12]
Present [(0,False),(1,False),(2,True),(3,True),(4,False),(5,True),(6,False),(7,True),(8,False),(9,False),(10,False),(11,True),(12,False)]
PresentT [(0,False),(1,False),(2,True),(3,True),(4,False),(5,True),(6,False),(7,True),(8,False),(9,False),(10,False),(11,True),(12,False)]
Instances
(PP p x ~ a, P p x, Show a, Integral a) => P (Prime p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

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

type ToEnumBF (t :: Type) = ToEnumB' (Hole t) (Failp "ToEnum bounded failed") Source #

type ToEnumB (t :: Type) def = ToEnumB' (Hole t) def Source #

data ToEnumB' t def Source #

bounded toEnum function

>>> pl @(ToEnumB Ordering LT) 2
Present GT
PresentT GT
>>> pl @(ToEnumB Ordering LT) 6
Present LT
PresentT LT
>>> pl @(ToEnumBF Ordering) 6
Error ToEnum bounded failed
FailT "ToEnum bounded failed"
Instances
(P def (Proxy (PP t a)), PP def (Proxy (PP t a)) ~ PP t a, Show a, Show (PP t a), Bounded (PP t a), Enum (PP t a), Integral a) => P (ToEnumB' t def :: Type) a Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (ToEnumB' t def :: Type) a = PP t a

type ToEnum (t :: Type) p = ToEnum' (Hole t) p Source #

data ToEnum' t p Source #

unsafe toEnum function

>>> pl @(ToEnum Char Id) 120
Present 'x'
PresentT 'x'
Instances
(PP p x ~ a, P p x, Show a, Enum (PP t x), Show (PP t x), Integral a) => P (ToEnum' t p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (ToEnum' t p :: Type) x = PP t x

data FromEnum p Source #

fromEnum function

>>> pl @(FromEnum Id) 'x'
Present 120
PresentT 120
Instances
(Show a, Enum a, PP p x ~ a, P p x) => P (FromEnum p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

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

data Pred p Source #

unbounded pred function

>>> pl @(Pred Id) 13
Present 12
PresentT 12
>>> pl @(Pred Id) LT
Error Pred IO e=Prelude.Enum.Ordering.pred: bad argument
FailT "Pred IO e=Prelude.Enum.Ordering.pred: bad argument"
Instances
(Show a, Enum a, PP p x ~ a, P p x) => P (Pred p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

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

data Succ p Source #

unbounded succ function

>>> pl @(Succ Id) 13
Present 14
PresentT 14
>>> pl @(Succ Id) LT
Present EQ
PresentT EQ
>>> pl @(Succ Id) GT
Error Succ IO e=Prelude.Enum.Ordering.succ: bad argument
FailT "Succ IO e=Prelude.Enum.Ordering.succ: bad argument"
Instances
(Show a, Enum a, PP p x ~ a, P p x) => P (Succ p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

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

type PredB' q = PredB (Failp "Pred bounded failed") q Source #

data PredB p q Source #

bounded pred function

>>> pl @(PredB' Id) (13 :: Int)
Present 12
PresentT 12
>>> pl @(PredB' Id) LT
Error Pred bounded failed
FailT "Pred bounded failed"
Instances
(PP q x ~ a, P q x, P p (Proxy a), PP p (Proxy a) ~ a, Show a, Eq a, Bounded a, Enum a) => P (PredB p q :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (PredB p q :: Type) x = PP q x

type SuccB' q = SuccB (Failp "Succ bounded failed") q Source #

data SuccB p q Source #

bounded succ function

>>> pl @(SuccB' Id) (13 :: Int)
Present 14
PresentT 14
>>> pl @(SuccB' Id) LT
Present EQ
PresentT EQ
>>> pl @(SuccB 'LT Id) GT
Present LT
PresentT LT
>>> pl @(SuccB' Id) GT
Error Succ bounded failed
FailT "Succ bounded failed"
Instances
(PP q x ~ a, P q x, P p (Proxy a), PP p (Proxy a) ~ a, Show a, Eq a, Bounded a, Enum a) => P (SuccB p q :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (SuccB p q :: Type) x = PP q x

class SwappedC p where Source #

Methods

swappedC :: p a b -> p b a Source #

Instances
SwappedC Either Source # 
Instance details

Defined in Predicate

Methods

swappedC :: Either a b -> Either b a Source #

SwappedC (,) Source # 
Instance details

Defined in Predicate

Methods

swappedC :: (a, b) -> (b, a) Source #

SwappedC These Source # 
Instance details

Defined in Predicate

Methods

swappedC :: These a b -> These b a Source #

data Swap Source #

swaps using swapped

>>> pl @Swap (Left 123)
Present Right 123
PresentT (Right 123)
>>> pl @Swap (Right 123)
Present Left 123
PresentT (Left 123)
>>> pl @Swap (These 'x' 123)
Present These 123 'x'
PresentT (These 123 'x')
>>> pl @Swap (This 'x')
Present That 'x'
PresentT (That 'x')
>>> pl @Swap (That 123)
Present This 123
PresentT (This 123)
>>> pl @Swap (123,'x')
Present ('x',123)
PresentT ('x',123)
>>> pl @Swap (Left "abc")
Present Right "abc"
PresentT (Right "abc")
>>> pl @Swap (Right 123)
Present Left 123
PresentT (Left 123)
Instances
(Show (p a b), SwappedC p, Show (p b a)) => P Swap (p a b) Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

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

data ReverseL Source #

reverses using reversing

>>> import Data.Text (Text)
>>> pl @ReverseL ("AbcDeF" :: Text)
Present "FeDcbA"
PresentT "FeDcbA"
>>> pl @ReverseL ("AbcDeF" :: String)
Present "FeDcbA"
PresentT "FeDcbA"
Instances
(Show t, Reversing t) => P ReverseL t Source # 
Instance details

Defined in Predicate

Associated Types

type PP ReverseL t :: Type Source #

Methods

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

type PP ReverseL t Source # 
Instance details

Defined in Predicate

type PP ReverseL t = t

data Reverse Source #

similar to reverse

>>> pl @Reverse [1,2,4]
Present [4,2,1]
PresentT [4,2,1]
>>> pl @Reverse "AbcDeF"
Present "FeDcbA"
PresentT "FeDcbA"
Instances
(Show a, as ~ [a]) => P Reverse as Source # 
Instance details

Defined in Predicate

Associated Types

type PP Reverse as :: Type Source #

Methods

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

type PP Reverse as Source # 
Instance details

Defined in Predicate

type PP Reverse as = as

type Left t = Right t >> Swap Source #

type Right t = Pure (Either t) Id Source #

data Pure2 (t :: Type -> Type) Source #

lift pure over a Functor

>>> pl @(Pure2 (Either String)) [1,2,4]
Present [Right 1,Right 2,Right 4]
PresentT [Right 1,Right 2,Right 4]
Instances
(Show (f (t a)), Show (f a), Applicative t, Functor f) => P (Pure2 t :: Type) (f a) Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (Pure2 t :: Type) (f a) = f (t a)

data MEmptyT2' t Source #

lift mempty over a Functor

>>> pl @(MEmptyT2 (SG.Product Int)) [Identity (-13), Identity 4, Identity 99]
Present [Product {getProduct = 1},Product {getProduct = 1},Product {getProduct = 1}]
PresentT [Product {getProduct = 1},Product {getProduct = 1},Product {getProduct = 1}]
Instances
(Show (f a), Show (f (PP t (f a))), Functor f, Monoid (PP t (f a))) => P (MEmptyT2' t :: Type) (f a) Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (MEmptyT2' t :: Type) (f a) = f (PP t (f a))

data Coerce2 (t :: k) Source #

see Coerce: coerce over a functor

>>> pl @(Coerce2 (SG.Sum Integer)) [Identity (-13), Identity 4, Identity 99]
Present [Sum {getSum = -13},Sum {getSum = 4},Sum {getSum = 99}]
PresentT [Sum {getSum = -13},Sum {getSum = 4},Sum {getSum = 99}]
>>> pl @(Coerce2 (SG.Sum Integer)) (Just (Identity (-13)))
Present Just (Sum {getSum = -13})
PresentT (Just (Sum {getSum = -13}))
>>> pl @(Coerce2 (SG.Sum Int)) (Nothing @(Identity Int))
Present Nothing
PresentT Nothing
Instances
(Show (f a), Show (f t), Coercible t a, Functor f) => P (Coerce2 t :: Type) (f a) Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (Coerce2 t :: Type) (f a) = f t

data Coerce (t :: k) Source #

similar to coerce

>>> pl @(Coerce (SG.Sum Integer)) (Identity (-13))
Present Sum {getSum = -13}
PresentT (Sum {getSum = -13})
Instances
(Show a, Show t, Coercible t a) => P (Coerce t :: Type) a Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

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

type Wrap (t :: Type) p = Wrap' (Hole t) p Source #

data Wrap' t p Source #

wraps a value (see Wrapped and Wrapped)

>>> :m + Data.List.NonEmpty
>>> pl @(Wrap (SG.Sum _) Id) (-13)
Present Sum {getSum = -13}
PresentT (Sum {getSum = -13})
>>> pl @(Wrap SG.Any (Ge 4)) 13
Present Any {getAny = True}
PresentT (Any {getAny = True})
>>> pl @(Wrap (NonEmpty _) (Uncons >> 'Just Id)) "abcd"
Present 'a' :| "bcd"
PresentT ('a' :| "bcd")
Instances
(Show (PP p x), P p x, Unwrapped (PP s x) ~ PP p x, Wrapped (PP s x), Show (PP s x)) => P (Wrap' s p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

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

data Unwrap p Source #

unwraps a value (see Wrapped)

>>> pl @(Unwrap Id) (SG.Sum (-13))
Present -13
PresentT (-13)
Instances
(PP p x ~ s, P p x, Show s, Show (Unwrapped s), Wrapped s) => P (Unwrap p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (Unwrap p :: Type) x = Unwrapped (PP p x)

data Signum p Source #

similar to signum

>>> pl @(Signum Id) (-14)
Present -1
PresentT (-1)
>>> pl @(Signum Id) 14
Present 1
PresentT 1
>>> pl @(Signum Id) 0
Present 0
PresentT 0
Instances
(Show (PP p x), Num (PP p x), P p x) => P (Signum p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

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

data Abs p Source #

similar to abs

>>> pl @(Abs Id) (-14)
Present 14
PresentT 14
>>> pl @(Abs (Snd Id)) ("xx",14)
Present 14
PresentT 14
>>> pl @(Abs Id) 0
Present 0
PresentT 0
>>> pl @(Abs (Negate 44)) "aaa"
Present 44
PresentT 44
Instances
(Show (PP p x), Num (PP p x), P p x) => P (Abs p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

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

data Negate p Source #

similar to negate

>>> pl @(Negate Id) 14
Present -14
PresentT (-14)
>>> pl @(Negate (Fst Id * Snd Id)) (14,3)
Present -42
PresentT (-42)
>>> pl @(Negate (15 %- 4)) "abc"
Present 15 % 4
PresentT (15 % 4)
>>> pl @(Negate (15 % 3)) ()
Present (-5) % 1
PresentT ((-5) % 1)
>>> pl @(Negate (Fst Id % Snd Id)) (14,3)
Present (-14) % 3
PresentT ((-14) % 3)
Instances
(Show (PP p x), Num (PP p x), P p x) => P (Negate p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

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

type (-%) p q = Negate (p % q) infixl 8 Source #

type (%-) p q = Negate (p % q) infixl 8 Source #

data p % q infixl 8 Source #

creates a Rational value

>>> pl @(Id < 21 % 5) (-3.1)
True
TrueT
>>> pl @(Id < 21 % 5) 4.5
False
FalseT
>>> pl @(Fst Id % Snd Id) (13,2)
Present 13 % 2
PresentT (13 % 2)
>>> pl @(13 % Id) 0
Error MkRatio zero denominator
FailT "MkRatio zero denominator"
>>> pl @(4 % 3 + 5 % 7) "asfd"
Present 43 % 21
PresentT (43 % 21)
>>> pl @(4 %- 7 * 5 %- 3) "asfd"
Present 20 % 21
PresentT (20 % 21)
>>> pl @(Negate (14 % 3)) ()
Present (-14) % 3
PresentT ((-14) % 3)
>>> pl @(14 % 3) ()
Present 14 % 3
PresentT (14 % 3)
>>> pl @(Negate (14 % 3) === FromIntegral _ (Negate 5)) ()
Present GT
PresentT GT
>>> pl @(14 -% 3 === 5 %- 1) "aa"
Present GT
PresentT GT
>>> pl @(Negate (14 % 3) === Negate 5 % 2) ()
Present LT
PresentT LT
>>> pl @(14 -% 3 * 5 -% 1) ()
Present 70 % 3
PresentT (70 % 3)
>>> pl @(14 % 3 === 5 % 1) ()
Present LT
PresentT LT
>>> pl @(15 % 3 / 4 % 2) ()
Present 5 % 2
PresentT (5 % 2)
Instances
(Integral (PP p x), Integral (PP q x), Eq (PP q x), P p x, P q x, Show (PP p x), Show (PP q x)) => P (p % q :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (p % q :: Type) x = Rational

type (/) p q = DivF p q infixl 7 Source #

data DivF p q Source #

fractional division

>>> pl @(Fst Id / Snd Id) (13,2)
Present 6.5
PresentT 6.5
>>> pl @(ToRational 13 / Id) 0
Error DivF zero denominator
FailT "DivF zero denominator"
Instances
(PP p a ~ PP q a, Eq (PP q a), P p a, P q a, Show (PP p a), Fractional (PP p a)) => P (DivF p q :: Type) a Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

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

data Bin (op :: BinOp) p q Source #

addition, multiplication and subtraction

>>> pl @(Fst Id * Snd Id) (13,5)
Present 65
PresentT 65
>>> pl @(Fst Id + 4 * (Snd Id >> Len) - 4) (3,"hello")
Present 19
PresentT 19
Instances
(GetBinOp op, PP p a ~ PP q a, P p a, P q a, Show (PP p a), Num (PP p a)) => P (Bin op p q :: Type) a Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (Bin op p q :: Type) a = PP p a

class GetBinOp (k :: BinOp) where Source #

Methods

getBinOp :: (Num a, a ~ b) => (String, a -> b -> a) Source #

Instances
GetBinOp BMult Source # 
Instance details

Defined in Predicate

Methods

getBinOp :: (Num a, a ~ b) => (String, a -> b -> a) Source #

GetBinOp BSub Source # 
Instance details

Defined in Predicate

Methods

getBinOp :: (Num a, a ~ b) => (String, a -> b -> a) Source #

GetBinOp BAdd Source # 
Instance details

Defined in Predicate

Methods

getBinOp :: (Num a, a ~ b) => (String, a -> b -> a) Source #

type (<?) p q = CmpI Clt p q infix 4 Source #

type (<=?) p q = CmpI Cle p q infix 4 Source #

type (/=?) p q = CmpI Cne p q infix 4 Source #

type (==?) p q = CmpI Ceq p q infix 4 Source #

type (>=?) p q = CmpI Cge p q infix 4 Source #

type (>?) p q = CmpI Cgt p q infix 4 Source #

type (<) p q = Cmp Clt p q infix 4 Source #

type (<=) p q = Cmp Cle p q infix 4 Source #

type (/=) p q = Cmp Cne p q infix 4 Source #

type (==) p q = Cmp Ceq p q infix 4 Source #

type (>=) p q = Cmp Cge p q infix 4 Source #

type (>) p q = Cmp Cgt p q infix 4 Source #

type * p q = Mult p q infixl 7 Source #

type (-) p q = Sub p q infixl 6 Source #

type (+) p q = Add p q infixl 6 Source #

type Sub p q = Bin BSub p q Source #

type Add p q = Bin BAdd p q Source #

type Mult p q = Bin BMult p q Source #

data BinOp Source #

Constructors

BMult 
BSub 
BAdd 
Instances
Eq BinOp Source # 
Instance details

Defined in Predicate

Methods

(==) :: BinOp -> BinOp -> Bool #

(/=) :: BinOp -> BinOp -> Bool #

Show BinOp Source # 
Instance details

Defined in Predicate

Methods

showsPrec :: Int -> BinOp -> ShowS #

show :: BinOp -> String #

showList :: [BinOp] -> ShowS #

type Dup = '(Id, Id) Source #

data (p :: k) +++ (q :: k1) infixr 2 Source #

similar +++

>>> pl @(Pred Id +++ Id) (Left 13)
Present Left 12
PresentT (Left 12)
>>> pl @(ShowP Id +++ Reverse) (Right "hello")
Present Right "olleh"
PresentT (Right "olleh")
Instances
(Show (PP p a), Show (PP q b), P p a, P q b, Show a, Show b) => P (p +++ q :: Type) (Either a b) Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

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

type EitherIn p q = p ||| q Source #

data (p :: k) ||| (q :: k1) infixr 2 Source #

similar |||

>>> pl @(Pred Id ||| Id) (Left 13)
Present 12
PresentT 12
>>> pl @(ShowP Id ||| Id) (Right "hello")
Present "hello"
PresentT "hello"
Instances
(Show (PP p a), P p a, P q b, PP p a ~ PP q b, Show a, Show b) => P (p ||| q :: Type) (Either a b) Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

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

type Second q = Star I q Source #

type First p = Star p I Source #

type Star p q = p *** q Source #

data (p :: k) *** (q :: k1) infixr 3 Source #

similar to ***

>>> pl @(Pred Id *** ShowP Id) (13, True)
Present (12,"True")
PresentT (12,"True")
Instances
(Show (PP p a), Show (PP q b), P p a, P q b, Show a, Show b) => P (p *** q :: Type) (a, b) Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

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

type (&&&) p q = W '(p, q) infixr 3 Source #

similar to &&&

type Drop n p = Snd (SplitAt n p) Source #

type Take n p = Fst (SplitAt n p) Source #

data SplitAt n p Source #

similar to splitAt

>>> pl @(SplitAt 4 Id) "hello world"
Present ("hell","o world")
PresentT ("hell","o world")
>>> pl @(SplitAt 20 Id) "hello world"
Present ("hello world","")
PresentT ("hello world","")
>>> pl @(SplitAt 0 Id) "hello world"
Present ("","hello world")
PresentT ("","hello world")
>>> pl @(SplitAt (Snd Id) (Fst Id)) ("hello world",4)
Present ("hell","o world")
PresentT ("hell","o world")
Instances
(PP p a ~ [b], P n a, P p a, Show b, Integral (PP n a)) => P (SplitAt n p :: Type) a Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (SplitAt n p :: Type) a = (PP p a, PP p a)

data SplitAts ns p Source #

split a list 'p' into parts using the lengths in the type level list 'ns'

>>> pl @(SplitAts '[2,3,1,1] Id) "hello world"
Present ["he","llo"," ","w","orld"]
PresentT ["he","llo"," ","w","orld"]
>>> pl @(SplitAts '[2] Id) "hello world"
Present ["he","llo world"]
PresentT ["he","llo world"]
>>> pl @(SplitAts '[10,1,1,5] Id) "hello world"
Present ["hello worl","d","",""]
PresentT ["hello worl","d","",""]
Instances
(P ns x, P p x, PP p x ~ [a], Show n, Show a, PP ns x ~ [n], Integral n) => P (SplitAts ns p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (SplitAts ns p :: Type) x = [PP p x]

type PadR n p q = Pad False n p q Source #

type PadL n p q = Pad True n p q Source #

data Pad (left :: Bool) n p q Source #

pad 'q' with '\n' values from '\p'\

>>> pl @(PadL 5 999 Id) [12,13]
Present [999,999,999,12,13]
PresentT [999,999,999,12,13]
>>> pl @(PadR 5 (Fst Id) '[12,13]) (999,'x')
Present [12,13,999,999,999]
PresentT [12,13,999,999,999]
>>> pl @(PadR 2 (Fst Id) '[12,13,14]) (999,'x')
Present [12,13,14]
PresentT [12,13,14]
Instances
(P n a, GetBool left, Integral (PP n a), [PP p a] ~ PP q a, P p a, P q a, Show (PP p a)) => P (Pad left n p q :: Type) a Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

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

type Msg' prt p = Msg (Printf "[%s] " prt) p Source #

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

create inductive tuples from a type level list of predicates

>>> pl @(TupleI '[Id,ShowP Id,Pred Id,W "str", W 999]) 666
Present (666,("666",(665,("str",(999,())))))
PresentT (666,("666",(665,("str",(999,())))))
>>> pl @(TupleI '[W 999,W "somestring",W 'True, Id, ShowP (Pred Id)]) 23
Present (999,("somestring",(True,(23,("22",())))))
PresentT (999,("somestring",(True,(23,("22",())))))
Instances
P (TupleI ([] :: [k]) :: Type) a Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (TupleI (p ': ps) :: Type) a = (PP p a, PP (TupleI ps) a)
type PP (TupleI ([] :: [k]) :: Type) a Source # 
Instance details

Defined in Predicate

type PP (TupleI ([] :: [k]) :: Type) a = ()

data EitherB b p q Source #

Convenient method to convert a 'p' or '\q' to a Either based on a predicate '\b\' if 'b' then Right 'p' else Left '\q\'

>>> pl @(EitherB (Fst Id > 4) (Snd Id >> Fst Id) (Snd Id >> Snd Id)) (24,(-1,999))
Present Right 999
PresentT (Right 999)
>>> pl @(EitherB (Fst Id > 4) (Snd Id >> Fst Id) (Snd Id >> Snd Id)) (1,(-1,999))
Present Left (-1)
PresentT (Left (-1))
Instances
(Show (PP p a), P p a, Show (PP q a), P q a, P b a, PP b a ~ Bool) => P (EitherB b p q :: Type) a Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (EitherB b p q :: Type) a = Either (PP p a) (PP q a)

data MaybeB b p Source #

Convenient method to convert a value 'p' to a Maybe based on a predicate '\b\' if '\b\' then Just 'p' else Nothing

>>> pl @(MaybeB (Id > 4) Id) 24
Present Just 24
PresentT (Just 24)
>>> pl @(MaybeB (Id > 4) Id) (-5)
Present Nothing
PresentT Nothing
Instances
(Show (PP p a), P b a, P p a, PP b a ~ Bool) => P (MaybeB b p :: Type) a Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (MaybeB b p :: Type) a = Maybe (PP p a)

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

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

>>> pl @(Do [Pred Id, ShowP Id, Id &&& Len]) 9876543
Present ("9876542",7)
PresentT ("9876542",7)
>>> pl @(Do '[W 123, W "xyz", Len &&& Id, Pred Id *** Id<>Id]) ()
Present (2,"xyzxyz")
PresentT (2,"xyzxyz")
Instances
P (DoExpandT ps) a => P (Do ps :: Type) a Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

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

type family DoExpandT (ps :: [k]) :: Type where ... Source #

Equations

DoExpandT '[] = TypeError (Text "'[] invalid: requires at least one predicate in the list") 
DoExpandT '[p] = Id >> p 
DoExpandT (p ': (p1 ': ps)) = p >> DoExpandT (p1 ': ps) 

data MkProxy Source #

converts a value to a Proxy: the same as '\'Proxy'

>>> pl @MkProxy 'x'
Present Proxy
PresentT Proxy
Instances
Show a => P MkProxy a Source # 
Instance details

Defined in Predicate

Associated Types

type PP MkProxy a :: Type Source #

Methods

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

type PP MkProxy a Source # 
Instance details

Defined in Predicate

type PP MkProxy a = Proxy a

type Floor (t :: Type) p = Floor' (Hole t) p Source #

data Floor' t p Source #

floor function where you need to provide the type 't' of the result

>>> pl @(Floor Int Id) (23 % 5)
Present 4
PresentT 4
Instances
(Show (PP p x), P p x, Show (PP t x), RealFrac (PP p x), Integral (PP t x)) => P (Floor' t p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (Floor' t p :: Type) x = PP t x

type Ceiling (t :: Type) p = Ceiling' (Hole t) p Source #

data Ceiling' t p Source #

ceiling function where you need to provide the type 't' of the result

>>> pl @(Ceiling Int Id) (23 % 5)
Present 5
PresentT 5
Instances
(Show (PP p x), P p x, Show (PP t x), RealFrac (PP p x), Integral (PP t x)) => P (Ceiling' t p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (Ceiling' t p :: Type) x = PP t x

type Truncate (t :: Type) p = Truncate' (Hole t) p Source #

data Truncate' t p Source #

truncate function where you need to provide the type 't' of the result

>>> pl @(Truncate Int Id) (23 % 5)
Present 4
PresentT 4
Instances
(Show (PP p x), P p x, Show (PP t x), RealFrac (PP p x), Integral (PP t x)) => P (Truncate' t p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (Truncate' t p :: Type) x = PP t x

type FromRational (t :: Type) p = FromRational' (Hole t) p Source #

data FromRational' t r Source #

fromRational function where you need to provide the type 't' of the result

>>> pl @(FromRational Rational Id) 23.5
Present 47 % 2
PresentT (47 % 2)
Instances
(P r a, PP r a ~ Rational, Show (PP t a), Fractional (PP t a)) => P (FromRational' t r :: Type) a Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (FromRational' t r :: Type) a = PP t a

data ToRational p Source #

toRational function

>>> pl @(ToRational Id) 23.5
Present 47 % 2
PresentT (47 % 2)
Instances
(a ~ PP p x, Show a, Real a, P p x) => P (ToRational p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (ToRational p :: Type) x = Rational

type FromIntegral (t :: Type) p = FromIntegral' (Hole t) p Source #

data FromIntegral' t n Source #

fromIntegral function where you need to provide the type 't' of the result

>>> pl @(FromIntegral (SG.Sum _) Id) 23
Present Sum {getSum = 23}
PresentT (Sum {getSum = 23})
Instances
(Num (PP t a), Integral (PP n a), P n a, Show (PP t a), Show (PP n a)) => P (FromIntegral' t n :: Type) a Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (FromIntegral' t n :: Type) a = PP t a

type FromInteger (t :: Type) p = FromInteger' (Hole t) p Source #

data FromInteger' t n Source #

fromInteger function where you need to provide the type 't' of the result

>>> pl @(FromInteger (SG.Sum _) Id) 23
Present Sum {getSum = 23}
PresentT (Sum {getSum = 23})
Instances
(Num (PP t a), Integral (PP n a), P n a, Show (PP t a)) => P (FromInteger' t n :: Type) a Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (FromInteger' t n :: Type) a = PP t a

type FromStringP (t :: Type) p = FromStringP' (Hole t) p Source #

data FromStringP' t s Source #

fromString function where you need to provide the type 't' of the result

>>> :set -XOverloadedStrings
>>> pl @(FromStringP (Identity _) Id) "abc"
Present Identity "abc"
PresentT (Identity "abc")
>>> pl @(FromStringP (Seq.Seq _) Id) "abc"
Present fromList "abc"
PresentT (fromList "abc")
Instances
(P s a, PP s a ~ String, Show (PP t a), IsString (PP t a)) => P (FromStringP' t s :: Type) a Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (FromStringP' t s :: Type) a = PP t a

class ExtractL6C tp where Source #

Associated Types

type ExtractL6T tp Source #

Methods

extractL6C :: tp -> ExtractL6T tp Source #

Instances
ExtractL6C (a, b) Source # 
Instance details

Defined in Predicate

Associated Types

type ExtractL6T (a, b) :: Type Source #

Methods

extractL6C :: (a, b) -> ExtractL6T (a, b) Source #

ExtractL6C (a, b, c) Source # 
Instance details

Defined in Predicate

Associated Types

type ExtractL6T (a, b, c) :: Type Source #

Methods

extractL6C :: (a, b, c) -> ExtractL6T (a, b, c) Source #

ExtractL6C (a, b, c, d) Source # 
Instance details

Defined in Predicate

Associated Types

type ExtractL6T (a, b, c, d) :: Type Source #

Methods

extractL6C :: (a, b, c, d) -> ExtractL6T (a, b, c, d) Source #

ExtractL6C (a, b, c, d, e) Source # 
Instance details

Defined in Predicate

Associated Types

type ExtractL6T (a, b, c, d, e) :: Type Source #

Methods

extractL6C :: (a, b, c, d, e) -> ExtractL6T (a, b, c, d, e) Source #

ExtractL6C (a, b, c, d, e, f) Source # 
Instance details

Defined in Predicate

Associated Types

type ExtractL6T (a, b, c, d, e, f) :: Type Source #

Methods

extractL6C :: (a, b, c, d, e, f) -> ExtractL6T (a, b, c, d, e, f) Source #

data L6 p Source #

similar to 6th element in a n-tuple

>>> pl @(L6 Id) (10,"Abc",'x',True,1,99)
Present 99
PresentT 99
Instances
(Show (ExtractL6T (PP p x)), ExtractL6C (PP p x), P p x, Show (PP p x)) => P (L6 p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

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

class ExtractL5C tp where Source #

Associated Types

type ExtractL5T tp Source #

Methods

extractL5C :: tp -> ExtractL5T tp Source #

Instances
ExtractL5C (a, b) Source # 
Instance details

Defined in Predicate

Associated Types

type ExtractL5T (a, b) :: Type Source #

Methods

extractL5C :: (a, b) -> ExtractL5T (a, b) Source #

ExtractL5C (a, b, c) Source # 
Instance details

Defined in Predicate

Associated Types

type ExtractL5T (a, b, c) :: Type Source #

Methods

extractL5C :: (a, b, c) -> ExtractL5T (a, b, c) Source #

ExtractL5C (a, b, c, d) Source # 
Instance details

Defined in Predicate

Associated Types

type ExtractL5T (a, b, c, d) :: Type Source #

Methods

extractL5C :: (a, b, c, d) -> ExtractL5T (a, b, c, d) Source #

ExtractL5C (a, b, c, d, e) Source # 
Instance details

Defined in Predicate

Associated Types

type ExtractL5T (a, b, c, d, e) :: Type Source #

Methods

extractL5C :: (a, b, c, d, e) -> ExtractL5T (a, b, c, d, e) Source #

ExtractL5C (a, b, c, d, e, f) Source # 
Instance details

Defined in Predicate

Associated Types

type ExtractL5T (a, b, c, d, e, f) :: Type Source #

Methods

extractL5C :: (a, b, c, d, e, f) -> ExtractL5T (a, b, c, d, e, f) Source #

data L5 p Source #

similar to 5th element in a n-tuple

>>> pl @(L5 Id) (10,"Abc",'x',True,1)
Present 1
PresentT 1
Instances
(Show (ExtractL5T (PP p x)), ExtractL5C (PP p x), P p x, Show (PP p x)) => P (L5 p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

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

class ExtractL4C tp where Source #

Associated Types

type ExtractL4T tp Source #

Methods

extractL4C :: tp -> ExtractL4T tp Source #

Instances
ExtractL4C (a, b) Source # 
Instance details

Defined in Predicate

Associated Types

type ExtractL4T (a, b) :: Type Source #

Methods

extractL4C :: (a, b) -> ExtractL4T (a, b) Source #

ExtractL4C (a, b, c) Source # 
Instance details

Defined in Predicate

Associated Types

type ExtractL4T (a, b, c) :: Type Source #

Methods

extractL4C :: (a, b, c) -> ExtractL4T (a, b, c) Source #

ExtractL4C (a, b, c, d) Source # 
Instance details

Defined in Predicate

Associated Types

type ExtractL4T (a, b, c, d) :: Type Source #

Methods

extractL4C :: (a, b, c, d) -> ExtractL4T (a, b, c, d) Source #

ExtractL4C (a, b, c, d, e) Source # 
Instance details

Defined in Predicate

Associated Types

type ExtractL4T (a, b, c, d, e) :: Type Source #

Methods

extractL4C :: (a, b, c, d, e) -> ExtractL4T (a, b, c, d, e) Source #

ExtractL4C (a, b, c, d, e, f) Source # 
Instance details

Defined in Predicate

Associated Types

type ExtractL4T (a, b, c, d, e, f) :: Type Source #

Methods

extractL4C :: (a, b, c, d, e, f) -> ExtractL4T (a, b, c, d, e, f) Source #

data L4 p Source #

similar to 4th element in a n-tuple

>>> pl @(L4 Id) (10,"Abc",'x',True)
Present True
PresentT True
>>> pl @(L4 (Fst (Snd Id))) ('x',((10,"Abc",'x',999),"aa",1),9)
Present 999
PresentT 999
Instances
(Show (ExtractL4T (PP p x)), ExtractL4C (PP p x), P p x, Show (PP p x)) => P (L4 p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

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

class ExtractL3C tp where Source #

Associated Types

type ExtractL3T tp Source #

Methods

extractL3C :: tp -> ExtractL3T tp Source #

Instances
ExtractL3C (a, b) Source # 
Instance details

Defined in Predicate

Associated Types

type ExtractL3T (a, b) :: Type Source #

Methods

extractL3C :: (a, b) -> ExtractL3T (a, b) Source #

ExtractL3C (a, b, c) Source # 
Instance details

Defined in Predicate

Associated Types

type ExtractL3T (a, b, c) :: Type Source #

Methods

extractL3C :: (a, b, c) -> ExtractL3T (a, b, c) Source #

ExtractL3C (a, b, c, d) Source # 
Instance details

Defined in Predicate

Associated Types

type ExtractL3T (a, b, c, d) :: Type Source #

Methods

extractL3C :: (a, b, c, d) -> ExtractL3T (a, b, c, d) Source #

ExtractL3C (a, b, c, d, e) Source # 
Instance details

Defined in Predicate

Associated Types

type ExtractL3T (a, b, c, d, e) :: Type Source #

Methods

extractL3C :: (a, b, c, d, e) -> ExtractL3T (a, b, c, d, e) Source #

ExtractL3C (a, b, c, d, e, f) Source # 
Instance details

Defined in Predicate

Associated Types

type ExtractL3T (a, b, c, d, e, f) :: Type Source #

Methods

extractL3C :: (a, b, c, d, e, f) -> ExtractL3T (a, b, c, d, e, f) Source #

type Thd p = L3 p Source #

data L3 p Source #

similar to 3rd element in a n-tuple

>>> pl @(Thd Id) (10,"Abc",133)
Present 133
PresentT 133
>>> pl @(Thd Id) (10,"Abc",133,True)
Present 133
PresentT 133
Instances
(Show (ExtractL3T (PP p x)), ExtractL3C (PP p x), P p x, Show (PP p x)) => P (L3 p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

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

class ExtractL2C tp where Source #

Associated Types

type ExtractL2T tp Source #

Methods

extractL2C :: tp -> ExtractL2T tp Source #

Instances
ExtractL2C (a, b) Source # 
Instance details

Defined in Predicate

Associated Types

type ExtractL2T (a, b) :: Type Source #

Methods

extractL2C :: (a, b) -> ExtractL2T (a, b) Source #

ExtractL2C (a, b, c) Source # 
Instance details

Defined in Predicate

Associated Types

type ExtractL2T (a, b, c) :: Type Source #

Methods

extractL2C :: (a, b, c) -> ExtractL2T (a, b, c) Source #

ExtractL2C (a, b, c, d) Source # 
Instance details

Defined in Predicate

Associated Types

type ExtractL2T (a, b, c, d) :: Type Source #

Methods

extractL2C :: (a, b, c, d) -> ExtractL2T (a, b, c, d) Source #

ExtractL2C (a, b, c, d, e) Source # 
Instance details

Defined in Predicate

Associated Types

type ExtractL2T (a, b, c, d, e) :: Type Source #

Methods

extractL2C :: (a, b, c, d, e) -> ExtractL2T (a, b, c, d, e) Source #

ExtractL2C (a, b, c, d, e, f) Source # 
Instance details

Defined in Predicate

Associated Types

type ExtractL2T (a, b, c, d, e, f) :: Type Source #

Methods

extractL2C :: (a, b, c, d, e, f) -> ExtractL2T (a, b, c, d, e, f) Source #

type Snd p = L2 p Source #

data L2 p Source #

similar to snd

>>> pl @(Snd Id) (10,"Abc")
Present "Abc"
PresentT "Abc"
>>> pl @(Snd Id) (10,"Abc",True)
Present "Abc"
PresentT "Abc"
Instances
(Show (ExtractL2T (PP p x)), ExtractL2C (PP p x), P p x, Show (PP p x)) => P (L2 p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

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

class ExtractL1C tp where Source #

Associated Types

type ExtractL1T tp Source #

Methods

extractL1C :: tp -> ExtractL1T tp Source #

Instances
ExtractL1C (a, b) Source # 
Instance details

Defined in Predicate

Associated Types

type ExtractL1T (a, b) :: Type Source #

Methods

extractL1C :: (a, b) -> ExtractL1T (a, b) Source #

ExtractL1C (a, b, c) Source # 
Instance details

Defined in Predicate

Associated Types

type ExtractL1T (a, b, c) :: Type Source #

Methods

extractL1C :: (a, b, c) -> ExtractL1T (a, b, c) Source #

ExtractL1C (a, b, c, d) Source # 
Instance details

Defined in Predicate

Associated Types

type ExtractL1T (a, b, c, d) :: Type Source #

Methods

extractL1C :: (a, b, c, d) -> ExtractL1T (a, b, c, d) Source #

ExtractL1C (a, b, c, d, e) Source # 
Instance details

Defined in Predicate

Associated Types

type ExtractL1T (a, b, c, d, e) :: Type Source #

Methods

extractL1C :: (a, b, c, d, e) -> ExtractL1T (a, b, c, d, e) Source #

ExtractL1C (a, b, c, d, e, f) Source # 
Instance details

Defined in Predicate

Associated Types

type ExtractL1T (a, b, c, d, e, f) :: Type Source #

Methods

extractL1C :: (a, b, c, d, e, f) -> ExtractL1T (a, b, c, d, e, f) Source #

type Fst p = L1 p Source #

data L1 p Source #

similar to fst

>>> pl @(Fst Id) (10,"Abc")
Present 10
PresentT 10
>>> pl @(Fst Id) (10,"Abc",'x')
Present 10
PresentT 10
>>> pl @(Fst Id) (10,"Abc",'x',False)
Present 10
PresentT 10
Instances
(Show (ExtractL1T (PP p x)), ExtractL1C (PP p x), P p x, Show (PP p x)) => P (L1 p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

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

data Length p Source #

similar to length for Foldable instances

>>> pl @(Length Id) (Left "aa")
Present 0
PresentT 0
>>> pl @(Length Id) (Right "aa")
Present 1
PresentT 1
>>> pl @(Length (Right' Id)) (Right "abcd")
Present 4
PresentT 4
>>> pl @(Length (Thd (Snd Id))) (True,(23,'x',[10,9,1,3,4,2]))
Present 6
PresentT 6
Instances
(PP p x ~ t a, P p x, Show (t a), Foldable t) => P (Length p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

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

data Len Source #

similar to length

>>> pl @Len [10,4,5,12,3,4]
Present 6
PresentT 6
>>> pl @Len []
Present 0
PresentT 0
Instances
(Show a, as ~ [a]) => P Len as Source # 
Instance details

Defined in Predicate

Associated Types

type PP Len as :: Type Source #

Methods

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

type PP Len as Source # 
Instance details

Defined in Predicate

type PP Len as = Int

type SortOnDesc p q = SortBy (Swap >> OrdA p) q Source #

type SortOn p q = SortBy (OrdA p) q Source #

data SortBy p q Source #

sort a list

>>> pl @(SortOn (Fst Id) Id) [(10,"abc"), (3,"def"), (4,"gg"), (10,"xyz"), (1,"z")]
Present [(1,"z"),(3,"def"),(4,"gg"),(10,"abc"),(10,"xyz")]
PresentT [(1,"z"),(3,"def"),(4,"gg"),(10,"abc"),(10,"xyz")]
Instances
(P p (a, a), P q x, Show a, PP q x ~ [a], PP p (a, a) ~ Ordering) => P (SortBy p q :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (SortBy p q :: Type) x = PP q x

type Max' t = FoldMap (Max t) Id Source #

data Max Source #

similar to maximum

>>> pl @Max [10,4,5,12,3,4]
Present 12
PresentT 12
>>> pl @Max []
Error empty list
FailT "empty list"
Instances
(Ord a, Show a) => P Max [a] Source # 
Instance details

Defined in Predicate

Associated Types

type PP Max [a] :: Type Source #

Methods

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

type PP Max [a] Source # 
Instance details

Defined in Predicate

type PP Max [a] = a

data Min Source #

similar to minimum

>>> pl @Min [10,4,5,12,3,4]
Present 3
PresentT 3
>>> pl @Min []
Error empty list
FailT "empty list"
Instances
(Ord a, Show a) => P Min [a] Source # 
Instance details

Defined in Predicate

Associated Types

type PP Min [a] :: Type Source #

Methods

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

type PP Min [a] Source # 
Instance details

Defined in Predicate

type PP Min [a] = a

type ReadP' (t :: Type) p = ReadP'' (Hole t) p Source #

type ReadP (t :: Type) = ReadP'' (Hole t) Id Source #

data ReadP'' t p Source #

uses the Read of the given type 't' and 'p' which points to the content to read

>>> pl @(ReadP Rational) "4 % 5"
Present 4 % 5
PresentT (4 % 5)
>>> pl @(ReadP' Day Id >> Between (ReadP' Day "2017-04-11") (ReadP' Day "2018-12-30")) "2018-10-12"
True
TrueT
>>> pl @(ReadP' Day Id >> Between (ReadP' Day "2017-04-11") (ReadP' Day "2018-12-30")) "2016-10-12"
False
FalseT
Instances
(P p x, PP p x ~ String, Typeable (PP t x), Show (PP t x), Read (PP t x)) => P (ReadP'' t p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (ReadP'' t p :: Type) x = PP t x

data UnMkDay p Source #

uncreate a Day returning year month and day

>>> pl @(UnMkDay Id) (read "2019-12-30")
Present (2019,12,30)
PresentT (2019,12,30)
Instances
(PP p x ~ Day, P p x) => P (UnMkDay p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (UnMkDay p :: Type) x = (Int, Int, Int)

type MkDay = MkDay' (Fst Id) (Snd Id) (Thd Id) Source #

data MkDay' p q r Source #

create a Day from three int values passed in as year month and day

>>> pl @MkDay (2019,12,30)
Present Just (2019-12-30,1,1)
PresentT (Just (2019-12-30,1,1))
>>> pl @(MkDay' (Fst Id) (Snd Id) (Thd Id)) (2019,99,99999)
Present Nothing
PresentT Nothing
>>> pl @MkDay (1999,3,13)
Present Just (1999-03-13,10,6)
PresentT (Just (1999-03-13,10,6))
Instances
(P p x, P q x, P r x, PP p x ~ Int, PP q x ~ Int, PP r x ~ Int) => P (MkDay' p q r :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (MkDay' p q r :: Type) x = Maybe (Day, Int, Int)

type ParseTimes (t :: Type) p q = ParseTimes' (Hole t) p q Source #

data ParseTimes' t p q Source #

A convenience method to match against many different datetime formats to find a match

>>> pl @(ParseTimes LocalTime '["%Y-%m-%d %H:%M:%S", "%m/%d/%y %H:%M:%S", "%B %d %Y %H:%M:%S", "%Y-%m-%dT%H:%M:%S"] "03/11/19 01:22:33") ()
Present 2019-03-11 01:22:33
PresentT 2019-03-11 01:22:33
>>> pl @(ParseTimes LocalTime (Fst Id) (Snd Id)) (["%Y-%m-%d %H:%M:%S", "%m/%d/%y %H:%M:%S", "%B %d %Y %H:%M:%S", "%Y-%m-%dT%H:%M:%S"], "03/11/19 01:22:33")
Present 2019-03-11 01:22:33
PresentT 2019-03-11 01:22:33
Instances
(ParseTime (PP t a), Typeable (PP t a), Show (PP t a), P p a, P q a, PP p a ~ [String], PP q a ~ String) => P (ParseTimes' t p q :: Type) a Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

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

type ParseTimeP (t :: Type) p q = ParseTimeP' (Hole t) p q Source #

data ParseTimeP' t p q Source #

similar to parseTimeM where 't' is the ParseTime type, 'p' is the datetime format and 'q' points to the content to parse

>>> pl @(ParseTimeP LocalTime "%F %T" Id) "2019-05-24 05:19:59"
Present 2019-05-24 05:19:59
PresentT 2019-05-24 05:19:59
>>> pl @(ParseTimeP LocalTime "%F %T" "2019-05-24 05:19:59") (Right "we ignore this using Symbol and not Id")
Present 2019-05-24 05:19:59
PresentT 2019-05-24 05:19:59

keeping 'q' as we might want to extract from a tuple

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

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

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

data FormatTimeP p q Source #

type level expression representing a formatted time similar to formatTime using a type level Symbol to get the formatting string

>>> pl @(FormatTimeP "%F %T" Id) (read "2019-05-24 05:19:59" :: LocalTime)
Present "2019-05-24 05:19:59"
PresentT "2019-05-24 05:19:59"
>>> pl @(FormatTimeP (Fst Id) (Snd Id)) ("the date is %d/%m/%Y", read "2019-05-24" :: Day)
Present "the date is 24/05/2019"
PresentT "the date is 24/05/2019"
Instances
(PP p x ~ String, FormatTime (PP q x), P p x, Show (PP q x), P q x) => P (FormatTimeP p q :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (FormatTimeP p q :: Type) x = String

data ShowP p Source #

similar to show

>>> pl @(ShowP Id) [4,8,3,9]
Present "[4,8,3,9]"
PresentT "[4,8,3,9]"
>>> pl @(ShowP Id) 'x'
Present "'x'"
PresentT "'x'"
>>> pl @(ShowP (42 %- 10)) 'x'
Present "(-21) % 5"
PresentT "(-21) % 5"
Instances
(Show (PP p x), P p x) => P (ShowP p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (ShowP p :: Type) x = String

data Ones p Source #

split a list into single values

>>> pl @(Ones Id) [4,8,3,9]
Present [[4],[8],[3],[9]]
PresentT [[4],[8],[3],[9]]
>>> pl @(Ones Id) []
Present []
PresentT []
Instances
(PP p x ~ [a], P p x, Show a) => P (Ones p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (Ones p :: Type) x = [PP p x]

data Tails Source #

similar to tails

>>> pl @Tails [4,8,3,9]
Present [[4,8,3,9],[8,3,9],[3,9],[9],[]]
PresentT [[4,8,3,9],[8,3,9],[3,9],[9],[]]
>>> pl @Tails []
Present [[]]
PresentT [[]]
Instances
Show a => P Tails [a] Source # 
Instance details

Defined in Predicate

Associated Types

type PP Tails [a] :: Type Source #

Methods

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

type PP Tails [a] Source # 
Instance details

Defined in Predicate

type PP Tails [a] = [[a]]

data Inits Source #

similar to inits

>>> pl @Inits [4,8,3,9]
Present [[],[4],[4,8],[4,8,3],[4,8,3,9]]
PresentT [[],[4],[4,8],[4,8,3],[4,8,3,9]]
>>> pl @Inits []
Present [[]]
PresentT [[]]
Instances
Show a => P Inits [a] Source # 
Instance details

Defined in Predicate

Associated Types

type PP Inits [a] :: Type Source #

Methods

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

type PP Inits [a] Source # 
Instance details

Defined in Predicate

type PP Inits [a] = [[a]]

data ToUpper Source #

converts a string IsText value to upper case

>>> pl @ToUpper "HeLlO wOrld!"
Present "HELLO WORLD!"
PresentT "HELLO WORLD!"
Instances
(Show a, IsText a) => P ToUpper a Source # 
Instance details

Defined in Predicate

Associated Types

type PP ToUpper a :: Type Source #

Methods

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

type PP ToUpper a Source # 
Instance details

Defined in Predicate

type PP ToUpper a = a

data ToLower Source #

converts a string IsText value to lower case

>>> pl @ToLower "HeLlO wOrld!"
Present "hello world!"
PresentT "hello world!"
Instances
(Show a, IsText a) => P ToLower a Source # 
Instance details

Defined in Predicate

Associated Types

type PP ToLower a :: Type Source #

Methods

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

type PP ToLower a Source # 
Instance details

Defined in Predicate

type PP ToLower a = a

type IsNumber = IsCharSet CNumber Source #

predicate for determining if the string is all digits >>> pl @IsNumber "213G" False FalseT

>>> pl @IsNumber "929"
True
TrueT

type IsLower = IsCharSet CLower Source #

predicate for determining if a string is all lowercase >>> pl @IsLower "abcdef213" False FalseT

>>> pl @IsLower "abcdef"
True
TrueT
>>> pl @IsLower ""
True
TrueT
>>> pl @IsLower "abcdefG"
False
FalseT

class GetCharSet (cs :: CharSet) where Source #

Instances
GetCharSet CLower Source # 
Instance details

Defined in Predicate

GetCharSet CUpper Source # 
Instance details

Defined in Predicate

GetCharSet CNumber Source # 
Instance details

Defined in Predicate

GetCharSet CPunctuation Source # 
Instance details

Defined in Predicate

GetCharSet CControl Source # 
Instance details

Defined in Predicate

GetCharSet CHexDigit Source # 
Instance details

Defined in Predicate

GetCharSet COctDigit Source # 
Instance details

Defined in Predicate

GetCharSet CSeparator Source # 
Instance details

Defined in Predicate

GetCharSet CLatin1 Source # 
Instance details

Defined in Predicate

data IsCharSet (cs :: CharSet) Source #

a predicate for determining if a string IsText belongs to the given character set

>>> import qualified Data.Text as T
>>> pl @IsLower "abc"
True
TrueT
>>> pl @IsLower "abcX"
False
FalseT
>>> pl @IsLower (T.pack "abcX")
False
FalseT
>>> pl @IsHexDigit "01efA"
True
TrueT
>>> pl @IsHexDigit "01egfA"
False
FalseT
Instances
(GetCharSet cs, Show a, IsText a) => P (IsCharSet cs :: Type) a Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (IsCharSet cs :: Type) a = Bool

data MakeRR3 p Source #

A replacement function ([String] -> String) which yields the groups Used by sub and sub Requires Text.Show.Functions

>>> :m + Text.Show.Functions
>>> pl @(ReplaceAll "^(\\d+)\\.(\\d+)\\.(\\d+)\\.(\\d+)$" (MakeRR3 (Fst Id)) (Snd Id)) (\ys -> intercalate  " | " $ map (show . succ . read @Int) ys, "141.201.1.22")
Present "142 | 202 | 2 | 23"
PresentT "142 | 202 | 2 | 23"
Instances
(PP p x ~ ([String] -> String), P p x) => P (MakeRR3 p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (MakeRR3 p :: Type) x = RR

data MakeRR2 p Source #

A replacement function (String -> String) that yields the whole match Used by sub and sub Requires Text.Show.Functions

>>> :m + Text.Show.Functions
>>> pl @(ReplaceAll "\\." (MakeRR2 (Fst Id)) (Snd Id)) (\x -> x <> ":" <> x, "141.201.1.22")
Present "141.:.201.:.1.:.22"
PresentT "141.:.201.:.1.:.22"
Instances
(PP p x ~ (String -> String), P p x) => P (MakeRR2 p :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (MakeRR2 p :: Type) x = RR

data MakeRR1 p Source #

A replacement function (String -> [String] -> String) which returns the whole match and the groups Used by sub and sub Requires Text.Show.Functions

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

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (MakeRR1 p :: Type) x = RR

data MakeRR p Source #

Simple replacement string: see ReplaceAllString and ReplaceOneString

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

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (MakeRR p :: Type) x = RR

type ReplaceOneString' (rs :: [ROpt]) p q r = ReplaceOne' rs p (MakeRR q) r Source #

type ReplaceAllString' (rs :: [ROpt]) p q r = ReplaceAll' rs p (MakeRR q) r Source #

type ReplaceOne p q r = ReplaceOne' '[] p q r Source #

type ReplaceOne' (rs :: [ROpt]) p q r = ReplaceImpl False rs p q r Source #

type ReplaceAll p q r = ReplaceAll' '[] p q r Source #

type ReplaceAll' (rs :: [ROpt]) p q r = ReplaceImpl True rs p q r Source #

data ReplaceImpl (alle :: Bool) (rs :: [ROpt]) p q r Source #

replaces regex 's' with a string 's1' inside the value

>>> pl @(ReplaceAllString "\\." ":" Id) "141.201.1.22"
Present "141:201:1:22"
PresentT "141:201:1:22"
Instances
(GetBool b, GetROpts rs, PP p x ~ String, PP q x ~ RR, PP r x ~ String, P p x, P q x, P r x) => P (ReplaceImpl b rs p q r :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (ReplaceImpl b rs p q r :: Type) x = String

type Resplit p q = Resplit' '[] p q Source #

data Resplit' (rs :: [ROpt]) p q Source #

splits a string on a regex delimiter

>>> pl @(Resplit "\\." Id) "141.201.1.22"
Present ["141","201","1","22"]
PresentT ["141","201","1","22"]
>>> pl @(Resplit (Singleton (Fst Id)) (Snd Id)) (':', "12:13:1")
Present ["12","13","1"]
PresentT ["12","13","1"]
Instances
(GetROpts rs, PP p x ~ String, PP q x ~ String, P p x, P q x) => P (Resplit' rs p q :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (Resplit' rs p q :: Type) x = [String]

type RescanRanges p q = RescanRanges' '[] p q Source #

data RescanRanges' (rs :: [ROpt]) p q Source #

similar to Rescan but gives the column start and ending positions instead of values

>>> pl @(RescanRanges "^(\\d{2}):(\\d{2}):(\\d{2})$" Id) "13:05:25"
Present [((0,8),[(0,2),(3,5),(6,8)])]
PresentT [((0,8),[(0,2),(3,5),(6,8)])]
Instances
(GetROpts rs, PP p x ~ String, PP q x ~ String, P p x, P q x) => P (RescanRanges' rs p q :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (RescanRanges' rs p q :: Type) x = [((Int, Int), [(Int, Int)])]

type Rescan p q = Rescan' '[] p q Source #

data Rescan' (rs :: [ROpt]) p q Source #

runs a regex matcher returning the original values and optionally any groups

>>> pl @(Rescan "^(\\d{2}):(\\d{2}):(\\d{2})$" Id) "13:05:25"
Present [("13:05:25",["13","05","25"])]
PresentT [("13:05:25",["13","05","25"])]
>>> pl @(Rescan (Snd Id) "13:05:25") ('a',"^(\\d{2}):(\\d{2}):(\\d{2})$")
Present [("13:05:25",["13","05","25"])]
PresentT [("13:05:25",["13","05","25"])]
Instances
(GetROpts rs, PP p x ~ String, PP q x ~ String, P p x, P q x) => P (Rescan' rs p q :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (Rescan' rs p q :: Type) x = [(String, [String])]

type Re p q = Re' '[] p q Source #

data Re' (rs :: [ROpt]) p q Source #

represents a predicate using a Symbol as a regular expression evaluates Re and returns True if there is a match

>>> pl @(Re "^\\d{2}:\\d{2}:\\d{2}$" Id) "13:05:25"
True
TrueT
Instances
(GetROpts rs, PP p x ~ String, PP q x ~ String, P p x, P q x) => P (Re' rs p q :: Type) x Source # 
Instance details

Defined in Predicate

Associated Types

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

Methods

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

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

Defined in Predicate

type PP (Re' rs p q :: Type) x = Bool

type Unzip = '(Map (Fst Id) Id, Map (Snd Id) Id) Source #

unzip equivalent

>>> pl @Unzip (zip [1..5] "abcd")
Present ([1,2,3,4],"abcd")
PresentT ([1,2,3,4],"abcd")

type Any x p = Ors (Map x p) Source #

similar to any

>>> pl @(Any Even Id) [1,5,11,5,3]
False
FalseT
>>> pl @(Any Even Id) [1,5,112,5,3]
True
TrueT
>>> pl @(Any Even Id) []
False
FalseT

type All x p = Ands (Map x p) Source #

similar to all

>>> pl @(All Even Id) [1,5,11,5,3]
False
FalseT
>>> pl @(All Odd Id) [1,5,11,5,3]
True
TrueT
>>> pl @(All Odd Id) []
True
TrueT

type Negative = Lt 0 Source #

type Positive = Gt 0 Source #

type AllNegative = Ands (Map Negative Id) Source #

a type level predicate for all negative elements in a list

type AllPositive = Ands (Map Positive Id) Source #

a type level predicate for all positive elements in a list

>>> pl @AllPositive [1,5,10,2,3]
True
TrueT
>>> pl @AllPositive [0,1,5,10,2,3]
False
FalseT
>>> pl @AllPositive [3,1,-5,10,2,3]
False
FalseT
>>> pl @AllNegative [-1,-5,-10,-2,-3]
True
TrueT

type Between' p q r = (r >= p) && (r <= q) Source #

This is the same as Between but where 'r' is Id

type Between p q = Ge p && Le q Source #

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

>>> pl @(Between' 5 8 Len) [1,2,3,4,5,5,7]
True
TrueT
>>> pl @(Between 5 8) 6
True
TrueT
>>> pl @(Between 5 8) 9
False
FalseT

type Desc' = Ands (Map (Fst Id > Snd Id) Pairs) Source #

a type level predicate for a strictly decreasing list

type Desc = Ands (Map (Fst Id >= Snd Id) Pairs) Source #

a type level predicate for a monotonic decreasing list

type Asc' = Ands (Map (Fst Id < Snd Id) Pairs) Source #

a type level predicate for a strictly increasing list

type Asc = Ands (Map (Fst Id <= Snd Id) Pairs) Source #

a type level predicate for a monotonic increasing list

>>> pl @Asc "aaacdef"
True
TrueT
>>> pl @Asc [1,2,3,4,5,5,7]
True
TrueT
>>> pl @Asc' [1,2,3,4,5,5,7]
False
FalseT
>>> pl @Asc "axacdef"
False
FalseT

strictmsg :: forall strict. GetBool strict => String Source #

simpleAlign :: [a] -> [b] -> [These a b] Source #

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