Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
This module contains safe functions to work with list type (mostly with NonEmpty
).
Synopsis
- viaNonEmpty :: (NonEmpty a -> b) -> [a] -> Maybe b
- uncons :: [a] -> Maybe (a, [a])
- whenNotNull :: Applicative f => [a] -> (NonEmpty a -> f ()) -> f ()
- whenNotNullM :: Monad m => m [a] -> (NonEmpty a -> m ()) -> m ()
Documentation
viaNonEmpty :: (NonEmpty a -> b) -> [a] -> Maybe b Source #
For safe work with lists using functinons for NonEmpty
.
>>>
viaNonEmpty head [1]
Just 1>>>
viaNonEmpty head []
Nothing
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
.