list1-0.1.0: Helpers for working with NonEmpty lists.
Copyright(c) Melanie Phoenix Brown 2023-2025
Maintainerbrown.m@proton.me
Safe HaskellNone
LanguageGHC2021

Data.List1

Description

 
Synopsis

Documentation

pattern Sole :: x -> List1 x Source #

Match a singleton List1.

pattern (:||) :: x -> List1 x -> List1 x infixr 5 Source #

Match a List1 of length at least 2.

pattern (:?) :: x -> Maybe (List1 x) -> List1 x infixr 5 Source #

Isomorphic to (:|), but instead with a Maybe List1.

(<|) :: List1 x -> [x] -> List1 x infixl 4 Source #

Prepend a List1 to a list.

(|>) :: [x] -> List1 x -> List1 x infixl 4 Source #

Append a List1 to a list.

(|:) :: [x] -> x -> List1 x infixr 5 Source #

Append an element to a list. C.f. (:|).

(||:) :: List1 x -> x -> List1 x infixr 5 Source #

Append an element to a List1. C.f. (:||).

(?:) :: Maybe (List1 x) -> x -> List1 x infixr 5 Source #

Append an element to a Maybe List1. C.f. (:?).

list1 :: [x] -> Maybe (List1 x) Source #

Together with unList1, witness the isomorphism [x] ~ Maybe (List1 x).

toList :: List1 x -> [x] Source #

Forget the nonemptiness information.

unList1 :: Maybe (List1 x) -> [x] Source #

Together with list1, witness the isomorphism [x] ~ Maybe (List1 x).

onList :: (List1 x -> List1 x) -> [x] -> [x] Source #

Apply a List1 function on a regular list.

asList :: HasCallStack => ([x] -> [x]) -> List1 x -> List1 x Source #

Apply a regular list function on a List1. Avoid shortening the list.

ifList1 :: Alternative m => [x] -> (List1 x -> y) -> m y Source #

Apply a List1 function if the list is not empty.

withList1 :: y -> (List1 x -> y) -> [x] -> y Source #

Flipped version of has01, consistent with other libraries' withNonEmpty.

whenList1 :: Applicative m => [x] -> (List1 x -> m ()) -> m () Source #

Run an action taking a List1 if the list is not empty.

has01 :: [x] -> y -> (List1 x -> y) -> y Source #

Case split on a list with a default value and a List1 function. Flipped variant of what some call withNonEmpty or withNotNull.

has1Plus :: List1 x -> (x -> y) -> (x -> List1 x -> y) -> y Source #

Case split on a List1 with a simple function and a List1 function.

uncons :: List1 x -> (x, [x]) Source #

Convenience function for decomposing List1 into its head and tail.

unsnoc :: List1 x -> ([x], x) Source #

Convenience function for decomposing List1 into its init and last.

(++) :: List1 x -> List1 x -> List1 x Source #

Type-restricted concatenation.

reverse :: List1 x -> List1 x Source #

List1 the elements backwards.

head :: List1 x -> x Source #

Extract the first element of a List1.

tail :: List1 x -> [x] Source #

Extract all but the first element of a List1.

init :: List1 x -> [x] Source #

Extract all but the last element of a List1.

last :: List1 x -> x Source #

Extract the last element of a List1.

inits :: List1 x -> List1 (List1 x) Source #

The sequence of prefixes of a List1, from shortest to longest.

tails :: List1 x -> List1 (List1 x) Source #

The sequence of suffixes of a List1, from longest to shortest.

take :: Int -> List1 x -> Maybe (List1 x) Source #

Take the first (possibly no) elements of a List1.

drop :: Int -> List1 x -> Maybe (List1 x) Source #

Get rid of the first (possibly all) elements of a List1.

takeWhile :: (x -> Bool) -> List1 x -> Maybe (List1 x) Source #

Keep the longest prefix of elements of a List1 that satisfy a predicate.

dropWhile :: (x -> Bool) -> List1 x -> Maybe (List1 x) Source #

Drop the longest prefix of elements of a List1 that satisfy a predicate.

delete :: Eq x => x -> List1 x -> Maybe (List1 x) Source #

Remove the first occurrence of the given element from a List1.

deleteBy :: (x -> x -> Bool) -> x -> List1 x -> Maybe (List1 x) Source #

Remove an element from a List1 according to a supplied equality test.

(\\) :: Eq x => List1 x -> List1 x -> Maybe (List1 x) Source #

Remove all of the elements of the second argument from the first argument.

filter :: (x -> Bool) -> List1 x -> Maybe (List1 x) Source #

Keep only (possibly no) elements satisfying a predicate.

span :: (x -> Bool) -> List1 x -> ([x], [x]) Source #

The prefix and suffix of a List1 where the elements of the prefix satisfy the predicate.

break :: (x -> Bool) -> List1 x -> ([x], [x]) Source #

The prefix and suffix of a List1 where the elements of the prefix do not satisfy the predicate.

partition :: (x -> Bool) -> List1 x -> ([x], [x]) Source #

The elements of a List1 that do and do not satisfy the predicate, in order.

splitAt :: Int -> List1 x -> ([x], [x]) Source #

Split a List1 at the given index.

index :: Integral n => List1 x -> List1 (n, x) Source #

Attach the index to each element of a List1.

elem :: Eq x => x -> List1 x -> Bool Source #

Whether the given element is found in the List1.

notElem :: Eq x => x -> List1 x -> Bool Source #

Whether the given element is not in the List1.

elemIndex :: Eq x => x -> List1 x -> Maybe Int Source #

The first index of the element, if it is found, within the List1.

elemIndices :: Eq x => x -> List1 x -> Maybe (List1 Int) Source #

All the indices of the element, if it is found, within the List1.

find :: (x -> Bool) -> List1 x -> Maybe x Source #

The first element, if any, to satisfy a predicate.

findIndex :: (x -> Bool) -> List1 x -> Maybe Int Source #

The index of the first element, if any, to satisfy a predicate.

findIndices :: (x -> Bool) -> List1 x -> Maybe (List1 Int) Source #

All of the positions of the elements satisfying a predicate.

(!?) :: List1 x -> Int -> Maybe x Source #

The element at a given index.

lookup :: Eq x => x -> List1 (x, y) -> Maybe y Source #

Given a List1 of pairs, find the second coordinate of the first element matching in the first coordinate.

map :: (x -> y) -> List1 x -> List1 y Source #

Apply a function to every element of a List1.

foldMap1 :: (Foldable1 t, Semigroup m) => (a -> m) -> t a -> m #

Map each element of the structure to a semigroup, and combine the results with (<>). This fold is right-associative and lazy in the accumulator. For strict left-associative folds consider foldMap1' instead.

>>> foldMap1 (:[]) (1 :| [2, 3, 4])
[1,2,3,4]

Since: base-4.18.0.0

mapMaybe :: (x -> Maybe y) -> List1 x -> Maybe (List1 y) Source #

A version of map that can eliminate (possibly all) values from a List1.

catMaybes :: List1 (Maybe x) -> Maybe (List1 x) Source #

Returns a list of all (possibly no) Just values in a List1.

zip :: List1 x -> List1 y -> List1 (x, y) Source #

Pointwise product of two List1s.

zipWith :: (x -> y -> z) -> List1 x -> List1 y -> List1 z Source #

Pointwise application of two List1s.

unzip :: List1 (x, y) -> (List1 x, List1 y) Source #

Decompose a List1 of pairs into a pair of List1s.

accuml :: (a -> x -> (a, y)) -> a -> List1 x -> (a, List1 y) Source #

Traverse a List1 with an accumulating parameter from left to right.

accumr :: (a -> x -> (a, y)) -> a -> List1 x -> (a, List1 y) Source #

Traverse a List1 with an accumulating parameter from right to left.

scanl :: (y -> x -> y) -> y -> [x] -> List1 y Source #

scanl is similar to foldl, but returns a List1 of successive reduced values from the left.

scanl' :: (y -> x -> y) -> y -> [x] -> List1 y Source #

Strict version of scanl.

scanl1 :: (x -> x -> x) -> List1 x -> List1 x Source #

A variant of scanl that has no starting value argument and works on a List1.

scanl1' :: (x -> x -> x) -> List1 x -> List1 x Source #

Strict version of scanl1.

scanr :: (x -> y -> y) -> y -> [x] -> List1 y Source #

scanr is the right-to-left dual of scanl. Note that the parameters of the accumulating function are also reversed.

scanr1 :: (x -> x -> x) -> List1 x -> List1 x Source #

A variant of scanr with no starting value argument and works on a List1.

unfoldr :: (x -> (y, Maybe x)) -> x -> List1 y Source #

Build a List1 from a generating function and seed value.

build1 :: (forall y. (x -> Maybe y -> y) -> Maybe y -> y) -> List1 x Source #

The List1 analogue of build.

sort :: Ord x => List1 x -> List1 x Source #

Sort a List1.

sortOn :: Ord y => (x -> y) -> List1 x -> List1 x Source #

Sort a List1 using the projection.

sortBy :: (x -> x -> Ordering) -> List1 x -> List1 x Source #

Sort a List1 using an explicit comparison.

group :: Eq x => List1 x -> List1 (List1 x) Source #

Group the elements of a List1 by equality.

groupOn :: Eq y => (x -> y) -> List1 x -> List1 (List1 x) Source #

Group the elements of a List1 by equality on a projection.

groupBy :: (x -> x -> Bool) -> List1 x -> List1 (List1 x) Source #

Group the elements of a List1 with an explicit equality test.

intersect :: Eq x => List1 x -> List1 x -> Maybe (List1 x) Source #

Find the (possibly no) elements that are in both List1s.

intersectOn :: Eq y => (x -> y) -> List1 x -> List1 x -> Maybe (List1 x) Source #

Find the (possibly no) elements that are found in both List1s using a projection.

intersectBy :: (x -> y -> Bool) -> List1 x -> List1 y -> Maybe (List1 x) Source #

Find the (possibly no) elements in the first List1 that match any element of the second List1 using an explicit equality test.

union :: Eq x => List1 x -> List1 x -> List1 x Source #

Combine two List1s, keeping only those elements from the second List1 that are not already in the first.

unionOn :: Eq y => (x -> y) -> List1 x -> List1 x -> List1 x Source #

Similar to union but using equality on a projection.

unionBy :: (x -> x -> Bool) -> List1 x -> List1 x -> List1 x Source #

Similar to union but with an explicit equality test.

nub :: Eq x => List1 x -> List1 x Source #

Keep only one copy of each element.

nubOn :: Eq y => (x -> y) -> List1 x -> List1 x Source #

Keep only one copy of each element whose projections match.

nubBy :: (x -> x -> Bool) -> List1 x -> List1 x Source #

Keep only one copy of each element whose projections match the explicit equality test.

maximum :: Ord x => List1 x -> x Source #

Find the maximum of a List1.

maximumOf :: Ord y => (x -> y) -> List1 x -> y Source #

Find the maximum of a projection function.

maximumOn :: Ord y => (x -> y) -> List1 x -> x Source #

Find the element with maximal projection.

maximumBy :: (x -> x -> Ordering) -> List1 x -> x Source #

Find the maximum using an explicit comparison function.

minimum :: Ord x => List1 x -> x Source #

Find the minimum of a List1.

minimumOf :: Ord y => (x -> y) -> List1 x -> y Source #

Find the minimum of a projection function.

minimumOn :: Ord y => (x -> y) -> List1 x -> x Source #

Find the element with minimal projection.

minimumBy :: (x -> x -> Ordering) -> List1 x -> x Source #

Find the minimum using an explicit comparison function.

iterate :: (x -> x) -> x -> List1 x Source #

Apply a function repeatedly to a starting value. The first element is the starting value.

iterated :: (x -> x) -> x -> List1 x Source #

Apply a function strictly to a starting value. The first element is the starting value.

repeat :: x -> List1 x Source #

The infinite List1 consisting of a single value.

replicate :: Int -> x -> List1 x Source #

The List1 of given length consisting only of the given value.

cycle :: List1 x -> List1 x Source #

The infinite List1 created by repeating the elements of the given List1.

intersperse :: x -> List1 x -> List1 x Source #

Place an element between all other elements in a List1.

intersperse 'y' ('a' :|| 'b' :|| Sole 'c') == ('a' :|| 'y' :|| 'b' :|| 'y' :|| Sole 'c')

intercalate :: List1 x -> List1 (List1 x) -> List1 x Source #

Squash a List1 of List1s together with the given argument in between each List1.

intercalate (1 :|| Sole 1) (Sole 2 :|| Sole 3 :|| Sole (Sole 4)) == (2 :|| 1 :|| 1 :|| 3 :|| 1 :|| 1 :|| Sole 4)

subsequences :: List1 x -> List1 (List1 x) Source #

All of the non-empty sublists of a List1, including those that skip elements.

windows :: Int -> List1 x -> Maybe (List1 (List1 x)) Source #

windows n lists the consecutive subsequences of length n of a List1: the subsequences of length n that do not skip any elements.

consecutiveSubsequences :: List1 x -> List1 (List1 x) Source #

All of the consecutive subsequences of a List1: the subsequences that do not skip any elements.

permutations :: List1 x -> List1 (List1 x) Source #

The List1 of all rearrangements of a List1.

diagonally :: (List1 x -> List1 x -> y) -> List1 x -> Maybe (List1 y) Source #

Apply a function on the prefix and suffix of a List1 at every index.

diagonals :: List1 x -> [(List1 x, List1 x)] Source #

The init and tail of the List1 at each positive index.

>>> diagonals (1 :| [2, 3, 4])
[(1 :| [],2 :| [3,4]),(1 :| [2],3 :| [4]),(1 :| [2,3],4 :| [])]

insertions :: x -> List1 x -> List1 (List1 x) Source #

Insert an element before each member of a List1.

insertions x (a :|| b :|| c :|| ...)
    == (x :|| a :|| b :|| c :|| ...)
   :|| (a :|| x :|| b :|| c :|| ...)
   :|| (a :|| b :|| x :|| c :|| ...) ...