| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Data.List.EitherFunctions
Description
Functions involving lists of Either.
Synopsis
- partlyMap :: (a -> Maybe b) -> [a] -> [Either a b]
- groupEither :: [Either a b] -> [Either [a] [b]]
- partition :: [Either a b] -> ([a], [b])
- spanLeft :: [Either a b] -> ([a], [Either a b])
- spanLeft' :: [Either a b] -> ([a], Maybe (b, [Either a b]))
- spanRight :: [Either a b] -> ([b], [Either a b])
- spanRight' :: [Either a b] -> ([b], Maybe (a, [Either a b]))
- leadLeft :: [Either a b] -> ([b], [(a, [b])])
- leadLeft' :: a -> [Either a b] -> [(a, [b])]
- leadRight :: [Either a b] -> ([a], [(b, [a])])
- leadRight' :: b -> [Either a b] -> [(b, [a])]
- branchLeft :: BranchComparison a -> [Either a b] -> ([b], Forest (a, [b]))
- branchRight :: BranchComparison b -> [Either a b] -> ([a], Forest (b, [a]))
- type BranchComparison a = Comparison a
Map
partlyMap :: (a -> Maybe b) -> [a] -> [Either a b] Source #
>>>import Prelude (even, show)
>>>partlyMap (\x -> if even x then Just (show x) else Nothing) [1..5][Left 1,Right "2",Left 3,Right "4",Left 5]
Group
groupEither :: [Either a b] -> [Either [a] [b]] Source #
>>>groupEither [Left 1, Left 2, Right 'a', Left 3, Right 'b', Right 'c'][Left [1,2],Right "a",Left [3],Right "bc"]
Partition
partition :: [Either a b] -> ([a], [b]) Source #
>>>partition [Left 1, Left 2, Right 'a', Left 3, Right 'b', Right 'c']([1,2,3],"abc")
Span
spanLeft :: [Either a b] -> ([a], [Either a b]) Source #
>>>spanLeft [Left 1, Left 2, Right 'a', Left 3, Right 'b', Right 'c']([1,2],[Right 'a',Left 3,Right 'b',Right 'c'])
>>>spanLeft [Right 'a', Left 3, Right 'b', Right 'c']([],[Right 'a',Left 3,Right 'b',Right 'c'])
spanLeft' :: [Either a b] -> ([a], Maybe (b, [Either a b])) Source #
Similar to spanLeft, but preserves a little more information in the return type: if the remainder of the list is non-empty, then it necessarily begins with a Right, and so we can go ahead and unwrap that and return it as a value of type b.
>>>spanLeft' [Left 1, Left 2, Right 'a', Left 3, Right 'b', Right 'c']([1,2],Just ('a',[Left 3,Right 'b',Right 'c']))
>>>spanLeft' [Right 'a', Left 3, Right 'b', Right 'c']([],Just ('a',[Left 3,Right 'b',Right 'c']))
>>>spanLeft' [Left 1, Left 2, Left 3]([1,2,3],Nothing)
spanRight :: [Either a b] -> ([b], [Either a b]) Source #
Similar to spanRight, but preserves a little more information in the return type: if the remainder of the list is non-empty, then it necessarily begins with a Left, and so we can go ahead and unwrap that and return it as a value of type a.
>>>spanRight [Left 1, Left 2, Right 'a', Left 3, Right 'b', Right 'c']("",[Left 1,Left 2,Right 'a',Left 3,Right 'b',Right 'c'])
>>>spanRight [Right 'a', Left 3, Right 'b', Right 'c']("a",[Left 3,Right 'b',Right 'c'])
spanRight' :: [Either a b] -> ([b], Maybe (a, [Either a b])) Source #
>>>spanRight' [Left 1, Left 2, Right 'a', Left 3, Right 'b', Right 'c']("",Just (1,[Left 2,Right 'a',Left 3,Right 'b',Right 'c']))
>>>spanRight' [Right 'a', Left 3, Right 'b', Right 'c']("a",Just (3,[Right 'b',Right 'c']))
>>>spanRight' [Right 'a', Right 'b', Right 'c']("abc",Nothing)
Lead
leadLeft :: [Either a b] -> ([b], [(a, [b])]) Source #
>>>leadLeft [Right 'a', Right 'b', Left 1, Right 'c', Right 'd', Left 2, Right 'e', Right 'f']("ab",[(1,"cd"),(2,"ef")])
>>>leadLeft [Left 1, Left 2, Right 'a', Left 3, Right 'b', Right 'c']("",[(1,""),(2,"a"),(3,"bc")])
Arguments
| :: a | Leader to use for the first group in case the list does not begin with a |
| -> [Either a b] | |
| -> [(a, [b])] |
>>>leadLeft' 0 [Right 'a', Right 'b', Left 1, Right 'c', Right 'd', Left 2, Right 'e', Right 'f'][(0,"ab"),(1,"cd"),(2,"ef")]
>>>leadLeft' 0 [Left 1, Left 2, Right 'a', Left 3, Right 'b', Right 'c'][(1,""),(2,"a"),(3,"bc")]
leadRight :: [Either a b] -> ([a], [(b, [a])]) Source #
>>>leadRight [Left 1, Left 2, Right 'a', Left 3, Left 4, Right 'b', Left 5, Left 6]([1,2],[('a',[3,4]),('b',[5,6])])
>>>leadRight [Right 'a', Left 3, Left 4, Right 'b', Right 'c', Left 5, Left 6]([],[('a',[3,4]),('b',[]),('c',[5,6])])
Arguments
| :: b | Leader to use for the first group in case the list does not begin with a |
| -> [Either a b] | |
| -> [(b, [a])] |
>>>leadRight' 'z' [Left 1, Left 2, Right 'a', Left 3, Left 4, Right 'b', Left 5, Left 6][('z',[1,2]),('a',[3,4]),('b',[5,6])]
>>>leadRight' 'z' [Right 'a', Left 3, Left 4, Right 'b', Right 'c', Left 5, Left 6][('a',[3,4]),('b',[]),('c',[5,6])]
Branch
branchLeft :: BranchComparison a -> [Either a b] -> ([b], Forest (a, [b])) Source #
>>>import Prelude
>>>heading level title = Left (level, title)>>>chapter = heading 1>>>section = heading 2>>>p text = Right text
>>>:{>>>list =>>>[ p "Copyright">>>, p "Preface">>>, chapter "Animals">>>, p "The kingdom animalia">>>, section "Vertebrates">>>, p "Cats">>>, p "Snakes">>>, section "Invertebrates">>>, p "Worms">>>, p "Jellyfishes">>>, chapter "Fungus">>>, p "Yeast">>>, p "Truffles">>>, p "Morels">>>]>>>:}
>>>import Data.Functor.Contravariant>>>flipComparison (Comparison f) = Comparison (flip f)>>>headingComparison = contramap fst (flipComparison defaultComparison)
>>>(frontMatter, mainMatter) = branchLeft headingComparison list
>>>frontMatter["Copyright","Preface"]
>>>import Data.List>>>showContent ((_, x), ys) = x ++ ": " ++ intercalate ", " ys
>>>import Data.Tree>>>putStrLn $ drawForest $ map (fmap showContent) mainMatterAnimals: The kingdom animalia | +- Vertebrates: Cats, Snakes | `- Invertebrates: Worms, Jellyfishes Fungus: Yeast, Truffles, Morels
branchRight :: BranchComparison b -> [Either a b] -> ([a], Forest (b, [a])) Source #
Same as branchLeft, but with the types flipped; here, Right is the case that indicates a branch.
type BranchComparison a = Comparison a Source #
The relative significance of branches (greater values are closer to the root).