How do you stack two ErrorT monad transformers on top of each other? - haskell

Let's say I have these two functions:
errorm :: ( MonadError String m ) => Bool -> m Int
errorm cond = if cond then return 1 else throwError "this is an error"
errorms :: ( MonadError String m ) => Bool -> m String
errorms cond = if cond then return "works" else throwError "does not work"
As you can see, one returns a string in the safe case, while the other returns an int
I now want to use them together within another monad. Trivially:
errErr :: MonadError String m => Bool -> Bool -> m (Int, String)
errErr b1 b2 = do
a <- errorm b1
b <- errorms b2
return (a,b)
The function signature here is derived by the GHC, and I am not sure how to use this function. I tried this:
runErrorT ( runErrorT ( errErr1 True True ) ) -- should give me (Right 1, Right "works")
But instead it gives me:
Ambiguous type variable `e0' in the constraint:
(Error e0) arising from a use of `errErr1'
Probable fix: add a type signature that fixes these type variable(s)
In the first argument of `runErrorT', namely `(errErr1 True True)'
In the first argument of `runErrorT', namely
`(runErrorT (errErr1 True True))'
In the expression: runErrorT (runErrorT (errErr1 True True))
In general, this is just one instance of my problem. I feel like I am not grasping how exactly to stack two monadT that are of the same class, but have different type parameters. Another example might be stacking the pair of a functions:
f :: ( MonadState Int m ) => m ()
g :: ( MonadState String m ) => m ()
---------------------------------------------------- Update ----------------------------------------------------
Per Daniel's comment below, I added a concrete instance of functions f and g from above. But thanks to Tikhon's answer, I think I figured it out.
type Counter = Int
type Msg = String
incr :: (MonadState Counter m) => Counter -> m ()
incr i = modify (+i)
addMsg :: ( MonadState Msg m ) => Msg -> m()
addMsg msg = modify ( ++ msg )
incrMsg:: (MonadTrans t, MonadState Msg m, MonadState Counter (t m)) => t m ()
incrMsg = do
lift . addMsg $ "one"
incr 1
return ()
incrMsgt = runIdentity $ runStateT ( runStateT incrMsg 1 ) "hello" :: (((), Int), String)

In this particular case, you do not need to stack two transformers--since both are MonadError String, they can be used as the same monad. You can use errorm and errorms together just like you would use two values in any other monad.
As a more concrete explanation, ignore the transformers for a second: you can imagine that the values are just Either String Int and Either String String. Clearly, you can just use them together. This is why you only need one runErrorT at the end rather than two: both values are in the same monad.
Now, what about your actual question: how do you stack two monad transformers? It works just like combining any two monad transformers. Two state transformers stacked upon each other look just like two different transformers stacked upon each other.
Now, it is a little tricky to use them. Depending on which one you're using, you will need to use lift differently. If you have a value in the base monad, you need to lift twice. If you have a value in the inner state monad, you will need to use it once. And if you have one in the outer level, you won't need it at all. This is just like normal transformers.
Going back to your error example, let's imagine you actually did want to stack two different error monad transformers instead of using them as one. This would mean that if you want to throw an error in the inner one, you would have to write lift (throwError "message"). If you had actually done this and had two stacked error transformers, than using runErrorT twice would have worked.

Related

Monad Transformers in an Interpeter

I am encountering a problem with Monad Transformers, but I think it's helpful to include some context of how I got to the state I'm currently in, so I'll start with a rough explanation of my program:
The project is an interpreter for a simple (toy) programming language. I have a monad that is used to represent evaluation. It has a definition that looks like:
type Eval a = ReaderT Environment (ExceptT String (State ProgState a))
This works quite nicely, and I can happy write an evaluation function:
eval :: Expr -> Eval Value
eval (Apply l r) = ...
eval ...
The Value datatype has a slight quirk in that I embed Haskell functions of type Value -> EvalM Value. To do this I added a generic type parameter to the definition, which I then instantiate with EvalM:
data Value' m
= IntVal Int
...
| Builtin (Value' m -> m (Value' m))
type Value = Value' EvalM
Things were going well, but then I had to write a function that heavily interleaved code using the Eval monad with IO operations. This looked kinda horrendous:
case runEval ({-- some computation--}) of
Right (val, state') -> do
result <- -- IO stuff here
case runEvaL {-- something involving result --} of
...
Left err -> ...
The function had like 5 levels of nesting, and was also recursive... definitely ugly :(. I hoped adapting to use a Monad Transformer would be the solution:
type EvalT m = ReaderT Environment (ExceptT String (StateT ProgState m))
This refactor was relatively painless: mostly it involved changing type-signatures rather than actual code, however there was a problem: Builtin. Given a expression that was applying argument x to a value of the form Builtin f, the eval function would simply return f x. However, this has type Eval Value, but the refactored eval needs to have type-signature:
eval :: Monad m => EvalT m Value
As far as Fixing this (i.e. making it typecheck) is concerned, I can think of a couple solutions each of which has a problem:
Implementing some kind of analog to lift where I can take Eval a to EvalT m a.
Problem: I'm not aware of how to do this (or if it's even possible)
Changing the Value type so that it is indexed by an inner monad, i.e. Value m = Value' (EvalT m).
Problem: now anything containing a Value m has to be
parameterized by m. I feel that it would unnecessarily clutters up the type-signatures of
anything containing a Value, which is a problem given the initial
motivation to do this change was cleaning up my code.
Of course, there may be a much better solution that I haven't thought of yet. Any feedback/suggestions are appreciated :).
You might like the mmorph package.
-- since State s = StateT s Identity, it's probably also the case
-- that Eval = EvalT Identity, under some light assumptions about
-- typos in the question
liftBuiltin :: Monad m => Eval a -> EvalT m a
liftBuiltin = hoist (hoist (hoist generalize))
Alternately, you could store a polymorphic function in your value. One way would be to parameterize over the transformer.
data Value' t = ... | Builtin (forall m. Monad m => Value' t -> t m (Value' t)
type Value = Value' EvalT
Another is to use mtl-style constraints.
data Value = ... | Builtin (forall m. (MonadReader Environment m, MonadError String m, MonadState ProgState m) => Value -> m Value)
This last one, though verbose, looks pretty nice to me; I'd probably start there.

Haskell: function signature

This program compiles without problems:
bar :: MonadIO m
=> m String
bar = undefined
run2IO :: MonadIO m
=> m String
-> m String
run2IO foo = liftIO bar
When I change bar to foo (argument name),
run2IO :: MonadIO m
=> m String
-> m String
run2IO foo = liftIO foo
I get:
Couldn't match type ‘m’ with ‘IO’
‘m’ is a rigid type variable bound by
the type signature for run2IO :: MonadIO m => m String -> m String
...
Expected type: IO String
Actual type: m String ...
Why are the 2 cases are not equivalent?
Remember the type of liftIO:
liftIO :: MonadIO m => IO a -> m a
Importantly, the first argument must be a concrete IO value. That means when you have an expression liftIO x, then x must be of type IO a.
When a Haskell function is universally quantified (using an implicit or explicit forall), then that means the function caller chooses what the type variable is replaced by. As an example, consider the id function: it has type a -> a, but when you evaluate the expression id True, then id takes the type Bool -> Bool because a is instantiated as the Bool type.
Now, consider your first example again:
run2IO :: MonadIO m => m Integer -> m Integer
run2IO foo = liftIO bar
The foo argument is completely irrelevant here, so all that actually matters is the liftIO bar expression. Since liftIO requires its first argument to be of type IO a, then bar must be of type IO a. However, bar is polymorphic: it actually has type MonadIO m => m Integer.
Fortunately, IO has a MonadIO instance, so the bar value is instantiated using IO to become IO Integer, which is okay, because bar is universally quantified, so its instantiation is chosen by its use.
Now, consider the other situation, in which liftIO foo is used, instead. This seems like it’s the same, but it actually isn’t at all: this time, the MonadIO m => m Integer value is an argument to the function, not a separate value. The quantification is over the entire function, not the individual value. To understand this more intuitively, it might be helpful to consider id again, but this time, consider its definition:
id :: a -> a
id x = x
In this case, x cannot be instantiated to be Bool within its definition, since that would mean id could only work on Bool values, which is obviously wrong. Effectively, within the implementation of id, x must be used completely generically—it cannot be instantiated to a specific type because that would violate the parametricity guarantees.
Therefore, in your run2IO function, foo must be used completely generically as an arbitrary MonadIO value, not a specific MonadIO instance. The liftIO call attempts to use the specific IO instance, which is disallowed, since the caller might not provide an IO value.
It is possible, of course, that you might want the argument to the function to be quantified in the same way as bar is; that is, you might want its instantiation to be chosen by the implementation, not the caller. In that case, you can use the RankNTypes language extension to specify a different type using an explicit forall:
{-# LANGUAGE RankNTypes #-}
run3IO :: MonadIO m => (forall m1. MonadIO m1 => m1 Integer) -> m Integer
run3IO foo = liftIO foo
This will typecheck, but it’s not a very useful function.
In the first, you're using liftIO on bar. That actually requires bar :: IO String. Now, IO happens to be (trivially) an instance on MonadIO, so this works – the compiler simply throws away the polymorphism of bar.
In the second case, the compiler doesn't get to decide what particular monad to use as the type of foo: it's fixed by the environment, i.e. the caller can decide what MonadIO instance it should be. To again get the freedom to choose IO as the monad, you'd need the following signature:
{-# LANGUAGE Rank2Types, UnicodeSyntax #-}
run2IO' :: MonadIO m
=> (∀ m' . MonadIO m' => m' String)
-> m String
run2IO' foo = liftIO foo
... however I don't think you really want that: you might then as well write
run2IO' :: MonadIO m => IO String -> m String
run2IO' foo = liftIO foo
or simply run2IO = liftIO.

Using in IO monad, a function from other monad

If I have a function like, in a monad T, f1 :: T String, and I want to use its outcome, print it, for example.
seeF1 :: IO String
seeF1 = do
res <- f1
print res
Why is it wrong?. It seems that I can't use f1 because it is not in the monad IO. So, How can I do it? lifting?
In do notation, when you do
x = do
y <- z
....
Then if x :: (Monad m) => m a, then z :: (Monad m) => m b were m is the same monad.
That is pretty logical after all : imagine if your T monad was list, what should your seeF1 return? Or if your T monad was Maybe, seeF1 wouldn't be able to print anything in case it encountered a Nothing since the result would be undefined.
Therefore in general, what you are asking for is not possible. But if you are a bit more specific about your T, then you might find a way to get an IO a from your T a. For instance if you look at the monads defined in transformers, many have a run function that transform them, and from which you can get an IO.

How do you `get` the current state from a a state monad that is part of a product monad?

I am building some product monads from Control.Monad.Product package. For reference, the product monad type is:
newtype Product g h a = Product { runProduct :: (g a, h a) }
Its monad instance is:
instance (Monad g, Monad h) => Monad (Product g h) where
return a = Product (return a, return a)
Product (g, h) >>= k = Product (g >>= fst . runProduct . k, h >>= snd . runProduct . k)
Product (ga, ha) >> Product (gb, hb) = Product (ga >> gb, ha >> hb)
source: http://hackage.haskell.org/packages/archive/monad-products/3.0.1/doc/html/src/Control-Monad-Product.html
Problem I
I build a simple monad that is a product of two State Int Monads, However, when I try to access the underlying state next:
ss :: Product (State Int) (State Int) Int
ss = do
let (a,b) = unp $ P.Product (get,get) :: (State Int Int,State Int Int)
return 404
You see get just creates another State Int Int, and I am not sure how to actually get the value of the underlying state, how might I do that? Note I could potentially runState a and b to get the underlying value, but this solution doesn't seem very useful since the two states' initial values must be fixed a priori.
Question II.
I would really like to be able to create a product monad over states of different types, ie:
ss2 :: Product (State Int) (State String) ()
ss2 = do
let (a,b) = unp $ P.Product (get,get) :: (State Int Int,State Int String)
return ()
But I get this type error:
Couldn't match expected type `String' with actual type `Int'
Expected type: (State Int Int, State String String)
Actual type: (StateT Int Identity Int,
StateT String Identity Int)
Because I presume the two get must return the same type, which is an unfortunate restriction. Any thoughts on how to get around this?
The solution is to use a state monad with a product of your states:
m :: State (Int, String) ()
Then you can run an operation that interacts with one of the two fields of the product using zoom and _1/_2 from the lens library, like this:
m = do
n <- zoom _1 get
zoom _2 $ put (show n)
To learn more about this technique, you can read my blog post on lenses which goes into much more detail.
It can't be done the way you want. Suppose there would be a way how to get the current state out of the left monad. Then you'd have a function of type
getLeft :: Product (State a) (State b) a
which is isomorphic to (State a a, State b a).
Now we can choose to throw away the left part and run only the right part:
evalState (snd (runProduct getLeft)) () :: a
So we get an inhabitant of an arbitrary type a.
In other words, the two monads inside Product are completely independent. They don't influence each other and can be run separately. Therefore we can't take a value out of one and use it in another (or both of them).

How do you reason about the order of execution of functions in a monadT stack?

General theme: While I find the idea of stacking monads together is very appealing, I am having a lot of trouble picturing how the code is executed, and what are the appropriate orders to run the layers. Below is one example of a stack: Writer, State, State, and Error, in no particular order ( or is there? ).
-----------------------
-- Utility Functions --
-----------------------
type Memory = Map String Int
type Counter = Int
type Log = String
tick :: (MonadState Counter m) => m ()
tick = modify (+1)
record :: (MonadWriter Log m) => Log -> m ()
record msg = tell $ msg ++ "; "
------------------
-- MonadT Stack --
------------------
mStack :: ( MonadTrans t, MonadState Memory m, MonadState Counter (t m), MonadError ErrMsg (t m), MonadWriter Log (t m) ) => t m Int
mStack = do
tick
m <- lift get
let x = fromJust ( M.lookup "x" m ) in x
record "accessed memory"
case True of
True -> return 100
False -> throwError "false"
Please note in mStack, whether an error is thrown or not has nothing to do with any other part of the function.
Now ideally I want the output to look like this:
( Right 100, 1, "accessed memory", fromList [...])
or in general:
( output of errorT, output of stateT Counter, output of writerT, output of StateT Memory )
But I cannot get it to work. Specifically, I tried running the stack as if Error is on the outermost layer:
mem1 = M.fromList [("x",10),("y",5)]
runIdentity $ runWriterT (runStateT (runStateT (runErrorT mStack ) 0 ) mem1 ) ""
But am getting this error message:
Couldn't match type `Int' with `Map [Char] Int'
The above instance aside, in general, when I am calling:
runMonadT_1 ( runMonadT_2 expr param2 ) param1,
are the functions relating to monadT_2 run first, then that output is piped into the functions relating to monadT_1 ? So in other words, as imperative as the code looks in the above function mStack, is the order of execution entirely dependent upon the order in which the monadT are run ( aside from any rigidness in structure introduced by lift ) ?
You would have gotten a more informative type error if you had tried to type your computation using an explicit monad transformer stack:
mStack :: ErrorT String (StateT (Map String Int) (StateT Int Writer)) Int
Had you done that, ghc would have caught the type error earlier. The reason is that you use the following two commands within mStack at the top-most level:
modify (+1) -- i.e. from `tick`
...
yourMap <- lift get
If you were to give this an explicit stack, then you'd catch the mistake: both modify and lift get are going to target the first StateT layer they encounter, which happens to be the same StateT layer.
modify begins from the ErrorT layer and proceeds downward until it hits the outer StateT layer, and concludes that the outer StateT must be using an Int state. get begins from the outer StateT layer, notices that it's already in a StateT layer and ignores the inner StateT layer entirely, so it concludes that the outer StateT layer must be storing a Map.
ghc then says "What gives? This layer can't be storing both an Int and a Map!", which explains the type error you got. However, because you used type classes instead of a concrete monad transformer stack, there was no way that ghc could know that this was a type error in waiting until you specified a concrete stack.
The solution is simple: just add another lift to your get and it will now target the inner StateT layer like you intended.
I personally prefer to avoid mtl classes entirely and always work with a concrete monad transformer stack using the transformers library alone. It's more verbose because you have to be precise about which layer you want using lift, but it causes fewer headaches down the road.

Resources