I came across an implementation of reader monads by Andy Gill,
<http://www.cse.ogi.edu/~andy/monads/MonadReader.htm>
inspired by the paper "Functional Programming with Overloading
and Higher-Order Polymorphism" (by Mark P Jones)
<http://www.cse.ogi.edu/~mpj/pubs/springschool.html>:

-- ------------------------------------------------------------
-- Reader monads.
-- A class of monads for describing computations that
-- consult some fixed environment.

class (Monad m) => ReaderMonad s m where
    -- asks for the (internal non-mutable) state
    ask :: m s

-- this allows you to provide a projection function
asks :: (ReaderMonad s m)  => (s -> a) -> m a
asks f = do s <- ask
            return (f s)

-- a parametarized reader monad
newtype Reader w a = Reader { runReader :: w -> a }

instance Functor (Reader w) where
    fmap f m = Reader ( \w -> f (runReader m w) )

instance Monad (Reader w) where
    return v = Reader ( \w -> v )

    p >>= f  = Reader ( \w -> runReader (f (runReader p w)) w )

    fail str = Reader ( \w -> error str )

instance ReaderMonad w (Reader w) where
    ask = Reader ( \w -> w )
-- -------------------------------------------------------------

Would someone write a simple Haskell program that ilustrates how
one can use this reader monad?

I have tried the following, but it fails at compilation:

---------------
test = do env <- ask
          if env == "choose a"
              then return 'a'
              else return 'b'

do_test = runReader test "choose a"

main = putStr (show do_test)
---------------

Thanks.

Romildo
--
Prof. Jos� Romildo Malaquias <[EMAIL PROTECTED]>
Departamento de Computa��o
Universidade Federal de Ouro Preto
Brasil

Reply via email to