-
Notifications
You must be signed in to change notification settings - Fork 82
Description
Hello!
First, thanks for authoring/maintaining this excellent library.
On a few occasions, I have run into some problems when trying to integrate haskeline
into another application, due to the API returning InputT
and the app not using a concrete monad transformer stack. Fortunately, I believe these issues are easily solved by providing ReaderT
conversions i.e.
-- InputTEnv is the internal environment, intentionally kept abstract.
toReaderT :: InputT m a -> ReaderT (InputTEnv m) m a
fromReaderT :: ReaderT (InputTEnv m) m a -> InputT m a
Motivation
Typeclasses
Suppose our core logic is written against typeclass constraints i.e. MTL-style:
-- Entry-point
runApp :: (MonadLogger m) => m ()
-- Application type, IO with some environment.
newtype AppT e m a = MkAppT (ReaderT e m a)
runAppT :: AppT e m a -> e -> m a
runAppT (MkAppT m) e = runReaderT m e
-- main
main :: IO ()
main = runAppT runApp mkEnv
We want to incorporate user input via haskeline
, so we modify this to:
import System.Console.Haskeline qualified as H
class MonadHaskeline m where
getInputLine :: String -> m (Maybe String)
runApp :: (MonadHaskeline m, MonadLogger m) => m ()
-- new instances for ReaderT and AppT
deriving newtype instance (MonadHaskeline m) => MonadHaskeline (AppT e m)
instance (MonadHaskeline m) => MonadHaskeline (ReaderT e m) where
getInputLine = lift . getInputLine
-- Running haskeline for real requires runInputT, so our transformer
-- stack is now:
--
-- AppT Env (InputT IO) a
main :: IO ()
main = H.runInputT H.defaultSettings $ runAppT runApp mkEnv
Unfortunately this will fail to typecheck because InputT
does not have our MonadLogger
constraint. We can write the (potentially orphan) instance ourselves, but this can be an enormous amount of boilerplate when we have many (possibly large) classes. The is essentially the classic N^2
instances problem for InputT
.
Thankfully, we can easily solve this with the above ReaderT
function:
instance {-# OVERLAPS #-} (MonadIO m, MonadMask m) => MonadHaskeline (ReaderT (InputTEnv m) m) where
getInputLine = toReaderT . H.getInputLine
-- 1. runApp: AppT () (ReaderT (InputTEnv IO) IO) ()
-- 2. runAppT: ReaderT (InputTEnv IO) IO ()
-- 3. fromReaderT: InputT IO ()
-- 4. runInputT: IO ()
main :: IO ()
main = H.runInputT H.defaultSettings $ fromReaderT $ runAppT runApp ()
The overlapping instance allows us to write our logic in terms of ReaderT
-- hence any instances written for it are passed through -- then we convert to InputT
with our new function, and run in IO
as expected.
Effects
Incorporting haskeline into an effects library runs into a similar problem. For instance, if we wanted to use effectful
, we'd have something like:
type instance DispatchOf Haskeline = Dynamic
data Haskeline :: Effect where
GetInputLine :: String -> Haskeline m (Maybe String)
getInputLine :: (Haskeline :> es) => String -> Eff es (Maybe String)
getInputLine = send . GetInputLine
Then our IO
handler would be:
runHaskeline ::
( IOE :> es
) =>
Eff (Haskeline : es) a ->
Eff es a
runHaskeline = interpret_ $ \case
-- Use H.getInputLine
GetInputLine s -> ???
For ???
we need to somehow use H.getInputLine :: String -> InputT IO (Maybe String)
, but we are stuck because:
- Eliminating
InputT
requiresH.runInputT
. - We need to return
Eff
.
Returning Eff es (InputT m a)
is possible, though means giving up on polymorphism, at least for haskeline.
We could use H.runInputT
in the handler, but it's probably not what we want, since it means we would be initializing haskeline for every function call.
Thankfully, the proposed ReaderT
functions work here too:
runHaskeline ::
( IOE :> es,
Reader (InputTEnv IO) :> es
) =>
Eff (Haskeline : es) a ->
Eff es a
runHaskeline = interpret_ $ \case
GetInputLine s -> liftInputT $ H.getInputLine s
liftInputT :: (IOE :> es, Reader (InputTEnv IO) :> es) => InputT IO a -> Eff es a
liftInputT f = ask >>= liftIO . runReaderT (HR.toReaderT f)
Remarks
-
There is precedence for a "haskeline interface", so I am not the only one who has had this idea:
-
This can be viewed as a generalization of the
withRunInBase
function added in 131:withRunInBase :: Monad m => ((forall a . InputT m a -> m a) -> m b) -> InputT m b withRunInBase inner = fromReaderT $ do env <- ask lift $ inner $ \input -> runReaderT (toReaderT input) env
-
I fleshed out these examples here.
-
Just to be clear: This does not expose any internal details, other than the fact that
InputT
is isomorphic toReaderT
.
Tl;dr
- Haskeline would be significantly more flexible if it provided conversions to/from
ReaderT
.
Any interest in this? I am happy to open a PR.
Thanks!