[Haskell-beginners] Understanding reason for Monad
Pietro Grandinetti
pietro.gra at hotmail.it
Tue Feb 28 14:01:15 UTC 2023
Travis,
Thank you very much. I have a question about the `putLanguage` function below.
________________________________
module Main (main) where
-- https://hackage.haskell.org/package/base
import Control.Monad.IO.Class (MonadIO(liftIO))
import Data.Bool (bool)
import System.Environment (getArgs)
-- https://hackage.haskell.org/package/transformers
import Control.Monad.Trans.Reader (ReaderT(runReaderT), asks)
data Locale = En | It
class HasLocale a where
getLocale :: a -> Locale
instance HasLocale Locale where
getLocale = id
class MonadLocale m where
askLocale :: m Locale
instance (HasLocale r, Monad m) => MonadLocale (ReaderT r m) where
askLocale = asks getLocale
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. But what would happen if the function type was
putLanguage' :: (MonadOut m, MonadIn v) => v () -> m () -- both MonadOut and MonadIn are instances of MonadLocale
putLanguage' = do
locale <- askLocale
... -- other things
which `askLocale` function would be used?
putHelloWorld :: (MonadIO m, MonadLocale m) => m ()
putHelloWorld = do
locale <- askLocale
liftIO . putStrLn $ case locale of
En -> "Hello world!"
It -> "Ciao mondo!"
app :: (MonadIO m, MonadLocale m) => m ()
app = do
putLanguage
putHelloWorld
main :: IO ()
main = do
locale <- bool En It . elem "--it" <$> getArgs
runReaderT app locale
In this example, the state/context is simply a `Locale` value, which
defaults to `En`. The `main` function checks if string `--it` is passed
as an argument and configures the locale to `It` in that case.
The final line runs the `app` function using a `ReaderT` monad
transformer with the locale as the "environment." The `app` function,
as well as all functions that it calls in the same monad, have access to
this environment.
Type class `HasLocale` just provides a `getLocale` function for getting
a `Locale` value from some possibly larger value. The instance is the
trivial case of `Locale` itself.
Type class `MonadLocale` provides a locale API, just `askLocale` in this
case. In a monad that implements `MonadLocale`, the `askLocale`
function is able to get the locale. The instance provides a way to do
this in a Reader monad that has an environment with a `HasLocale`
instance. In this minimal example, the Reader environment is a `Locale`
value, so that trivial `HasLocale` instance is used.
The remaining three functions implement the example application. They
do not specify a concrete monad; they instead specify constraints on the
monad, allowing them to run in any monad that meets those constraints.
The `MonadIO m` constraint is required to use `liftIO . putStrLn` in
order to print to the screen, and the `MonadLocale m` constraint is
required to get the configured locale. In this example, they are run
in concrete monad `ReaderT Locale IO`, but note that they could also be
run in different monads as long as the constraints are satisfied.
The `app` function calls `putLanguage` and then `putHelloWorld`, and
both of these functions are able to use `askLocale` to get the
configured locale.
$ minimal-context
English
Hello world!
$ minimal-context --it
Italiano
Ciao mondo!
The architecture/design of a project/program depends on the needs. In
some programs, explicitly passing context as arguments is the best
approach. In others, even `MonadIO` should be avoided, since `IO` makes
anything possible. Getting back to your original question, the use of
type classes allows a library author to implement functions that work
across a wide variety of coding styles.
Cheers,
Travis
On Sun, Feb 26, 2023 at 6:35 PM Pietro Grandinetti
<pietro.gra at hotmail.it> wrote:
> Hi Travis,
>
> Thanks. This was indeed helpful. I think I haven't grasped the concept of "context" yet. Do you know any minimal example that shows this?
>
> Thanks.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/beginners/attachments/20230228/3fcc79c7/attachment.html>
More information about the Beginners
mailing list