Blog Archive

Saturday, April 18, 2009

Using Haskeline

Earlier today I decided to unearth an old project of mine - figuring that the best way to learn two languages was to implement one in the other, I wrote a MUMPS interpreter in Haskell. I was learning MUMPS for work, and Haskell for fun.

Back when I wrote it, I used readline in the REPL part of the interpreter - during the cleanup I wanted to move away from readline as GHC doesn't ship with it any more, and sometimes it can be a pain to install on its own. So I switched to Haskeline. It doesn't ship with GHC either, but it's proven easier for me to install.

Haskeline has got a really friendly API, with all of the functions operating inside the InputT m monad transformer. "Great," I think, "I can just pile this on top of my existing monad transformers stack in the interpreter!"

All was not so simple, as InputT has it's own instance of MonadState and MonadReader which allows the user of the library to peer into the guts of the implementation. But I didn't want to monkey with my text entry, I just wanted it to work and get out of my way, and I wanted the rest of my code to use the MonadState instance further down the stack that I had already set up.

So I wrote a small wrapper for Haskeline that's more friendly to mtl-style monad transformer composition. As written, it only composes with MonadIO and MonadState, but it would be straightforward to do more.

My wrapper uses HaskelineT instead of InputT, and exposes the same core functions as Haskeline (except for withInterrupt). It doesn't do anything I couldn't do by peppering lifts all over the place, but this way feels a but cleaner to me - Haskeline keeps its workings to itself, and I don't have to think about the order of the layered monad transformers.


{-# LANGUAGE FlexibleInstances
, MultiParamTypeClasses
, UndecidableInstances
, GeneralizedNewtypeDeriving
#-}

import qualified System.Console.Haskeline as H
import System.Console.Haskeline.Completion
import System.Console.Haskeline.MonadException

import Control.Applicative
import Control.Monad.State

newtype HaskelineT m a = HaskelineT {unHaskeline :: H.InputT m a}
deriving (Monad, Functor, Applicative, MonadIO, MonadException, MonadTrans, MonadHaskeline)

runHaskelineT :: MonadException m => H.Settings m -> HaskelineT m a -> m a
runHaskelineT s m = H.runInputT s (unHaskeline m)

runHaskelineTWithPrefs :: MonadException m => H.Prefs -> H.Settings m -> HaskelineT m a -> m a
runHaskelineTWithPrefs p s m = H.runInputTWithPrefs p s (unHaskeline m)

class MonadException m => MonadHaskeline m where
getInputLine :: String -> m (Maybe String)
getInputChar :: String -> m (Maybe Char)
outputStr :: String -> m ()
outputStrLn :: String -> m ()


instance MonadException m => MonadHaskeline (H.InputT m) where
getInputLine = H.getInputLine
getInputChar = H.getInputChar
outputStr = H.outputStr
outputStrLn = H.outputStrLn


instance MonadState s m => MonadState s (HaskelineT m) where
get = lift get
put = lift . put

instance MonadHaskeline m => MonadHaskeline (StateT s m) where
getInputLine = lift . getInputLine
getInputChar = lift . getInputChar
outputStr = lift . outputStr
outputStrLn = lift . outputStrLn

Listening:

Watching:

  • House
  • Ride Back