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

Safe HaskellNone
LanguageHaskell2010

Predicate.Data.List

Contents

Description

promoted list functions

Synopsis

constructors

data p :+ q infixr 5 Source #

similar to cons

>>> pz @(Fst Id :+ Snd Id) (99,[1,2,3,4])
PresentT [99,1,2,3,4]
>>> pz @(Snd Id :+ Fst Id) ([],5)
PresentT [5]
>>> pz @(123 :+ EmptyList _) "somestuff"
PresentT [123]
>>> pl @(FlipT (:+) (Fst Id) (Snd Id)) ([1..5],99)
Present [99,1,2,3,4,5] ((:+) [99,1,2,3,4,5] | p=99 | q=[1,2,3,4,5])
PresentT [99,1,2,3,4,5]
>>> pl @(Fst Id :+ Snd Id) (99,[1..5])
Present [99,1,2,3,4,5] ((:+) [99,1,2,3,4,5] | p=99 | q=[1,2,3,4,5])
PresentT [99,1,2,3,4,5]
>>> pl @(4 :+ '[1,2,3]) ()
Present [4,1,2,3] ((:+) [4,1,2,3] | p=4 | q=[1,2,3])
PresentT [4,1,2,3]
>>> pl @(Fst Id :+ Snd Id) (4,[1,2,3])
Present [4,1,2,3] ((:+) [4,1,2,3] | p=4 | q=[1,2,3])
PresentT [4,1,2,3]
>>> pl @(FlipT (:+) '[1,2,3] 5) ()
Present [5,1,2,3] ((:+) [5,1,2,3] | p=5 | q=[1,2,3])
PresentT [5,1,2,3]
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.Data.List

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

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

data p +: q infixl 5 Source #

similar to snoc

>>> pz @(Snd Id +: Fst Id) (99,[1,2,3,4])
PresentT [1,2,3,4,99]
>>> pz @(Fst Id +: Snd Id) ([],5)
PresentT [5]
>>> pz @(EmptyT [] Id +: 5) 5
PresentT [5]
>>> pl @('[1,2,3] +: 4) ()
Present [1,2,3,4] ((+:) [1,2,3,4] | p=[1,2,3] | q=4)
PresentT [1,2,3,4]
>>> pl @(Snd Id +: Fst Id) (4,[1,2,3])
Present [1,2,3,4] ((+:) [1,2,3,4] | p=[1,2,3] | q=4)
PresentT [1,2,3,4]
>>> pl @("abc" +: Char1 "x") ()
Present "abcx" ((+:) "abcx" | p="abc" | q='x')
PresentT "abcx"
>>> pl @(Fst Id +: Snd Id) ("abc" :: T.Text,'x')
Present "abcx" ((+:) "abcx" | p="abc" | q='x')
PresentT "abcx"
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.Data.List

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

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

data p ++ q infixr 5 Source #

similar to (++)

>>> pz @(Fst Id ++ Snd Id) ([9,10,11],[1,2,3,4])
PresentT [9,10,11,1,2,3,4]
>>> pz @(Snd Id ++ Fst Id) ([],[5])
PresentT [5]
>>> pz @(Char1 "xyz" :+ W "ab" ++ W "cdefg") ()
PresentT "xabcdefg"
>>> pz @([1,2,3] ++ EmptyList _) "somestuff"
PresentT [1,2,3]
Instances
(P p x, P q x, Show (PP p x), PP p x ~ [a], PP q x ~ [a]) => P (p ++ q :: Type) x Source # 
Instance details

Defined in Predicate.Data.List

Associated Types

type PP (p ++ q) x :: 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.List

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

data Singleton p Source #

creates a singleton from a value

>>> pz @(Singleton (Char1 "aBc")) ()
PresentT "a"
>>> pz @(Singleton Id) False
PresentT [False]
>>> pz @(Singleton (Snd Id)) (False,"hello")
PresentT ["hello"]
Instances
P p x => P (Singleton p :: Type) x Source # 
Instance details

Defined in Predicate.Data.List

Associated Types

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

Methods

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

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

Defined in Predicate.Data.List

type PP (Singleton p :: Type) x = [PP p x]

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

similar to empty

>>> pz @(EmptyT Maybe Id) ()
PresentT Nothing
>>> pz @(EmptyT [] Id) ()
PresentT []
>>> pz @(EmptyT [] (Char1 "x")) (13,True)
PresentT ""
>>> pz @(EmptyT (Either String) (Fst Id)) (13,True)
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.Data.List

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

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

data EmptyList (t :: Type) Source #

creates an empty list for the given type

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

Defined in Predicate.Data.List

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

type PP (EmptyList t :: Type) x

data EmptyList' t Source #

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

Defined in Predicate.Data.List

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

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

destructors

data Uncons Source #

similar to uncons

>>> pz @Uncons [1,2,3,4]
PresentT (Just (1,[2,3,4]))
>>> pz @Uncons []
PresentT Nothing
>>> pz @Uncons (Seq.fromList "abc")
PresentT (Just ('a',fromList "bc"))
>>> pz @Uncons ("xyz" :: T.Text)
PresentT (Just ('x',"yz"))
>>> pl @Uncons ("asfd" :: T.Text)
Present Just ('a',"sfd") (Uncons Just ('a',"sfd") | "asfd")
PresentT (Just ('a',"sfd"))
>>> pl @Uncons ("" :: T.Text)
Present Nothing (Uncons Nothing | "")
PresentT Nothing
>>> pl @Uncons [1..5] -- with Typeable would need to specify the type of [1..5]
Present Just (1,[2,3,4,5]) (Uncons Just (1,[2,3,4,5]) | [1,2,3,4,5])
PresentT (Just (1,[2,3,4,5]))
Instances
(Show (ConsT s), Show s, Cons s s (ConsT s) (ConsT s)) => P Uncons s Source # 
Instance details

Defined in Predicate.Data.List

Associated Types

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

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

data Unsnoc Source #

similar to unsnoc

>>> pz @Unsnoc [1,2,3,4]
PresentT (Just ([1,2,3],4))
>>> pz @Unsnoc []
PresentT Nothing
>>> pz @Unsnoc ("xyz" :: T.Text)
PresentT (Just ("xy",'z'))
>>> pl @Unsnoc ("asfd" :: T.Text)
Present Just ("asf",'d') (Unsnoc Just ("asf",'d') | "asfd")
PresentT (Just ("asf",'d'))
>>> pl @Unsnoc ("" :: T.Text)
Present Nothing (Unsnoc Nothing | "")
PresentT Nothing
>>> pl @Unsnoc [1..5]
Present Just ([1,2,3,4],5) (Unsnoc Just ([1,2,3,4],5) | [1,2,3,4,5])
PresentT (Just ([1,2,3,4],5))
Instances
(Show (ConsT s), Show s, Snoc s s (ConsT s) (ConsT s)) => P Unsnoc s Source # 
Instance details

Defined in Predicate.Data.List

Associated Types

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

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

data Head p Source #

takes the head of a list-like container: similar to head

>>> pz @(Head Id) "abcd"
PresentT 'a'
>>> pz @(Head Id) []
FailT "Head(empty)"
>>> pl @(Head Id) ([] :: [Int])
Error Head(empty)
FailT "Head(empty)"
>>> pl @(Head Id) ([] :: [Double])
Error Head(empty)
FailT "Head(empty)"
>>> pl @(Head (Fst Id) >> Le 6) ([]::[Int], True)
Error Head(empty) ((>>) lhs failed)
FailT "Head(empty)"
>>> pl @(Head Id) [1,2,3]
Present 1 (Head 1 | [1,2,3])
PresentT 1
Instances
(Show (ConsT s), Show s, Cons s s (ConsT s) (ConsT s), PP p x ~ s, P p x) => P (Head p :: Type) x Source # 
Instance details

Defined in Predicate.Data.List

Associated Types

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

Methods

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

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

Defined in Predicate.Data.List

type PP (Head p :: Type) x = ConsT (PP p x)

data Tail p Source #

takes the tail of a list-like container: similar to tail

>>> pz @(Tail Id) "abcd"
PresentT "bcd"
>>> pl @(Tail Id) [1..5]
Present [2,3,4,5] (Tail [2,3,4,5] | [1,2,3,4,5])
PresentT [2,3,4,5]
>>> pl @(Tail Id) ([] :: [()])
Error Tail(empty)
FailT "Tail(empty)"
Instances
(Show s, Cons s s (ConsT s) (ConsT s), PP p x ~ s, P p x) => P (Tail p :: Type) x Source # 
Instance details

Defined in Predicate.Data.List

Associated Types

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

Methods

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

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

Defined in Predicate.Data.List

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

data Init p Source #

takes the init of a list-like container: similar to init

>>> pz @(Init Id) "abcd"
PresentT "abc"
>>> pz @(Init Id) (T.pack "abcd")
PresentT "abc"
>>> pz @(Init Id) []
FailT "Init(empty)"
>>> pl @(Init Id) [1..5]
Present [1,2,3,4] (Init [1,2,3,4] | [1,2,3,4,5])
PresentT [1,2,3,4]
>>> pl @(Init Id) ([] :: [()])
Error Init(empty)
FailT "Init(empty)"
Instances
(Show s, Snoc s s (ConsT s) (ConsT s), PP p x ~ s, P p x) => P (Init p :: Type) x Source # 
Instance details

Defined in Predicate.Data.List

Associated Types

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

Methods

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

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

Defined in Predicate.Data.List

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

data Last p Source #

takes the last of a list-like container: similar to last

>>> pz @(Last Id) "abcd"
PresentT 'd'
>>> pz @(Last Id) []
FailT "Last(empty)"
>>> pl @(Last Id) [1,2,3]
Present 3 (Last 3 | [1,2,3])
PresentT 3
Instances
(Show (ConsT s), Show s, Snoc s s (ConsT s) (ConsT s), PP p x ~ s, P p x) => P (Last p :: Type) x Source # 
Instance details

Defined in Predicate.Data.List

Associated Types

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

Methods

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

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

Defined in Predicate.Data.List

type PP (Last p :: Type) x = ConsT (PP p x)

sort

data SortBy p q Source #

sort a list

>>> pz @(SortOn (Fst Id) Id) [(10,"abc"), (3,"def"), (4,"gg"), (10,"xyz"), (1,"z")]
PresentT [(1,"z"),(3,"def"),(4,"gg"),(10,"abc"),(10,"xyz")]
>>> pz @(SortBy (OrdP (Snd Id) (Fst Id)) Id) [(10,"ab"),(4,"x"),(20,"bbb")]
PresentT [(20,"bbb"),(10,"ab"),(4,"x")]
>>> pz @(SortBy 'LT Id) [1,5,2,4,7,0]
PresentT [1,5,2,4,7,0]
>>> pz @(SortBy 'GT Id) [1,5,2,4,7,0]
PresentT [0,7,4,2,5,1]
>>> pz @(SortBy ((Fst (Fst Id) ==! Fst (Snd Id)) <> (Snd (Fst Id) ==! Snd (Snd Id))) Id) [(10,"ab"),(4,"x"),(20,"bbb"),(4,"a"),(4,"y")]
PresentT [(4,"a"),(4,"x"),(4,"y"),(10,"ab"),(20,"bbb")]
>>> pz @(SortBy ((Fst (Fst Id) ==! Fst (Snd Id)) <> (Snd (Snd Id) ==! Snd (Fst Id))) Id) [(10,"ab"),(4,"x"),(20,"bbb"),(4,"a"),(4,"y")]
PresentT [(4,"y"),(4,"x"),(4,"a"),(10,"ab"),(20,"bbb")]
>>> pl @(SortBy (Swap >> OrdA (Fst Id)) (Snd Id)) ((),[('z',1),('a',10),('m',22)])
Present [('z',1),('m',22),('a',10)] (SortBy [('z',1),('m',22),('a',10)])
PresentT [('z',1),('m',22),('a',10)]
>>> pl @(SortBy (OrdA Reverse) Id) ["az","by","cx","aa"]
Present ["aa","cx","by","az"] (SortBy ["aa","cx","by","az"])
PresentT ["aa","cx","by","az"]
>>> pl @(SortBy (If (Fst Id==5 && Snd Id==3) (Failt _ (PrintT "pivot=%d value=%d" Id)) 'GT) (Snd Id)) ((), [5,7,3,1,6,2,1,3])
Error pivot=5 value=3(2) (SortBy)
FailT "pivot=5 value=3(2)"
>>> pl @(SortBy (If (Fst Id==50 && Snd Id==3) (Failt _ (PrintT "pivot=%d value=%d" Id)) (OrdA Id)) (Snd Id)) ((), [5,7,3,1,6,2,1,3])
Present [1,1,2,3,3,5,6,7] (SortBy [1,1,2,3,3,5,6,7])
PresentT [1,1,2,3,3,5,6,7]
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.Data.List

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

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

data SortOn p q Source #

similar to sortOn

>>> pl @(SortOn Id Id) [10,4,2,12,14]
Present [2,4,10,12,14] (SortBy [2,4,10,12,14])
PresentT [2,4,10,12,14]
>>> pl @(SortOn (Negate Id) Id) [10,4,2,12,14]
Present [14,12,10,4,2] (SortBy [14,12,10,4,2])
PresentT [14,12,10,4,2]
>>> pl @(SortOn (Fst Id) Id) (zip "cabdaz" [10,4,2,12,14,1])
Present [('a',4),('a',14),('b',2),('c',10),('d',12),('z',1)] (SortBy [('a',4),('a',14),('b',2),('c',10),('d',12),('z',1)])
PresentT [('a',4),('a',14),('b',2),('c',10),('d',12),('z',1)]
>>> pl @(SortOn (FailS "asdf") Id) [10,4,2,12,14]
Error asdf(4) (SortBy)
FailT "asdf(4)"
>>> pl @(SortOn (Snd Id) (Snd Id)) ((),[('z',14),('a',10),('m',22),('a',1)])
Present [('a',1),('a',10),('z',14),('m',22)] (SortBy [('a',1),('a',10),('z',14),('m',22)])
PresentT [('a',1),('a',10),('z',14),('m',22)]
>>> pl @(SortOn (Fst Id) (Snd Id)) ((),[('z',1),('a',10),('m',22)])
Present [('a',10),('m',22),('z',1)] (SortBy [('a',10),('m',22),('z',1)])
PresentT [('a',10),('m',22),('z',1)]
>>> pl @(SortOn (Fst Id) Id) [('z',1),('a',10),('m',22),('a',9),('m',10)]
Present [('a',10),('a',9),('m',22),('m',10),('z',1)] (SortBy [('a',10),('a',9),('m',22),('m',10),('z',1)])
PresentT [('a',10),('a',9),('m',22),('m',10),('z',1)]
>>> pl @(SortOn Id Id) [('z',1),('a',10),('m',22),('a',9),('m',10)]
Present [('a',9),('a',10),('m',10),('m',22),('z',1)] (SortBy [('a',9),('a',10),('m',10),('m',22),('z',1)])
PresentT [('a',9),('a',10),('m',10),('m',22),('z',1)]
Instances
P (SortOnT p q) x => P (SortOn p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.List

Associated Types

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

Methods

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

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

Defined in Predicate.Data.List

type PP (SortOn p q :: Type) x

data SortOnDesc p q Source #

SortOn but descending order

>>> pl @(SortOnDesc Id Id) [10,4,2,12,14]
Present [14,12,10,4,2] (SortBy [14,12,10,4,2])
PresentT [14,12,10,4,2]
>>> pl @(SortOnDesc (Fst Id) (Snd Id)) ((),[('z',1),('a',10),('m',22)])
Present [('z',1),('m',22),('a',10)] (SortBy [('z',1),('m',22),('a',10)])
PresentT [('z',1),('m',22),('a',10)]
Instances
P (SortOnDescT p q) x => P (SortOnDesc p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.List

Associated Types

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

Methods

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

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

Defined in Predicate.Data.List

type PP (SortOnDesc p q :: Type) x

zip related

data Unzip Source #

unzip equivalent

>>> pz @Unzip (zip [1..5] "abcd")
PresentT ([1,2,3,4],"abcd")
Instances
P UnzipT x => P Unzip x Source # 
Instance details

Defined in Predicate.Data.List

Associated Types

type PP Unzip x :: Type Source #

Methods

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

type PP Unzip x Source # 
Instance details

Defined in Predicate.Data.List

type PP Unzip x

data Unzip3 Source #

unzip3 equivalent

>>> pz @Unzip3 (zip3 [1..5] "abcd" (cycle [True,False]))
PresentT ([1,2,3,4],"abcd",[True,False,True,False])
Instances
P Unzip3T x => P Unzip3 x Source # 
Instance details

Defined in Predicate.Data.List

Associated Types

type PP Unzip3 x :: Type Source #

Methods

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

type PP Unzip3 x Source # 
Instance details

Defined in Predicate.Data.List

type PP Unzip3 x

data ZipL l p q Source #

zip two lists optionally padding the left hand side

>>> pl @(ZipL 99 '[1,2,3] "abc") ()
Present [(1,'a'),(2,'b'),(3,'c')] (ZipL [(1,'a'),(2,'b'),(3,'c')] | p=[1,2,3] | q="abc")
PresentT [(1,'a'),(2,'b'),(3,'c')]
>>> pl @(ZipL 99 '[1,2] "abc") ()
Present [(1,'a'),(2,'b'),(99,'c')] (ZipL [(1,'a'),(2,'b'),(99,'c')] | p=[1,2] | q="abc")
PresentT [(1,'a'),(2,'b'),(99,'c')]
>>> pl @(ZipL 99 '[1] "abc") ()
Present [(1,'a'),(99,'b'),(99,'c')] (ZipL [(1,'a'),(99,'b'),(99,'c')] | p=[1] | q="abc")
PresentT [(1,'a'),(99,'b'),(99,'c')]
>>> pl @(ZipL 99 '[1,2,3] "ab") ()
Error ZipL(3,2) rhs would be truncated (p=[1,2,3] | q="ab")
FailT "ZipL(3,2) rhs would be truncated"
>>> pl @(ZipL 99 Id "abcdefg") [1..4]
Present [(1,'a'),(2,'b'),(3,'c'),(4,'d'),(99,'e'),(99,'f'),(99,'g')] (ZipL [(1,'a'),(2,'b'),(3,'c'),(4,'d'),(99,'e'),(99,'f'),(99,'g')] | p=[1,2,3,4] | q="abcdefg")
PresentT [(1,'a'),(2,'b'),(3,'c'),(4,'d'),(99,'e'),(99,'f'),(99,'g')]
>>> pl @(ZipL (99 % 4) '[1 % 1 , 2 % 1 , 3 % 1] Id) "abcde"
Present [(1 % 1,'a'),(2 % 1,'b'),(3 % 1,'c'),(99 % 4,'d'),(99 % 4,'e')] (ZipL [(1 % 1,'a'),(2 % 1,'b'),(3 % 1,'c'),(99 % 4,'d'),(99 % 4,'e')] | p=[1 % 1,2 % 1,3 % 1] | q="abcde")
PresentT [(1 % 1,'a'),(2 % 1,'b'),(3 % 1,'c'),(99 % 4,'d'),(99 % 4,'e')]
>>> pl @(ZipL "X" (EmptyT _ Id) Id) ("abcd" :: String)
Present [("X",'a'),("X",'b'),("X",'c'),("X",'d')] (ZipL [("X",'a'),("X",'b'),("X",'c'),("X",'d')] | p=[] | q="abcd")
PresentT [("X",'a'),("X",'b'),("X",'c'),("X",'d')]
Instances
(PP l a ~ x, P l a, PP p a ~ [x], PP q a ~ [y], P p a, P q a, Show x, Show y) => P (ZipL l p q :: Type) a Source # 
Instance details

Defined in Predicate.Data.List

Associated Types

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

Methods

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

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

Defined in Predicate.Data.List

type PP (ZipL l p q :: Type) a = [(ExtractAFromList (PP p a), ExtractAFromList (PP q a))]

data ZipR r p q Source #

zip two lists optionally padding the right hand side

>>> pl @(ZipR (Char1 "Z") '[1,2,3] "abc") ()
Present [(1,'a'),(2,'b'),(3,'c')] (ZipR [(1,'a'),(2,'b'),(3,'c')] | p=[1,2,3] | q="abc")
PresentT [(1,'a'),(2,'b'),(3,'c')]
>>> pl @(ZipR (Char1 "Z") '[1,2,3] "ab") ()
Present [(1,'a'),(2,'b'),(3,'Z')] (ZipR [(1,'a'),(2,'b'),(3,'Z')] | p=[1,2,3] | q="ab")
PresentT [(1,'a'),(2,'b'),(3,'Z')]
>>> pl @(ZipR (Char1 "Z") '[1,2,3] "a") ()
Present [(1,'a'),(2,'Z'),(3,'Z')] (ZipR [(1,'a'),(2,'Z'),(3,'Z')] | p=[1,2,3] | q="a")
PresentT [(1,'a'),(2,'Z'),(3,'Z')]
>>> pl @(ZipR (Char1 "Z") '[1,2] "abc") ()
Error ZipR(2,3) rhs would be truncated (p=[1,2] | q="abc")
FailT "ZipR(2,3) rhs would be truncated"
>>> pl @(ZipR (Char1 "Y") (EmptyT _ Id) Id) "abcd"
Error ZipR(0,4) rhs would be truncated (p=[] | q="abcd")
FailT "ZipR(0,4) rhs would be truncated"
Instances
(PP r a ~ y, P r a, PP p a ~ [x], PP q a ~ [y], P p a, P q a, Show x, Show y) => P (ZipR r p q :: Type) a Source # 
Instance details

Defined in Predicate.Data.List

Associated Types

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

Methods

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

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

Defined in Predicate.Data.List

type PP (ZipR r p q :: Type) a = [(ExtractAFromList (PP p a), ExtractAFromList (PP q a))]

data Zip p q Source #

zip two lists with the same length

>>> pl @(Zip '[1,2,3] "abc") ()
Present [(1,'a'),(2,'b'),(3,'c')] (Zip [(1,'a'),(2,'b'),(3,'c')] | p=[1,2,3] | q="abc")
PresentT [(1,'a'),(2,'b'),(3,'c')]
>>> pl @(Zip '[1,2,3] "ab") ()
Error Zip(3,2) length mismatch (p=[1,2,3] | q="ab")
FailT "Zip(3,2) length mismatch"
>>> pl @(Zip '[1,2] "abc") ()
Error Zip(2,3) length mismatch (p=[1,2] | q="abc")
FailT "Zip(2,3) length mismatch"
>>> pl @(Zip "abc" Id) [1..7]
Error Zip(3,7) length mismatch (p="abc" | q=[1,2,3,4,5,6,7])
FailT "Zip(3,7) length mismatch"
Instances
(PP p a ~ [x], PP q a ~ [y], P p a, P q a, Show x, Show y) => P (Zip p q :: Type) a Source # 
Instance details

Defined in Predicate.Data.List

Associated Types

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

Methods

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

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

Defined in Predicate.Data.List

type PP (Zip p q :: Type) a = [(ExtractAFromList (PP p a), ExtractAFromList (PP q a))]

data ZipWith p q r Source #

like zipWith

>>> pz @(ZipWith Id (1...5) (Char1 "a" ... Char1 "e")) ()
PresentT [(1,'a'),(2,'b'),(3,'c'),(4,'d'),(5,'e')]
>>> pz @(ZipWith (ShowP (Fst Id) <> ShowP (Snd Id)) (1...5) (Char1 "a" ... Char1 "e")) ()
PresentT ["1'a'","2'b'","3'c'","4'd'","5'e'"]
>>> pz @(ZipWith (MkThese (Fst Id) (Snd Id)) (1...6) (Char1 "a" ... Char1 "f")) ()
PresentT [These 1 'a',These 2 'b',These 3 'c',These 4 'd',These 5 'e',These 6 'f']
>>> pz @(ZipWith (MkThese (Fst Id) (Snd Id)) '[] (Char1 "a" ... Char1 "f")) ()
FailT "ZipWith(0,6) length mismatch"
>>> pz @(ZipWith (MkThese (Fst Id) (Snd Id)) (1...3) (Char1 "a" ... Char1 "f")) ()
FailT "ZipWith(3,6) length mismatch"
Instances
(PP q a ~ [x], PP r a ~ [y], P q a, P r a, P p (x, y), Show x, Show y, Show (PP p (x, y))) => P (ZipWith p q r :: Type) a Source # 
Instance details

Defined in Predicate.Data.List

Associated Types

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

Methods

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

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

Defined in Predicate.Data.List

type PP (ZipWith p q r :: Type) a = [PP p (ExtractAFromList (PP q a), ExtractAFromList (PP r a))]

higher order methods

data Partition p q Source #

similar to partition

>>> pz @(Partition (Ge 3) Id) [10,4,1,7,3,1,3,5]
PresentT ([10,4,7,3,3,5],[1,1])
>>> pz @(Partition (Prime Id) Id) [10,4,1,7,3,1,3,5]
PresentT ([7,3,3,5],[10,4,1,1])
>>> pz @(Partition (Ge 300) Id) [10,4,1,7,3,1,3,5]
PresentT ([],[10,4,1,7,3,1,3,5])
>>> pz @(Partition (Id < 300) Id) [10,4,1,7,3,1,3,5]
PresentT ([10,4,1,7,3,1,3,5],[])
>>> pl @(Partition (Lt 2) Id >> Id) [1,2,3,4,5]
Present ([1],[2,3,4,5]) ((>>) ([1],[2,3,4,5]) | {Id ([1],[2,3,4,5])})
PresentT ([1],[2,3,4,5])
>>> pl @(Partition (Gt 3) Id) [1..10]
Present ([4,5,6,7,8,9,10],[1,2,3]) (Partition ([4,5,6,7,8,9,10],[1,2,3]) | s=[1,2,3,4,5,6,7,8,9,10])
PresentT ([4,5,6,7,8,9,10],[1,2,3])
>>> pl @(Partition Even Id) [1..6]
Present ([2,4,6],[1,3,5]) (Partition ([2,4,6],[1,3,5]) | s=[1,2,3,4,5,6])
PresentT ([2,4,6],[1,3,5])
>>> pl @(Partition Even Id >> Null *** (Len > 4) >> Fst Id == Snd Id) [1..6]
True ((>>) True | {False == False})
TrueT
>>> pl @(Partition (ExitWhen "ExitWhen" (Gt 10) >> Gt 2) Id) [1..11]
Error ExitWhen (Partition(i=10, a=11) excnt=1)
FailT "ExitWhen"
>>> pl @(Partition (Prime Id) Id) [1..15]
Present ([2,3,5,7,11,13],[1,4,6,8,9,10,12,14,15]) (Partition ([2,3,5,7,11,13],[1,4,6,8,9,10,12,14,15]) | s=[1,2,3,4,5,6,7,8,9,10,11,12,13,14,15])
PresentT ([2,3,5,7,11,13],[1,4,6,8,9,10,12,14,15])
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.Data.List

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

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

data PartitionBy t p q Source #

partition values based on a function

>>> pz @(PartitionBy Ordering (Case 'EQ '[Id < 0, Id > 0] '[ 'LT, 'GT] Id) Id) [-4,-2,5,6,7,0,-1,2,-3,4,0]
PresentT (fromList [(LT,[-3,-1,-2,-4]),(EQ,[0,0]),(GT,[4,2,7,6,5])])
>>> pl @(PartitionBy Ordering (Case (Failt _ "asdf") '[Id < 2, Id == 2, Id > 2] '[ 'LT, 'EQ, 'GT] Id) Id) [-4,2,5,6,7,1,2,3,4]
Present fromList [(LT,[1,-4]),(EQ,[2,2]),(GT,[4,3,7,6,5])] (PartitionBy fromList [(LT,[1,-4]),(EQ,[2,2]),(GT,[4,3,7,6,5])] | s=[-4,2,5,6,7,1,2,3,4])
PresentT (fromList [(LT,[1,-4]),(EQ,[2,2]),(GT,[4,3,7,6,5])])
>>> pl @(PartitionBy Ordering (Case (Failt _ "xyzxyzxyzzyyysyfsyfydf") '[Id < 2, Id == 2, Id > 3] '[ 'LT, 'EQ, 'GT] Id) Id) [-4,2,5,6,7,1,2,3,4]
Error xyzxyzxyzzyyysyfsyfydf (PartitionBy(i=7, a=3) excnt=1)
FailT "xyzxyzxyzzyyysyfsyfydf"
Instances
(P p x, Ord t, Show x, Show t, PP q a ~ [x], PP p x ~ t, P q a) => P (PartitionBy t p q :: Type) a Source # 
Instance details

Defined in Predicate.Data.List

Associated Types

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

Methods

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

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

Defined in Predicate.Data.List

type PP (PartitionBy t p q :: Type) a = Map t (PP q a)

data GroupBy p q Source #

similar to groupBy

>>> pz @(GroupBy (Fst Id == Snd Id) Id) [1,3,4,5,1,5,5]
PresentT [[1],[3],[4],[5],[1],[5,5]]
>>> pz @(GroupBy (Fst Id == Snd Id) Id) [1,1,1,3,4,5,1,5,5]
PresentT [[1,1,1],[3],[4],[5],[1],[5,5]]
>>> pz @(GroupBy (Fst Id == Snd Id) Id) [5,5]
PresentT [[5,5]]
>>> pz @(GroupBy (Fst Id == Snd Id) Id) [1,2]
PresentT [[1],[2]]
>>> pz @(GroupBy (Fst Id == Snd Id) Id) [1]
PresentT [[1]]
>>> pz @(GroupBy (Fst Id == Snd Id) Id) []
PresentT []
>>> pz @(GroupBy (Fst Id < Snd Id) Id) [1,2,3,4,4,1,2]
PresentT [[1,2,3,4],[4],[1,2]]
>>> pz @(GroupBy (Fst Id /= Snd Id) Id) [1,2,3,4,4,4,1]
PresentT [[1,2,3,4],[4],[4,1]]
>>> pan @(GroupBy (Fst Id == Snd Id) Id) "hello    goodbye"
P GroupBy ["h","e","ll","o","    ","g","oo","d","b","y","e"]
|
+- P Id "hello    goodbye"
|
+- False i=0: 'h' == 'e'
|
+- False i=1: 'e' == 'l'
|
+- True i=2: 'l' == 'l'
|
+- False i=3: 'l' == 'o'
|
+- False i=4: 'o' == ' '
|
+- True i=5: ' ' == ' '
|
+- True i=6: ' ' == ' '
|
+- True i=7: ' ' == ' '
|
+- False i=8: ' ' == 'g'
|
+- False i=9: 'g' == 'o'
|
+- True i=10: 'o' == 'o'
|
+- False i=11: 'o' == 'd'
|
+- False i=12: 'd' == 'b'
|
+- False i=13: 'b' == 'y'
|
`- False i=14: 'y' == 'e'
PresentT ["h","e","ll","o","    ","g","oo","d","b","y","e"]
Instances
(Show x, PP q a ~ [x], PP p (x, x) ~ Bool, P p (x, x), P q a) => P (GroupBy p q :: Type) a Source # 
Instance details

Defined in Predicate.Data.List

Associated Types

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

Methods

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

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

Defined in Predicate.Data.List

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

data Filter p q Source #

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

Defined in Predicate.Data.List

Associated Types

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

Methods

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

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

Defined in Predicate.Data.List

type PP (Filter p q :: Type) x

data Break p q Source #

similar to break

>>> pz @(Break (Ge 3) Id) [10,4,1,7,3,1,3,5]
PresentT ([],[10,4,1,7,3,1,3,5])
>>> pz @(Break (Lt 3) Id) [10,4,1,7,3,1,3,5]
PresentT ([10,4],[1,7,3,1,3,5])
>>> pl @(Break (Gt 2) Id) [1..11]
Present ([1,2],[3,4,5,6,7,8,9,10,11]) (Break cnt=(2,9))
PresentT ([1,2],[3,4,5,6,7,8,9,10,11])
>>> pl @(Break (If (Gt 2) 'True (If (Gt 4) (Failt _ "ASfd") 'False)) Id) [1..8]
Present ([1,2],[3,4,5,6,7,8]) (Break cnt=(2,6))
PresentT ([1,2],[3,4,5,6,7,8])
>>> pl @(Break (Case 'False '[Gt 2,Gt 4] '[ W 'True, Failt _ "ASfd"] Id) Id) [1..8]  -- case version
Present ([1,2],[3,4,5,6,7,8]) (Break cnt=(2,6))
PresentT ([1,2],[3,4,5,6,7,8])
>>> pl @(Break (If (Gt 2) (Failt _ "ASfd") 'False) Id) [1..8]
Error ASfd (Break predicate failed)
FailT "ASfd"
>>> pl @(Break (Snd Id) Id) (zip [1..] [False,False,False,True,True,False])
Present ([(1,False),(2,False),(3,False)],[(4,True),(5,True),(6,False)]) (Break cnt=(3,3))
PresentT ([(1,False),(2,False),(3,False)],[(4,True),(5,True),(6,False)])
>>> pl @(Break (Snd Id) Id) (zip [1..] [False,False,False,False])
Present ([(1,False),(2,False),(3,False),(4,False)],[]) (Break cnt=(4,0))
PresentT ([(1,False),(2,False),(3,False),(4,False)],[])
>>> pl @(Break (Snd Id) Id) (zip [1..] [True,True,True,True])
Present ([],[(1,True),(2,True),(3,True),(4,True)]) (Break cnt=(0,4))
PresentT ([],[(1,True),(2,True),(3,True),(4,True)])
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.Data.List

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

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

data Span p q Source #

similar to span

>>> pl @(Span (Lt 4) Id) [1..11]
Present ([1,2,3],[4,5,6,7,8,9,10,11]) (Break cnt=(3,8))
PresentT ([1,2,3],[4,5,6,7,8,9,10,11])
Instances
P (SpanT p q) x => P (Span p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.List

Associated Types

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

Methods

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

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

Defined in Predicate.Data.List

type PP (Span p q :: Type) x

data Intercalate p q Source #

intercalate two lists

>>> pz @(Intercalate '["aB"] '["xxxx","yz","z","www","xyz"]) ()
PresentT ["xxxx","aB","yz","aB","z","aB","www","aB","xyz"]
>>> pz @(Intercalate '[W 99,Negate 98] Id) [1..5]
PresentT [1,99,-98,2,99,-98,3,99,-98,4,99,-98,5]
>>> pz @(Intercalate '[99,100] Id) [1..5]
PresentT [1,99,100,2,99,100,3,99,100,4,99,100,5]
>>> pl @(Intercalate (Fst Id) (Snd Id)) ([0,1], [12,13,14,15,16])
Present [12,0,1,13,0,1,14,0,1,15,0,1,16] (Intercalate [12,0,1,13,0,1,14,0,1,15,0,1,16] | [0,1] | [12,13,14,15,16])
PresentT [12,0,1,13,0,1,14,0,1,15,0,1,16]
>>> pl @((Pure [] (Negate Len) &&& Id) >> Intercalate (Fst Id) (Snd Id)) [12,13,14,15,16]
Present [12,-5,13,-5,14,-5,15,-5,16] ((>>) [12,-5,13,-5,14,-5,15,-5,16] | {Intercalate [12,-5,13,-5,14,-5,15,-5,16] | [-5] | [12,13,14,15,16]})
PresentT [12,-5,13,-5,14,-5,15,-5,16]
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.Data.List

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

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

miscellaneous

data Len Source #

similar to length

>>> pz @Len [10,4,5,12,3,4]
PresentT 6
>>> pz @Len []
PresentT 0
Instances
(Show a, as ~ [a]) => P Len as Source # 
Instance details

Defined in Predicate.Core

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

type PP Len as = Int

data Length p Source #

similar to length for Foldable instances

>>> pz @(Length Id) (Left "aa")
PresentT 0
>>> pz @(Length Id) (Right "aa")
PresentT 1
>>> pz @(Length Right') (Right "abcd")
PresentT 4
>>> pz @(Length (Thd (Snd Id))) (True,(23,'x',[10,9,1,3,4,2]))
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.Core

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

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

data Elem p q Source #

elem function

>>> pz @(Elem (Fst Id) (Snd Id)) ('x',"abcdxy")
TrueT
>>> pz @(Elem (Fst Id) (Snd Id)) ('z',"abcdxy")
FalseT
>>> pl @(Elem Id '[2,3,4]) 2
True (2 `elem` [2,3,4])
TrueT
>>> pl @(Elem Id '[2,3,4]) 6
False (6 `elem` [2,3,4])
FalseT
>>> pl @(Elem Id '[13 % 2]) 6.5
True (13 % 2 `elem` [13 % 2])
TrueT
>>> pl @(Elem Id '[13 % 2, 12 % 1]) 6.5
True (13 % 2 `elem` [13 % 2,12 % 1])
TrueT
>>> pl @(Elem Id '[13 % 2, 12 % 1]) 6
False (6 % 1 `elem` [13 % 2,12 % 1])
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.Data.List

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

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

data Inits Source #

similar to inits

>>> pz @Inits [4,8,3,9]
PresentT [[],[4],[4,8],[4,8,3],[4,8,3,9]]
>>> pz @Inits []
PresentT [[]]
Instances
([a] ~ x, Show a) => P Inits x Source # 
Instance details

Defined in Predicate.Data.List

Associated Types

type PP Inits x :: Type Source #

Methods

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

type PP Inits x Source # 
Instance details

Defined in Predicate.Data.List

type PP Inits x = [x]

data Tails Source #

similar to tails

>>> pz @Tails [4,8,3,9]
PresentT [[4,8,3,9],[8,3,9],[3,9],[9],[]]
>>> pz @Tails []
PresentT [[]]
>>> pl @Tails "abcd"
Present ["abcd","bcd","cd","d",""] (Tails ["abcd","bcd","cd","d",""] | "abcd")
PresentT ["abcd","bcd","cd","d",""]
Instances
([a] ~ x, Show a) => P Tails x Source # 
Instance details

Defined in Predicate.Data.List

Associated Types

type PP Tails x :: Type Source #

Methods

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

type PP Tails x Source # 
Instance details

Defined in Predicate.Data.List

type PP Tails x = [x]

data Ones p Source #

split a list into single values

>>> pz @(Ones Id) [4,8,3,9]
PresentT [[4],[8],[3],[9]]
>>> pz @(Ones Id) []
PresentT []
Instances
(PP p x ~ [a], P p x, Show a) => P (Ones p :: Type) x Source # 
Instance details

Defined in Predicate.Data.List

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

type PP (Ones p :: Type) x = [PP p x]

data PadL n p q Source #

left pad 'q' with 'n' values from 'p'

>>> pl @(PadL 5 0 Id) [1..3]
Present [0,0,1,2,3] (PadL 5 pad=0 [0,0,1,2,3] | [1,2,3])
PresentT [0,0,1,2,3]
>>> pz @(PadL 5 999 Id) [12,13]
PresentT [999,999,999,12,13]
>>> pz @(PadR 5 (Fst Id) '[12,13]) (999,'x')
PresentT [12,13,999,999,999]
>>> pz @(PadR 2 (Fst Id) '[12,13,14]) (999,'x')
PresentT [12,13,14]
>>> pl @(PadL 10 0 Id) [1..3]
Present [0,0,0,0,0,0,0,1,2,3] (PadL 10 pad=0 [0,0,0,0,0,0,0,1,2,3] | [1,2,3])
PresentT [0,0,0,0,0,0,0,1,2,3]
Instances
P (PadLT n p q) x => P (PadL n p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.List

Associated Types

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

Methods

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

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

Defined in Predicate.Data.List

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

data PadR n p q Source #

right pad 'q' with 'n' values from 'p'

>>> pl @(PadR 5 8 Id) [1..3]
Present [1,2,3,8,8] (PadR 5 pad=8 [1,2,3,8,8] | [1,2,3])
PresentT [1,2,3,8,8]
>>> pl @(PadR 5 0 Id) [1..5]
Present [1,2,3,4,5] (PadR 5 pad=0 [1,2,3,4,5] | [1,2,3,4,5])
PresentT [1,2,3,4,5]
>>> pl @(PadR 5 0 Id) [1..6]
Present [1,2,3,4,5,6] (PadR 5 pad=0 [1,2,3,4,5,6] | [1,2,3,4,5,6])
PresentT [1,2,3,4,5,6]
Instances
P (PadRT n p q) x => P (PadR n p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.List

Associated Types

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

Methods

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

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

Defined in Predicate.Data.List

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

data SplitAts ns p Source #

split a list 'p' into parts using the lengths in the type level list 'ns'

>>> pz @(SplitAts '[2,3,1,1] Id) "hello world"
PresentT ["he","llo"," ","w","orld"]
>>> pz @(SplitAts '[2] Id) "hello world"
PresentT ["he","llo world"]
>>> pz @(SplitAts '[10,1,1,5] Id) "hello world"
PresentT ["hello worl","d","",""]
>>> pl @(SplitAts '[1,3,4] Id) [1..12]
Present [[1],[2,3,4],[5,6,7,8],[9,10,11,12]] (SplitAts [[1],[2,3,4],[5,6,7,8],[9,10,11,12]] | ns=[1,3,4] | [1,2,3,4,5,6,7,8,9,10,11,12])
PresentT [[1],[2,3,4],[5,6,7,8],[9,10,11,12]]
>>> pl @(SplitAts '[3,1,1,1] Id >> Filter (Not Null) Id) [1..4]
Present [[1,2,3],[4]] ((>>) [[1,2,3],[4]] | {Fst [[1,2,3],[4]] | ([[1,2,3],[4]],[[],[]])})
PresentT [[1,2,3],[4]]
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.Data.List

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

type PP (SplitAts ns p :: Type) x = [PP p x]

data SplitAt n p Source #

similar to splitAt

>>> pz @(SplitAt 4 Id) "hello world"
PresentT ("hell","o world")
>>> pz @(SplitAt 20 Id) "hello world"
PresentT ("hello world","")
>>> pz @(SplitAt 0 Id) "hello world"
PresentT ("","hello world")
>>> pz @(SplitAt (Snd Id) (Fst Id)) ("hello world",4)
PresentT ("hell","o world")
>>> pz @(SplitAt (Negate 2) Id) "hello world"
PresentT ("hello wor","ld")
>>> pl @(Snd Id >> SplitAt 2 Id >> Len *** Len >> Fst Id > Snd Id) ('x',[1..5])
False ((>>) False | {2 > 3})
FalseT
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.Data.List

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

type PP (SplitAt n p :: Type) a = (PP p a, PP p a)

data ChunksOf n p Source #

splits a list pointed to by 'p' into lists of size 'n'

>>> pz @(ChunksOf 2 Id) "abcdef"
PresentT ["ab","cd","ef"]
>>> pz @(ChunksOf 2 Id) "abcdefg"
PresentT ["ab","cd","ef","g"]
>>> pz @(ChunksOf 2 Id) ""
PresentT []
>>> pz @(ChunksOf 2 Id) "a"
PresentT ["a"]
Instances
(PP p a ~ [b], P n a, P p a, Show b, Integral (PP n a)) => P (ChunksOf n p :: Type) a Source # 
Instance details

Defined in Predicate.Data.List

Associated Types

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

Methods

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

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

Defined in Predicate.Data.List

type PP (ChunksOf n p :: Type) a = [PP p a]

data Rotate n p Source #

rotate a list 'p' 'n' units

>>> pz @(Rotate 0 Id) [1,2,3,4]
PresentT [1,2,3,4]
>>> pz @(Rotate (Negate 1) Id) [1,2,3,4]
PresentT [4,1,2,3]
>>> pz @(Rotate 2 Id) [1,2,3,4]
PresentT [3,4,1,2]
>>> pz @(Map (Rotate Id "abcd") Id) [-3..7]
PresentT ["bcda","cdab","dabc","abcd","bcda","cdab","dabc","abcd","bcda","cdab","dabc"]
Instances
P (RotateT n p) x => P (Rotate n p :: Type) x Source # 
Instance details

Defined in Predicate.Data.List

Associated Types

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

Methods

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

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

Defined in Predicate.Data.List

type PP (Rotate n p :: Type) x

data Take n p Source #

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

Defined in Predicate.Data.List

Associated Types

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

Methods

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

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

Defined in Predicate.Data.List

type PP (Take n p :: Type) x

data Drop n p Source #

Instances
P (DropT n p) x => P (Drop n p :: Type) x Source # 
Instance details

Defined in Predicate.Data.List

Associated Types

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

Methods

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

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

Defined in Predicate.Data.List

type PP (Drop n p :: Type) x

data Remove p q Source #

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

>>> pz @(Remove '[5] '[1,5,5,2,5,2]) ()
PresentT [1,2,2]
>>> pz @(Remove '[0,1,1,5] '[1,5,5,2,5,2]) ()
PresentT [2,2]
>>> pz @(Remove '[99] '[1,5,5,2,5,2]) ()
PresentT [1,5,5,2,5,2]
>>> pz @(Remove '[99,91] '[1,5,5,2,5,2]) ()
PresentT [1,5,5,2,5,2]
>>> pz @(Remove Id '[1,5,5,2,5,2]) []
PresentT [1,5,5,2,5,2]
>>> pz @(Remove '[] '[1,5,5,2,5,2]) 44 -- works if you make this a number!
PresentT [1,5,5,2,5,2]
Instances
P (RemoveT p q) x => P (Remove p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.List

Associated Types

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

Methods

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

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

Defined in Predicate.Data.List

type PP (Remove p q :: Type) x

data Keep p q Source #

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

>>> pz @(Keep '[5] '[1,5,5,2,5,2]) ()
PresentT [5,5,5]
>>> pz @(Keep '[0,1,1,5] '[1,5,5,2,5,2]) ()
PresentT [1,5,5,5]
Instances
P (KeepT p q) x => P (Keep p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.List

Associated Types

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

Methods

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

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

Defined in Predicate.Data.List

type PP (Keep p q :: Type) x

data Reverse Source #

similar to reverse

>>> pz @Reverse [1,2,4]
PresentT [4,2,1]
>>> pz @Reverse "AbcDeF"
PresentT "FeDcbA"
Instances
(Show a, as ~ [a]) => P Reverse as Source # 
Instance details

Defined in Predicate.Data.List

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

type PP Reverse as = as

data ReverseL Source #

reverses using reversing

>>> pz @ReverseL (T.pack "AbcDeF")
PresentT "FeDcbA"
>>> pz @ReverseL ("AbcDeF" :: String)
PresentT "FeDcbA"
>>> pl @ReverseL ("asfd" :: T.Text)
Present "dfsa" (ReverseL "dfsa" | "asfd")
PresentT "dfsa"
Instances
(Show t, Reversing t) => P ReverseL t Source # 
Instance details

Defined in Predicate.Data.List

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

type PP ReverseL t = t

data Sum Source #

similar to sum

>>> pz @Sum [10,4,5,12,3,4]
PresentT 38
>>> pz @Sum []
PresentT 0
Instances
(Num a, Show a) => P Sum [a] Source # 
Instance details

Defined in Predicate.Data.List

Associated Types

type PP Sum [a] :: Type Source #

Methods

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

type PP Sum [a] Source # 
Instance details

Defined in Predicate.Data.List

type PP Sum [a] = a

data Product Source #

similar to product

>>> pz @Product [10,4,5,12,3,4]
PresentT 28800
>>> pz @Product []
PresentT 1
Instances
(Num a, Show a) => P Product [a] Source # 
Instance details

Defined in Predicate.Data.List

Associated Types

type PP Product [a] :: Type Source #

Methods

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

type PP Product [a] Source # 
Instance details

Defined in Predicate.Data.List

type PP Product [a] = a

data Min Source #

similar to minimum

>>> pz @Min [10,4,5,12,3,4]
PresentT 3
>>> pz @Min []
FailT "empty list"
Instances
(Ord a, Show a) => P Min [a] Source # 
Instance details

Defined in Predicate.Data.List

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

type PP Min [a] = a

data Max Source #

similar to maximum

>>> pz @Max [10,4,5,12,3,4]
PresentT 12
>>> pz @Max []
FailT "empty list"
Instances
(Ord a, Show a) => P Max [a] Source # 
Instance details

Defined in Predicate.Data.List

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

type PP Max [a] = a