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

Safe HaskellNone
LanguageHaskell2010

Predicate.Data.Extra

Description

extra promoted functions

Synopsis

Documentation

data Pure2 (t :: Type -> Type) Source #

lift pure over a Functor

>>> pz @(Pure2 (Either String)) [1,2,4]
PresentT [Right 1,Right 2,Right 4]
>>> pl @(Pure2 []) (Just 10)
Present Just [10] (Pure2 Just [10] | Just 10)
PresentT (Just [10])
>>> pl @(Pure2 SG.Sum) (Just 20)
Present Just (Sum {getSum = 20}) (Pure2 Just (Sum {getSum = 20}) | Just 20)
PresentT (Just (Sum {getSum = 20}))
Instances
(Show (f (t a)), Show (f a), Applicative t, Functor f) => P (Pure2 t :: Type) (f a) Source # 
Instance details

Defined in Predicate.Data.Extra

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.Data.Extra

type PP (Pure2 t :: Type) (f a) = f (t a)

data p <$ q infixl 4 Source #

similar to <$

>>> pz @(Fst Id <$ Snd Id) ("abc",Just 20)
PresentT (Just "abc")
>>> pl @(Fst Id <$ Snd Id) (4,These "xxx" 'a')
Present These "xxx" 4 ((<$) 4)
PresentT (These "xxx" 4)
>>> pl @(Fst Id <$ Snd Id) (4,This 'a')
Present This 'a' ((<$) 4)
PresentT (This 'a')
>>> pl @(Fst Id <$ Snd Id) (4,Just 'a')
Present Just 4 ((<$) 4)
PresentT (Just 4)
>>> pl @(Fst Id <$ Snd Id) (4,Nothing @Int)
Present Nothing ((<$) 4)
PresentT Nothing
>>> pl @('True <$ Id) [1..4]
Present [True,True,True,True] ((<$) True)
PresentT [True,True,True,True]
>>> import Data.Functor.Compose
>>> pl @(Char1 "ab" <$ Id) (Compose $ Just [1..4])
Present Compose (Just "aaaa") ((<$) 'a')
PresentT (Compose (Just "aaaa"))
>>> pl @(Snd Id <$ Fst Id) (Just 10,'x')
Present Just 'x' ((<$) 'x')
PresentT (Just 'x')
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.Data.Extra

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.Data.Extra

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

data p <* q infixl 4 Source #

similar to Applicative <*

>>> pl @(Fst Id <* Snd Id) (Just 4,Just 'a')
Present Just 4 ((<*) Just 4 | p=Just 4 | q=Just 'a')
PresentT (Just 4)
>>> pz @(Fst Id <* Snd Id) (Just "abc",Just 20)
PresentT (Just "abc")
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.Data.Extra

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.Data.Extra

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

data p *> q infixl 4 Source #

similar to Applicative *>

>>> pl @(Fst Id *> Snd Id) (Just 4,Just 'a')
Present Just 'a' ((<*) Just 'a' | p=Just 'a' | q=Just 4)
PresentT (Just 'a')
Instances
P (ArrowRT p q) x => P (p *> q :: Type) x Source # 
Instance details

Defined in Predicate.Data.Extra

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.Data.Extra

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

data FMapFst Source #

similar to fmap fst

>>> pz @FMapFst (Just (13,"Asf"))
PresentT (Just 13)
>>> pl @FMapFst (Just (1,'x'))
Present Just 1 (FMapFst)
PresentT (Just 1)
>>> pl @FMapFst [(1,'x'), (2,'y'), (3,'z')]
Present [1,2,3] (FMapFst)
PresentT [1,2,3]
Instances
Functor f => P FMapFst (f (a, x)) Source # 
Instance details

Defined in Predicate.Data.Extra

Associated Types

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

Methods

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

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

Defined in Predicate.Data.Extra

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

data FMapSnd Source #

similar to fmap snd

>>> pz @FMapSnd (Just ("asf",13))
PresentT (Just 13)
>>> pl @FMapSnd (Just (1,'x'))
Present Just 'x' (FMapSnd)
PresentT (Just 'x')
>>> pl @FMapSnd (Nothing @(Char,Int))
Present Nothing (FMapSnd)
PresentT Nothing
>>> pl @FMapSnd (Right (1,'x'))
Present Right 'x' (FMapSnd)
PresentT (Right 'x')
>>> pl @FMapSnd (Left @_ @(Int,Double) "x")
Present Left "x" (FMapSnd)
PresentT (Left "x")
Instances
Functor f => P FMapSnd (f (x, a)) Source # 
Instance details

Defined in Predicate.Data.Extra

Associated Types

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

Methods

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

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

Defined in Predicate.Data.Extra

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

data Sequence Source #

similar to sequenceA

>>> pz @Sequence [Just 10, Just 20, Just 30]
PresentT (Just [10,20,30])
>>> pz @Sequence [Just 10, Just 20, Just 30, Nothing, Just 40]
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.Data.Extra

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.Data.Extra

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

data Traverse p q Source #

like traverse

>>> pl @(Traverse (If (Gt 3) (Pure Maybe Id) (EmptyT Maybe Id)) Id) [1..5]
Present Nothing ((>>) Nothing | {Sequence Nothing | [Nothing,Nothing,Nothing,Just 4,Just 5]})
PresentT Nothing
>>> pl @(Traverse (MaybeBool (Le 3) Id) Id) [1..5]
Present Nothing ((>>) Nothing | {Sequence Nothing | [Just 1,Just 2,Just 3,Nothing,Nothing]})
PresentT Nothing
>>> pl @(Traverse (If (Gt 0) (Pure Maybe Id) (EmptyT Maybe Id)) Id) [1..5]
Present Just [1,2,3,4,5] ((>>) Just [1,2,3,4,5] | {Sequence Just [1,2,3,4,5] | [Just 1,Just 2,Just 3,Just 4,Just 5]})
PresentT (Just [1,2,3,4,5])
>>> pl @(Traverse (If (Gt 0) (Pure Maybe Id) (MkNothing _)) Id) [1..5]
Present Just [1,2,3,4,5] ((>>) Just [1,2,3,4,5] | {Sequence Just [1,2,3,4,5] | [Just 1,Just 2,Just 3,Just 4,Just 5]})
PresentT (Just [1,2,3,4,5])
>>> pl @(Traverse (MaybeBool (Id >= 0) Id) Id) [1..5]
Present Just [1,2,3,4,5] ((>>) Just [1,2,3,4,5] | {Sequence Just [1,2,3,4,5] | [Just 1,Just 2,Just 3,Just 4,Just 5]})
PresentT (Just [1,2,3,4,5])
>>> pl @(Traverse (MaybeBool (Id <= 3) Id) Id) [1..5]
Present Nothing ((>>) Nothing | {Sequence Nothing | [Just 1,Just 2,Just 3,Nothing,Nothing]})
PresentT Nothing
Instances
P (TraverseT p q) x => P (Traverse p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.Extra

Associated Types

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

Methods

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

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

Defined in Predicate.Data.Extra

type PP (Traverse p q :: Type) x

data Join Source #

similar to join

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

Defined in Predicate.Data.Extra

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.Data.Extra

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

data p <|> q infixl 3 Source #

similar to <|>

>>> pz @(Fst Id <|> Snd Id) (Nothing,Just 20)
PresentT (Just 20)
>>> pz @(Fst Id <|> Snd Id) (Just 10,Just 20)
PresentT (Just 10)
>>> pz @(Fst Id <|> Snd Id) (Nothing,Nothing)
PresentT Nothing
>>> pl @(Fst Id <|> Snd Id) (Just "cdef",Just "ab")
Present Just "cdef" ((<|>) Just "cdef" | p=Just "cdef" | q=Just "ab")
PresentT (Just "cdef")
>>> pl @(Fst Id <|> Snd Id) ("cdef","ab"::String)
Present "cdefab" ((<|>) "cdefab" | p="cdef" | q="ab")
PresentT "cdefab"
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.Data.Extra

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.Data.Extra

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

data Extract Source #

similar to extract

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

Defined in Predicate.Data.Extra

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.Data.Extra

type PP Extract (t a) = a

data Duplicate Source #

similar to duplicate

>>> pz @Duplicate (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.Data.Extra

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.Data.Extra

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

data p $$ q infixl 0 Source #

function application for expressions: similar to $

>>> :m + Text.Show.Functions
>>> pz @(Fst Id $$ Snd Id) ((*16),4)
PresentT 64
>>> pz @(Id $$ "def") ("abc"<>)
PresentT "abcdef"
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.Data.Extra

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.Data.Extra

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

data q $& p infixr 1 Source #

flipped function application for expressions: similar to &

>>> :m + Text.Show.Functions
>>> pz @(Snd Id $& Fst Id) ((*16),4)
PresentT 64
>>> pz @("def" $& Id) ("abc"<>)
PresentT "abcdef"
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 (q $& p :: Type) x Source # 
Instance details

Defined in Predicate.Data.Extra

Associated Types

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

Methods

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

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

Defined in Predicate.Data.Extra

type PP (q $& p :: Type) x

data Skip p Source #

just run the effect ignoring the result passing the original value through for example for use with Stdout so it doesnt interfere with the 'a' on the rhs unless there is an failure

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

Defined in Predicate.Data.Extra

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.Data.Extra

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

data p |> q infixr 1 Source #

run 'p' for the effect and then run 'q' using that original value

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

Defined in Predicate.Data.Extra

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.Data.Extra

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

data p >| q infixr 1 Source #

run run 'p' and then 'q' for the effect but using the result from 'p'

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

Defined in Predicate.Data.Extra

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.Data.Extra

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

data p >|> q infixr 1 Source #

run both 'p' and 'q' for their effects but ignoring the results

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

Defined in Predicate.Data.Extra

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.Data.Extra

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

data HeadDef p q Source #

takes the head of a list-like object or uses the given default value

see ConsT for other supported types eg Seq

>>> pz @(HeadDef 444 Id) []
PresentT 444
>>> pz @(HeadDef 444 Id) [1..5]
PresentT 1
>>> pz @(HeadDef 444 Id) [1..5]
PresentT 1
>>> pz @(HeadDef (Char1 "w") Id) (Seq.fromList "abcdef")
PresentT 'a'
>>> pz @(HeadDef (Char1 "w") Id) Seq.empty
PresentT 'w'
>>> pz @(HeadDef (MEmptyT _) Id) ([] :: [SG.Sum Int])
PresentT (Sum {getSum = 0})
>>> pz @(HeadDef (MEmptyT String) '["abc","def","asdfadf"]) ()
PresentT "abc"
>>> pz @(HeadDef (MEmptyT _) (Snd Id)) (123,["abc","def","asdfadf"])
PresentT "abc"
>>> pz @(HeadDef (MEmptyT _) (Snd Id)) (123,[])
PresentT ()
>>> pl @(HeadDef 9 (Fst Id)) ([],True)
Present 9 (JustDef Nothing)
PresentT 9
>>> pl @(HeadDef 9 (Fst Id)) ([1..5],True)
Present 1 (JustDef Just)
PresentT 1
>>> pl @(HeadDef 3 (Fst Id)) ([10..15],True)
Present 10 (JustDef Just)
PresentT 10
>>> pl @(HeadDef 12 (Fst Id) >> Le 6) ([],True)
False ((>>) False | {12 <= 6})
FalseT
>>> pl @(HeadDef 1 (Fst Id) >> Le 6) ([],True)
True ((>>) True | {1 <= 6})
TrueT
>>> pl @(HeadDef 10 (Fst Id) >> Le 6) ([],True)
False ((>>) False | {10 <= 6})
FalseT
>>> pl @(HeadDef (MEmptyT _) Id) (map (:[]) ([] :: [Int]))
Present [] (JustDef Nothing)
PresentT []
>>> pl @(HeadDef (MEmptyT _) Id) (map (:[]) ([10..14] :: [Int]))
Present [10] (JustDef Just)
PresentT [10]
>>> pl @(HeadDef (Fst Id) (Snd Id)) (99,[10..14])
Present 10 (JustDef Just)
PresentT 10
>>> pl @(HeadDef (Fst Id) (Snd Id)) (99,[] :: [Int])
Present 99 (JustDef Nothing)
PresentT 99
>>> pl @(HeadDef 43 (Snd Id)) (99,[] :: [Int])
Present 43 (JustDef Nothing)
PresentT 43
Instances
P (HeadDefT p q) x => P (HeadDef p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.Extra

Associated Types

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

Methods

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

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

Defined in Predicate.Data.Extra

type PP (HeadDef p q :: Type) x

data HeadFail msg q Source #

takes the head of a list or fails with the given message

see ConsT for other supported types eg Seq

>>> pz @(HeadFail "dude" Id) ["abc","def","asdfadf"]
PresentT "abc"
>>> pz @(HeadFail "empty list" Id) []
FailT "empty list"
>>> pl @(HeadFail "zz" (Fst Id) >> Le 6) ([],True)
Error zz ((>>) lhs failed)
FailT "zz"
>>> pl @((HeadFail "failed1" (Fst Id) >> Le 6) || 'False) ([],True)
Error failed1 (||)
FailT "failed1"
>>> pl @((Fst Id >> HeadFail "failed2" Id >> Le (6 -% 1)) || 'False) ([-9],True)
True (True || False)
TrueT
>>> pl @(HeadFail "Asdf" Id) ([] :: [()]) -- breaks otherwise
Error Asdf (JustFail Nothing)
FailT "Asdf"
>>> pl @(HeadFail (PrintF "msg=%s def" (Fst Id)) (Snd Id)) ("Abc" :: String,[]::[Int])
Error msg=Abc def (JustFail Nothing)
FailT "msg=Abc def"
Instances
P (HeadFailT msg q) x => P (HeadFail msg q :: Type) x Source # 
Instance details

Defined in Predicate.Data.Extra

Associated Types

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

Methods

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

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

Defined in Predicate.Data.Extra

type PP (HeadFail msg q :: Type) x

data TailDef p q Source #

takes the tail of a list-like object or uses the given default value

>>> pl @(TailDef '[9,7] (Fst Id)) ([],True)
Present [9,7] (JustDef Nothing)
PresentT [9,7]
>>> pl @(TailDef '[9,7] (Fst Id)) ([1..5],True)
Present [2,3,4,5] (JustDef Just)
PresentT [2,3,4,5]
>>> pl @(TailDef '[3] (Fst Id)) ([10..15],True)
Present [11,12,13,14,15] (JustDef Just)
PresentT [11,12,13,14,15]
Instances
P (TailDefT p q) x => P (TailDef p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.Extra

Associated Types

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

Methods

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

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

Defined in Predicate.Data.Extra

type PP (TailDef p q :: Type) x

data TailFail msg q Source #

takes the tail of a list-like object or fails with the given message

>>> pl @(TailFail (PrintT "a=%d b=%s" (Snd Id)) (Fst Id)) ([]::[()],(4::Int,"someval" :: String))
Error a=4 b=someval (JustFail Nothing)
FailT "a=4 b=someval"
Instances
P (TailFailT msg q) x => P (TailFail msg q :: Type) x Source # 
Instance details

Defined in Predicate.Data.Extra

Associated Types

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

Methods

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

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

Defined in Predicate.Data.Extra

type PP (TailFail msg q :: Type) x

data LastDef p q Source #

takes the last value of a list-like object or a default value

>>> pl @(LastDef 9 (Fst Id)) ([],True)
Present 9 (JustDef Nothing)
PresentT 9
>>> pl @(LastDef 9 (Fst Id)) ([1..5],True)
Present 5 (JustDef Just)
PresentT 5
>>> pl @(LastDef 3 (Fst Id)) ([10..15],True)
Present 15 (JustDef Just)
PresentT 15
>>> pl @(LastDef 0 Id) [1..12]
Present 12 (JustDef Just)
PresentT 12
>>> pl @(LastDef 0 Id) []
Present 0 (JustDef Nothing)
PresentT 0
Instances
P (LastDefT p q) x => P (LastDef p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.Extra

Associated Types

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

Methods

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

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

Defined in Predicate.Data.Extra

type PP (LastDef p q :: Type) x

data LastFail msg q Source #

takes the init of a list-like object or fails with the given message

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

Defined in Predicate.Data.Extra

Associated Types

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

Methods

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

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

Defined in Predicate.Data.Extra

type PP (LastFail msg q :: Type) x

data InitDef p q Source #

takes the init of a list-like object or uses the given default value

>>> pl @(InitDef '[9,7] (Fst Id)) ([],True)
Present [9,7] (JustDef Nothing)
PresentT [9,7]
>>> pl @(InitDef '[9,7] (Fst Id)) ([1..5],True)
Present [1,2,3,4] (JustDef Just)
PresentT [1,2,3,4]
>>> pl @(InitDef '[3] (Fst Id)) ([10..15],True)
Present [10,11,12,13,14] (JustDef Just)
PresentT [10,11,12,13,14]
Instances
P (InitDefT p q) x => P (InitDef p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.Extra

Associated Types

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

Methods

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

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

Defined in Predicate.Data.Extra

type PP (InitDef p q :: Type) x

data InitFail msg q Source #

takes the init of a list-like object or fails with the given message

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

Defined in Predicate.Data.Extra

Associated Types

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

Methods

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

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

Defined in Predicate.Data.Extra

type PP (InitFail msg q :: Type) x

data Coerce2 (t :: k) Source #

coerce over a functor

>>> pz @(Coerce2 (SG.Sum Integer)) [Identity (-13), Identity 4, Identity 99]
PresentT [Sum {getSum = -13},Sum {getSum = 4},Sum {getSum = 99}]
>>> pz @(Coerce2 (SG.Sum Integer)) (Just (Identity (-13)))
PresentT (Just (Sum {getSum = -13}))
>>> pz @(Coerce2 (SG.Sum Int)) (Nothing @(Identity Int))
PresentT Nothing
>>> pl @(Coerce2 (SG.Sum Int)) (Just (10 :: Int))
Present Just (Sum {getSum = 10}) (Coerce2 Just (Sum {getSum = 10}) | Just 10)
PresentT (Just (Sum {getSum = 10}))
Instances
(Show (f a), Show (f t), Coercible t a, Functor f) => P (Coerce2 t :: Type) (f a) Source # 
Instance details

Defined in Predicate.Data.Extra

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.Data.Extra

type PP (Coerce2 t :: Type) (f a) = f t

data ProxyT (t :: Type) Source #

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

Defined in Predicate.Data.Extra

Associated Types

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

Methods

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

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

Defined in Predicate.Data.Extra

type PP (ProxyT t :: Type) x

data ProxyT' t Source #

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

Defined in Predicate.Data.Extra

Associated Types

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

Methods

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

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

Defined in Predicate.Data.Extra

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

data Prime p Source #

a predicate on prime numbers

>>> pz @(Prime Id) 2
TrueT
>>> pz @(Map '(Id,Prime Id) Id) [0..12]
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.Data.Extra

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.Data.Extra

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

data PrimeNext p Source #

get the next prime number

>>> pz @(PrimeNext Id) 6
PresentT 7
>>> pz @(ScanN 4 (PrimeNext Id) Id) 3
PresentT [3,5,7,11,13]
Instances
(PP p x ~ a, P p x, Show a, Integral a) => P (PrimeNext p :: Type) x Source # 
Instance details

Defined in Predicate.Data.Extra

Associated Types

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

Methods

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

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

Defined in Predicate.Data.Extra

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

data Luhn p Source #

Luhn predicate check on last digit

>>> pz @(Luhn Id) [1,2,3,0]
TrueT
>>> pz @(Luhn Id) [1,2,3,4]
FalseT
>>> pz @(GuardSimple (Luhn Id)) [15,4,3,1,99]
FailT "(Luhn map=[90,2,3,8,6] sum=109 ret=9 | [15,4,3,1,99])"
>>> pl @(Luhn Id) [15,4,3,1,99]
False (Luhn map=[90,2,3,8,6] sum=109 ret=9 | [15,4,3,1,99])
FalseT
Instances
(PP p x ~ [Int], P p x) => P (Luhn p :: Type) x Source # 
Instance details

Defined in Predicate.Data.Extra

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.Data.Extra

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

data Catch p q Source #

run an expression 'p' and on failure run 'q'

>>> pz @(Catch (Succ Id) (Fst Id >> Second (ShowP Id) >> PrintT "%s %s" Id >> 'LT)) GT
PresentT LT
>>> pz @(Len > 1 && Catch (Id !! 3 == 66) 'False) [1,2]
FalseT
>>> pl @(Catch (Resplit "\\d+(" Id) (Snd Id >> MEmptyP)) "123"
Present [] (Catch caught exception[Regex failed to compile])
PresentT []
>>> pl @(Catch (OneP Id) 99) [10,11]
Present 99 (Catch caught exception[OneP 2 elements])
PresentT 99
>>> pl @(Catch (OneP Id) 99) [10]
Present 10 (Catch did not fire)
PresentT 10
>>> pl @(Catch (OneP Id) 'True) [False]  -- cant know that this is FalseT cos is driven by type of the list not the 'True part
Present False (Catch did not fire)
PresentT False
>>> pl @(Catch (OneP Id) 'False) [True,True,False]
False (Catch caught exception[OneP 3 elements])
FalseT
>>> pl @(Catch (OneP Id) 'True) []
True (Catch caught exception[OneP empty])
TrueT
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.Data.Extra

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.Data.Extra

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

data Catch' p s Source #

run an expression 'p' and on failure print a custom error 's' using the error string and the input value

>>> pz @(Catch' (Succ Id) (Second (ShowP Id) >> PrintT "%s %s" Id)) GT
FailT "Succ IO e=Prelude.Enum.Ordering.succ: bad argument GT"
>>> pz @(Catch' (Succ Id) (Second (ShowP Id) >> PrintT "%s %s" Id)) LT
PresentT EQ
>>> pl @(Catch' (Failt Int "someval") (PrintT "msg=%s caught(%03d)" Id)) (44 :: Int)
Error msg=someval caught(044) (Catch default condition failed)
FailT "msg=someval caught(044)"
>>> pl @(Catch' (OneP Id) (Second (ShowP Id) >> PrintT "msg=%s caught(%s)" Id)) [10,12,13]
Error msg=OneP 3 elements caught([10,12,13]) (Catch default condition failed)
FailT "msg=OneP 3 elements caught([10,12,13])"
>>> pl @(Catch' (OneP Id) (PrintT "msg=%s caught(%s)" (Second (ShowP Id)))) [10]
Present 10 (Catch did not fire)
PresentT 10
>>> pl @(Catch' (OneP Id) (PrintT "msg=%s err s=%s" (Second (ShowP Id)))) [10,11]
Error msg=OneP 2 elements err s=[10,11] (Catch default condition failed)
FailT "msg=OneP 2 elements err s=[10,11]"
Instances
P (CatchT' p s) x => P (Catch' p s :: Type) x Source # 
Instance details

Defined in Predicate.Data.Extra

Associated Types

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

Methods

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

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

Defined in Predicate.Data.Extra

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

data Dot (ps :: [Type -> Type]) (q :: Type) Source #

compose simple functions

>>> pl @(Dot '[Thd,Snd,Fst] Id) ((1,(2,9,10)),(3,4))
Present 10 (Thd 10 | (2,9,10))
PresentT 10
Instances
P (DotExpandT ps q) a => P (Dot ps q :: Type) a Source # 
Instance details

Defined in Predicate.Data.Extra

Associated Types

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

Methods

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

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

Defined in Predicate.Data.Extra

type PP (Dot ps q :: Type) a

data RDot (ps :: [Type -> Type]) (q :: Type) Source #

reversed version of Dot

>>> pl @(RDot '[Fst,Snd,Thd] Id) ((1,(2,9,10)),(3,4))
Present 10 (Thd 10 | (2,9,10))
PresentT 10
>>> pl @(RDot '[Fst,Snd] Id) (('a',2),(True,"zy"))
Present 2 (Snd 2 | ('a',2))
PresentT 2
Instances
P (RDotExpandT ps q) a => P (RDot ps q :: Type) a Source # 
Instance details

Defined in Predicate.Data.Extra

Associated Types

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

Methods

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

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

Defined in Predicate.Data.Extra

type PP (RDot ps q :: Type) a

data K (p :: k) (q :: k1) Source #

creates a constant expression ignoring the second argument

>>> pl @(RDot '[Fst,Snd,Thd,K "xxx"] Id) ((1,(2,9,10)),(3,4))
Present "xxx" (K '"xxx")
PresentT "xxx"
>>> pl @(RDot '[Fst,Snd,Thd,K '("abc",Id)] Id) ((1,(2,9,10)),(3,4))
Present ("abc",((1,(2,9,10)),(3,4))) (K '("abc",((1,(2,9,10)),(3,4))))
PresentT ("abc",((1,(2,9,10)),(3,4)))
>>> pl @(Thd $ Snd $ Fst $ K Id "dud") ((1,("W",9,'a')),(3,4))
Present 'a' (Thd 'a' | ("W",9,'a'))
PresentT 'a'
>>> pl @((Thd $ Snd $ Fst $ K Id "dud") >> Pred Id) ((1,("W",9,'a')),(3,4))
Present '`' ((>>) '`' | {Pred '`' | 'a'})
PresentT '`'
Instances
P p a => P (K p q :: Type) a Source # 
Instance details

Defined in Predicate.Data.Extra

Associated Types

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

Methods

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

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

Defined in Predicate.Data.Extra

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