Copyright | (c) Grant Weyburne 2022 |
---|---|
License | BSD-3 |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- partitionEithersL :: Foldable t => (a -> Bool) -> (a -> e) -> (a -> b) -> t a -> ([e], [b])
- partitionEithersL' :: Foldable t => (a -> Either e b) -> t a -> ([e], [b])
- partitionTheseL :: Foldable t => (a -> Bool) -> (a -> Bool) -> (a -> e) -> (a -> b) -> t a -> ([e], [b], [(e, b)])
- partitionTheseL' :: Foldable t => (a -> These e b) -> t a -> ([e], [b], [(e, b)])
- partitionM :: Applicative m => (a -> m Bool) -> [a] -> m ([a], [a])
- spanMaybe :: (a -> Bool) -> (a -> b) -> [a] -> ([b], [a])
- spanMaybe' :: (a -> Maybe b) -> [a] -> ([b], [a])
- lengthExact :: Int -> [a] -> Either String [a]
- zipWithLongest :: forall a b c. (These a b -> c) -> [a] -> [b] -> [c]
- zipLongest :: [a] -> [b] -> [These a b]
- pairsOf1 :: [a] -> ([(a, a)], Maybe a)
- pairsOf2 :: [a] -> ([(a, a)], Maybe a)
- pairsOf' :: forall a. Pos -> [a] -> ([(a, a)], Maybe a)
- chunksOf :: forall a. Pos -> [a] -> [[a]]
- splitAtLGE :: Int -> [a] -> Either String ([a], [a])
- splits :: forall a. [a] -> [([a], [a])]
- data SplitL a
- splitAtL :: forall a. Int -> [a] -> ([a], SplitL a)
- atL :: Int -> [a] -> Maybe a
- atNoteL :: HasCallStack => String -> [a] -> Int -> a
- updateAtL :: Int -> (a -> a) -> [a] -> Maybe [a]
- setAtL :: Int -> a -> [a] -> Maybe [a]
- allEqual :: Eq a => [a] -> Either (a, a) ()
- allEqualBy :: (a -> a -> Bool) -> [a] -> Either (a, a) ()
- snocL :: [a] -> a -> [a]
- unsnocL :: [a] -> Maybe ([a], a)
- unsnocL' :: a -> [a] -> ([a], a)
- list :: b -> (a -> [a] -> b) -> [a] -> b
- list' :: [a] -> b -> (a -> [a] -> b) -> b
- listSnoc :: b -> ([a] -> a -> b) -> [a] -> b
partition methods
partitionEithersL :: Foldable t => (a -> Bool) -> (a -> e) -> (a -> b) -> t a -> ([e], [b]) Source #
like partitionEithersL'
using boolEither
partitionEithersL' :: Foldable t => (a -> Either e b) -> t a -> ([e], [b]) Source #
partitionTheseL :: Foldable t => (a -> Bool) -> (a -> Bool) -> (a -> e) -> (a -> b) -> t a -> ([e], [b], [(e, b)]) Source #
like partitionTheseL
using boolThese
partitionTheseL' :: Foldable t => (a -> These e b) -> t a -> ([e], [b], [(e, b)]) Source #
partitionM :: Applicative m => (a -> m Bool) -> [a] -> m ([a], [a]) Source #
partition for an applicative
span methods
spanMaybe' :: (a -> Maybe b) -> [a] -> ([b], [a]) Source #
lengthExact :: Int -> [a] -> Either String [a] Source #
compares the length of a potentially infinite list with "n" and succeeds if they are the same
zipWithLongest :: forall a b c. (These a b -> c) -> [a] -> [b] -> [c] Source #
zipLongest :: [a] -> [b] -> [These a b] Source #
zipWithLongest
for id
chunking
pairsOf2 :: [a] -> ([(a, a)], Maybe a) Source #
split a list into non-overlapping pairs plus overflow
pairsOf' :: forall a. Pos -> [a] -> ([(a, a)], Maybe a) Source #
split into pairs skipping given number of values
chunksOf :: forall a. Pos -> [a] -> [[a]] Source #
simple utility for chunking data but guarantees we make progress
split methods
splitAtLGE :: Int -> [a] -> Either String ([a], [a]) Source #
split a list but has to have enough elements else fails
splits :: forall a. [a] -> [([a], [a])] Source #
break up a list into all possible pairs of nonempty lists: see splits1
represents the status of a split on a list
splitAtL :: forall a. Int -> [a] -> ([a], SplitL a) Source #
split a list preserving information about the split
miscellaneous
allEqualBy :: (a -> a -> Bool) -> [a] -> Either (a, a) () Source #
checks that the list has all the same values with a predicate