| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Predicate.Data.List
Description
promoted list functions
Synopsis
- data p :+ q
- data p +: q
- data p ++ q
- data Singleton p
- data EmptyT (t :: Type -> Type)
- data EmptyList (t :: Type)
- data EmptyList' t
- data Uncons
- data Unsnoc
- data Head
- data Tail
- data Init
- data Last
- data SortBy p q
- data SortOn p q
- data SortOnDesc p q
- data Sort
- data Unzip
- data Unzip3
- data ZipL l p q
- data ZipR r p q
- data Zip p q
- data ZipWith p q r
- data ZipCartesian p q
- data ZipPad l r p q
- data Partition p q
- data Quant p
- data All1 p
- data PartitionBy t p q
- data Group
- data GroupBy p q
- data GroupCnt
- data GroupCntStable
- data Filter p q
- data Break p q
- data Span p q
- data Intercalate p q
- data Elem p q
- data Inits
- data Tails
- data Ones
- data PadL n p q
- data PadR n p q
- data SplitAts ns p
- data SplitAt n p
- data ChunksOf n
- data ChunksOf' n i p
- data Rotate n p
- data Take n p
- data Drop n p
- data Remove p q
- data Keep p q
- data Reverse
- data ReverseL
- data Nub
- data Sum
- data Product
- data Min
- data Max
- data IsPrefix p q
- data IsInfix p q
- data IsSuffix p q
constructors
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 @(FlipT (:+) 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 @(FlipT (:+) '[1,2,3] 5) ()Present [5,1,2,3] ((:+) [5,1,2,3] | p=5 | q=[1,2,3]) Val [5,1,2,3]
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) 5Val [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"
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]
creates a singleton from a value
>>>pz @(Singleton (C "aBc")) ()Val "a"
>>>pz @(Singleton Id) FalseVal [False]
>>>pz @(Singleton Snd) (False,"hello")Val ["hello"]
data EmptyT (t :: Type -> Type) Source #
similar to empty
>>>pz @(EmptyT Maybe) ()Val Nothing
>>>pz @(EmptyT []) ()Val []
>>>pz @(C "x" >> EmptyT []) (13,True)Val ""
>>>pz @(Fst >> EmptyT (Either String)) (13,True)Val (Left "")
data EmptyList (t :: Type) Source #
creates an empty list for the given type
>>>pz @(Id :+ EmptyList _) 99Val [99]
data EmptyList' t Source #
Instances
| P (EmptyList' t :: Type) x Source # | |
Defined in Predicate.Data.List Associated Types type PP (EmptyList' t) x Source # Methods eval :: MonadEval m => proxy (EmptyList' t) -> POpts -> x -> m (TT (PP (EmptyList' t) x)) Source # | |
| Show (EmptyList' t) Source # | |
Defined in Predicate.Data.List Methods showsPrec :: Int -> EmptyList' t -> ShowS # show :: EmptyList' t -> String # showList :: [EmptyList' t] -> ShowS # | |
| type PP (EmptyList' t :: Type) x Source # | |
Defined in Predicate.Data.List | |
destructors
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]))
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))
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
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)"
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)"
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
sort
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 >> OrdA' Fst 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 (OrdA' Reverse 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)) OrdA) 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]
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)]
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
| P (SortOnDescT p q) x => P (SortOnDesc p q :: Type) x Source # | |
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 # | |
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 # | |
Defined in Predicate.Data.List | |
simple sort: similar to sort
zip related
unzip equivalent
>>>pz @Unzip (zip [1..5] "abcd")Val ([1,2,3,4],"abcd")
unzip3 equivalent
>>>pz @Unzip3 (zip3 [1..5] "abcd" (cycle [True,False]))Val ([1,2,3,4],"abcd",[True,False,True,False])
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')]
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"
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"
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"
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)) TrueVal [((),1),((),2),((),3),((),4),((),5)]
Instances
| (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 # | |
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 # | |
Defined in Predicate.Data.List Methods showsPrec :: Int -> ZipCartesian p q -> ShowS # show :: ZipCartesian p q -> String # showList :: [ZipCartesian p q] -> ShowS # | |
| type PP (ZipCartesian p q :: Type) x Source # | |
Defined in Predicate.Data.List | |
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)]
higher order methods
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])
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)
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
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
| (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 # | |
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 # | |
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 # | |
Defined in Predicate.Data.List | |
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]]
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"]
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)]
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
| Show GroupCntStable Source # | |
Defined in Predicate.Data.List Methods showsPrec :: Int -> GroupCntStable -> ShowS # show :: GroupCntStable -> String # showList :: [GroupCntStable] -> ShowS # | |
| (a ~ [x], Ord x) => P GroupCntStable a Source # | |
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 # | |
Defined in Predicate.Data.List | |
similar to filter
>>>pz @(Filter (Gt 4) Id) [10,1,3,5,-10,12,1]Val [10,5,12]
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 versionPresent ([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)])
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])
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
| (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 # | |
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 # | |
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 # | |
Defined in Predicate.Data.List | |
miscellaneous
elem function
>>>pz @(Elem Fst Snd) ('x',"abcdxy")Val True
>>>pz @(Elem Fst Snd) ('z',"abcdxy")Val False
>>>pl @(Elem Id '[2,3,4]) 2True (2 `elem` [2,3,4]) Val True
>>>pl @(Elem Id '[2,3,4]) 6False (6 `elem` [2,3,4]) Val False
>>>pl @(Elem Id '[13 % 2]) 6.5True (13 % 2 `elem` [13 % 2]) Val True
>>>pl @(Elem Id '[13 % 2, 12 % 1]) 6.5True (13 % 2 `elem` [13 % 2,12 % 1]) Val True
>>>pl @(Elem Id '[13 % 2, 12 % 1]) 6False (6 % 1 `elem` [13 % 2,12 % 1]) Val False
similar to inits
>>>pz @Inits [4,8,3,9]Val [[],[4],[4,8],[4,8,3],[4,8,3,9]]
>>>pz @Inits []Val [[]]
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",""]
split a list into single values
>>>pz @Ones [4,8,3,9]Val [[4],[8],[3],[9]]
>>>pz @Ones []Val []
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]
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]
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]]
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
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]]
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]]
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"]
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 ""
drop n values from a list p: similar to drop
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]
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]
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"
similar to nub
>>>pz @Nub "abcdbc"Val "abcd"
>>>pz @Nub []Val []
>>>pz @Nub [1,4,1,1,1,1,1]Val [1,4]
similar to sum
>>>pz @Sum [10,4,5,12,3,4]Val 38
>>>pz @Sum []Val 0
>>>pz @(1 ... 10 >> Sum) ()Val 55
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
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
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