[Haskell-beginners] Understanding reason for Monad
Travis Cardwell
travis.cardwell at extrema.is
Wed Mar 1 09:59:02 UTC 2023
Hi Pietro,
On Tue, Feb 28, 2023 at 11:01 PM Pietro Grandinetti wrote:
> Thank you very much. I have a question about the `putLanguage`
> function below.
You are welcome!
putLanguage :: (MonadIO m, MonadLocale m) => m ()
putLanguage = do
locale <- askLocale
liftIO . putStrLn $ case locale of
En -> "English"
It -> "Italiano"
> I understand that the result type, in this case
> `MonadLocale m => m ()`, determines in what context the function
> `askLocale` is resolved.
Correct. This function runs in monad `m`: it runs in any monad with
both `MonadIO` and `MonadLocale` instances, returning `()` (pronounced
"unit"). Function `askLocale` can be used here because the monad has a
`MonadLocale` instance.
> But what would happen if the function type was
putLanguage' :: (MonadOut m, MonadIn v) => v () -> m ()
putLanguage' = do
locale <- askLocale
...
> which `askLocale` function would be used?
This function runs in monad `m`: it runs in any monad with a `MonadOut`
instance, returning `()`. Function `askLocale` cannot be used here
because there is no `MonadLocale m` constraint. To answer the gist of
your question, however, the functions available to use are determined by
the `m` monad, *not* `v`.
In this function, `v ()` is a function that is passed as an argument.
Such a monadic argument is generally called an "action." You can
execute that action if you can create the appropriate monadic context.
In this case, there is no `MonadIn m` constraint, so it is not possible
to execute the action within `putLanguage'` (given just the above
information).
Here is a minimal example:
module Main (main) where
-- https://hackage.haskell.org/package/base
import Control.Monad.IO.Class (MonadIO(liftIO))
actionDemo
:: MonadIO m
=> (String -> IO ())
-> m ()
actionDemo trace = liftIO $ trace "Hello!"
main :: IO ()
main = actionDemo putStrLn
Function `actionDemo` runs in monad `m`: it runs in any monad with a
`MonadIO` instance, returning `()`. It accepts argument `trace`, which
is an action that accepts a `String` argument, runs in the `IO` monad,
and returns `()`. The `main` function passes `putStrLn`, which has this
type.
Since `actionDemo` runs in monad `m`, it cannot execute an action in the
`IO` monad directly. `MonadIO` provides a `liftIO` function to execute
actions in the `IO` monad, however, so `liftIO` is used here to execute
`trace` in the `IO` monad.
Cheers,
Travis
More information about the Beginners
mailing list