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 with mzero
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 lifts, 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.
You're trying to compose the two monads, one on top of the another. But in general monads don't compose this way. Let's have a look at a simplified version of your case. Let's assume we have just Maybe instead of MaybeT ... and Reader instead of Lang. So the type of your monad would be
Maybe (LangConfig -> a)
Now if this were a monad, we would have a total join function, which would have type
join :: Maybe (LangConfig -> Maybe (LangConfig -> a)) -> Maybe (LangConfig -> a)
And here a problem comes: What if the argument is a value Just f where
f :: LangConfig -> Maybe (LangConfig -> a)
and for some input f returns Nothing? There is no reasonable way how we could construct a meaningful value of Maybe (LangConfig -> a) from Just f. We need to read the LangConfig so that f can decide if its output will be Nothing or Just something, but within Maybe (LangConfig -> a) we can either return Nothing or read LangConfig, not both! So we can't have such a join function.
If you carefully look at monad transformers, you see that sometimes there is just one way how to combine two monads, and it's not their naive composition. In particular, both ReaderT r Maybe a and MaybeT (Reader r) a are isomorphic to r -> Maybe a. As we saw earlier, the reverse isn't a monad.
So the solution to your problem is to construct monad transformers instead of monads. You can either have both as monad transformers:
newtype LangT m a = Lang { unLang :: RWST LangConfig LangLog LangState m a }
newtype ReplT m a = Repl { unRepl :: MaybeT (InputT m) a }
and use them as LangT (ReplT IO) a or ReplT (LangT IO) a (as described in one of the comments, IO always has to be at the bottom of the stack). Or you can have just one of them (the outer one) as a transformer and another as a monad. But as you're using IO, the inner monad will have to internally include IO.
Note that there is a difference between LangT (ReplT IO) a and ReplT (LangT IO) a. It's similar to the difference between StateT s Maybe a and MaybeT (State s) a: If the former fails with mzero, neither result nor output state is produed. But in the latter fails with mzero, there is no result, but the state will remain available.
Related
I am writing a project that involves composing several stacks of StateT and ReaderT monads:
newtype FooT m a = FooT { unFooT :: (StateT State1 (ReaderT Reader1 m)) a }
newtype BarT m a = BarT { unBarT :: (StateT State2 (ReaderT Reader2 m)) a }
Then, I basically just run everything in FooT (BarT m) and lift into the appropriate monad as necessary. I'm using lens to interact with the various state/reader types:
foo :: Monad m => FooT m ()
foo = do
field1 .= ... -- where field1 is a lens into State1
...
However, this approach gets ugly as I add more StateT + ReaderT transformers (and seems like it might incur some performance costs).
My only idea so far is to combine the states like:
newtype BazT m a = BazT { unBazT :: StateT (State1, State2) (ReaderT (Reader1, Reader2) m)) a }
and then I can just project into the state types with more lenses.
foo :: Monad m => BazT m ()
foo = do
(_1 . field1) .= ... -- where field1 is a lens into State1
...
Is there a canonical way to combine multiple states like this? If possible I'd like to avoid modifying all the lens code.
If you happen to work on both states in the same context a lot, you should combine these states, as they fit to one functionality.
A stack is typically encapsulating one functionality at a time. So, within one stack, you would generally need every monad transformer at most once.
To encapsulate a stack, you'll have to make sure that inner transformers are not exposed outside. That way, your stacks can be combined further.
Complete example on how to encapsulate a monad stack:
{-# LANGUAGE UndecidableInstances #-} -- Needed for all things around transformers.
import Control.Monad.Reader
import Control.Monad.State
import Control.Monad.Writer
import Control.Monad.Except
import Control.Applicative
data Reader1 = Reader1
data State1 = State1
newtype FooT m a = FooT { unFooT :: (StateT State1 (ReaderT Reader1 m)) a }
deriving
( Functor, Applicative, Monad, Alternative
, MonadWriter w, MonadError e, MonadIO
-- ..
)
-- Note that Reader and State are not derived automatically.
-- Instead, the instances are lifted past its inside manually.
instance MonadTrans FooT where
lift = FooT . lift . lift
instance MonadState s m => MonadState s (FooT m) where
get = lift $ get
put = lift . put
instance MonadReader r m => MonadReader r (FooT m) where
ask = lift $ ask
local f = mapFooT $ mapStateT $ mapReaderT $ local f
where
mapFooT g = FooT . g . unFooT
-- Your class that provides the functionality of the stack.
class Monad m => MonadFoo m where
fooThings :: m Reader1
-- ...
-- Access to the inside of your stack, to implement your class.
instance Monad m => MonadFoo (FooT m) where
fooThings = FooT $ ask
-- Boilerplate to include all the typical transformers,
-- so that MonadFoo can be accessed and derived through them.
instance MonadFoo m => MonadFoo (ReaderT r m) where
fooThings = lift $ fooThings
instance MonadFoo m => MonadFoo (StateT s m) where
fooThings = lift $ fooThings
-- ..... instances for all the other common transformers go here ..
-- Another stack, that can now derive MonadFoo.
data Reader2 = Reader2
data State2 = State2
newtype BarT m a = BarT { unBarT :: (StateT State2 (ReaderT Reader2 m)) a }
deriving
( Functor, Applicative, Monad, Alternative
, MonadWriter w, MonadError e, MonadIO
, MonadFoo
)
-- Bar class and related instances would follow here as before.
-- A new stack that can make use of Bar and Foo, preferably through their classes.
newtype BazT m a = BazT { unBazT :: BarT (FooT m) a }
-- Baz can have its own ReaderT and StateT transformers,
-- without interfering with these in FooT and BarT.
As you can see, it requires quite a lot of boilerplate code. You may omit some boilerplate, if its for internal code. If you write a library, your users will appreciate it though.
Various packages tackle the boilerplate issue.
I was trying to write my own monad transformers where it would make sense to have multiple of the same monad transformer on the stack with different types. The issue can be illustrated with the reader monad.
The reader monad is offered as a way to hold a read only context of a given type
ex1 :: Reader Bool Bool
ex1 = ask
or
ex2 :: Reader Char Bool
ex2 = pure True
monad transformers allow less restrictive assumptions about the underlining monad
ex3 :: (MonadReader Bool m) => m Bool
ex3 = ask
However, what if I want to have more than 1 read only environment? I can write a function like
ex4 :: (MonadReader Bool m, MonadReader Char m) => m Bool
ex4 = ask
However, as far as I can tell, there is no way to run ex4 since
class Monad m => MonadReader r m | m -> r
means that each MonadReader has a unique reading type. Is there a standard work around for multiple transformers on the same stack? Should I try to avoid this entirely?
Use a transformer and lift to get to your inner monad:
import Control.Monad.Trans.Reader
import Control.Monad.Trans.Class (lift)
type MyMonad a = ReaderT Bool (Reader Char) a
askBool :: MyMonad Bool
askBool = ask
askChar :: MyMonad Char
askChar = lift ask
The code you presented didn't use any monad transformer (directly). It used the reader monad (which happens to be a transformer applied to the identity monad) and the MonadReader type class. As you noticed, the type function implied by MonadReader can't result in two different outputs (the environment types) for the same input (the monad m).
One way to deal with it in a relatively straightforward way is to create a type that represents the state you wanna keep track of. Say you want to keep track of both a Bool and a Char as in your example
data MyState = MyState { getBool :: Bool, getChar :: Char }
f :: MonadReader MyState m => m Bool
f = asks getBool
Others may have more advanced solutions!
How do I create a monad which uses State, Cont, and Reader transformers? I would like to read an environment, and update/use state. However, I would also like to pause/interrupt the action. For example, if a condition is met, the state remains unchanged.
So far I have a monad using ReaderT and StateT, but I cannot work out how to include ContT:
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Test where
-- monads
import Data.Functor.Identity (Identity, runIdentity)
import Control.Monad.State
import Control.Monad.Reader
import Control.Monad.Cont
-- reader environment
type In = Integer
-- cont: if true then pause, else continue
type Pause = Bool
-- state environment:
newtype StateType = StateType { s :: Integer }
newtype M r = M {_unM :: ReaderT In (ContT Pause (StateT StateType Identity)) r}
deriving ( Functor, Applicative, Monad
, MonadReader In
, MonadCont Pause
, MonadState StateType
)
-- run monadic action
runM :: In -> Pause -> StateType -> M r -> StateType
runM inp pause initial act
= runIdentity -- unwrap identity
$ flip execStateT initial -- unwrap state
$ flip runContT pause -- unwrap cont
$ flip runReaderT inp -- unwrap reader
$ _unM act -- unwrap action
This gives the error:
* Expected kind `* -> *', but `Pause' has kind `*'
* In the first argument of `MonadCont', namely `Pause'
In the newtype declaration for `M'
|
24| , MonadCont Pause
|
Ok, but why does Pause need kind * -> *?... I'm drowning in types, in need of explanation. What form does Pause have to take, a function? How does ContT integrate? Ultimately, I plan to use Cont for a control structure.
Unlike MonadReader and MonadState, the MonadCont type class takes only one parameter. Since that parameter m must be a Monad, it must have kind * -> *.
In your deriving clause, you want MonadCont, not MonadCont Pause.
added in response to followup question:
ContT is defined as:
newtype ContT r m a = ContT { runContT :: (a -> m r) -> m r }
Note that the r in your definition of newtype M r is passed as the final (a) parameter to ContT. Plugging in the variables, you have
ContT Bool (State StateType) a = ContT {
runContT :: (a -> State StateType Bool) -> (State StateType Bool)
}
This provides a computational context in which you can manipulate the StateType, and use delimited continuations. Eventually, you will construct a ContT Bool (State StateType) Bool. Then you can run the continuation (with evalContT), and return to the simpler State StateType context. (In practice, you may unwrap all 3 of your monad transformers in the same part of your program.)
I'm writing a small DSL using monad-transformers following the ideas presented
here here. For the sake of
illustration I present a small subset here.
class Monad m => ProjectServiceM m where
-- | Create a new project.
createProject :: Text -- ^ Name of the project
-> m Project
-- | Fetch all the projects.
getProjects :: m [Project]
-- | Delete project.
deleteProject :: Project -> m ()
The idea of this DSL is to be able to write API-level tests. To this end, all
these actions createProject, getProjects, deleteProject will be
implemented by REST calls to a web-service.
I also wrote an DSL to write expectations. An snippet is given below:
class (MonadError e m, Monad m) => ExpectationM e m | m -> e where
shouldContain :: (Show a, Eq a) => [a] -> a -> m ()
And you could imagine that more DSL's can be added to the mix for logging, and
performance metrics see the gist linked above.
With these DSL is possible to write some simple tests like the following:
createProjectCreates :: (ProjectServiceM m, ExpectationM e m) => m ()
createProjectCreates = do
p <- createProject "foobar"
ps <- getProjects
ps `shouldContain` p
Two interpreters are shown below:
newtype ProjectServiceREST m a =
ProjectServiceREST {runProjectServiceREST :: m a}
deriving (Functor, Applicative, Monad, MonadIO)
type Error = Text
instance (MonadIO m, MonadError Text m) => ProjectServiceM (ProjectServiceREST m) where
createProject projectName = return $ Project projectName
getProjects = return []
deleteProject p = ProjectServiceREST (throwError "Cannot delete")
newtype ExpectationHspec m a =
ExpectationHspec {runExpectationHspec :: m a}
deriving (Functor, Applicative, Monad, MonadIO)
instance (MonadError Text m, MonadIO m) => ExpectationM Text (ExpectationHspec m) where
shouldContain xs x = if any (==x) xs
then ExpectationHspec $ return ()
else ExpectationHspec $ throwError msg
where msg = T.pack (show xs) <> " does not contain " <> T.pack (show x)
Now to run the scenario createProjectCreates the monad transformers can be
stacked in different ways. One way I found it makes sense is:
runCreateProjectCreates :: IO (Either Text ())
runCreateProjectCreates = ( runExceptT
. runExpectationHspec
. runProjectServiceREST
) createProjectCreates
Which requires:
instance ProjectServiceM (ProjectServiceREST (ExpectationM (ExceptT Text IO)))
instance ExpectationM Text (ProjectServiceREST (ExpectationM (ExceptT Text IO)))
The problem with this is that either the instances of ProjectSeviceM have to
know about ExpectationM and create instances for it, or vice-versa. These
instances can be readily created by using the StandaloneDeriving extension, e.g.:
deriving instance (ExpectationM Text m) => ExpectationM Text (ProjectServiceREST m)
However it'd be nice if this could be avoided, since I'm leaking some
information to either implementations of the DSL's. Can the problem above be
overcome?
The concrete constructors for your monad stack don't have to correspond directly to the mtl-style type classes. This article and Reddit discussion are relevant. The mtl class MonadState s m has a generic dumb implementation in StateT, but you can instantiate MonadState for ReaderT (IORef s) IO too, or for a CPS variant. Ultimately, you remain abstract in how you want the effect to be handled, you just require that it is handled.
Suppose instead you wrote two abstract monad transformers:
newtype ProdT m a = ProdT { runProdT :: ... }
deriving (Functor, Applicative, Monad, MonadTrans, ...)
newtype TestT m a = TestT { runTestT :: ... }
deriving (Functor, Applicative, Monad, MonadTrans, ...)
and you then define the instances you require. Instead of needing to write all the pass through instances, you can just write the ones you need directly.
As an aside, I would recommend not defining type classes if they are trivial combinations of other classes. The class/instance definitions for
class (MonadError e m, Monad m) => ExpectationM e m | m -> e where
shouldContain :: (Show a, Eq a) => [a] -> a -> m ()
works just as well as
shouldContain :: (MonadError e m, Show a, Eq a) => [a] -> a -> m ()
You already have the ability to alter the base monad, as long as it has MonadError. A test implementation would possibly be
newtype ExpectationT m e a = ExpectationT { runExpectation :: WriterT [e] m a }
instance Monad m => MonadError (ExpectationT m e) e where
throwError = ExpectationT . tell
-- etc..
While building a monad stack with monad transformers to write a library, I hit a question about the behavior of it.
The following code won't pass the type checker:
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Foo (FooM, runFooM, foo) where
import Control.Applicative
import Control.Monad.Reader
newtype FooM m a = FooM { runFooM :: ReaderT Int m a }
deriving (Functor, Applicative, Monad, MonadReader Int)
foo :: FooM m Int
foo = do
x <- ask
return x
The error is:
$ ghc foo.hs
[1 of 1] Compiling Foo ( foo.hs, foo.o )
foo.hs:12:3:
No instance for (Monad m) arising from a do statement
Possible fix:
add (Monad m) to the context of
the type signature for foo :: FooM m Int
In a stmt of a 'do' block: x <- ask
In the expression:
do { x <- ask;
return x }
In an equation for ‘foo’:
foo
= do { x <- ask;
return x }
The fix is easy as GHC suggests, just adds Monad constraint to the foo function:
foo :: Monad m => FooM m Int
foo = do
x <- ask
return x
But here, the foo function only asks the FooM value to give its Int value and it is already an (automatically derived) MonadReader instance.
So I think Monad constraint is not required to m.
I guess this relates to the implementation of the monad transformers (I use mlt==2.2.1),
but I cannot figure out the exact reason.
I may miss something obvious though.
Could you explain why this doesn't pass the checker?
Thanks.
It's because the Monad instance for ReaderT is defined as
instance Monad m => Monad (ReaderT r m)
i.e. the type ReaderT r m is an instance of Monad only if the inne rm is an instance of Monad. That's why you cannot have an unconstrained m when using the Monad instance of ReaderT (which your FooM type is using via the deriving mechanism).
returns type is Monad m => a -> m a, hence the need for the constraint.
By the monad laws, foo ≡ ask, which will indeed work without the Monad constraint. But if you don't require Monad, then GHC can hardly make simplifications based on these laws, can it? Certainly not before type checking the code. And what you wrote is syntactic sugar for
foo = ask >>= \x -> return x
which requires both (>>=) :: Monad (FooM m) => FooM m Int -> (Int->FooM m Int) -> FooM m Int and return :: Monad (FooM m) => Int->FooM m Int.
Again, the >>= return does nothing whatsoever for a correct monad, but for a non-monad it isn't even defined and can thus not just be ignored.