Does Backwards admit a Monad instance? - haskell

I just asked this on haskell-cafe, but I figure I might as well ask here too. Is the following Monad instance for Backwards m valid?
{-# Language RecursiveDo #-}
import Control.Applicative.Backwards
import Control.Monad.Fix
instance MonadFix m => Monad (Backwards m) where
m >>= f = Backwards $
do
fin <- forwards (f int)
int <- forwards m
pure fin
If so, could I also add this?
instance MonadFix m => MonadFix (Backwards m) where
mfix f = Backwards $ mfix (forwards . f)

No, it is not valid; the monad laws at best hold in some approximate fashion. As Petr Pudlák's answer shows, Backwards m >>= f does not behave very nicely when f is strict in its argument.
According to the monad laws,
pure () >>= (\() -> m) = m
But with this instance, if I'm not mistaken,
pure () >>= (\() -> m) = Backwards $ do
fin <- forwards (int `seq` m)
int <- pure ()
pure fin
= Backwards $ fmap fst $ mfix $ \ ~(_, int) -> do
fin <- forwards (int `seq` m)
pure (fin, ())
If the underlying monad is "strict" (i.e., its >>= is strict in its left operand), this will diverge.

For this f would need to be lazy, that is, the effect must not depend on the argument. The docs say
mfix f executes the action f only once, with the eventual output fed back as the input. Hence f should not be strict, for then mfix f would diverge.
Buf if f in your case m >>= f will be strict, then so will be the block passed to mfix.
Let's consider a practical example where m is readLine >>= putStrLn. Reversing the order would mean "print the data, then read it". Unless the effect of the function behind >>= doesn't depend on the input, this diverges.

Related

Cases in which we shall not use monadic bind to write mfix down using loop

I have been trying to write mfix down using Control.Arrow.loop. I came up with different definitions and would like to see which one is mfix's actual workalike.
So, the solution I reckon to be the right one is the following:
mfix' :: MonadFix m => (a -> m a) -> m a
mfix' k = let f ~(_, d) = sequenceA (d, k d)
in (flip runKleisli () . loop . Kleisli) f
As one can see, the loop . Kleisli's argument works for Applicative instances. I find it to be a good sign as we mostly have our knot-tying ruined by (>>=)'s strictness in the right argument.
Here is another function. I can tell that it is not mfix's total workalike, but the only case I found is not very natural. Take a look:
mfix'' k = let f ~(_, d) = fmap ((,) d) (return d >>= k)
in (flip runKleisli () . loop . Kleisli) f
As far as I understand, not every strict on the right-hand bind forces its argument entirely. For example, in case of IO:
GHCi> mfix'' ((return :: a -> IO a) . (1:))
[1,1,1,1,1,Interrupted.
So, I decided to fix this. I just took Maybe and forced x in Just x >>= k:
data Maybe' a = Just' a | Nothing' deriving Show
instance Functor Maybe' where
fmap = liftM
instance Applicative Maybe' where
pure = return
(<*>) = ap
instance Monad Maybe' where
return = Just'
Nothing' >>= k = Nothing'
Just' x >>= k = x `seq` k x
instance MonadFix Maybe' where
mfix f = let a = f (unJust' a) in a
where unJust' (Just' x) = x
unJust' Nothing' = errorWithoutStackTrace "mfix Maybe': Nothing'."
Having this on our hands:
GHCi> mfix ((return :: a -> Maybe' a) . (1:))
[1,1,1,1,1,Interrupted.
GHCi> mfix' ((return :: a -> Maybe' a) . (1:))
[1,1,1,1,1,Interrupted.
GHCi> mfix'' ((return :: a -> Maybe' a) . (1:))
Interrupted.
So, here are my questions:
Is there any other example which could show that mfix'' is not
totally mfix?
Are monads with such a strict bind, like Maybe',
interesting in practice?
Are there any examples which show that mfix' is not totally mfix that I have not found?
A small side note on IO:
mfix3 k' =
let
k = return . k'
f ~(_, d) = fmap ((,) d) (d >>= k)
in (join . flip runKleisli () . loop . Kleisli) f
Do not worry about all the returns and joins - they are here just to have mfix3's and mfix's types match. The idea is that we pass d itself instead of return d to the (>>=) on the right-hand. It gives us the following:
GHCi> mfix3 ((return :: a -> IO a) . (1:))
Interrupted.
Yet, for example (thanks to Li-yao Xia for their comment):
GHCi> mfix3 ((return :: a -> e -> a) . (1:)) ()
[1,1,1,1,1,Interrupted.
Edit: thanks to HTNW for an important note on pattern-matching in the comments: it is better to use \ ~(_, d) -> ..., not \ (_, d) -> ....
Here's a partial answer, which I hope is better than no answer.
Is there any other example which could show that mfix'' is not totally mfix?
We can distinguish mfix'' from mfix also by making return strict instead of (>>=).
Are monads with such a strict bind, like Maybe', interesting in practice?
Probably not. (Questions about the existence of "practical" examples are not easy to answer negatively.)
Containers that are strict in their elements might be an example of this. (In case you're wondering about the official containers package, it does not actually define Monad instances for Map and IntMap, and the Monad instance of Seq is lazy in the elements of the sequence).
Note also that it is unclear whether the monad laws take strictness into account. If you do, then such things are not lawfully monads because they break the left identity law: (return x >>= k) = k x for x = undefined.
Are there any examples which show that mfix' is not totally mfix that I have not found?
If you take the definition of loop in the standard library, in terms of mfix, then I think that mfix' = mfix, though I couldn't complete a proof (I could either be missing a good trick, or there's a missing MonadFix law).
The main point of contention, as was hinted at in the comments, is strictness. Both your definition of mfix' and the standard library's definition of loop are careful to expand the argument function to be lazier (using lazy patterns (~(_, d)) and snd respectively; the two techniques are equivalent). mfix and mfix' are still equal if exactly one of those precautions is dropped. There is a mismatch (mfix /= mfix') if both are dropped.

guard and pure in Haskell

I was reading Dynamic programming example, there is a code like this:
buy n = r!n
where r = listArray (0,n) (Just (0,0,0) : map f [1..n])
f i = do (x,y,z) <- attempt (i-6)
return (x+1,y,z)
`mplus`
do (x,y,z) <- attempt (i-9)
return (x,y+1,z)
`mplus`
do (x,y,z) <- attempt (i-20)
return (x,y,z+1)
attempt x = guard (x>=0) >> r!x
My question is how the attempt x = guard (x>=0) >> r!x works?
According to this Control.Monad source code,
guard True = pure ()
guard False = empty
pure :: a -> f a
m >> k = m >>= \_ -> k
so if x>0, then:
attempt x
= (guard True) >> (r!x) = (pure ()) >> (r!x)
= (pure ()) >>= \_ -> r!x = (f ()) >>= (\_ -> r!x)
hence f () should be of type m a (Maybe a in this case), but how does Haskell know what f is? f () may return empty since it has never been specified. (f means f in pure)
And if x<0, empty is not in Maybe, how can this still applied to >>=?
That's multiple questions in one, but let's see if I can make things a bit more clear.
How does Haskell know what f is when interpreting pure ()? pure is a typeclass method, so this simply comes from the instance declaration of the type we're in. This changed recently, so you may have to follow a different path to reach the answer, but the result ends up the same: pure for Maybe is defined as Just.
In the same way, empty is in Maybe, and is defined as Nothing.
You'll find out what typeclass provides those functions by typing :i pure or :i empty at a ghci prompt; then you can seek the instance declaration Maybe makes for them.
It is unfortunate from an SO point of view that this changed recently so there's no clear permanent answer without knowing the specific versions you're using. Hopefully this will settle soon.
In the last expression of your manual evaluation of attempt x you are mixing up types and values. pure :: a -> f a is not a definition; it is a type signature (note the ::). To quote it fully, the type of pure is:
GHCi> :t pure
pure :: Applicative f => a -> f a
Here, the f stands for any instance of Applicative, and the a for any type. In your case, you are working with the Maybe monad/applicative functor, and so f is Maybe. The type of pure () is Maybe (). (() :: () is a dummy value used when you are not interested in a result. The () in pure () is a value, but the () in Maybe () is a type -- the type of the () value).
We will continue from the last correct step in your evaluation:
(pure ()) >>= \_ -> r!x
how does Haskell know what [pure ()] is?
In a sense, it doesn't need to. The function which makes use of pure () here is (>>=). It has the following type:
GHCi> :t (>>=)
(>>=) :: Monad m => m a -> (a -> m b) -> m b
Setting m to Maybe, as in your case, we get:
Maybe a -> (a -> Maybe b) -> Maybe b
The type of the first argument is Maybe a, and so (>>=) is able to handle any Maybe a value, including pure (), regardless of whether it is a Just-something or Nothing. Naturally, it will handle Just and Nothing differently, as that is the whole point of the Monad instance:
(Just x) >>= k = k x
Nothing >>= _ = Nothing
We still have to complete the evaluation. To do so, we need to know how pure is defined for Maybe. We can find the definition in the Applicative instance of Maybe:
pure = Just
Now we can finally continue:
(pure ()) >>= \_ -> r!x
Just () >>= \_ -> r!x
(\_ -> r!x) () -- See the implementation of `(>>=)` above.
r!x

Left recursion of >>= in Haskell

I've just read this very interesting article about an alternative implementation for the Prompt Monad : http://joeysmandatory.blogspot.com/2012/06/explaining-prompt-monad-with-simpler.html
Here is a simplified code that can be run :
data Request a where
GetLine :: Request String
PutStrLn :: String -> Request ()
data Prompt p r
= forall a. Ask (p a) (a -> Prompt p r)
| Answer r
instance Monad (Prompt p) where
return = Answer
Ask req cont >>= k = Ask req (\ans -> cont ans >>= k)
Answer x >>= k = k x
prompt :: p a -> Prompt p a
prompt req = Ask req Answer
runPromptM :: Monad m => (forall a. p a -> m a) -> Prompt p r -> m r
runPromptM perform (Ask req cont) = perform req
>>= runPromptM perform . cont
runPromptM _ (Answer r) = return r
handleIO :: Request a -> IO a
handleIO GetLine = return ""
handleIO (PutStrLn s) = putStrLn s
req :: Prompt Request ()
req = do
answers <- sequence $ replicate 20000 (prompt GetLine)
prompt $ PutStrLn (concat answers)
main = runPromptM handleIO req
A comment in the article mentions that :
it has a problem that left recursion of >>= takes quadratic time to evaluate (it's the same as the left-recursion of ++ problem!)
I don't understand where the quadratic time (which I checked experimentally) come from. Is it related to lazy evaluation ?
Can someone explain me why ?
I feel this is a little easier to explain using the Free monad over Prompt, though they are very similar.
data Free f a = Pure a | Free (f (Free f a)) deriving Functor
The Free monad is either a completed operation marked by Pure or an f-indexed effect marked by Free. If f is a Functor then Free f is a Monad
instance Functor f => Monad (Free f) where
return = Pure
Pure a >>= f = f a
Free m >>= f = Free (fmap (>>= f) m)
This Monad instance work by "pushing" binds down through the layers of the Functor to reach the Pure nodes at the bottom and then applying f. What's important about this is that the number of Functor layers does not change. To wit, here's an example bind occurring in Free Maybe ().
Free (Just (Free (Just (Free Nothing)))) >>= (const (return ()))
Free (fmap (>>= (const (return ()))) (Just (Free (Just (Free Nothing))))
Free (Just (Free (Just (Free Nothing)) >>= (const (return ())))
Free (Just (Free (fmap (>>= (const (return ()))) (Just (Free Nothing))))
Free (Just (Free (Just (Free Nothing >>= (const (return ()))))))
Free (Just (Free (Just (Free Nothing))))
We see here a hint of what's to come—we had to traverse the entire tree down to the root just to do nothing at all.
The "Tree-Grafting" Substitution Monad
One way to see the Free monad is to think of it as the "substitution monad". Its bind looks like
(=<<) :: (a -> Free f b) -> Free f a -> Free f b
and if you think of a -> Free f b as converting Pure leaf values into new trees of effects then (=<<) just descends through the tree of effects Free f a and performs substitution over the a values.
Now if we have a chain of right associating binds (written using Kleisli composition (>=>) to prove that reassociation is valid—Kleisli arrows are a category)
f >=> (g >=> h)
then we only must descend into the tree once—the substitution function is computed at all of the nodes of the tree. However, if we're associated the other direction
(f >=> g) >=> h
we get the same result, but must compute the entire result (f >=> g) before we're able to apply the substitution function in h. What this means is that if we have a deeply nested left-associated bind sequence
((((f >=> g) >=> h) >=> i) >=> j) >=> k
then we're continually recomputing the left results so that we can recurse on them. This is where the quadratic slowdown appears.
Speedup with Codensity
There's a really strange type called Codensity which is related to continuation passing style and the ContT monad.
data Codensity m a = Codensity { runCodensity :: forall b . (a -> m b) -> m b }
-- Codensity m a = forall b . ContT b m a
Codensity has the interesting property that it's a Functor even when m isn't:
instance Functor (Codensity m) where
fmap f m = Codensity (\amb -> runCodensity m (amb . f))
and the unique property that it's a Monad even when m isn't:
instance Monad (Codensity m) where
return a = Codensity (\amb -> amb a)
m >>= f = Codensity (\bmc -> runCodensity m (\a -> runCodensity (f a) bmc))
We can also round-trip Monads through Codensity
toCodensity :: Monad m => m a -> Codensity m a
toCodensity ma = Codensity (\amb -> ma >>= amb)
fromCodensity :: Monad m => Codensity m a -> m a
fromCodensity m = runCodensity m return
roundtrip :: Monad m => m a -> m a
roundtrip = fromCodensity . toCodensity
but when we do this something very, very interesting happens: all of the binds become right-associated!.
Consider the classic left associated append problem. You are probably aware that whenever you have a series of left associated append-like functions (I'll use (++) here), you run into O(n^2) issues:
(((as ++ bs) ++ cs) ++ ds) ++ ...
It is easy to see that each additional append will have to traverse the entire length of the previously appended list, resulting in horrendously slow O(n^2) algorithm.
The solution is to right associate:
as ++ (bs ++ (cs ++ (ds ++ ...)))
This is O(a + b + c + d + ...) where a is the length of as, etc. or simply O(n) in the length of the total list.
Now, what does this have to do with Free? Let's suggestively compare the definition of Free with []:
data Free f r = Pure r | Free (f (Free f r))
data [] a = [] | Cons a [a]
While [] has values at each Cons node, Free only has a value at the Pure tip. Apart from that the definitions are very similar. A good intuition for Free is that it is a list-like data structure of Functors.
Now the Monad instance for Free, we only care about (>>=):
Pure r >>= f = f r
Free x >>= f = Free (fmap (>>= f) x)
Notice that (>>=) traverses the structure of Free until it reaches the Pure value, and then grafts (appends) additional Free structure onto the end. Remarkably similar to (++)!
With this intuition of Free as a list of Functor, and (>>=) behaving as (++), it should be clear why left associated (>>=) causes problems.

How to show that a monad is a functor and an applicative functor?

Monads are known to be theoretically a subset of functors and specifically applicative functors, even though it's not indicated in Haskell's type system.
Knowing that, given a monad and basing on return and bind, how to:
derive fmap,
derive <*> ?
Well, fmap is just (a -> b) -> f a -> f b, i.e. we want to transform the monadic action's result with a pure function. That's easy to write with do notation:
fmap f m = do
a <- m
return (f a)
or, written "raw":
fmap f m = m >>= \a -> return (f a)
This is available as Control.Monad.liftM.
pure :: a -> f a is of course return. (<*>) :: f (a -> b) -> f a -> f b is a little trickier. We have an action returning a function, and an action returning its argument, and we want an action returning its result. In do notation again:
mf <*> mx = do
f <- mf
x <- mx
return (f x)
Or, desugared:
mf <*> mx =
mf >>= \f ->
mx >>= \x ->
return (f x)
Tada! This is available as Control.Monad.ap, so we can give a complete instance of Functor and Applicative for any monad M as follows:
instance Functor M where
fmap = liftM
instance Applicative M where
pure = return
(<*>) = ap
Ideally, we'd be able to specify these implementations directly in Monad, to relieve the burden of defining separate instances for every monad, such as with this proposal. If that happens, there'll be no real obstacle to making Applicative a superclass of Monad, as it'll ensure it doesn't break any existing code. On the other hand, this means that the boilerplate involved in defining Functor and Applicative instances for a given Monad is minimal, so it's easy to be a "good citizen" (and such instances should be defined for any monad).
fmap = liftM and (<*>) = ap. Here are links to the source code for liftM and ap. I presume you know how to desugar do notation.

mapMonadTrans :: MonadTrans xT => (m a -> n b) -> xT m a -> xT n b

The problem is this. I have:
f :: MonadIO m => ReaderT FooBar m Answer;
f = (liftIO getArgs) >>= ...
I need to run this with modified arguments. However, since m is unknown, I cannot simply use
mapReaderT (withArgs args) :: ReaderT r IO b -> ReaderT r IO b
since I need somehow to transform (withArgs args) into m for all m.
One possibility I found is to define my own withArgs, thus:
import System.Environment (setArgs, freeArgv);
withArgv new_args act = do {
pName <- liftIO System.Environment.getProgName;
existing_args <- liftIO System.Environment.getArgs;
bracket (liftIO $ setArgs new_args)
(\argv -> do {
_ <- liftIO $ setArgs (pName:existing_args);
liftIO $ freeArgv argv;
})
(const act);
};
withArgs xs act = do {
p <- liftIO System.Environment.getProgName;
withArgv (p:xs) act;
};
However, this is a kludge, and specific to one function -- I would need to re-write every withX :: X -> IO a -> IO a, e.g. Control.Exception.handle
What, if any, is a better way to do this?
Edit: In the case of handle, I found Control.Monad.CatchIO. In the other case, I used yet another, briefer kludge (not worth posting) to avoid the kludge above. Still seeking a better solution!
Part of what you are looking for is a hoisting of a monad homomorphism into a monad transformer.
class MonadHoist t where
hoist :: (Monad m, Monad n) => (forall a. m a -> n a) -> t m a -> t n a
t :: Monad m => t Identity a -> t m a
t = hoist (return . runIdentity)
That is to say, given a monad homomorphism f from m to n, you can obtain a monad homomorphism from t m to t n using hoist.
A monad homomorphism is slightly stronger than the types above enforce, namely it is responsible for preserving the monad laws.
f . return = return
f . fmap g = fmap g . f
f . join = join . f . fmap f
= join . fmap f . f -- by the second law
= (>>= f) . f -- >>= in terms of join
Notice the quantifier that I snuck in the type of hoist, MonadHoist turns out to need that flexibility for almost all instances! (Reader happens to be the one case where it doesn't. Try to write MaybeT without it.)
Monad transformers can, in general, instantiate this class. For instance:
instance MonadHoist (StateT s) where
hoist f (StateT m) = StateT (f . m)
instance MonadHoist (ReaderT e) where
hoist f (ReaderT m) = ReaderT (f . m)
instance MonadHoist MaybeT where
hoist f (MaybeT m) = MaybeT (f m)
We don't currently provide it in transformers or mtl package because it would require a Rank2Type, but it is pretty straightforward to implement.
If there is enough demand for it, I'll happily package it up in a monad-extras package.
Now, I said part, because while this answers the question given by the type in the topic of your post, it doesn't address the need reflected by the bulk of the text associated with your question!
For that, you probably want to follow luqui's advice. =)
The monad-control package will do this. I think you want the function liftIOOp_ from Control.Monad.IO.Control.
Specifically,
liftIOOp_ (withArgs newArgs) f
should do what you want. You can lift things like bracket too, with the liftIOOp function.
I believe the interleavableIO package addresses this problem. It is discussed in this cafe thread.
It seems you can use runReaderT to get the effect you want, as well:
*> :t withArgs [] (runReaderT f FooBar)
withArgs [] (runReaderT f FooBar) :: IO Answer
where FooBar is some data constructor and f is defined as above.

Resources