[Haskell-cafe] How to use Reader?

Hilco Wijbenga hilco.wijbenga at gmail.com
Wed Jun 20 04:46:55 UTC 2018


Ah, quite simple. Thanks!

On Tue, Jun 19, 2018 at 9:39 PM, Matt <parsonsmatt at gmail.com> wrote:
> showText text = do
>     a <- showA
>     return ("[" `append` text `append` a `append` "]")
>
>
> Matt Parsons
>
> On Tue, Jun 19, 2018 at 10:35 PM, Hilco Wijbenga <hilco.wijbenga at gmail.com>
> wrote:
>>
>> Hi all,
>>
>> I think I'm pretty close but not quite there yet. Let's say I have the
>> following:
>>
>> {-# LANGUAGE OverloadedStrings #-}
>>
>> module Main where
>>
>> import Prelude (IO)
>> import Data.Text (Text, append)
>> import Data.Text.IO (putStrLn)
>>
>> main :: IO ()
>> main =
>>     putStrLn (showText "Hello World!" config)
>>     where
>>         config :: Config
>>         config = Config (A "Boo")
>>
>> data A = A Text
>>
>> data Config = Config { a :: A }
>>
>> showText :: Text -> Config -> Text
>> showText text config =
>>     "[" `append` text `append` (showA config) `append` "]"
>>
>> showA :: Config -> Text
>> showA config =
>>     "'" `append` text `append` "'"
>>     where
>>         A text = a config
>>
>> Now I want to use Reader. This is as close as I can get:
>>
>> {-# LANGUAGE OverloadedStrings #-}
>>
>> module Main where
>>
>> import Prelude (IO, return, ($))
>> import Data.Text (Text, append)
>> import Data.Text.IO (putStrLn)
>> import Control.Monad.Reader (Reader, asks, runReader)
>>
>> main :: IO ()
>> main =
>>     putStrLn (runReader (showText "Hello World!") config)
>>     where
>>         config :: Config
>>         config = Config (A "Boo")
>>
>> data A = A Text
>>
>> data Config = Config { a :: A }
>>
>> showText :: Text -> Reader Config Text
>> showText text =
>>     return $
>>         "[" `append` text `append` showA `append` "]"
>>
>> showA :: Reader Config Text
>> showA = do
>>     A text <- asks a
>>     return $
>>         "'" `append` text `append` "'"
>>
>> This is almost correct, except for the showA invocation in showText.
>> It wants a Text but it's getting a Reader Config Text. What is the
>> magic to make this work?
>>
>> Cheers,
>> Hilco
>> _______________________________________________
>> Haskell-Cafe mailing list
>> To (un)subscribe, modify options or view archives go to:
>> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
>> Only members subscribed via the mailman list are allowed to post.
>
>


More information about the Haskell-Cafe mailing list