How would you run a monad within another monad?

Hey All, Suppose we have this generalized situation: I have some class that does IO with user data, but we want to hide the full IO interface, so we do something like this: class (Monad m) => Doohickey m where getCurrentTime :: m Time olderRecords :: m [String] addRecord :: String -> m () Suppose next that we want to run a monadic value of that type, with some context, inside another monad. For example, we have some file on disk with user data. We want the top level to open the file, and then run a monadic action with the above signature. The username provides the context. Give us a username, and we'll open a file, and then run a monadic value w/ the above signature on the file. e.g. class (Monad m) => TopLevel m where openFileAndRun :: (Doohickey n) => UserName -> n a -> m a In this example, we could have a function that takes an input string s, goes through the old records, and if it sees that s is not present, then it will add it to the records. Suppose then that we want to generalize the interface, so that it could apply equally to a local file, a db, the cloud, whatever. That's why we need the Toplevel monad. We want to separate "what we want to do with the user data" from "how we will store and modify the userdata". Toplevel actions therefore needs to be able to execute Doohickey actions. How would you guys do this? I'm trying to write the signatures but ghc borks on "Ambiguous type variable in the constraints" error. It appears to be caused by the usage of the Doohickey typeclass in the signature of Toplevel, when I actually try to write a monadic value of type Toplevel, that calls a monadic value of type Doohickey. Much thanks for any help! -Arthur

Copypasting and loading your code doesn't throw an error. Please, pastebin an example that demonstrates the error. -- Jason Dusek

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
Copypasting and loading your code doesn't throw an error. Please, pastebin an example that demonstrates the error.
-- Jason Dusek

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
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
wrote: Copypasting and loading your code doesn't throw an error. Please, pastebin an example that demonstrates the error.
-- Jason Dusek

I wonder how you would do this with type familes...
On Tue, Apr 14, 2009 at 2:39 PM, Arthur Chan
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
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
wrote: Copypasting and loading your code doesn't throw an error. Please, pastebin an example that demonstrates the error.
-- Jason Dusek

Congratulations. -- Jason Dusek
participants (2)
-
Arthur Chan
-
Jason Dusek