primus-0.3.0.0: nonempty and positive functions
Copyright(c) Grant Weyburne 2022
LicenseBSD-3
Safe HaskellNone
LanguageHaskell2010

Primus.List

Description

 
Synopsis

partition methods

partitionEithersL :: Foldable t => (a -> Bool) -> (a -> e) -> (a -> b) -> t a -> ([e], [b]) Source #

partitionEithersL' :: Foldable t => (a -> Either e b) -> t a -> ([e], [b]) Source #

like partition but allow the user to change the types of "e" and "b" using Either

partitionTheseL :: Foldable t => (a -> Bool) -> (a -> Bool) -> (a -> e) -> (a -> b) -> t a -> ([e], [b], [(e, b)]) Source #

partitionTheseL' :: Foldable t => (a -> These e b) -> t a -> ([e], [b], [(e, b)]) Source #

like partition but allow the user to change the types of "e" and "b" using These

partitionM :: Applicative m => (a -> m Bool) -> [a] -> m ([a], [a]) Source #

partition for an applicative

span methods

spanMaybe :: (a -> Bool) -> (a -> b) -> [a] -> ([b], [a]) Source #

spanMaybe' :: (a -> Maybe b) -> [a] -> ([b], [a]) Source #

like span but allow the user to change the success type using Maybe

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 #

creates the longest of the two lists: fills with This or That

zipLongest :: [a] -> [b] -> [These a b] Source #

chunking

pairsOf1 :: [a] -> ([(a, a)], Maybe a) Source #

split a list into overlapping pairs plus overflow

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

data SplitL a Source #

represents the status of a split on a list

Instances

Instances details
Eq a => Eq (SplitL a) Source # 
Instance details

Defined in Primus.List

Methods

(==) :: SplitL a -> SplitL a -> Bool #

(/=) :: SplitL a -> SplitL a -> Bool #

Ord a => Ord (SplitL a) Source # 
Instance details

Defined in Primus.List

Methods

compare :: SplitL a -> SplitL a -> Ordering #

(<) :: SplitL a -> SplitL a -> Bool #

(<=) :: SplitL a -> SplitL a -> Bool #

(>) :: SplitL a -> SplitL a -> Bool #

(>=) :: SplitL a -> SplitL a -> Bool #

max :: SplitL a -> SplitL a -> SplitL a #

min :: SplitL a -> SplitL a -> SplitL a #

Show a => Show (SplitL a) Source # 
Instance details

Defined in Primus.List

Methods

showsPrec :: Int -> SplitL a -> ShowS #

show :: SplitL a -> String #

showList :: [SplitL a] -> ShowS #

splitAtL :: forall a. Int -> [a] -> ([a], SplitL a) Source #

split a list preserving information about the split

atL :: Int -> [a] -> Maybe a Source #

index into a list

atNoteL :: HasCallStack => String -> [a] -> Int -> a Source #

unsafe index into a list

updateAtL :: Int -> (a -> a) -> [a] -> Maybe [a] Source #

update a value at a given index in a list

setAtL :: Int -> a -> [a] -> Maybe [a] Source #

set a value at a given index in a list

miscellaneous

allEqual :: Eq a => [a] -> Either (a, a) () Source #

checks that the list has all the same values

allEqualBy :: (a -> a -> Bool) -> [a] -> Either (a, a) () Source #

checks that the list has all the same values with a predicate

snocL :: [a] -> a -> [a] Source #

snoc for a list

unsnocL :: [a] -> Maybe ([a], a) Source #

unsnoc for a list

unsnocL' :: a -> [a] -> ([a], a) Source #

unsnoc for a value and a list

list :: b -> (a -> [a] -> b) -> [a] -> b Source #

break up a list into cases using cons

list' :: [a] -> b -> (a -> [a] -> b) -> b Source #

break up a list into cases using cons

listSnoc :: b -> ([a] -> a -> b) -> [a] -> b Source #

break up a list into cases using snoc