[Haskell-cafe] Generalizing IO

Gregory Crosswhite gcross at phys.washington.edu
Mon Oct 5 20:27:33 EDT 2009


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 at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe



More information about the Haskell-Cafe mailing list