Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
This module contains safe functions to work with list type (mostly with NonEmpty
).
Synopsis
- uncons :: [a] -> Maybe (a, [a])
- whenNotNull :: Applicative f => [a] -> (NonEmpty a -> f ()) -> f ()
- whenNotNullM :: Monad m => m [a] -> (NonEmpty a -> m ()) -> m ()
- foldr1 :: (a -> a -> a) -> NonEmpty a -> a
- foldl1 :: (a -> a -> a) -> NonEmpty a -> a
- minimum :: Ord a => NonEmpty a -> a
- maximum :: Ord a => NonEmpty a -> a
- minimumBy :: (a -> a -> Ordering) -> NonEmpty a -> a
- maximumBy :: (a -> a -> Ordering) -> NonEmpty a -> a
Documentation
uncons :: [a] -> Maybe (a, [a]) Source #
Destructuring list into its head and tail if possible. This function is total.
>>>
uncons []
Nothing>>>
uncons [1..5]
Just (1,[2,3,4,5])>>>
uncons (5 : [1..5]) >>= \(f, l) -> pure $ f == length l
Just True
whenNotNull :: Applicative f => [a] -> (NonEmpty a -> f ()) -> f () Source #
Performs given action over NonEmpty
list if given list is non empty.
>>>
whenNotNull [] $ \(b :| _) -> print (not b)
>>>
whenNotNull [False,True] $ \(b :| _) -> print (not b)
True
whenNotNullM :: Monad m => m [a] -> (NonEmpty a -> m ()) -> m () Source #
Monadic version of whenNotNull
.
foldr1 :: (a -> a -> a) -> NonEmpty a -> a Source #
A variant of foldr
that has no base case, and thus may only be
applied to NonEmpty
.
>>>
foldr1 (+) (1 :| [2,3,4,5])
15
foldl1 :: (a -> a -> a) -> NonEmpty a -> a Source #
A variant of foldl
that has no base case, and thus may only be
applied to NonEmpty
.
>>>
foldl1 (+) (1 :| [2,3,4,5])
15
minimum :: Ord a => NonEmpty a -> a Source #
The least element of a NonEmpty
.
>>>
minimum (1 :| [2,3,4,5])
1
maximum :: Ord a => NonEmpty a -> a Source #
The largest element of a NonEmpty
.
>>>
maximum (1 :| [2,3,4,5])
5