Copyright | (c) 2016 Stephen Diehl (c) 2016-2018 Serokell (c) 2018-2021 Kowainik |
---|---|
License | MIT |
Maintainer | Kowainik <xrom.xkov@gmail.com> |
Stability | Stable |
Portability | Portable |
Safe Haskell | Safe |
Language | Haskell2010 |
Utility functions to work with Maybe
data type as monad.
Synopsis
- (?:) :: Maybe a -> a -> a
- whenJust :: Applicative f => Maybe a -> (a -> f ()) -> f ()
- whenJustM :: Monad m => m (Maybe a) -> (a -> m ()) -> m ()
- whenNothing :: Applicative f => Maybe a -> f a -> f a
- whenNothing_ :: Applicative f => Maybe a -> f () -> f ()
- whenNothingM :: Monad m => m (Maybe a) -> m a -> m a
- whenNothingM_ :: Monad m => m (Maybe a) -> m () -> m ()
- mapMaybeM :: Monad m => (a -> m (Maybe b)) -> [a] -> m [b]
Combinators
(?:) :: Maybe a -> a -> a infixr 0 Source #
Similar to fromMaybe
but with flipped arguments.
>>>
readMaybe "True" ?: False
True
>>>
readMaybe "Tru" ?: False
False
whenJust :: Applicative f => Maybe a -> (a -> f ()) -> f () Source #
Specialized version of for_
for Maybe
. It's used for code readability.
Also helps to avoid space leaks: Foldable.mapM_ space leak.
>>>
whenJust Nothing $ \b -> print (not b)
>>>
whenJust (Just True) $ \b -> print (not b)
False
whenJustM :: Monad m => m (Maybe a) -> (a -> m ()) -> m () Source #
Monadic version of whenJust
.
>>>
whenJustM (pure Nothing) $ \b -> print (not b)
>>>
whenJustM (pure $ Just True) $ \b -> print (not b)
False
whenNothing :: Applicative f => Maybe a -> f a -> f a Source #
Performs default Applicative
action if Nothing
is given.
Otherwise returns content of Just
pured to Applicative
.
>>>
whenNothing Nothing [True, False]
[True,False]>>>
whenNothing (Just True) [True, False]
[True]
whenNothing_ :: Applicative f => Maybe a -> f () -> f () Source #
Performs default Applicative
action if Nothing
is given.
Do nothing for Just
. Convenient for discarding Just
content.
>>>
whenNothing_ Nothing $ putTextLn "Nothing!"
Nothing!>>>
whenNothing_ (Just True) $ putTextLn "Nothing!"
Monadic combinators
whenNothingM :: Monad m => m (Maybe a) -> m a -> m a Source #
Monadic version of whenNothingM
.
>>>
whenNothingM (pure $ Just True) $ True <$ putTextLn "Is Just!"
True>>>
whenNothingM (pure Nothing) $ False <$ putTextLn "Is Nothing!"
Is Nothing! False
whenNothingM_ :: Monad m => m (Maybe a) -> m () -> m () Source #
Monadic version of whenNothingM_
.
>>>
whenNothingM_ (pure $ Just True) $ putTextLn "Is Just!"
>>>
whenNothingM_ (pure Nothing) $ putTextLn "Is Nothing!"
Is Nothing!