问题
Ok, so I have figured out how to implement Reader
(and ReaderT
, not shown) using the operational package:
{-# LANGUAGE GADTs, ScopedTypeVariables #-}
import Control.Monad.Operational
data ReaderI r a where
Ask :: ReaderI r r
type Reader r a = Program (ReaderI r) a
ask :: Reader r r
ask = singleton Ask
runReader :: forall r a. Reader r a -> r -> a
runReader = interpretWithMonad evalI
where evalI :: forall b. ReaderI r b -> (r -> b)
evalI Ask = id
But I can't figure out for my life how to do this with free monads (I'm using Edward Kmett's free package). The closest I've gotten is this, which I understand is cheating (something about how ((->) r)
is already a monad):
import Control.Monad.Free
type Reader r a = Free ((->) r) a
ask :: Reader r r
ask = Free Pure
runReader :: Reader r a -> r -> a
runReader (Pure a) _ = a
runReader (Free k) r = runReader (k r) r
-- Or, more simply and tellingly:
--
-- > runReader = retract
Even if this wasn't as dumb as I suspect it is, it's not what I want because what I want, basically, is to be able to inspect a Reader
as data...
回答1:
I don't think it can be done except they way you have. But, I don't think this is unique to reader. Consider the free monad version of writer
data WriterF m a = WriterF m a deriving (Functor)
type Writer m = Free (WriterF m)
obviously, WriterF
is isomorphic to writer, but this does behave the way we would expect with the simple algebra
algebraWriter :: Monoid m => WriterF m (m,a) -> (m,a)
algebraWriter (WriterF m1 (m2,a)) = (m1 <> m2,a)
thus
runWriter :: Monoid m => Writer m a -> (m,a)
runWriter (Pure a) = (mempty,a)
runWriter (Free x) = algebraWriter . fmap runWriter $ x
Similarly, I think of the Free reader as
type ReaderF r = (->) r
type Reader r = Free (ReaderF r)
I like this, because adding them gives you the state monad
type State x = Free ((ReaderF x) :+: (WriterF x))
runState :: State x a -> x -> (a,x)
runState (Pure a) x = (a,x)
runState (Free (Inl f)) x = runState (f x) x
runState (Free (Inr (WriterF x f))) _ = runState f x
Note, that your operational solution could be made to work with Free
by using the "free functor", as can anything that works with operational
data FreeFunctor f x = forall a. FreeFunctor (f a) (a -> x)
but, that FreeFunctor ReaderI
is also isomorphic to (->)
.
回答2:
Well, I've been looking at this for 3 hours now, and I think I found something I like better. Since the Reader
applicative is the same as the Reader
monad, we can try an applicative version of operational
:
{-# LANGUAGE RankNTypes, GADTs, FlexibleInstances #-}
import Control.Applicative
data ProgramA instr a where
Pure :: a -> ProgramA r a
Ap :: ProgramA r (a -> b) -> ProgramA r a -> ProgramA r b
Instr :: instr a -> ProgramA instr a
infixl `Ap`
instance Functor (ProgramA instr) where
fmap f (Pure a) = Pure (f a)
fmap f (ff `Ap` fa) = ((f .) <$> ff) `Ap` fa
fmap f instr = Pure f `Ap` instr
instance Applicative (ProgramA instr) where
pure = Pure
(<*>) = Ap
interpretA :: Applicative f =>
(forall a. instr a -> f a)
-> ProgramA instr a
-> f a
interpretA evalI (Pure a) = pure a
interpretA evalI (ff `Ap` fa) = interpretA evalI ff <*> interpretA evalI fa
interpretA evalI (Instr i) = evalI i
data ReaderI r a where
Ask :: ReaderI r r
type Reader r a = ProgramA (ReaderI r) a
ask :: Reader r r
ask = Instr Ask
runReader :: Reader r a -> r -> a
runReader = interpretA (\Ask -> id)
instance Monad (ProgramA (ReaderI r)) where
return = pure
ma >>= f = runReader <$> fmap f ma <*> ask
The structure of a ProgramA (ReaderI r) a)
can be inspected more straightforwardly than either Program (ReaderI r) a
or Free ((->) r) a
.
来源:https://stackoverflow.com/questions/15426320/how-do-i-implement-reader-using-free-monads