| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Agda.Utils.List1
Description
Synopsis
- type List1 = NonEmpty
- initLast :: List1 a -> ([a], a)
- singleton :: a -> List1 a
- appendList :: List1 a -> [a] -> List1 a
- prependList :: [a] -> List1 a -> List1 a
- snoc :: [a] -> a -> List1 a
- groupBy' :: forall a. (a -> a -> Bool) -> [a] -> [List1 a]
- breakAfter :: (a -> Bool) -> List1 a -> (List1 a, [a])
- concat :: [List1 a] -> [a]
- union :: Eq a => List1 a -> List1 a -> List1 a
- ifNull :: [a] -> b -> (List1 a -> b) -> b
- ifNotNull :: [a] -> (List1 a -> b) -> b -> b
- unlessNull :: Null m => [a] -> (List1 a -> m) -> m
- allEqual :: Eq a => List1 a -> Bool
- catMaybes :: List1 (Maybe a) -> [a]
- mapMaybe :: (a -> Maybe b) -> List1 a -> [b]
- partitionEithers :: List1 (Either a b) -> ([a], [b])
- lefts :: List1 (Either a b) -> [a]
- rights :: List1 (Either a b) -> [b]
- nubM :: Monad m => (a -> a -> m Bool) -> List1 a -> m (List1 a)
- zipWithM :: Applicative m => (a -> b -> m c) -> List1 a -> List1 b -> m (List1 c)
- zipWithM_ :: Applicative m => (a -> b -> m c) -> List1 a -> List1 b -> m ()
- sortWith :: Ord o => (a -> o) -> NonEmpty a -> NonEmpty a
- sortBy :: (a -> a -> Ordering) -> NonEmpty a -> NonEmpty a
- transpose :: NonEmpty (NonEmpty a) -> NonEmpty (NonEmpty a)
- nubBy :: (a -> a -> Bool) -> NonEmpty a -> NonEmpty a
- nub :: Eq a => NonEmpty a -> NonEmpty a
- unzip :: Functor f => f (a, b) -> (f a, f b)
- zipWith :: (a -> b -> c) -> NonEmpty a -> NonEmpty b -> NonEmpty c
- zip :: NonEmpty a -> NonEmpty b -> NonEmpty (a, b)
- (!!) :: NonEmpty a -> Int -> a
- isPrefixOf :: Eq a => [a] -> NonEmpty a -> Bool
- groupAllWith1 :: Ord b => (a -> b) -> NonEmpty a -> NonEmpty (NonEmpty a)
- groupWith1 :: Eq b => (a -> b) -> NonEmpty a -> NonEmpty (NonEmpty a)
- groupBy1 :: (a -> a -> Bool) -> NonEmpty a -> NonEmpty (NonEmpty a)
- group1 :: Eq a => NonEmpty a -> NonEmpty (NonEmpty a)
- groupAllWith :: Ord b => (a -> b) -> [a] -> [NonEmpty a]
- groupWith :: (Foldable f, Eq b) => (a -> b) -> f a -> [NonEmpty a]
- groupBy :: Foldable f => (a -> a -> Bool) -> f a -> [NonEmpty a]
- group :: (Foldable f, Eq a) => f a -> [NonEmpty a]
- partition :: (a -> Bool) -> NonEmpty a -> ([a], [a])
- filter :: (a -> Bool) -> NonEmpty a -> [a]
- break :: (a -> Bool) -> NonEmpty a -> ([a], [a])
- span :: (a -> Bool) -> NonEmpty a -> ([a], [a])
- dropWhile :: (a -> Bool) -> NonEmpty a -> [a]
- takeWhile :: (a -> Bool) -> NonEmpty a -> [a]
- splitAt :: Int -> NonEmpty a -> ([a], [a])
- drop :: Int -> NonEmpty a -> [a]
- take :: Int -> NonEmpty a -> [a]
- repeat :: a -> NonEmpty a
- reverse :: NonEmpty a -> NonEmpty a
- cycle :: NonEmpty a -> NonEmpty a
- iterate :: (a -> a) -> a -> NonEmpty a
- intersperse :: a -> NonEmpty a -> NonEmpty a
- scanr1 :: (a -> a -> a) -> NonEmpty a -> NonEmpty a
- scanl1 :: (a -> a -> a) -> NonEmpty a -> NonEmpty a
- scanr :: Foldable f => (a -> b -> b) -> b -> f a -> NonEmpty b
- scanl :: Foldable f => (b -> a -> b) -> b -> f a -> NonEmpty b
- some1 :: Alternative f => f a -> f (NonEmpty a)
- insert :: (Foldable f, Ord a) => a -> f a -> NonEmpty a
- tails :: Foldable f => f a -> NonEmpty [a]
- inits :: Foldable f => f a -> NonEmpty [a]
- map :: (a -> b) -> NonEmpty a -> NonEmpty b
- toList :: NonEmpty a -> [a]
- fromList :: [a] -> NonEmpty a
- sort :: Ord a => NonEmpty a -> NonEmpty a
- cons :: a -> NonEmpty a -> NonEmpty a
- (<|) :: a -> NonEmpty a -> NonEmpty a
- init :: NonEmpty a -> [a]
- last :: NonEmpty a -> a
- tail :: NonEmpty a -> [a]
- head :: NonEmpty a -> a
- unfoldr :: (a -> (b, Maybe a)) -> a -> NonEmpty b
- uncons :: NonEmpty a -> (a, Maybe (NonEmpty a))
- nonEmpty :: [a] -> Maybe (NonEmpty a)
- unfold :: (a -> (b, Maybe a)) -> a -> NonEmpty b
- xor :: NonEmpty Bool -> Bool
- length :: NonEmpty a -> Int
- pattern (:|) :: a -> [a] -> NonEmpty a
Documentation
appendList :: List1 a -> [a] -> List1 a Source #
Append a list to a non-empty list.
prependList :: [a] -> List1 a -> List1 a Source #
Prepend a list to a non-empty list.
breakAfter :: (a -> Bool) -> List1 a -> (List1 a, [a]) Source #
Breaks a list just after an element satisfying the predicate is found.
>>>breakAfter even [1,3,5,2,4,7,8]([1,3,5,2],[4,7,8])
union :: Eq a => List1 a -> List1 a -> List1 a Source #
Like union.  Duplicates in the first list are not removed.
 O(nm).
unlessNull :: Null m => [a] -> (List1 a -> m) -> m Source #
allEqual :: Eq a => List1 a -> Bool Source #
Checks if all the elements in the list are equal. Assumes that
   the Eq instance stands for an equivalence relation.
   O(n).
partitionEithers :: List1 (Either a b) -> ([a], [b]) Source #
Like partitionEithers.
nubM :: Monad m => (a -> a -> m Bool) -> List1 a -> m (List1 a) Source #
Non-efficient, monadic nub.
 O(n²).
zipWithM :: Applicative m => (a -> b -> m c) -> List1 a -> List1 b -> m (List1 c) Source #
Like zipWithM.
zip :: NonEmpty a -> NonEmpty b -> NonEmpty (a, b) #
The zip function takes two streams and returns a stream of
 corresponding pairs.
(!!) :: NonEmpty a -> Int -> a infixl 9 #
xs !! n returns the element of the stream xs at index
 n. Note that the head of the stream has index 0.
Beware: a negative or out-of-bounds index will cause an error.
isPrefixOf :: Eq a => [a] -> NonEmpty a -> Bool #
The isPrefixOf function returns True if the first argument is
 a prefix of the second.
groupAllWith1 :: Ord b => (a -> b) -> NonEmpty a -> NonEmpty (NonEmpty a) #
groupAllWith1 is to groupWith1 as groupAllWith is to groupWith
groupWith1 :: Eq b => (a -> b) -> NonEmpty a -> NonEmpty (NonEmpty a) #
groupWith1 is to group1 as groupWith is to group
groupAllWith :: Ord b => (a -> b) -> [a] -> [NonEmpty a] #
groupAllWith operates like groupWith, but sorts the list
 first so that each equivalence class has, at most, one list in the
 output
group :: (Foldable f, Eq a) => f a -> [NonEmpty a] #
The group function takes a stream and returns a list of
 streams such that flattening the resulting list is equal to the
 argument.  Moreover, each stream in the resulting list
 contains only equal elements.  For example, in list notation:
'group' $ 'cycle' "Mississippi" = "M" : "i" : "ss" : "i" : "ss" : "i" : "pp" : "i" : "M" : "i" : ...
partition :: (a -> Bool) -> NonEmpty a -> ([a], [a]) #
The partition function takes a predicate p and a stream
 xs, and returns a pair of lists. The first list corresponds to the
 elements of xs for which p holds; the second corresponds to the
 elements of xs for which p does not hold.
'partition' p xs = ('filter' p xs, 'filter' (not . p) xs)filter :: (a -> Bool) -> NonEmpty a -> [a] #
filter p xsxs that do not satisfy p.
span :: (a -> Bool) -> NonEmpty a -> ([a], [a]) #
span p xsxs that satisfies
 p, together with the remainder of the stream.
'span' p xs == ('takeWhile' p xs, 'dropWhile' p xs)
xs == ys ++ zs where (ys, zs) = 'span' p xstakeWhile :: (a -> Bool) -> NonEmpty a -> [a] #
takeWhile p xsxs for which the predicate p holds.
splitAt :: Int -> NonEmpty a -> ([a], [a]) #
splitAt n xsxs
 of length n and the remaining stream immediately following this prefix.
'splitAt' n xs == ('take' n xs, 'drop' n xs)
xs == ys ++ zs where (ys, zs) = 'splitAt' n xsdrop :: Int -> NonEmpty a -> [a] #
drop n xsn elements off the front of
 the sequence xs.
cycle :: NonEmpty a -> NonEmpty a #
cycle xsxs:
cycle (1 :| [2,3]) = 1 :| [2,3,1,2,3,...]
iterate :: (a -> a) -> a -> NonEmpty a #
iterate f xf to x.
iterate f x = x :| [f x, f (f x), ..]
intersperse :: a -> NonEmpty a -> NonEmpty a #
'intersperse x xs' alternates elements of the list with copies of x.
intersperse 0 (1 :| [2,3]) == 1 :| [0,2,0,3]
some1 :: Alternative f => f a -> f (NonEmpty a) #
some1 xx one or more times.
insert :: (Foldable f, Ord a) => a -> f a -> NonEmpty a #
insert x xsx into the last position in xs where it
 is still less than or equal to the next element. In particular, if the
 list is sorted beforehand, the result will also be sorted.
tails :: Foldable f => f a -> NonEmpty [a] #
The tails function takes a stream xs and returns all the
 suffixes of xs.
inits :: Foldable f => f a -> NonEmpty [a] #
The inits function takes a stream xs and returns all the
 finite prefixes of xs.
fromList :: [a] -> NonEmpty a #
Converts a normal list to a NonEmpty stream.
Raises an error if given an empty list.
uncons :: NonEmpty a -> (a, Maybe (NonEmpty a)) #
uncons produces the first element of the stream, and a stream of the
 remaining elements, if any.