
The code below is a little interactive program that uses some state. It uses StateT with IO to keep state. My question is: what is the best way to generalize this program to work with any IO-like monad/medium? For example, I would like the program to function as it does now using stdin but I would also like it to function over IRC using the Net monad from http://haskell.org/haskellwiki/Roll_your_own_IRC_bot. Thanks for any suggestions. -- begin code -- import Control.Monad import Control.Monad.State import Data.List data PD = PD { pdCount :: Int , pdList :: [String] } deriving (Show) type PDState = StateT PD IO main = runStateT loop (PD { pdCount = 0, pdList = [] }) loop :: PDState a loop = forever $ do cmd <- liftIO getLine runCmd cmd runCmd :: String -> PDState () runCmd "Inc" = increment runCmd "PrintCount" = liftIO . print =<< getCount runCmd "PrintList" = liftIO . print =<< getList runCmd str | "Add " `isPrefixOf` str = addToList $ drop 4 str runCmd _ = return () getCount :: PDState Int getCount = pdCount `liftM` get getList :: PDState [String] getList = pdList `liftM` get increment :: PDState () increment = modify $ \st -> st { pdCount = pdCount st + 1 } addToList :: String -> PDState () addToList str = modify $ \st -> st { pdList = pdList st ++ [str]} -- end code --

On Mon, Oct 5, 2009 at 7:56 PM, Floptical Logic
The code below is a little interactive program that uses some state. It uses StateT with IO to keep state. My question is: what is the best way to generalize this program to work with any IO-like monad/medium? For example, I would like the program to function as it does now using stdin but I would also like it to function over IRC using the Net monad from http://haskell.org/haskellwiki/Roll_your_own_IRC_bot. Thanks for any suggestions.
Instead of specifying the monad implementation, specify the interface.
That is, you are using state operations (from MonadState) and IO
operations (from MonadIO). Try removing all the type signatures that
mention PDState and see what you get.
E.g., loop :: (MonadState PD m, MonadIO m) => m a
--
Dave Menendez

Instead of specifying the monad implementation, specify the interface. That is, you are using state operations (from MonadState) and IO operations (from MonadIO). Try removing all the type signatures that mention PDState and see what you get.
E.g., loop :: (MonadState PD m, MonadIO m) => m a
If I were to make an instance of MonadIO be a parameter to StateT and I wanted to use the Net monad (from Roll your own IRC bot on the wiki) with it, I would need to make Net an instance of MonadIO. What would this instance look like? I think the loop function is the least of my worries. I am more concerned about the runCmd function. What would go in place of print in runCmd? Thanks

On Mon, Oct 5, 2009 at 10:54 PM, Floptical Logic
If I were to make an instance of MonadIO be a parameter to StateT and I wanted to use the Net monad (from Roll your own IRC bot on the wiki) with it, I would need to make Net an instance of MonadIO. What would this instance look like?
If you define 'Net' as in the tutorial above, it will already be an instance of MonadIO :-)
I think the loop function is the least of my worries. I am more concerned about the runCmd function. What would go in place of print in runCmd?
The function 'liftIO . print' will work in any monad which is an instance of MonadIO. Take a look at http://hackage.haskell.org/packages/archive/mtl/1.1.0.2/doc/html/Control-Mon... for where 'liftIO' comes from. Antoine

On Mon, Oct 5, 2009 at 11:54 PM, Floptical Logic
Instead of specifying the monad implementation, specify the interface. That is, you are using state operations (from MonadState) and IO operations (from MonadIO). Try removing all the type signatures that mention PDState and see what you get.
E.g., loop :: (MonadState PD m, MonadIO m) => m a
If I were to make an instance of MonadIO be a parameter to StateT and I wanted to use the Net monad (from Roll your own IRC bot on the wiki) with it, I would need to make Net an instance of MonadIO. What would this instance look like?
You're referring to this type? type Net = ReaderT Bot IO That already is an instance of MonadIO. The relevant instances are instance MonadIO IO where liftIO = id instance MonadIO m => MonadIO (ReaderT r m) where liftIO = lift . liftIO
I think the loop function is the least of my worries. I am more concerned about the runCmd function. What would go in place of print in runCmd?
You're already using liftIO from MonadIO in the definition of runCmd,
so no changes need to be made.
Now, I didn't notice that getCount, getList, and increment don't take
arguments, so you either need to provide explicit type signatures or
set NoMonomorphismRestriction. If you do the latter and load the code
into ghci, you get:
*Main> :t runCmd
runCmd :: (MonadState PD m, MonadIO m) => [Char] -> m ()
--
Dave Menendez

It isn't clear what it is that you are trying to generalize the code to do. If you are trying to generalize it to work with an arbitrary input/output stream of lines, then unless you are doing arbitrary I/O it seems to me that all of these instance declarations are overkill. All that you need is to know how to get a line from the stream, and how to send a line. Assuming that this is the case, you have a couple of options. If you are only going to write to the stream within runCmd, then I'd just pass in the line writing function as an extra argument: type PDState = StateT PD loop :: (m String) -> (String -> m ()) -> PDState m a loop fetchLine sendLine = forever $ lift fetchLine >>= runCmd (lift sendLine) runCmd :: (String -> PDState m ()) -> PDstate m () runCmd sendLine cmd = case cmd of "Inc" -> increment "PrintCount" -> getCount >>= sendLine . show "PrintList" -> getList >>= sendLine . show ... If you forsee doing reading and writing at other points in your code, you could use the RWS monad to supply your code not only with a state but also with an environment with the reading and writing functions: data StreamFunctions m = StreamFunctions { streamLineFetcher :: m String , streamLineSender :: String -> m () } fetchLineFromStream = lift $ asks streamLineFetcher sendLineDownStream cmd = lift (asks streamLineSender >>= return . ($ cmd)) data PDMonad = RWST (StreamFunctions m) () PD m main = evalRWST loop (StreamFunctions ...) (PD { pdCount = 0, pdList = [] }) loop :: PDMonad m () loop = forever $ fetchLineFromStream >>= runCmd runCmd :: String -> PDMonad m () runCmd "Inc" = increment runCmd "PrintCount" = getCount >>= sendLineDownStream runCmd "PrintList" = getList >>= sendLineDownStream Note that we didn't have to put any additional constraints on the monad type variable "m", because other than the fact that we can get a line and send a line within it we don't otherwise care what it is. If you want to do other arbitrary I/O within this framework, though, then you will need to add a "MonadIO m" constraint. Cheers, Greg On Oct 5, 2009, at 8:54 PM, Floptical Logic wrote:
Instead of specifying the monad implementation, specify the interface. That is, you are using state operations (from MonadState) and IO operations (from MonadIO). Try removing all the type signatures that mention PDState and see what you get.
E.g., loop :: (MonadState PD m, MonadIO m) => m a
If I were to make an instance of MonadIO be a parameter to StateT and I wanted to use the Net monad (from Roll your own IRC bot on the wiki) with it, I would need to make Net an instance of MonadIO. What would this instance look like?
I think the loop function is the least of my worries. I am more concerned about the runCmd function. What would go in place of print in runCmd?
Thanks _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Oh, and I just thought of one more approach: class StreamMonad m where fetchLine = m sendLine = String -> m () instance StreamMonad IO where fetchLine = getLine sendLine = putLine fetchLineFromStream = lift fetchLine sendLineToStream = lift . sendLine type PDState = StateT PD main = runStateT loop (PD { pdCount = 0, pdList = [] }) loop :: (StreamMonad m) => PDState m a loop = forever $ fetchLineFromStream >>= runCmd runCmd :: (StreamMonad m) => String -> PDState m () runCmd "Inc" = increment runCmd "PrintCount" = getCount >>= sendLineToStream . . . i.e., you could use type-classes instead of passing around a datatype to specify how to send/fetch lines. On Oct 6, 2009, at 12:36 AM, Gregory Crosswhite wrote:
It isn't clear what it is that you are trying to generalize the code to do. If you are trying to generalize it to work with an arbitrary input/output stream of lines, then unless you are doing arbitrary I/ O it seems to me that all of these instance declarations are overkill. All that you need is to know how to get a line from the stream, and how to send a line.
Assuming that this is the case, you have a couple of options. If you are only going to write to the stream within runCmd, then I'd just pass in the line writing function as an extra argument:
type PDState = StateT PD
loop :: (m String) -> (String -> m ()) -> PDState m a loop fetchLine sendLine = forever $ lift fetchLine >>= runCmd (lift sendLine)
runCmd :: (String -> PDState m ()) -> PDstate m () runCmd sendLine cmd = case cmd of "Inc" -> increment "PrintCount" -> getCount >>= sendLine . show "PrintList" -> getList >>= sendLine . show ...
If you forsee doing reading and writing at other points in your code, you could use the RWS monad to supply your code not only with a state but also with an environment with the reading and writing functions:
data StreamFunctions m = StreamFunctions { streamLineFetcher :: m String , streamLineSender :: String -> m () }
fetchLineFromStream = lift $ asks streamLineFetcher sendLineDownStream cmd = lift (asks streamLineSender >>= return . ($ cmd))
data PDMonad = RWST (StreamFunctions m) () PD m
main = evalRWST loop (StreamFunctions ...) (PD { pdCount = 0, pdList = [] })
loop :: PDMonad m () loop = forever $ fetchLineFromStream >>= runCmd
runCmd :: String -> PDMonad m () runCmd "Inc" = increment runCmd "PrintCount" = getCount >>= sendLineDownStream runCmd "PrintList" = getList >>= sendLineDownStream
Note that we didn't have to put any additional constraints on the monad type variable "m", because other than the fact that we can get a line and send a line within it we don't otherwise care what it is. If you want to do other arbitrary I/O within this framework, though, then you will need to add a "MonadIO m" constraint.
Cheers, Greg
On Oct 5, 2009, at 8:54 PM, Floptical Logic wrote:
Instead of specifying the monad implementation, specify the interface. That is, you are using state operations (from MonadState) and IO operations (from MonadIO). Try removing all the type signatures that mention PDState and see what you get.
E.g., loop :: (MonadState PD m, MonadIO m) => m a
If I were to make an instance of MonadIO be a parameter to StateT and I wanted to use the Net monad (from Roll your own IRC bot on the wiki) with it, I would need to make Net an instance of MonadIO. What would this instance look like?
I think the loop function is the least of my worries. I am more concerned about the runCmd function. What would go in place of print in runCmd?
Thanks _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

class StreamMonad m where fetchLine = m sendLine = String -> m ()
instance StreamMonad IO where fetchLine = getLine sendLine = putLine
fetchLineFromStream = lift fetchLine sendLineToStream = lift . sendLine
This approach makes more sense to me. The equivalent to printing something to the screen in the Net (IRC) monad is privmsg and it is easy to make that connection using type classes. I don't see how to make this connection using MonadIO.

Putting a constraint on the MonadIO class actually makes your code less general rather than more since it prevents your code from ever being used in a purely functional setting. If you leave out this constraint, you can actually turn your code into a pure function by doing things like feeding it a wrapper monad that supplies a list of strings as input and returns the list of written strings at the end. The only reason why you would add a MonadIO constraint would be if you wanted to do other things that require the IO monad (e.g., connecting to a database, working with files, etc.) and so you wanted to require that the IO monad be ultimately present somewhere in the type so that you could use it. Cheers, Greg On Oct 6, 2009, at 8:22 AM, Floptical Logic wrote:
class StreamMonad m where fetchLine = m sendLine = String -> m ()
instance StreamMonad IO where fetchLine = getLine sendLine = putLine
fetchLineFromStream = lift fetchLine sendLineToStream = lift . sendLine
This approach makes more sense to me. The equivalent to printing something to the screen in the Net (IRC) monad is privmsg and it is easy to make that connection using type classes. I don't see how to make this connection using MonadIO.

David Menendez wrote:
Floptical Logic wrote:
The code below is a little interactive program that uses some state. It uses StateT with IO to keep state. My question is: what is the best way to generalize this program to work with any IO-like monad/medium? For example, I would like the program to function as it does now using stdin but I would also like it to function over IRC using the Net monad from http://haskell.org/haskellwiki/Roll_your_own_IRC_bot. Thanks for any suggestions.
Instead of specifying the monad implementation, specify the interface. That is, you are using state operations (from MonadState) and IO operations (from MonadIO). Try removing all the type signatures that mention PDState and see what you get.
E.g., loop :: (MonadState PD m, MonadIO m) => m a
Alternatively, you can use algebraic data types instead of type classes to generalize one program to different implementations. For monads, this can be achieved with http://hackage.haskell.org/package/MonadPrompt In particular, the idea is to turn every effect like getLine into a constructor GetLine and have different implementations pattern match on that. Regards, apfelmus -- http://apfelmus.nfshost.com

Heinrich Apfelmus wrote:
Alternatively, you can use algebraic data types instead of type classes to generalize one program to different implementations. For monads, this can be achieved with
http://hackage.haskell.org/package/MonadPrompt
In particular, the idea is to turn every effect like
getLine
into a constructor
GetLine
and have different implementations pattern match on that.
Ooo, that's interesting... I did wonder for a moment whether this would allow you to analyse what the monadic action does without actually "doing" it, but on reflection this is fundamentally impossible. The action that happens next can (and often does) depend on the result of a previous effect. I guess if you wanted to run your action through an optimiser before actually running it, you'd need to use arrows (and all the terrifying syntax that entails)...

On Thu, Oct 8, 2009 at 1:42 PM, Andrew Coppin
Heinrich Apfelmus wrote:
Alternatively, you can use algebraic data types instead of type classes to generalize one program to different implementations. For monads, this can be achieved with
http://hackage.haskell.org/package/MonadPrompt
In particular, the idea is to turn every effect like
getLine
into a constructor
GetLine
and have different implementations pattern match on that.
Ooo, that's interesting...
I did wonder for a moment whether this would allow you to analyse what the monadic action does without actually "doing" it, but on reflection this is fundamentally impossible. The action that happens next can (and often does) depend on the result of a previous effect.
I guess if you wanted to run your action through an optimiser before actually running it, you'd need to use arrows (and all the terrifying syntax that entails)...
Or Applicatives, or some other action algebra which is appropriate for the kind of actions you are trying to encode. Don't fool yourself into thinking that Monads and Arrows are all there are; those are just two formalisms for which we have discovered a lot of uses. But if what you're trying to encode doesn't match those, then don't use them. If you want to encode actions that can be optimized before usage, expose just enough so you can find the information you need to optimize it. Luke

My thought is that you could simply drop the IO from your type definition, type PDState = StateT PD You will need to change all of your type signature from "PDState <type>" to "PDState m <type>" to make them all polymorphic over the choice of monad. Then all you should need to do is to generalize the loop function to accept a line-fetching monad from the user: loop :: m a -> PDState m a loop getLine = forever $ do cmd <- lift getLine runCmd cmd Note how liftIO was changed to lift, which works for any monad and comes built-in with the StateT monad. Hope this helps! Cheers, Greg On Oct 5, 2009, at 4:56 PM, Floptical Logic wrote:
The code below is a little interactive program that uses some state. It uses StateT with IO to keep state. My question is: what is the best way to generalize this program to work with any IO-like monad/medium? For example, I would like the program to function as it does now using stdin but I would also like it to function over IRC using the Net monad from http://haskell.org/haskellwiki/Roll_your_own_IRC_bot. Thanks for any suggestions.
-- begin code -- import Control.Monad import Control.Monad.State import Data.List
data PD = PD { pdCount :: Int , pdList :: [String] } deriving (Show)
type PDState = StateT PD IO
main = runStateT loop (PD { pdCount = 0, pdList = [] })
loop :: PDState a loop = forever $ do cmd <- liftIO getLine runCmd cmd
runCmd :: String -> PDState () runCmd "Inc" = increment runCmd "PrintCount" = liftIO . print =<< getCount runCmd "PrintList" = liftIO . print =<< getList runCmd str | "Add " `isPrefixOf` str = addToList $ drop 4 str runCmd _ = return ()
getCount :: PDState Int getCount = pdCount `liftM` get
getList :: PDState [String] getList = pdList `liftM` get
increment :: PDState () increment = modify $ \st -> st { pdCount = pdCount st + 1 }
addToList :: String -> PDState () addToList str = modify $ \st -> st { pdList = pdList st ++ [str]} -- end code -- _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (7)
-
Andrew Coppin
-
Antoine Latter
-
David Menendez
-
Floptical Logic
-
Gregory Crosswhite
-
Heinrich Apfelmus
-
Luke Palmer