[Haskell-cafe] Doing without IORef

Jinwoo Lee jinwoo68 at gmail.com
Thu Apr 3 06:03:30 EDT 2008


Hi,

Recently I wrote a code that uses readline library
(System.Console.Readline).
I had to maintain a state (file path) and do IO throughout the code, so I
decided to use StateT monad.

The problem was that in order to retrieve the current state (file path)
inside the handler that had been registered by using bindKey function of
readline, I had to resort back to using IORef rather than using the state
stored in the StateT monad. It's because the handler for bindKey should have
the type of Int -> Char -> IO Int.

Here is my code snippet.


type MyState a = StateT FilePath IO a


rootDir :: FilePath
rootDir = "/root/"


main :: IO ()
main = do hSetBuffering stdout NoBuffering
          execStateT (do
            pwd <- get
            pwdRef <- lift $ newIORef pwd
            lift $ bindKey '\t' (tabHandler pwdRef)
            lift $ bindKey '\^L' ctlLHandler
            commandLoop pwdRef) rootDir
          return ()


tabHandler :: IORef FilePath -> Int -> Char -> IO Int
tabHandler pwdRef _ _ = do
  *pwd <- readIORef pwdRef*
  insertText pwd
  return 0

...

commandLoop :: IORef FilePath -> MyState ()
commandLoop pwdRef = commandLoop'
  where
    commandLoop' = do
      pwd <- get
      *lift $ writeIORef pwdRef pwd*
      maybeLine <- lift $ readline $ makePrompt $ dropTrailingPathSeparator
pwd
      case maybeLine of
        Nothing     -> return ()
        Just "exit" -> return ()
        Just line   -> do
          let tokens = words line
          case tokens of
            []         -> commandLoop'
            ("exit":_) -> return ()
            _          -> do lift $ addHistory line
                             processLine tokens
                             commandLoop'
...


Is there any way in which I can do without IORef in tabHandler and
commandLoop (written in red and bold, if you can see)?

Thanks,
Jinwoo


-- 
Jinwoo Lee
Always remember that you are unique. Just like everyone else.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20080403/32876846/attachment.htm


More information about the Haskell-Cafe mailing list