I've written two monads for a domain-specific language I'm developing. The first is Lang
, which is supposed to include everything needed to parse the language line by line. I knew I would want reader, writer, and state, so I used the RWS
monad:
type LangLog = [String]
type LangState = [(String, String)]
type LangConfig = [(String, String)]
newtype Lang a = Lang { unLang :: RWS LangConfig LangLog LangState a }
deriving
( Functor
, Applicative
, Monad
, MonadReader LangConfig
, MonadWriter LangLog
, MonadState LangState
)
The second is Repl
, which uses Haskeline to interact with a user:
newtype Repl a = Repl { unRepl :: MaybeT (InputT IO) a }
deriving
( Functor
, Applicative
, Monad
, MonadIO
)
Both seem to work individually (they compile and I've played around with their behavior in GHCi), but I've been unable to embed Lang
into Repl
to parse lines from the user. The main question is, how can I do that?
More specifically, if I write Repl
to include Lang
the way I originally intended:
newtype Repl a = Repl { unRepl :: MaybeT (InputT IO) (Lang a) }
deriving
( Functor
, Applicative
, Monad
, MonadIO
, MonadReader LangConfig
, MonadWriter LangLog
, MonadState LangState
)
It mostly typechecks, but I can't derive Applicative
(required for Monad
and all the rest).
Since I'm new to monad transformers and designing REPLs, I've been studying/cargo-culting from Glambda's Repl.hs
and Monad.hs
. I originally picked it because I will try to use GADTs for my expressions too. It includes a couple unfamiliar practices, which I've adopted but am totally open to changing:
newtype
+GeneralizedNewtypeDeriving
(is this dangerous?)MaybeT
to allow quitting the REPL withmzero
Here's my working code so far:
{- LANGUAGE GeneralizedNewtypeDeriving #-}
module Main where
import Control.Monad.RWS.Lazy
import Control.Monad.Trans.Maybe
import System.Console.Haskeline
-- Lang monad for parsing language line by line
type LangLog = [String]
type LangState = [(String, String)]
type LangConfig = [(String, String)]
newtype Lang a = Lang { unLang :: RWS LangConfig LangLog LangState a }
deriving
( Functor
, Applicative
, Monad
, MonadReader LangConfig
, MonadWriter LangLog
, MonadState LangState
)
-- Repl monad for responding to user input
newtype Repl a = Repl { unRepl :: MaybeT (InputT IO) (Lang a) }
deriving
( Functor
, Applicative
, Monad
, MonadIO
)
And a couple attempts to extend it. First, including Lang
in Repl
as mentioned above:
newtype Repl a = Repl { unRepl :: MaybeT (InputT IO) (Lang a) }
deriving
( Functor
, Applicative
)
-- Can't make a derived instance of ‘Functor Repl’
-- (even with cunning newtype deriving):
-- You need DeriveFunctor to derive an instance for this class
-- In the newtype declaration for ‘Repl’
--
-- After :set -XDeriveFunctor, it still complains:
--
-- Can't make a derived instance of ‘Applicative Repl’
-- (even with cunning newtype deriving):
-- cannot eta-reduce the representation type enough
-- In the newtype declaration for ‘Repl’
Next, trying to just use both of them at once:
-- Repl around Lang:
-- can't access Lang operations (get, put, ask, tell)
type ReplLang a = Repl (Lang a)
test1 :: ReplLang ()
test1 = do
liftIO $ putStrLn "can do liftIO here"
-- but not ask
return $ return ()
-- Lang around Repl:
-- can't access Repl operations (liftIO, getInputLine)
type LangRepl a = Lang (Repl a)
test2 :: LangRepl ()
test2 = do
_ <- ask -- can do ask
-- but not liftIO
return $ return ()
Not shown: I also tried various permutations of lift
on the ask
and putStrLn
calls. Finally, to be sure this isn't an RWS-specific issue I tried writing Lang
without it:
newtype Lang2 a = Lang2
{ unLang2 :: ReaderT LangConfig (WriterT LangLog (State LangState)) a
}
deriving
( Functor
, Applicative
)
That gives the same eta-reduce error.
So to recap, the main thing I want to know is how do I combine these two monads? Am I missing an obvious combination of lift
s, or arranging the transformer stack wrong, or running into some deeper issue?
Here are a couple possibly-related questions I looked at:
- Tidying up Monads - turning application of a monad transformer into newtype monad
- Generalized Newtype DerivingGeneralized Newtype Deriving
- Issue deriving MonadTrans for chained custom monad transformers
Update: my hand-wavy understanding of monad transformers was the main problem. Using RWST
instead of RWS
so LangT
can be inserted between Repl
and IO
mostly solves it:
newtype LangT m a = LangT { unLangT :: RWST LangConfig LangLog LangState m a }
deriving
( Functor
, Applicative
, Monad
, MonadReader LangConfig
, MonadWriter LangLog
, MonadState LangState
)
type Lang2 a = LangT Identity a
newtype Repl2 a = Repl2 { unRepl2 :: MaybeT (LangT (InputT IO)) a }
deriving
( Functor
, Applicative
, Monad
-- , MonadIO -- ghc: No instance for (MonadIO (LangT (InputT IO)))
, MonadReader LangConfig
, MonadWriter LangLog
, MonadState LangState
)
The only remaining issue is I need to figure out how to make Repl2
an instance io MonadIO
.
Update 2: All good now! Just needed to add MonadTrans
to the list of instances derived for LangT
.
IO
must be at the bottom of your monad transformer stack because there is noIOT
monad transformer. Something likenewtype LangT m a = LangT (RWST .. .. .. m a); newtype Repl a = Repl (MaybeT (InputT (LangT IO)) a)
might work for you. – UnconstitutionalIO
has to be on the bottom, but for some reason it hadn't occurred to me that the whole stack is linear. I thought you could put another type sort of "off to the side". Will update the question. – ShrovetideLangT
needs aMonadIO m => MonadIO (LangT m)
instance (which can probably be derived) because theMonadIO m => MonadIO (MaybeT m)
instance requires it. – Unconstitutional