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

Predicate.Data.List

Description

promoted list functions

Synopsis

constructors

data p :+ q infixr 5 Source #

similar to cons

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

Instances

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

Defined in Predicate.Data.List

Associated Types

type PP (p :+ q) x Source #

Methods

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

Show (p :+ q) Source # 
Instance details

Defined in Predicate.Data.List

Methods

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

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

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

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

Defined in Predicate.Data.List

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

data p +: q infixl 5 Source #

similar to snoc

>>> pz @(Snd +: Fst) (99,[1,2,3,4])
Val [1,2,3,4,99]
>>> pz @(Fst +: Snd) ([],5)
Val [5]
>>> pz @(EmptyT [] _ +: 5) 5
Val [5]
>>> pl @('[1,2,3] +: 4) ()
Present [1,2,3,4] ((+:) [1,2,3,4] | p=[1,2,3] | q=4)
Val [1,2,3,4]
>>> pl @(Snd +: Fst) (4,[1,2,3])
Present [1,2,3,4] ((+:) [1,2,3,4] | p=[1,2,3] | q=4)
Val [1,2,3,4]
>>> pl @("abc" +: C "x") ()
Present "abcx" ((+:) "abcx" | p="abc" | q='x')
Val "abcx"
>>> pl @(Fst +: Snd) ("abc" :: T.Text,'x')
Present "abcx" ((+:) "abcx" | p="abc" | q='x')
Val "abcx"

Instances

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

Defined in Predicate.Data.List

Associated Types

type PP (p +: q) x Source #

Methods

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

Show (p +: q) Source # 
Instance details

Defined in Predicate.Data.List

Methods

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

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

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

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

Defined in Predicate.Data.List

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

data p ++ q infixr 5 Source #

similar to (++)

>>> pz @(Fst ++ Snd) ([9,10,11],[1,2,3,4])
Val [9,10,11,1,2,3,4]
>>> pz @(Snd ++ Fst) ([],[5])
Val [5]
>>> pz @(C "xyz" :+ W "ab" ++ W "cdefg") ()
Val "xabcdefg"
>>> pz @([1,2,3] ++ EmptyList _) "somestuff"
Val [1,2,3]

Instances

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

Defined in Predicate.Data.List

Associated Types

type PP (p ++ q) x Source #

Methods

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

Show (p ++ q) Source # 
Instance details

Defined in Predicate.Data.List

Methods

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

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

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

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

Defined in Predicate.Data.List

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

data Singleton p Source #

creates a singleton from a value

>>> pz @(Singleton (C "aBc")) ()
Val "a"
>>> pz @(Singleton Id) False
Val [False]
>>> pz @(Singleton Snd) (False,"hello")
Val ["hello"]

Instances

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

Defined in Predicate.Data.List

Associated Types

type PP (Singleton p) x Source #

Methods

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

Show (Singleton p) Source # 
Instance details

Defined in Predicate.Data.List

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

Defined in Predicate.Data.List

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

destructors

data Uncons Source #

similar to uncons

>>> pz @Uncons [1,2,3,4]
Val (Just (1,[2,3,4]))
>>> pz @Uncons []
Val Nothing
>>> pz @Uncons (Seq.fromList "abc")
Val (Just ('a',fromList "bc"))
>>> pz @Uncons ("xyz" :: T.Text)
Val (Just ('x',"yz"))
>>> pl @Uncons ("asfd" :: T.Text)
Present Just ('a',"sfd") (Uncons Just ('a',"sfd") | "asfd")
Val (Just ('a',"sfd"))
>>> pl @Uncons ("" :: T.Text)
Present Nothing (Uncons Nothing | "")
Val 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])
Val (Just (1,[2,3,4,5]))

Instances

Instances details
Show Uncons Source # 
Instance details

Defined in Predicate.Data.List

(Show (ConsT s), Show s, Cons s s (ConsT s) (ConsT s)) => P Uncons s Source # 
Instance details

Defined in Predicate.Data.List

Associated Types

type PP Uncons s Source #

Methods

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

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]
Val (Just ([1,2,3],4))
>>> pz @Unsnoc []
Val Nothing
>>> pz @Unsnoc ("xyz" :: T.Text)
Val (Just ("xy",'z'))
>>> pl @Unsnoc ("asfd" :: T.Text)
Present Just ("asf",'d') (Unsnoc Just ("asf",'d') | "asfd")
Val (Just ("asf",'d'))
>>> pl @Unsnoc ("" :: T.Text)
Present Nothing (Unsnoc Nothing | "")
Val Nothing
>>> pl @Unsnoc [1..5]
Present Just ([1,2,3,4],5) (Unsnoc Just ([1,2,3,4],5) | [1,2,3,4,5])
Val (Just ([1,2,3,4],5))

Instances

Instances details
Show Unsnoc Source # 
Instance details

Defined in Predicate.Data.List

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

Defined in Predicate.Data.List

Associated Types

type PP Unsnoc s Source #

Methods

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

type PP Unsnoc s Source # 
Instance details

Defined in Predicate.Data.List

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

data Head Source #

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

>>> pz @Head "abcd"
Val 'a'
>>> pl @Head []
Error Head(empty)
Fail "Head(empty)"
>>> pl @(Fst >> Head >> Le 6) ([], True)
Error Head(empty)
Fail "Head(empty)"
>>> pl @Head [1,2,3]
Present 1 (Head 1 | [1,2,3])
Val 1

Instances

Instances details
Show Head Source # 
Instance details

Defined in Predicate.Data.List

Methods

showsPrec :: Int -> Head -> ShowS #

show :: Head -> String #

showList :: [Head] -> ShowS #

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

Defined in Predicate.Data.List

Associated Types

type PP Head x Source #

Methods

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

type PP Head x Source # 
Instance details

Defined in Predicate.Data.List

type PP Head x = ConsT x

data Tail Source #

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

>>> pz @Tail "abcd"
Val "bcd"
>>> pl @Tail [1..5]
Present [2,3,4,5] (Tail [2,3,4,5] | [1,2,3,4,5])
Val [2,3,4,5]
>>> pl @Tail []
Error Tail(empty)
Fail "Tail(empty)"

Instances

Instances details
Show Tail Source # 
Instance details

Defined in Predicate.Data.List

Methods

showsPrec :: Int -> Tail -> ShowS #

show :: Tail -> String #

showList :: [Tail] -> ShowS #

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

Defined in Predicate.Data.List

Associated Types

type PP Tail x Source #

Methods

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

type PP Tail x Source # 
Instance details

Defined in Predicate.Data.List

type PP Tail x = x

data Init Source #

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

>>> pz @Init "abcd"
Val "abc"
>>> pz @Init (T.pack "abcd")
Val "abc"
>>> pz @Init []
Fail "Init(empty)"
>>> pl @Init [1..5]
Present [1,2,3,4] (Init [1,2,3,4] | [1,2,3,4,5])
Val [1,2,3,4]
>>> pl @Init []
Error Init(empty)
Fail "Init(empty)"

Instances

Instances details
Show Init Source # 
Instance details

Defined in Predicate.Data.List

Methods

showsPrec :: Int -> Init -> ShowS #

show :: Init -> String #

showList :: [Init] -> ShowS #

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

Defined in Predicate.Data.List

Associated Types

type PP Init x Source #

Methods

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

type PP Init x Source # 
Instance details

Defined in Predicate.Data.List

type PP Init x = x

data Last Source #

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

>>> pz @Last "abcd"
Val 'd'
>>> pz @Last []
Fail "Last(empty)"
>>> pl @Last [1,2,3]
Present 3 (Last 3 | [1,2,3])
Val 3

Instances

Instances details
Show Last Source # 
Instance details

Defined in Predicate.Data.List

Methods

showsPrec :: Int -> Last -> ShowS #

show :: Last -> String #

showList :: [Last] -> ShowS #

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

Defined in Predicate.Data.List

Associated Types

type PP Last x Source #

Methods

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

type PP Last x Source # 
Instance details

Defined in Predicate.Data.List

type PP Last x = ConsT x

sort

data SortBy p q Source #

sort a list (stable)

>>> pz @(SortBy (Snd ==! Fst) Id) [(10,"ab"),(4,"x"),(20,"bbb")]
Val [(20,"bbb"),(10,"ab"),(4,"x")]
>>> pz @(SortBy 'LT Id) [1,5,2,4,7,0]
Val [1,5,2,4,7,0]
>>> pz @(SortBy 'GT Id) [1,5,2,4,7,0]
Val [0,7,4,2,5,1]
>>> pz @(SortBy ((L11 ==! L21) <> (L12 ==! L22)) Id) [(10,"ab"),(4,"x"),(20,"bbb"),(4,"a"),(4,"y")]
Val [(4,"a"),(4,"x"),(4,"y"),(10,"ab"),(20,"bbb")]
>>> pz @(SortBy ((L11 ==! L21) <> (L22 ==! L12)) Id) [(10,"ab"),(4,"x"),(20,"bbb"),(4,"a"),(4,"y")]
Val [(4,"y"),(4,"x"),(4,"a"),(10,"ab"),(20,"bbb")]
>>> pl @(SortBy (Swap >> Comparing Fst) Snd) ((),[('z',1),('a',10),('m',22)])
Present [('z',1),('m',22),('a',10)] (SortBy [('z',1),('m',22),('a',10)])
Val [('z',1),('m',22),('a',10)]
>>> pl @(SortBy (Comparing Reverse) Id) ["az","by","cx","aa"]
Present ["aa","cx","by","az"] (SortBy ["aa","cx","by","az"])
Val ["aa","cx","by","az"]
>>> pl @(SortBy (If (Fst==5 && Snd==3) (FailT _ (PrintT "pivot=%d value=%d" Id)) 'GT) Snd) ((), [5,7,3,1,6,2,1,3])
Error pivot=5 value=3(2) (Partition(i=1, a=(5,3)) excnt=2 | SortBy)
Fail "pivot=5 value=3(2)"
>>> pl @(SortBy (If (Fst==50 && Snd==3) (FailT _ (PrintT "pivot=%d value=%d" Id)) Compare) Snd) ((), [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])
Val [1,1,2,3,3,5,6,7]

Instances

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

Defined in Predicate.Data.List

Associated Types

type PP (SortBy p q) x Source #

Methods

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

Show (SortBy p q) Source # 
Instance details

Defined in Predicate.Data.List

Methods

showsPrec :: Int -> SortBy p q -> ShowS #

show :: SortBy p q -> String #

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

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

>>> pz @(SortOn Fst Id) [(10,"abc"), (3,"def"), (4,"gg"), (10,"xyz"), (1,"z")]
Val [(1,"z"),(3,"def"),(4,"gg"),(10,"abc"),(10,"xyz")]
>>> pl @(SortOn Id Id) [10,4,2,12,14]
Present [2,4,10,12,14] (SortBy [2,4,10,12,14])
Val [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])
Val [14,12,10,4,2]
>>> pl @(SortOn Fst 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)])
Val [('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) (Partition(i=0, a=(10,4)) excnt=4 | SortBy)
Fail "asdf(4)"
>>> pl @(SortOn Snd Snd) ((),[('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)])
Val [('a',1),('a',10),('z',14),('m',22)]
>>> pl @(SortOn Fst Snd) ((),[('z',1),('a',10),('m',22)])
Present [('a',10),('m',22),('z',1)] (SortBy [('a',10),('m',22),('z',1)])
Val [('a',10),('m',22),('z',1)]
>>> pl @(SortOn Fst 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)])
Val [('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)])
Val [('a',9),('a',10),('m',10),('m',22),('z',1)]

Instances

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

Defined in Predicate.Data.List

Associated Types

type PP (SortOn p q) x Source #

Methods

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

Show (SortOn p q) Source # 
Instance details

Defined in Predicate.Data.List

Methods

showsPrec :: Int -> SortOn p q -> ShowS #

show :: SortOn p q -> String #

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

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 #

like 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])
Val [14,12,10,4,2]
>>> pl @(SortOnDesc Fst Snd) ((),[('z',1),('a',10),('m',22)])
Present [('z',1),('m',22),('a',10)] (SortBy [('z',1),('m',22),('a',10)])
Val [('z',1),('m',22),('a',10)]

Instances

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

Defined in Predicate.Data.List

Associated Types

type PP (SortOnDesc p q) x Source #

Methods

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

Show (SortOnDesc p q) Source # 
Instance details

Defined in Predicate.Data.List

Methods

showsPrec :: Int -> SortOnDesc p q -> ShowS #

show :: SortOnDesc p q -> String #

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

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

Defined in Predicate.Data.List

type PP (SortOnDesc p q :: Type) x

data Sort Source #

simple sort: similar to sort

Instances

Instances details
Show Sort Source # 
Instance details

Defined in Predicate.Data.List

Methods

showsPrec :: Int -> Sort -> ShowS #

show :: Sort -> String #

showList :: [Sort] -> ShowS #

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

Defined in Predicate.Data.List

Associated Types

type PP Sort x Source #

Methods

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

type PP Sort x Source # 
Instance details

Defined in Predicate.Data.List

type PP Sort x

zip related

data Unzip Source #

unzip equivalent

>>> pz @Unzip (zip [1..5] "abcd")
Val ([1,2,3,4],"abcd")

Instances

Instances details
Show Unzip Source # 
Instance details

Defined in Predicate.Data.List

Methods

showsPrec :: Int -> Unzip -> ShowS #

show :: Unzip -> String #

showList :: [Unzip] -> ShowS #

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

Defined in Predicate.Data.List

Associated Types

type PP Unzip x Source #

Methods

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

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]))
Val ([1,2,3,4],"abcd",[True,False,True,False])

Instances

Instances details
Show Unzip3 Source # 
Instance details

Defined in Predicate.Data.List

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

Defined in Predicate.Data.List

Associated Types

type PP Unzip3 x Source #

Methods

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

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")
Val [(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")
Val [(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")
Val [(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")
Fail "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")
Val [(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")
Val [(1 % 1,'a'),(2 % 1,'b'),(3 % 1,'c'),(99 % 4,'d'),(99 % 4,'e')]
>>> pl @(ZipL "X" (EmptyT _ _) Id) "abcd"
Present [("X",'a'),("X",'b'),("X",'c'),("X",'d')] (ZipL [("X",'a'),("X",'b'),("X",'c'),("X",'d')] | p=[] | q="abcd")
Val [("X",'a'),("X",'b'),("X",'c'),("X",'d')]

Instances

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

Defined in Predicate.Data.List

Associated Types

type PP (ZipL l p q) a Source #

Methods

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

Show (ZipL l p q) Source # 
Instance details

Defined in Predicate.Data.List

Methods

showsPrec :: Int -> ZipL l p q -> ShowS #

show :: ZipL l p q -> String #

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

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 (C "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")
Val [(1,'a'),(2,'b'),(3,'c')]
>>> pl @(ZipR (C "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")
Val [(1,'a'),(2,'b'),(3,'Z')]
>>> pl @(ZipR (C "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")
Val [(1,'a'),(2,'Z'),(3,'Z')]
>>> pl @(ZipR (C "Z") '[1,2] "abc") ()
Error ZipR(2,3) rhs would be truncated (p=[1,2] | q="abc")
Fail "ZipR(2,3) rhs would be truncated"
>>> pl @(ZipR (C "Y") (EmptyT _ _) Id) "abcd"
Error ZipR(0,4) rhs would be truncated (p=[] | q="abcd")
Fail "ZipR(0,4) rhs would be truncated"

Instances

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

Defined in Predicate.Data.List

Associated Types

type PP (ZipR r p q) a Source #

Methods

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

Show (ZipR r p q) Source # 
Instance details

Defined in Predicate.Data.List

Methods

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

show :: ZipR r p q -> String #

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

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")
Val [(1,'a'),(2,'b'),(3,'c')]
>>> pl @(Zip '[1,2,3] "ab") ()
Error Zip(3,2) length mismatch (p=[1,2,3] | q="ab")
Fail "Zip(3,2) length mismatch"
>>> pl @(Zip '[1,2] "abc") ()
Error Zip(2,3) length mismatch (p=[1,2] | q="abc")
Fail "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])
Fail "Zip(3,7) length mismatch"

Instances

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

Defined in Predicate.Data.List

Associated Types

type PP (Zip p q) a Source #

Methods

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

Show (Zip p q) Source # 
Instance details

Defined in Predicate.Data.List

Methods

showsPrec :: Int -> Zip p q -> ShowS #

show :: Zip p q -> String #

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

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) (C "a" ... C "e")) ()
Val [(1,'a'),(2,'b'),(3,'c'),(4,'d'),(5,'e')]
>>> pz @(ZipWith (ShowP Fst <> ShowP Snd) (1...5) (C "a" ... C "e")) ()
Val ["1'a'","2'b'","3'c'","4'd'","5'e'"]
>>> pz @(ZipWith (MkThese Fst Snd) (1...6) (C "a" ... C "f")) ()
Val [These 1 'a',These 2 'b',These 3 'c',These 4 'd',These 5 'e',These 6 'f']
>>> pz @(ZipWith (MkThese Fst Snd) '[] (C "a" ... C "f")) ()
Fail "ZipWith(0,6) length mismatch"
>>> pz @(ZipWith (MkThese Fst Snd) (1...3) (C "a" ... C "f")) ()
Fail "ZipWith(3,6) length mismatch"

Instances

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

Defined in Predicate.Data.List

Associated Types

type PP (ZipWith p q r) a Source #

Methods

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

Show (ZipWith p q r) Source # 
Instance details

Defined in Predicate.Data.List

Methods

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

show :: ZipWith p q r -> String #

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

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))]

data ZipCartesian p q Source #

zip cartesian product for lists: see LiftA2 for Applicative version

>>> pz @(ZipCartesian (EnumFromTo Fst Snd) ('LT ... 'GT)) (10,11)
Val [(10,LT),(10,EQ),(10,GT),(11,LT),(11,EQ),(11,GT)]
>>> pz @(ZipCartesian '[ '() ] (1 ... 5)) True
Val [((),1),((),2),((),3),((),4),((),5)]

Instances

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

Defined in Predicate.Data.List

Associated Types

type PP (ZipCartesian p q) x Source #

Methods

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

Show (ZipCartesian p q) Source # 
Instance details

Defined in Predicate.Data.List

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

Defined in Predicate.Data.List

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

data ZipPad l r p q Source #

Zip two lists to their maximum length using optional padding

>>> pz @(ZipPad (C "Z") 99 Fst Snd) ("abc", [1..5])
Val [('a',1),('b',2),('c',3),('Z',4),('Z',5)]
>>> pz @(ZipPad (C "Z") 99 Fst Snd) ("abcdefg", [1..5])
Val [('a',1),('b',2),('c',3),('d',4),('e',5),('f',99),('g',99)]
>>> pz @(ZipPad (C "Z") 99 Fst Snd) ("abcde", [1..5])
Val [('a',1),('b',2),('c',3),('d',4),('e',5)]
>>> pz @(ZipPad (C "Z") 99 Fst Snd) ("", [1..5])
Val [('Z',1),('Z',2),('Z',3),('Z',4),('Z',5)]
>>> pz @(ZipPad (C "Z") 99 Fst Snd) ("abcde", [])
Val [('a',99),('b',99),('c',99),('d',99),('e',99)]

Instances

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

Defined in Predicate.Data.List

Associated Types

type PP (ZipPad l r p q) a Source #

Methods

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

Show (ZipPad l r p q) Source # 
Instance details

Defined in Predicate.Data.List

Methods

showsPrec :: Int -> ZipPad l r p q -> ShowS #

show :: ZipPad l r p q -> String #

showList :: [ZipPad l r p q] -> ShowS #

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

Defined in Predicate.Data.List

type PP (ZipPad l r p q :: Type) a = [(PP l a, 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]
Val ([10,4,7,3,3,5],[1,1])
>>> pz @(Partition IsPrime Id) [10,4,1,7,3,1,3,5]
Val ([7,3,3,5],[10,4,1,1])
>>> pz @(Partition (Ge 300) Id) [10,4,1,7,3,1,3,5]
Val ([],[10,4,1,7,3,1,3,5])
>>> pz @(Partition (Id < 300) Id) [10,4,1,7,3,1,3,5]
Val ([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])})
Val ([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])
Val ([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])
Val ([2,4,6],[1,3,5])
>>> pl @(Partition Even Id >> Null *** (Len > 4) >> Fst == Snd) [1..6]
True ((>>) True | {False == False})
Val True
>>> pl @(Partition (ExitWhen "ExitWhen" (Gt 10) >> Gt 2) Id) [1..11]
Error ExitWhen (Partition(i=10, a=11) excnt=1)
Fail "ExitWhen"
>>> pl @(Partition IsPrime 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])
Val ([2,3,5,7,11,13],[1,4,6,8,9,10,12,14,15])

Instances

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

Defined in Predicate.Data.List

Associated Types

type PP (Partition p q) a Source #

Methods

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

Show (Partition p q) Source # 
Instance details

Defined in Predicate.Data.List

Methods

showsPrec :: Int -> Partition p q -> ShowS #

show :: Partition p q -> String #

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

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 Quant p Source #

counts number on matches and non matches: ie All is length snd==0 and Any is length fst > 0

>>> pz @(Quant Even) [2,3,3,7,2,8,1,5,9]
Val (3,6)
>>> pz @(Quant (Gt 10)) [2,8,1,5,9]
Val (0,5)
>>> pz @(Quant (Gt 10)) []
Val (0,0)
>>> pz @(Quant (Same 4)) [3]
Val (0,1)
>>> pz @(Quant (Same 4)) [4]
Val (1,0)

Instances

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

Defined in Predicate.Data.List

Associated Types

type PP (Quant p) x Source #

Methods

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

Show (Quant p) Source # 
Instance details

Defined in Predicate.Data.List

Methods

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

show :: Quant p -> String #

showList :: [Quant p] -> ShowS #

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

Defined in Predicate.Data.List

type PP (Quant p :: Type) x

data All1 p Source #

similar to All for non-empty lists

>>> pz @(All1 Even) [2,4,6]
Val True
>>> pz @(All1 Even) [2,3,3,7,2,8,1,5,9]
Val False
>>> pz @(All1 Even) []
Val False
>>> pz @(All1 Even) [1]
Val False
>>> pz @(All1 Even) [2]
Val True

Instances

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

Defined in Predicate.Data.List

Associated Types

type PP (All1 p) x Source #

Methods

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

Show (All1 p) Source # 
Instance details

Defined in Predicate.Data.List

Methods

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

show :: All1 p -> String #

showList :: [All1 p] -> ShowS #

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

Defined in Predicate.Data.List

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

data PartitionBy t p q Source #

partition values based on a function

>>> pz @(PartitionBy Ordering (Id ==! 0)  Id) [17,3,-12,0,1,0,-3]
Val (fromList [(LT,[-3,-12]),(EQ,[0,0]),(GT,[1,3,17])])
>>> pz @(PartitionBy Char (Mod Id 16 >> ShowBase 16 >> Head) Id) [-4,-2,5,0,15,12,-1,2,-3,4,0]
Val (fromList [('0',[0,0]),('2',[2]),('4',[4]),('5',[5]),('c',[12,-4]),('d',[-3]),('e',[-2]),('f',[-1,15])])
>>> 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])
Val (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)
Fail "xyzxyzxyzzyyysyfsyfydf"
>>> pz @(PartitionBy Ordering (Case 'EQ '[Id < 0, Id > 0] '[ 'LT, 'GT] Id) Id) [-4,-2,5,6,7,0,-1,2,-3,4,0]
Val (fromList [(LT,[-3,-1,-2,-4]),(EQ,[0,0]),(GT,[4,2,7,6,5])])

Instances

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

Defined in Predicate.Data.List

Associated Types

type PP (PartitionBy t p q) a Source #

Methods

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

Show (PartitionBy t p q) Source # 
Instance details

Defined in Predicate.Data.List

Methods

showsPrec :: Int -> PartitionBy t p q -> ShowS #

show :: PartitionBy t p q -> String #

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

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 Group Source #

similar to group

>>> pz @Group [1,3,4,5,1,5,5]
Val [[1],[3],[4],[5],[1],[5,5]]
>>> pz @(Sort >> Group) [1,3,4,5,1,5,5]
Val [[1,1],[3],[4],[5,5,5]]

Instances

Instances details
Show Group Source # 
Instance details

Defined in Predicate.Data.List

Methods

showsPrec :: Int -> Group -> ShowS #

show :: Group -> String #

showList :: [Group] -> ShowS #

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

Defined in Predicate.Data.List

Associated Types

type PP Group x Source #

Methods

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

type PP Group x Source # 
Instance details

Defined in Predicate.Data.List

type PP Group x

data GroupBy p q Source #

similar to groupBy

>>> pz @(GroupBy (Fst == Snd) Id) [1,3,4,5,1,5,5]
Val [[1],[3],[4],[5],[1],[5,5]]
>>> pz @(GroupBy (Fst == Snd) Id) [1,1,1,3,4,5,1,5,5]
Val [[1,1,1],[3],[4],[5],[1],[5,5]]
>>> pz @(GroupBy (Fst == Snd) Id) [5,5]
Val [[5,5]]
>>> pz @(GroupBy (Fst == Snd) Id) [1,2]
Val [[1],[2]]
>>> pz @(GroupBy (Fst == Snd) Id) [1]
Val [[1]]
>>> pz @(GroupBy (Fst == Snd) Id) []
Val []
>>> pz @(GroupBy (Fst < Snd) Id) [1,2,3,4,4,1,2]
Val [[1,2,3,4],[4],[1,2]]
>>> pz @(GroupBy (Fst /= Snd) Id) [1,2,3,4,4,4,1]
Val [[1,2,3,4],[4],[4,1]]
>>> pan @(GroupBy (Fst == Snd) 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'
Val ["h","e","ll","o","    ","g","oo","d","b","y","e"]
>>> pz @(GroupBy (Fst == Snd)  Id) (map (uncurry SG.Arg) [(10,0),(9,4),(9,3),(1,1),(9,6)])
Val [[Arg 10 0],[Arg 9 4,Arg 9 3],[Arg 1 1],[Arg 9 6]]

Instances

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

Defined in Predicate.Data.List

Associated Types

type PP (GroupBy p q) a Source #

Methods

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

Show (GroupBy p q) Source # 
Instance details

Defined in Predicate.Data.List

Methods

showsPrec :: Int -> GroupBy p q -> ShowS #

show :: GroupBy p q -> String #

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

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 GroupCnt Source #

similar to Group but returns the value and count

>>> pz @GroupCnt [1,3,4,5,1,5,5]
Val [(1,1),(3,1),(4,1),(5,1),(1,1),(5,2)]
>>> pz @(Sort >> GroupCnt) [1,3,4,5,1,5,5]
Val [(1,2),(3,1),(4,1),(5,3)]
>>> pz @(Sort >> GroupCnt) "xyabxaaaz"
Val [('a',4),('b',1),('x',2),('y',1),('z',1)]

Instances

Instances details
Show GroupCnt Source # 
Instance details

Defined in Predicate.Data.List

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

Defined in Predicate.Data.List

Associated Types

type PP GroupCnt x Source #

Methods

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

type PP GroupCnt x Source # 
Instance details

Defined in Predicate.Data.List

type PP GroupCnt x

data GroupCntStable Source #

version of GroupCnt that retains the original ordering

>>> pz @GroupCntStable "bababab"
Val [('b',4),('a',3)]
>>> pz @GroupCntStable "fedbfefa"
Val [('f',3),('e',2),('d',1),('b',1),('a',1)]
>>> pz @GroupCntStable "fedc"
Val [('f',1),('e',1),('d',1),('c',1)]
>>> pz @GroupCntStable "ffff"
Val [('f',4)]
>>> pz @GroupCntStable ""
Val []

Instances

Instances details
Show GroupCntStable Source # 
Instance details

Defined in Predicate.Data.List

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

Defined in Predicate.Data.List

Associated Types

type PP GroupCntStable a Source #

Methods

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

type PP GroupCntStable a Source # 
Instance details

Defined in Predicate.Data.List

data Filter p q Source #

similar to filter

>>> pz @(Filter (Gt 4) Id) [10,1,3,5,-10,12,1]
Val [10,5,12]

Instances

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

Defined in Predicate.Data.List

Associated Types

type PP (Filter p q) x Source #

Methods

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

Show (Filter p q) Source # 
Instance details

Defined in Predicate.Data.List

Methods

showsPrec :: Int -> Filter p q -> ShowS #

show :: Filter p q -> String #

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

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]
Val ([],[10,4,1,7,3,1,3,5])
>>> pz @(Break (Lt 3) Id) [10,4,1,7,3,1,3,5]
Val ([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))
Val ([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))
Val ([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))
Val ([1,2],[3,4,5,6,7,8])
>>> pl @(Break (If (Gt 2) (FailT _ "ASfd") 'False) Id) [1..8]
Error ASfd (If 'True | Break predicate failed)
Fail "ASfd"
>>> pl @(Break Snd 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))
Val ([(1,False),(2,False),(3,False)],[(4,True),(5,True),(6,False)])
>>> pl @(Break Snd Id) (zip [1..] [False,False,False,False])
Present ([(1,False),(2,False),(3,False),(4,False)],[]) (Break cnt=(4,0))
Val ([(1,False),(2,False),(3,False),(4,False)],[])
>>> pl @(Break Snd Id) (zip [1..] [True,True,True,True])
Present ([],[(1,True),(2,True),(3,True),(4,True)]) (Break cnt=(0,4))
Val ([],[(1,True),(2,True),(3,True),(4,True)])

Instances

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

Defined in Predicate.Data.List

Associated Types

type PP (Break p q) a Source #

Methods

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

Show (Break p q) Source # 
Instance details

Defined in Predicate.Data.List

Methods

showsPrec :: Int -> Break p q -> ShowS #

show :: Break p q -> String #

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

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))
Val ([1,2,3],[4,5,6,7,8,9,10,11])

Instances

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

Defined in Predicate.Data.List

Associated Types

type PP (Span p q) x Source #

Methods

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

Show (Span p q) Source # 
Instance details

Defined in Predicate.Data.List

Methods

showsPrec :: Int -> Span p q -> ShowS #

show :: Span p q -> String #

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

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

Instances

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

Defined in Predicate.Data.List

Associated Types

type PP (Intercalate p q) x Source #

Methods

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

Show (Intercalate p q) Source # 
Instance details

Defined in Predicate.Data.List

Methods

showsPrec :: Int -> Intercalate p q -> ShowS #

show :: Intercalate p q -> String #

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

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

data PartitionsBy p q r Source #

experimental: sorts then partitions and then sorts each partitions based on the leftmost occurring value in the original list if the existing order of data is fine then use GroupBy as you do not need this

>>> pz @(PartitionsBy (Fst ==! Snd) (L11 == L21) Id) [10,9,9,1,9]
Val [[10],[9,9,9],[1]]
>>> pz @(PartitionsBy Compare (L11 < L21) Id) "efaffabec"
Val ["a","f","f","abce","ef"]
>>> pz @(PartitionsBy 'GT 'True Id) "efaffabec"
Val ["cebaffafe"]
>>> pz @(PartitionsBy 'GT 'False Id) "efaffabec"
Val ["e","f","a","f","f","a","b","e","c"]
>>> pz @(PartitionsBy (Fst ==! Snd) (L12 > L22) Id) [10,9,9,1,9,4]
Val [[9],[1],[9,10],[4,9]]
>>> pz @(PartitionsBy (L11 ==! L21) (L12 > L22) Id) "eddadc"
Val ["d","a","de","cd"]
>>> pz @(PartitionsBy (L11 ==! L21) (L11 < L21) Id) [10,9,9,1,9,4]
Val [[9],[1,4,9],[9,10]]
>>> pz @(PartitionsBy (Fst ==! Snd) (L11 == L21) Id) (map (uncurry SG.Arg) [(10,0),(9,4),(9,3),(1,1),(9,6)])
Val [[Arg 10 0],[Arg 9 4,Arg 9 3,Arg 9 6],[Arg 1 1]]

Instances

Instances details
P (PartitionsByT p q r) x => P (PartitionsBy p q r :: Type) x Source # 
Instance details

Defined in Predicate.Data.List

Associated Types

type PP (PartitionsBy p q r) x Source #

Methods

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

Show (PartitionsBy p q r) Source # 
Instance details

Defined in Predicate.Data.List

Methods

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

show :: PartitionsBy p q r -> String #

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

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

Defined in Predicate.Data.List

type PP (PartitionsBy p q r :: Type) x

data IMap p q Source #

add an index to map

>>> pz @(IMap (Second Succ) Id) "hello"
Val [(0,'i'),(1,'f'),(2,'m'),(3,'m'),(4,'p')]
>>> pz @(IMap (10 ^ Fst * Snd) Id >> Sum) [3,2,7,9]
Val 9723
>>> pz @(IMap (2 ^ Fst * Snd) Id) [1,1,1,0,1,0,1]
Val [1,2,4,0,16,0,64]
>>> pz @(Rescan "^(\\d+)\\.(\\d+)\\.(\\d+)\\.(\\d+)$" >> Map (Snd >> IMap (GuardBool (PrintT "bad value=%d %s" Id) (Snd >> ReadP Int Id < 255)) Id)) "123.222.999.3"
Fail "bad value=2 999"
>>> pz @(Rescan "^(\\d+)\\.(\\d+)\\.(\\d+)\\.(\\d+)$" >> Map (Snd >> IMap (GuardBool (PrintT "bad value=%d %s" Id) (Snd >> ReadP Int Id < 255)) Id)) "123.222.99.3"
Val [[True,True,True,True]]

Instances

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

Defined in Predicate.Data.List

Associated Types

type PP (IMap p q) x Source #

Methods

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

Show (IMap p q) Source # 
Instance details

Defined in Predicate.Data.List

Methods

showsPrec :: Int -> IMap p q -> ShowS #

show :: IMap p q -> String #

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

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

Defined in Predicate.Data.List

type PP (IMap p q :: Type) x

data IList Source #

add an index to list

>>> pz @IList "abcdef"
Val [(0,'a'),(1,'b'),(2,'c'),(3,'d'),(4,'e'),(5,'f')]

Instances

Instances details
Show IList Source # 
Instance details

Defined in Predicate.Data.List

Methods

showsPrec :: Int -> IList -> ShowS #

show :: IList -> String #

showList :: [IList] -> ShowS #

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

Defined in Predicate.Data.List

Associated Types

type PP IList x Source #

Methods

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

type PP IList x Source # 
Instance details

Defined in Predicate.Data.List

type PP IList x

miscellaneous

data Elem p q Source #

elem function

>>> pz @(Elem Fst Snd) ('x',"abcdxy")
Val True
>>> pz @(Elem Fst Snd) ('z',"abcdxy")
Val False
>>> pl @(Elem Id '[2,3,4]) 2
True (2 `elem` [2,3,4])
Val True
>>> pl @(Elem Id '[2,3,4]) 6
False (6 `elem` [2,3,4])
Val False
>>> pl @(Elem Id '[13 % 2]) 6.5
True (13 % 2 `elem` [13 % 2])
Val True
>>> pl @(Elem Id '[13 % 2, 12 % 1]) 6.5
True (13 % 2 `elem` [13 % 2,12 % 1])
Val True
>>> pl @(Elem Id '[13 % 2, 12 % 1]) 6
False (6 % 1 `elem` [13 % 2,12 % 1])
Val False

Instances

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

Defined in Predicate.Data.List

Associated Types

type PP (Elem p q) a Source #

Methods

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

Show (Elem p q) Source # 
Instance details

Defined in Predicate.Data.List

Methods

showsPrec :: Int -> Elem p q -> ShowS #

show :: Elem p q -> String #

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

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]
Val [[],[4],[4,8],[4,8,3],[4,8,3,9]]
>>> pz @Inits []
Val [[]]

Instances

Instances details
Show Inits Source # 
Instance details

Defined in Predicate.Data.List

Methods

showsPrec :: Int -> Inits -> ShowS #

show :: Inits -> String #

showList :: [Inits] -> ShowS #

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

Defined in Predicate.Data.List

Associated Types

type PP Inits x Source #

Methods

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

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]
Val [[4,8,3,9],[8,3,9],[3,9],[9],[]]
>>> pz @Tails []
Val [[]]
>>> pl @Tails "abcd"
Present ["abcd","bcd","cd","d",""] (Tails ["abcd","bcd","cd","d",""] | "abcd")
Val ["abcd","bcd","cd","d",""]

Instances

Instances details
Show Tails Source # 
Instance details

Defined in Predicate.Data.List

Methods

showsPrec :: Int -> Tails -> ShowS #

show :: Tails -> String #

showList :: [Tails] -> ShowS #

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

Defined in Predicate.Data.List

Associated Types

type PP Tails x Source #

Methods

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

type PP Tails x Source # 
Instance details

Defined in Predicate.Data.List

type PP Tails x = [x]

data Ones Source #

split a list into single values

>>> pz @Ones [4,8,3,9]
Val [[4],[8],[3],[9]]
>>> pz @Ones []
Val []

Instances

Instances details
Show Ones Source # 
Instance details

Defined in Predicate.Data.List

Methods

showsPrec :: Int -> Ones -> ShowS #

show :: Ones -> String #

showList :: [Ones] -> ShowS #

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

Defined in Predicate.Data.List

Associated Types

type PP Ones x Source #

Methods

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

type PP Ones x Source # 
Instance details

Defined in Predicate.Data.List

type PP Ones x = [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])
Val [0,0,1,2,3]
>>> pz @(PadL 5 999 Id) [12,13]
Val [999,999,999,12,13]
>>> pz @(PadR 5 Fst '[12,13]) (999,'x')
Val [12,13,999,999,999]
>>> pz @(PadR 2 Fst '[12,13,14]) (999,'x')
Val [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])
Val [0,0,0,0,0,0,0,1,2,3]

Instances

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

Defined in Predicate.Data.List

Associated Types

type PP (PadL n p q) x Source #

Methods

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

Show (PadL n p q) Source # 
Instance details

Defined in Predicate.Data.List

Methods

showsPrec :: Int -> PadL n p q -> ShowS #

show :: PadL n p q -> String #

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

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])
Val [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])
Val [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])
Val [1,2,3,4,5,6]

Instances

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

Defined in Predicate.Data.List

Associated Types

type PP (PadR n p q) x Source #

Methods

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

Show (PadR n p q) Source # 
Instance details

Defined in Predicate.Data.List

Methods

showsPrec :: Int -> PadR n p q -> ShowS #

show :: PadR n p q -> String #

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

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"
Val ["he","llo"," ","w","orld"]
>>> pz @(SplitAts '[2] Id) "hello world"
Val ["he","llo world"]
>>> pz @(SplitAts '[10,1,1,5] Id) "hello world"
Val ["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])
Val [[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]],[[],[]])})
Val [[1,2,3],[4]]

Instances

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

Defined in Predicate.Data.List

Associated Types

type PP (SplitAts ns p) x Source #

Methods

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

Show (SplitAts ns p) Source # 
Instance details

Defined in Predicate.Data.List

Methods

showsPrec :: Int -> SplitAts ns p -> ShowS #

show :: SplitAts ns p -> String #

showList :: [SplitAts ns p] -> ShowS #

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

Instances

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

Defined in Predicate.Data.List

Associated Types

type PP (SplitAt n p) a Source #

Methods

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

Show (SplitAt n p) Source # 
Instance details

Defined in Predicate.Data.List

Methods

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

show :: SplitAt n p -> String #

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

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 Source #

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

>>> pz @(ChunksOf 2) "abcdef"
Val ["ab","cd","ef"]
>>> pz @(ChunksOf 2) "abcdefg"
Val ["ab","cd","ef","g"]
>>> pz @(ChunksOf 2) ""
Val []
>>> pz @(ChunksOf 2) "a"
Val ["a"]
>>> pz @(PadR (Len + RoundUp 5 Len) 999 Id >> ChunksOf 5) [1..17]
Val [[1,2,3,4,5],[6,7,8,9,10],[11,12,13,14,15],[16,17,999,999,999]]
>>> pz @(PadR (Len + RoundUp 5 Len) 999 Id >> ChunksOf 5) [1..15]
Val [[1,2,3,4,5],[6,7,8,9,10],[11,12,13,14,15]]

Instances

Instances details
P (ChunksOfT n) x => P (ChunksOf n :: Type) x Source # 
Instance details

Defined in Predicate.Data.List

Associated Types

type PP (ChunksOf n) x Source #

Methods

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

Show (ChunksOf n) Source # 
Instance details

Defined in Predicate.Data.List

Methods

showsPrec :: Int -> ChunksOf n -> ShowS #

show :: ChunksOf n -> String #

showList :: [ChunksOf n] -> ShowS #

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

Defined in Predicate.Data.List

type PP (ChunksOf n :: Type) x

data ChunksOf' n i p Source #

splits a list pointed to by p into lists of size n with a gap of i

>>> pz @(Unfoldr (If Null (MkNothing _) (MkJust '(Take 3 Id,Drop 2 Id))) Id) [1..10]
Val [[1,2,3],[3,4,5],[5,6,7],[7,8,9],[9,10]]
>>> pz @(ChunksOf' 3 2 Id) [1..10]
Val [[1,2,3],[3,4,5],[5,6,7],[7,8,9],[9,10]]

Instances

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

Defined in Predicate.Data.List

Associated Types

type PP (ChunksOf' n i p) a Source #

Methods

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

Show (ChunksOf' n i p) Source # 
Instance details

Defined in Predicate.Data.List

Methods

showsPrec :: Int -> ChunksOf' n i p -> ShowS #

show :: ChunksOf' n i p -> String #

showList :: [ChunksOf' n i p] -> ShowS #

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

Defined in Predicate.Data.List

type PP (ChunksOf' n i 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]
Val [1,2,3,4]
>>> pz @(Rotate (Negate 1) Id) [1,2,3,4]
Val [4,1,2,3]
>>> pz @(Rotate 2 Id) [1,2,3,4]
Val [3,4,1,2]
>>> pz @(Map (Rotate Id "abcd")) [-3..7]
Val ["bcda","cdab","dabc","abcd","bcda","cdab","dabc","abcd","bcda","cdab","dabc"]

Instances

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

Defined in Predicate.Data.List

Associated Types

type PP (Rotate n p) x Source #

Methods

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

Show (Rotate n p) Source # 
Instance details

Defined in Predicate.Data.List

Methods

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

show :: Rotate n p -> String #

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

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 #

take n values from a list p: similar to take

>>> pz @(Take 3 Id) "abcdef"
Val "abc"
>>> pz @(Take 3 Id) "ab"
Val "ab"
>>> pz @(Take 10 Id) "abcdef"
Val "abcdef"
>>> pz @(Take 0 Id) "abcdef"
Val ""
>>> pz @(Take 10 Id) ""
Val ""

Instances

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

Defined in Predicate.Data.List

Associated Types

type PP (Take n p) x Source #

Methods

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

Show (Take n p) Source # 
Instance details

Defined in Predicate.Data.List

Methods

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

show :: Take n p -> String #

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

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 #

drop n values from a list p: similar to drop

Instances

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

Defined in Predicate.Data.List

Associated Types

type PP (Drop n p) x Source #

Methods

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

Show (Drop n p) Source # 
Instance details

Defined in Predicate.Data.List

Methods

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

show :: Drop n p -> String #

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

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]) ()
Val [1,2,2]
>>> pz @(Remove '[0,1,1,5] '[1,5,5,2,5,2]) ()
Val [2,2]
>>> pz @(Remove '[99] '[1,5,5,2,5,2]) ()
Val [1,5,5,2,5,2]
>>> pz @(Remove '[99,91] '[1,5,5,2,5,2]) ()
Val [1,5,5,2,5,2]
>>> pz @(Remove Id '[1,5,5,2,5,2]) []
Val [1,5,5,2,5,2]
>>> pz @(Remove '[] '[1,5,5,2,5,2]) 44 -- works if you make this a number!
Val [1,5,5,2,5,2]

Instances

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

Defined in Predicate.Data.List

Associated Types

type PP (Remove p q) x Source #

Methods

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

Show (Remove p q) Source # 
Instance details

Defined in Predicate.Data.List

Methods

showsPrec :: Int -> Remove p q -> ShowS #

show :: Remove p q -> String #

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

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]) ()
Val [5,5,5]
>>> pz @(Keep '[0,1,1,5] '[1,5,5,2,5,2]) ()
Val [1,5,5,5]

Instances

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

Defined in Predicate.Data.List

Associated Types

type PP (Keep p q) x Source #

Methods

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

Show (Keep p q) Source # 
Instance details

Defined in Predicate.Data.List

Methods

showsPrec :: Int -> Keep p q -> ShowS #

show :: Keep p q -> String #

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

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]
Val [4,2,1]
>>> pz @Reverse "AbcDeF"
Val "FeDcbA"

Instances

Instances details
Show Reverse Source # 
Instance details

Defined in Predicate.Data.List

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

Defined in Predicate.Data.List

Associated Types

type PP Reverse x Source #

Methods

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

type PP Reverse x Source # 
Instance details

Defined in Predicate.Data.List

type PP Reverse x = x

data ReverseL Source #

reverses using reversing

>>> pz @ReverseL (T.pack "AbcDeF")
Val "FeDcbA"
>>> pz @ReverseL "AbcDeF"
Val "FeDcbA"
>>> pl @ReverseL ("asfd" :: T.Text)
Present "dfsa" (ReverseL "dfsa" | "asfd")
Val "dfsa"

Instances

Instances details
Show ReverseL Source # 
Instance details

Defined in Predicate.Data.List

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

Defined in Predicate.Data.List

Associated Types

type PP ReverseL t Source #

Methods

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

type PP ReverseL t Source # 
Instance details

Defined in Predicate.Data.List

type PP ReverseL t = t

data Nub Source #

similar to nub

>>> pz @Nub "abcdbc"
Val "abcd"
>>> pz @Nub []
Val []
>>> pz @Nub [1,4,1,1,1,1,1]
Val [1,4]

Instances

Instances details
Show Nub Source # 
Instance details

Defined in Predicate.Data.List

Methods

showsPrec :: Int -> Nub -> ShowS #

show :: Nub -> String #

showList :: [Nub] -> ShowS #

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

Defined in Predicate.Data.List

Associated Types

type PP Nub x Source #

Methods

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

type PP Nub x Source # 
Instance details

Defined in Predicate.Data.List

type PP Nub x = x

data Sum Source #

similar to sum

>>> pz @Sum [10,4,5,12,3,4]
Val 38
>>> pz @Sum []
Val 0
>>> pz @(1 ... 10 >> Sum) ()
Val 55

Instances

Instances details
Show Sum Source # 
Instance details

Defined in Predicate.Data.List

Methods

showsPrec :: Int -> Sum -> ShowS #

show :: Sum -> String #

showList :: [Sum] -> ShowS #

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

Defined in Predicate.Data.List

Associated Types

type PP Sum x Source #

Methods

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

type PP Sum x Source # 
Instance details

Defined in Predicate.Data.List

type PP Sum x = ExtractAFromTA x

data Product Source #

similar to product

>>> pz @Product [10,4,5,12,3,4]
Val 28800
>>> pz @Product []
Val 1

Instances

Instances details
Show Product Source # 
Instance details

Defined in Predicate.Data.List

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

Defined in Predicate.Data.List

Associated Types

type PP Product x Source #

Methods

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

type PP Product x Source # 
Instance details

Defined in Predicate.Data.List

data Min Source #

similar to minimum

>>> pz @Min [10,4,5,12,3,4]
Val 3
>>> pz @Min []
Fail "empty list"

Instances

Instances details
Show Min Source # 
Instance details

Defined in Predicate.Data.List

Methods

showsPrec :: Int -> Min -> ShowS #

show :: Min -> String #

showList :: [Min] -> ShowS #

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

Defined in Predicate.Data.List

Associated Types

type PP Min x Source #

Methods

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

type PP Min x Source # 
Instance details

Defined in Predicate.Data.List

type PP Min x = ExtractAFromTA x

data Max Source #

similar to maximum

>>> pz @Max [10,4,5,12,3,4]
Val 12
>>> pz @Max []
Fail "empty list"

Instances

Instances details
Show Max Source # 
Instance details

Defined in Predicate.Data.List

Methods

showsPrec :: Int -> Max -> ShowS #

show :: Max -> String #

showList :: [Max] -> ShowS #

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

Defined in Predicate.Data.List

Associated Types

type PP Max x Source #

Methods

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

type PP Max x Source # 
Instance details

Defined in Predicate.Data.List

type PP Max x = ExtractAFromTA x

data IsPrefix p q Source #

similar to isPrefixOf

>>> pl @(IsPrefix '[2,3] Id) [2,3,4]
True (IsPrefix | [2,3] [2,3,4])
Val True
>>> pl @(IsPrefix '[2,3] Id) [1,2,3]
False (IsPrefix | [2,3] [1,2,3])
Val False
>>> pl @(IsPrefix "xy" Id) "xyzabw"
True (IsPrefix | "xy" "xyzabw")
Val True
>>> pl @(IsPrefix "ab" Id) "xyzbaw"
False (IsPrefix | "ab" "xyzbaw")
Val False
>>> pz @(IsPrefix "abc" "aBcbCd") ()
Val False

Instances

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

Defined in Predicate.Data.List

Associated Types

type PP (IsPrefix p q) x Source #

Methods

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

Show (IsPrefix p q) Source # 
Instance details

Defined in Predicate.Data.List

Methods

showsPrec :: Int -> IsPrefix p q -> ShowS #

show :: IsPrefix p q -> String #

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

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

Defined in Predicate.Data.List

type PP (IsPrefix p q :: Type) x

data IsInfix p q Source #

similar to isInfixOf

>>> pl @(IsInfix '[2,3] Id) [1,2,3]
True (IsInfix | [2,3] [1,2,3])
Val True
>>> pl @(IsInfix '[2,3] Id) [1,2,1,3]
False (IsInfix | [2,3] [1,2,1,3])
Val False
>>> pl @(IsInfix "ab" Id) "xyzabw"
True (IsInfix | "ab" "xyzabw")
Val True
>>> pl @(IsInfix "aB" Id) "xyzAbw"
False (IsInfix | "aB" "xyzAbw")
Val False
>>> pl @(IsInfix "ab" Id) "xyzbaw"
False (IsInfix | "ab" "xyzbaw")
Val False
>>> pl @(IsInfix Fst Snd) ("ab","xyzabw")
True (IsInfix | "ab" "xyzabw")
Val True

Instances

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

Defined in Predicate.Data.List

Associated Types

type PP (IsInfix p q) x Source #

Methods

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

Show (IsInfix p q) Source # 
Instance details

Defined in Predicate.Data.List

Methods

showsPrec :: Int -> IsInfix p q -> ShowS #

show :: IsInfix p q -> String #

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

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

Defined in Predicate.Data.List

type PP (IsInfix p q :: Type) x

data IsSuffix p q Source #

similar to isSuffixOf

>>> pl @(IsSuffix '[2,3] Id) [1,2,3]
True (IsSuffix | [2,3] [1,2,3])
Val True
>>> pl @(IsSuffix '[2,3] Id) [2,3,4]
False (IsSuffix | [2,3] [2,3,4])
Val False
>>> pl @(IsSuffix "bw" Id) "xyzabw"
True (IsSuffix | "bw" "xyzabw")
Val True
>>> pl @(IsSuffix "bw" Id) "xyzbaw"
False (IsSuffix | "bw" "xyzbaw")
Val False
>>> pz @(IsSuffix "bCd" "aBcbCd") ()
Val True

Instances

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

Defined in Predicate.Data.List

Associated Types

type PP (IsSuffix p q) x Source #

Methods

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

Show (IsSuffix p q) Source # 
Instance details

Defined in Predicate.Data.List

Methods

showsPrec :: Int -> IsSuffix p q -> ShowS #

show :: IsSuffix p q -> String #

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

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

Defined in Predicate.Data.List

type PP (IsSuffix p q :: Type) x