Copyright | (c) Melanie Phoenix Brown 2023-2025 |
---|---|
Maintainer | brown.m@proton.me |
Safe Haskell | None |
Language | GHC2021 |
Data.List1
Description
Synopsis
- type List1 = NonEmpty
- pattern Sole :: x -> List1 x
- pattern (:||) :: x -> List1 x -> List1 x
- pattern (:?) :: x -> Maybe (List1 x) -> List1 x
- (<|) :: List1 x -> [x] -> List1 x
- (|>) :: [x] -> List1 x -> List1 x
- (|:) :: [x] -> x -> List1 x
- (||:) :: List1 x -> x -> List1 x
- (?:) :: Maybe (List1 x) -> x -> List1 x
- list1 :: [x] -> Maybe (List1 x)
- toList :: List1 x -> [x]
- unList1 :: Maybe (List1 x) -> [x]
- onList :: (List1 x -> List1 x) -> [x] -> [x]
- asList :: HasCallStack => ([x] -> [x]) -> List1 x -> List1 x
- ifList1 :: Alternative m => [x] -> (List1 x -> y) -> m y
- withList1 :: y -> (List1 x -> y) -> [x] -> y
- whenList1 :: Applicative m => [x] -> (List1 x -> m ()) -> m ()
- has01 :: [x] -> y -> (List1 x -> y) -> y
- has1Plus :: List1 x -> (x -> y) -> (x -> List1 x -> y) -> y
- uncons :: List1 x -> (x, [x])
- unsnoc :: List1 x -> ([x], x)
- (++) :: List1 x -> List1 x -> List1 x
- reverse :: List1 x -> List1 x
- head :: List1 x -> x
- tail :: List1 x -> [x]
- init :: List1 x -> [x]
- last :: List1 x -> x
- inits :: List1 x -> List1 (List1 x)
- tails :: List1 x -> List1 (List1 x)
- take :: Int -> List1 x -> Maybe (List1 x)
- drop :: Int -> List1 x -> Maybe (List1 x)
- takeWhile :: (x -> Bool) -> List1 x -> Maybe (List1 x)
- dropWhile :: (x -> Bool) -> List1 x -> Maybe (List1 x)
- delete :: Eq x => x -> List1 x -> Maybe (List1 x)
- deleteBy :: (x -> x -> Bool) -> x -> List1 x -> Maybe (List1 x)
- (\\) :: Eq x => List1 x -> List1 x -> Maybe (List1 x)
- filter :: (x -> Bool) -> List1 x -> Maybe (List1 x)
- span :: (x -> Bool) -> List1 x -> ([x], [x])
- break :: (x -> Bool) -> List1 x -> ([x], [x])
- partition :: (x -> Bool) -> List1 x -> ([x], [x])
- splitAt :: Int -> List1 x -> ([x], [x])
- index :: Integral n => List1 x -> List1 (n, x)
- elem :: Eq x => x -> List1 x -> Bool
- notElem :: Eq x => x -> List1 x -> Bool
- elemIndex :: Eq x => x -> List1 x -> Maybe Int
- elemIndices :: Eq x => x -> List1 x -> Maybe (List1 Int)
- find :: (x -> Bool) -> List1 x -> Maybe x
- findIndex :: (x -> Bool) -> List1 x -> Maybe Int
- findIndices :: (x -> Bool) -> List1 x -> Maybe (List1 Int)
- (!?) :: List1 x -> Int -> Maybe x
- lookup :: Eq x => x -> List1 (x, y) -> Maybe y
- map :: (x -> y) -> List1 x -> List1 y
- foldMap1 :: (Foldable1 t, Semigroup m) => (a -> m) -> t a -> m
- mapMaybe :: (x -> Maybe y) -> List1 x -> Maybe (List1 y)
- catMaybes :: List1 (Maybe x) -> Maybe (List1 x)
- zip :: List1 x -> List1 y -> List1 (x, y)
- zipWith :: (x -> y -> z) -> List1 x -> List1 y -> List1 z
- unzip :: List1 (x, y) -> (List1 x, List1 y)
- accuml :: (a -> x -> (a, y)) -> a -> List1 x -> (a, List1 y)
- accumr :: (a -> x -> (a, y)) -> a -> List1 x -> (a, List1 y)
- scanl :: (y -> x -> y) -> y -> [x] -> List1 y
- scanl' :: (y -> x -> y) -> y -> [x] -> List1 y
- scanl1 :: (x -> x -> x) -> List1 x -> List1 x
- scanl1' :: (x -> x -> x) -> List1 x -> List1 x
- scanr :: (x -> y -> y) -> y -> [x] -> List1 y
- scanr1 :: (x -> x -> x) -> List1 x -> List1 x
- unfoldr :: (x -> (y, Maybe x)) -> x -> List1 y
- build1 :: (forall y. (x -> Maybe y -> y) -> Maybe y -> y) -> List1 x
- sort :: Ord x => List1 x -> List1 x
- sortOn :: Ord y => (x -> y) -> List1 x -> List1 x
- sortBy :: (x -> x -> Ordering) -> List1 x -> List1 x
- group :: Eq x => List1 x -> List1 (List1 x)
- groupOn :: Eq y => (x -> y) -> List1 x -> List1 (List1 x)
- groupBy :: (x -> x -> Bool) -> List1 x -> List1 (List1 x)
- intersect :: Eq x => List1 x -> List1 x -> Maybe (List1 x)
- intersectOn :: Eq y => (x -> y) -> List1 x -> List1 x -> Maybe (List1 x)
- intersectBy :: (x -> y -> Bool) -> List1 x -> List1 y -> Maybe (List1 x)
- union :: Eq x => List1 x -> List1 x -> List1 x
- unionOn :: Eq y => (x -> y) -> List1 x -> List1 x -> List1 x
- unionBy :: (x -> x -> Bool) -> List1 x -> List1 x -> List1 x
- nub :: Eq x => List1 x -> List1 x
- nubOn :: Eq y => (x -> y) -> List1 x -> List1 x
- nubBy :: (x -> x -> Bool) -> List1 x -> List1 x
- maximum :: Ord x => List1 x -> x
- maximumOf :: Ord y => (x -> y) -> List1 x -> y
- maximumOn :: Ord y => (x -> y) -> List1 x -> x
- maximumBy :: (x -> x -> Ordering) -> List1 x -> x
- minimum :: Ord x => List1 x -> x
- minimumOf :: Ord y => (x -> y) -> List1 x -> y
- minimumOn :: Ord y => (x -> y) -> List1 x -> x
- minimumBy :: (x -> x -> Ordering) -> List1 x -> x
- iterate :: (x -> x) -> x -> List1 x
- iterated :: (x -> x) -> x -> List1 x
- repeat :: x -> List1 x
- replicate :: Int -> x -> List1 x
- cycle :: List1 x -> List1 x
- intersperse :: x -> List1 x -> List1 x
- intercalate :: List1 x -> List1 (List1 x) -> List1 x
- transpose :: List1 (List1 x) -> List1 (List1 x)
- subsequences :: List1 x -> List1 (List1 x)
- windows :: Int -> List1 x -> Maybe (List1 (List1 x))
- consecutiveSubsequences :: List1 x -> List1 (List1 x)
- permutations :: List1 x -> List1 (List1 x)
- diagonally :: (List1 x -> List1 x -> y) -> List1 x -> Maybe (List1 y)
- diagonals :: List1 x -> [(List1 x, List1 x)]
- insertions :: x -> List1 x -> List1 (List1 x)
Documentation
list1 :: [x] -> Maybe (List1 x) Source #
Together with unList1
, witness the isomorphism [x] ~ Maybe (List1 x)
.
unList1 :: Maybe (List1 x) -> [x] Source #
Together with list1
, witness the isomorphism [x] ~ Maybe (List1 x)
.
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
.
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.
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.
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.
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.
zipWith :: (x -> y -> z) -> List1 x -> List1 y -> List1 z Source #
Pointwise application of two List1
s.
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.
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
.
sortBy :: (x -> x -> Ordering) -> List1 x -> List1 x Source #
Sort a List1
using an explicit comparison.
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 List1
s.
intersectOn :: Eq y => (x -> y) -> List1 x -> List1 x -> Maybe (List1 x) Source #
Find the (possibly no) elements that are found in both List1
s using a projection.
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.
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.
maximumBy :: (x -> x -> Ordering) -> List1 x -> x Source #
Find the maximum using an explicit comparison function.
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.
replicate :: Int -> x -> List1 x Source #
The List1
of given length consisting only of the given value.
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')
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.
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.