[Haskell-cafe] Generalizing IO

Floptical Logic flopticalogic at gmail.com
Mon Oct 5 19:56:50 EDT 2009


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 --


More information about the Haskell-Cafe mailing list