[Haskell-beginners] How would you run a monad within another
monad?
Arthur Chan
baguasquirrel at gmail.com
Tue Apr 14 17:40:25 EDT 2009
I wonder how you would do this with type familes...
On Tue, Apr 14, 2009 at 2:39 PM, Arthur Chan <baguasquirrel at gmail.com>wrote:
> I seem to have finally solved my own problem, via something I learned from
> RWH. The solution is to use functional dependencies...
>
> The problem was that the compiler needed to know the relationship between
> Doohickeys and Toplevels, and I couldn't figure out how to tell it that...
>
>
>
> {-# LANGUAGE GeneralizedNewtypeDeriving, NoMonomorphismRestriction,
> FunctionalDependencies, MultiParamTypeClasses #-}
>
> import IO
> import Control.Monad.Reader
>
>
> class (Monad n) => Doohickey n where
> putRecord :: String -> n ()
>
> class (Monad m, Doohickey n) => Toplevel m n | m -> n where
> foo :: FilePath -> n a -> m a
>
> newtype IODoohickey a = IODoohickey { runIODoohickey :: ReaderT Handle IO a
> } deriving (Monad, MonadReader Handle, MonadIO)
>
> instance Doohickey IODoohickey where
> putRecord = liftIO . putStrLn
>
> instance Toplevel IO IODoohickey where
> foo s k = do
> f <- liftIO $ openFile s AppendMode
> runReaderT (runIODoohickey k) f
>
>
> myDoohickey = do
> putRecord "foo"
> putRecord "bar"
>
> myOtherDoohickey = do
> putRecord "hello"
> putRecord "world"
> return True
>
>
>
>
> On Tue, Apr 14, 2009 at 2:05 PM, Arthur Chan <baguasquirrel at gmail.com>wrote:
>
>> Here's my contrived example that threw the error.
>>
>> If you go into ghci, and do a `:t (foo' "blah" myDoohickey)`, you will get
>> the type signature "IO ()".
>> Doing the same for myOtherDoohickey returns "IO True"
>>
>> So you would think that you'd be able to uncomment the code that makes IO
>> an instance of Toplevel. foo' is a function that allows IO to run monadic
>> values of type Doohickey. But it doesn't work.
>>
>>
>> ---
>>
>> import IO
>> import Control.Monad.Reader
>>
>>
>> class (Monad n) => Doohickey n where
>> putRecord :: String -> n ()
>>
>> class (Monad m) => Toplevel m where
>> foo :: (Doohickey n) => FilePath -> n a -> m a
>>
>> newtype IOToplevelT a = IOToplevelT { runIOToplevelT :: ReaderT Handle IO
>> a } deriving (Monad, MonadReader Handle, MonadIO)
>>
>> instance Doohickey IOToplevelT where
>> putRecord = liftIO . putStrLn
>>
>> foo' s k = do
>> f <- liftIO $ openFile s AppendMode
>> runReaderT (runIOToplevelT k) f
>>
>> --instance Toplevel IO where
>> -- foo = foo'
>>
>> myDoohickey = do
>> putRecord "foo"
>> putRecord "bar"
>>
>> myOtherDoohickey = do
>> putRecord "hello"
>> putRecord "world"
>> return True
>>
>>
>>
>> On Mon, Apr 13, 2009 at 7:55 PM, Jason Dusek <jason.dusek at gmail.com>wrote:
>>
>>> Copypasting and loading your code doesn't throw an error. Please,
>>> pastebin an example that demonstrates the error.
>>>
>>> --
>>> Jason Dusek
>>>
>>
>>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/beginners/attachments/20090414/e56db9ad/attachment.htm
More information about the Beginners
mailing list