relude-1.1.0.0: Safe, performant, user-friendly and lightweight Haskell Standard Library
Copyright(c) 2016 Stephen Diehl
(c) 2016-2018 Serokell
(c) 2018-2022 Kowainik
LicenseMIT
MaintainerKowainik <xrom.xkov@gmail.com>
StabilityStable
PortabilityPortable
Safe HaskellSafe
LanguageHaskell2010

Relude.Bool.Guard

Description

Monadic boolean combinators.

Synopsis

Documentation

guarded :: Alternative f => (a -> Bool) -> a -> f a Source #

Either lifts a value into an alternative context or gives a minimal value depending on a predicate. Works with Alternatives.

>>> guarded even 3 :: [Int]
[]
>>> guarded even 2 :: [Int]
[2]
>>> guarded (const True) "hello" :: Maybe String
Just "hello"
>>> guarded (const False) "world" :: Maybe String
Nothing

You can use this function to implement smart constructors simpler:

newtype HttpHost = HttpHost
    { unHttpHost :: Text
    }

mkHttpHost :: Text -> Maybe HttpHost
mkHttpHost host = HttpHost <$> guarded (not . Text.null) host

Since: 0.6.0.0

guardM :: MonadPlus m => m Bool -> m () Source #

Monadic version of guard that help to check that a condition (Bool) holds inside. Works with Monads that are also Alternative.

>>> guardM (Just True)
Just ()
>>> guardM (Just False)
Nothing
>>> guardM Nothing
Nothing

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
>>> ifM (pure False) (putTextLn "True text") (putTextLn "False text")
False text

unlessM :: Monad m => m Bool -> m () -> m () Source #

Monadic version of unless. Reverse of whenM. Conditionally don't execute the provided action.

>>> 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. Conditionally executes the provided action.

>>> 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

(&&^) :: Monad m => m Bool -> m Bool -> m Bool Source #

Monadic version of (&&) operator.

It is lazy by the second argument (similar to (||)), meaning that if the first argument is False, the function will return False without evaluating the second argument.

>>> Just False &&^ Just True
Just False
>>> Just True &&^ Just True
Just True
>>> Just True &&^ Nothing
Nothing
>>> Just False &&^ Nothing
Just False
>>> Just False &&^ error "Shouldn't be evaluated"
Just False

Since: 0.4.0

(||^) :: Monad m => m Bool -> m Bool -> m Bool Source #

Monadic version of (||) operator.

It is lazy by the second argument (similar to (||)), meaning that if the first argument is True, the function will return True without evaluating the second argument.

>>> Just False ||^ Just True
Just True
>>> Just False ||^ Just False
Just False
>>> Just False ||^ Nothing
Nothing
>>> Just True ||^ Nothing
Just True
>>> Just True ||^ error "Shouldn't be evaluated"
Just True

Since: 0.4.0