Copyright | (c) 2016 Stephen Diehl (c) 2016-2018 Serokell (c) 2018-2019 Kowainik |
---|---|
License | MIT |
Maintainer | Kowainik <xrom.xkov@gmail.com> |
Safe Haskell | Safe |
Language | Haskell2010 |
Monadic boolean combinators.
Documentation
guardM :: MonadPlus m => m Bool -> m () Source #
Monadic version of guard
. Occasionally useful.
Here some complex but real-life example:
findSomePath :: IO (Maybe FilePath) somePath :: MaybeT IO FilePath somePath = do path <- MaybeT findSomePath guardM $ liftIO $ doesDirectoryExist path return path
ifM :: Monad m => m Bool -> m a -> m a -> m a Source #
Monadic version of if-then-else
.
>>>
ifM (pure True) (putTextLn "True text") (putTextLn "False text")
True text
unlessM :: Monad m => m Bool -> m () -> m () Source #
Monadic version of unless
.
>>>
unlessM (pure False) $ putTextLn "No text :("
No text :(>>>
unlessM (pure True) $ putTextLn "Yes text :)"
whenM :: Monad m => m Bool -> m () -> m () Source #
Monadic version of when
.
>>>
whenM (pure False) $ putTextLn "No text :("
>>>
whenM (pure True) $ putTextLn "Yes text :)"
Yes text :)>>>
whenM (Just True) (pure ())
Just ()>>>
whenM (Just False) (pure ())
Just ()>>>
whenM Nothing (pure ())
Nothing