Send Beginners mailing list submissions to
        beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
        http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
        beginners-requ...@haskell.org

You can reach the person managing the list at
        beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than "Re: Contents of Beginners digest..."


Today's Topics:

   1. Re:  Understanding reason for Monad (Pietro Grandinetti)
   2. Re:  Understanding reason for Monad (Travis Cardwell)


----------------------------------------------------------------------

Message: 1
Date: Tue, 28 Feb 2023 14:01:15 +0000
From: Pietro Grandinetti <pietro....@hotmail.it>
To: Travis Cardwell <travis.cardw...@extrema.is>, The
        Haskell-Beginners Mailing List - Discussion of primarily
        beginner-level topics related to Haskell <beginners@haskell.org>
Subject: Re: [Haskell-beginners] Understanding reason for Monad
Message-ID:
        
<db9p191mb1514d1d85824036f56bb24bdfc...@db9p191mb1514.eurp191.prod.outlook.com>
        
Content-Type: text/plain; charset="iso-8859-1"

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....@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-0001.html>

------------------------------

Message: 2
Date: Wed, 1 Mar 2023 18:59:02 +0900
From: Travis Cardwell <travis.cardw...@extrema.is>
To: Pietro Grandinetti <pietro....@hotmail.it>
Cc: The Haskell-Beginners Mailing List - Discussion of primarily
        beginner-level topics related to Haskell <beginners@haskell.org>
Subject: Re: [Haskell-beginners] Understanding reason for Monad
Message-ID:
        <CACaJP_QSi85-LDLE5bzJJv=U7U-C1z8co0_eY=lhtz7hk2k...@mail.gmail.com>
Content-Type: text/plain; charset="UTF-8"

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


------------------------------

Subject: Digest Footer

_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners


------------------------------

End of Beginners Digest, Vol 170, Issue 1
*****************************************

Reply via email to