When learning the Reader Monad, I find that it is defined as:
newtype Reader r a = Reader { runReader :: r -> a }
instance Monad (Reader r) where
return a = Reader $ \_ -> a
m >>= k = Reader $ \r -> runReader (k (runReader m r)) r
I want to known why using function as constructor parameter instead of something else such as a tuple:
newtype Reader r a = Reader { runReader :: (r, a) }
instance Monad (Reader r) where
-- Here I cannot get r when defining return function,
-- so does that's the reason that must using a function whose input is an "r"?
return a = Reader (r_unknown, a)
m >>= k = Reader (fst $ runReader m) (f (snd $ runReader m))
According to the Reader definition, we need a "environment" which we can use to generate a "value". I think a Reader type should contain the information of "environment" and "value", so the tuple seems perfect.
You didn't mention it in the question, but I guess you thought specifically of using a pair for defining Reader because it also makes sense to think of that as a way of providing a fixed environment. Let's say we have an earlier result in the Reader monad:
return 2 :: Reader Integer Integer
We can use this result to do further calculations with the fixed environment (and the Monad methods guarantee it remains fixed throughout the chain of (>>=)):
GHCi> runReader (return 2 >>= \x -> Reader (\r -> x + r)) 3
5
(If you substitute the definitions of return, (>>=) and runReader in the expression above and simplify it, you will see exactly how it reduces to 2 + 3.)
Now, let's follow your suggestion and define:
newtype Env r a = Env { runEnv :: (r, a) }
If we have an environment of type r and a previous result of type a, we can make an Env r a out of them...
Env (3, 2) :: Env Integer Integer
... and we can also get a new result from that:
GHCi> (\(r, x) -> x + r) . runEnv $ Env (3, 2)
5
The question, then, is whether we can capture this pattern through the Monad interface. The answer is no. While there is a Monad instance for pairs, it does something quite different:
newtype Writer r a = Writer { Writer :: (r, a) }
instance Monoid r => Monad (Writer r) where
return x = (mempty, x)
m >>= f = Writer
. (\(r, x) -> (\(s, y) -> (mappend r s, y)) $ f x)
$ runWriter m
The Monoid constraint is needed so that we can use mempty (which solves the problem that you noticed of having to create a r_unknown out of nowhere) and mappend (which makes it possible to combine the first elements of the pair in a way that doesn't violate the monad laws). This Monad instance, however, does something very different than what the Reader one does. The first element of the pair isn't fixed (it is subject to change, as we mappend other generated values to it) and we don't use it to compute the second element of the pair (in the definition above, y does not depend neither on r nor on s). Writer is a logger; the r values here are output, not input.
There is one way, however, in which your intuition is justified: we can't make a reader-like monad using a pair, but we can make a reader-like comonad. To put it very loosely, Comonad is what you get when you turn the Monad interface upside down:
-- This is slightly different than what you'll find in Control.Comonad,
-- but it boils down to the same thing.
class Comonad w where
extract :: w a -> a -- compare with return
(=>>) :: w a -> (w a -> b) -> w b -- compare with (>>=)
We can give the Env we had abandoned a Comonad instance:
newtype Env r a = Env { runEnv :: (r, a) }
instance Comonad (Env r) where
extract (Env (_, x)) = x
w#(Env (r, _)) =>> f = Env (r, f w)
That allows us to write the 2 + 3 example from the beginning in terms of (=>>):
GHCi> runEnv $ Env (3, 2) =>> ((\(r, x) -> x + r) . runEnv)
(3,5)
One way to see why this works is noting that an a -> Reader r b function (i.e. what you give to Reader's (>>=)) is essentially the same thing that an Env r a -> b one (i.e. what you give to Env's (=>>)):
a -> Reader r b
a -> (r -> b) -- Unwrap the Reader result
r -> (a -> b) -- Flip the function
(r, a) -> b -- Uncurry the function
Env r a -> b -- Wrap the argument pair
As further evidence of that, here is a function that changes one into the other:
GHCi> :t \f -> \w -> (\(r, x) -> runReader (f x) r) $ runEnv w
\f -> \w -> (\(r, x) -> runReader (f x) r) $ runEnv w
:: (t -> Reader r a) -> Env r t -> a
GHCi> -- Or, equivalently:
GHCi> :t \f -> uncurry (flip (runReader . f)) . runEnv
\f -> uncurry (flip (runReader . f)) . runEnv
:: (a -> Reader r c) -> Env r a -> c
To wrap things up, here is a slightly longer example, with Reader and Env versions side-by-side:
GHCi> :{
GHCi| flip runReader 3 $
GHCi| return 2 >>= \x ->
GHCi| Reader (\r -> x ^ r) >>= \y ->
GHCi| Reader (\r -> y - r)
GHCi| :}
5
GHCi> :{
GHCi| extract $
GHCi| Env (3, 2) =>> (\w ->
GHCi| (\(r, x) -> x ^ r) $ runEnv w) =>> (\z ->
GHCi| (\(r, x) -> x - r) $ runEnv z)
GHCi| :}
5
First of all note that your bind function is wrong and would not compile.
If the Reader were defined as you describe with a tuple, there would be problems:
The monad laws would be violated, e.g. left identity, which states that:
return a >>= f == f a
or the right identity:
m >>= return == m
would be broken, depending on the implmentation of >>= because >>= would forget either the first tuple element of the first argument or the second, i.e. if the implmentation would be:
(Reader (mr, mv)) >>= f =
let (Reader (fr, fv)) = f mv
in Reader (mr, fv)
then we would always lose the reader value that comes out of f (aka fr) and otherwise if >>= would be
(Reader (mr, mv)) >>= f =
let (Reader (fr, fv)) = f mv
in Reader (fr, fv)
-- ^^^ tiny difference here ;)
we would always lose mr.
A Reader is some action, that may ask for a constant value, which cannot be changed by another monadic action, which is read-only.
But when defined with a tuple, we could super-easy overwrite the reader value, e.g. whith this function:
tell :: x -> BadReader x ()
tell x = BadReader (x, ())
If a reader is instead defined with a function, this is impossible (try it)
Also, that enviroment is actually not required before converting a Reader to a pure value (aka running the Reader), so from this alone it makes sense to use a function instead of a tuple.
When using a tuple, we would have to provide the Reader value even before we actually run an action.
You can see that in your return definition, you even point out the problem, where the r_unknown comes from ...
To get a btter intuition, let's assume a Reader action that returns the Persons with a certain age from the Addressbook:
data Person = MkPerson {name :: String, age :: Int}
type Addressbook = [Person]
personsWithThisAge :: Int -> Reader Addressbook [Person]
personsWithThisAge a = do
addressbook <- ask
return (filter (\p -> age p == a) addressbook)
This personsWithAge function returns a Reader action and since it only asks for the Addressbook, it is like a function that accepts an addressbook and gives back a [Person] list,
so it is natural to define a reader as just that, a function from some input to a result.
We could rewrite this Reader action to be a function of the Addressbook like this:
personsWithThisAgeFun :: Int -> Addressbook -> [Person]
personsWithThisAgeFun a addressbook =
filter (\p -> age p == a) addressbook
But why invent Reader??
The real value of Reader shows when combining several functions like e.g. personsWithThisAge, that all depend on (the same) one constant Addressbook.
Using a Reader we don't have to explicitly pass some Addressbook around, individual Reader actions don't even have any way at all to modify the Addressbook - Reader guarantees us, that every action uses the same, unmodified Addressbook, and all a Reader action can ever to with the environment is ask for it.
The only way to implement this, with these guarantees is with a function.
Also if you look at the monad instances that are included in the standard library, you will see that (r ->) is a monad; actually it is identical to the Reader monad apart from some technical differences.
Now the structure you describe with the tuple is actually pretty close to a Writer monad, what is write-only , but that's out of scope.
Related
I'm trying to create an instance for bind operator (>>=) to the custom type ST a
I found this way to do it but I don't like that hardcoded 0.
Is there any way to implement it without having the hardcoded 0 and respecting the type of the function?
newtype ST a = S (Int -> (a, Int))
-- This may be useful to implement ">>=" (bind), but it is not mandatory to use it
runState :: ST a -> Int -> (a, Int)
runState (S s) = s
instance Monad ST where
return :: a -> ST a
return x = S (\n -> (x, n))
(>>=) :: ST a -> (a -> ST b) -> ST b
s >>= f = f (fst (runState s 0))
I often find it easier to follow such code with a certain type of a pseudocode rewrite, like this: starting with the
instance Monad ST where
return :: a -> ST a
return x = S (\n -> (x, n))
we get to the
runState (return x) n = (x, n)
which expresses the same thing exactly. It is now a kind of a definition through an interaction law that it must follow. This allows me to ignore the "noise"/wrapping around the essential stuff.
Similarly, then, we have
(>>=) :: ST a -> (a -> ST b) -> ST b
s >>= f = -- f (fst (runState s 0)) -- nah, 0? what's that?
--
-- runState (s >>= f) n = runState (f a) i where
-- (a, i) = runState s n
--
S $ \ n -> let (a, i) = runState s n in
runState (f a) i
because now we have an Int in sight (i.e. in scope), n, that will get provided to us when the combined computation s >>= f will "run". I mean, when it will runState.
Of course nothing actually runs until called upon from main. But it can be a helpful metaphor to hold in mind.
The way we've defined it is both the easiest and the most general, which is usually the way to go. There are more ways to make the types fit though.
One is to use n twice, in the input to the second runState as well, but this will leave the i hanging unused.
Another way is to flip the time arrow around w.r.t. the state passing, with
S $ \ n -> let (a, i2) = runState s i
(b, i ) = runState (f a) n
in (b, i2)
which is a bit weird to say the least. s still runs first (as expected for the s >>= f combination) to produce the value a from which f creates the second computation stage, but the state is being passed around in the opposite direction.
The most important thing to keep in mind is that your ST type is a wrapper around a function. What if you started your definition as (>>=) = \s -> \f -> S (\n -> ... )? It might be (ok, is) a bit silly to write separate lambdas for the s and f parameters there, but I did it to show that they're not really any different from the n parameter. You can use it in your definition of (>>=).
the Cont r a type stands for a function which takes a continuation a->r and produces a result of type r. So both the continuation and the entire Cont r a produce a result of the same type r.
My question is: are the two results necessarily the same value, or can a Cont r a post-process the result from the continuation and produce a different value, albeit of the same type r?
I tried using (+1) for post-processing (note the + 1 --<--):
c1 :: Int -> Cont r Int
c1 x = let y = 2*x
in cont $ \k -> (k y) + 1 --<--
Now that doesn't typecheck, because my post-processing function (+1) only accepts an argument whose type belongs to the Num typeclass. However, I pass the result of the continuation (k y) which is of some type r that is not guaranteed to belong to the Num typeclass.
Whatever I do to (k y), it must be a function of type r->r. The only function which can do this for all r is the id function and using id for post-processing is no post-processing at all.
However, the whole thing does typecheck if I restrict r to the Num typeclass or even to the concrete type Int. It then produces the expected result:
*Main> runCont (c1 1) id
3
I am quite unsure,
if such post-processing and restricting the type of r is a normal thing to do, and if so, in what circumstances this might be useful
or if the type variable rhas to be read as for all r and restricting the type of r will lead to all sorts of trouble.
Can someone shed some light on this?
Technically, I think it's fine. Specializing Cont r a to Num r => Cont r a doesn't seem fundamentally more problematic than specializing Reader r a to Num r => Reader r a.
An implication of doing so is that the resulting CPS computation can only be run against a (final) continuation that produces a number, but that's obvious -- if you have a computation that post-processes the continuation result as a number, it can only be used with continuations that produce numbers!
As additional evidence that this is sanctioned at least to some degree, note that there's a function:
mapCont :: (r -> r) -> Cont r a -> Cont r a
If this function was to be used with no restriction on r, the only valid values for its first argument would be id or functions that don't terminate, as you have noted.
A version of your c1 using mapCont might look like:
c2 :: (Num r) => Int -> Cont r Int
c2 x = mapCont (+1) $ return (2*x)
and seems to work fine:
> runCont (c2 10) id
21
> runCont (c2 10) (const 5)
6
> runCont (c2 10) show
... No instance for (Num String) arising from a use of 'c2' ...
As for when this would be useful, I'm not sure. I can think of a few somewhat lame applications. You could define an computation that overrides the final result (provided no other kind of post-processing is used):
override x = cont (const x)
to be used like:
> runCont (return 2 >>= \x -> cont (\f -> f (x*3))) id
6
> runCont (return 2 >> override 1000 >>= \x -> cont (\f -> f (x*3))) id
1000
>
or a computation transformer that emulates a writer to add log functionality:
annotate note comp = mapCont (\(a, w) -> (a, note:w)) comp
which you might use like this:
runCont (annotate "two" (return 2)
>>= \x -> annotate "times three" (cont (\f -> f (x*3))))
(\a -> (a, []))
yielding:
(6,["two","times three"])
These don't seem like very compelling applications, though.
#KABuhr has shown that post-processing in the ordinary Cont works, but didn't find "very compelling applications". I'm going to show you how post-processing is useful, but it only works best when you generalize Cont. First, some header stuff (mostly used in the examples):
{-# LANGUAGE RebindableSyntax #-}
import Prelude(Num(..), Eq(..), Enum(..))
import Data.Bool
import Data.Function
import Data.Functor.Identity
import Data.List
import Data.Maybe
import Data.Tuple
import Control.Lens(_1, _2, traversed)
Now, a generalized Cont.
newtype Cont r f a = Cont { runCont :: (a -> r) -> f }
Your question was "is post-processing allowed in Cont?" The answer is yes. If would like it to not be so, you can use newtype ContS a = { runContS :: forall r. (a -> r) -> r } which totally disallows it. In fact, ContS a is isomorphic to a. The Cont I just defined takes the opposite position: even type-changing post-processors are allowed. We can define a standard Functorial (<$>).
infixl 1 <$>
(<$>) :: (a -> b) -> Cont r f a -> Cont r f b
f <$> Cont x = Cont $ \cont -> x $ \realX -> cont (f realX)
Before continuing, let's get an understanding of the metaphor behind Cont. A Cont r f a is a computation that can produce as. It will give you the as, but will ask you to produce rs. Once you do that, it'll make fs. It's sort of like a (r -> f, a), but with heavy restrictions on use. If we try to define an Applicative-ish operator, we see something interesting.
infixl 1 <*>
(<*>) :: Cont m f (a -> b) -> Cont r m a -> Cont r f b
Cont f <*> Cont x = Cont $ \cont -> x $ \realX -> f $ \realF -> cont (realF realX)
(<*>) is sort of doing two operations at once. It is applying the a -> b to an a to get b, but it's also composing the m -> f and r -> m aspects into a r -> f part. However, the type of (<*>) no longer fits into the normal Applicative format. This is why we use Cont r a instead of Cont r f a. The former is less powerful, but it fits into our existing framework. To get our Cont to work, we have to leave some of the established infrastructure behind.
Before we get into the RebindableSyntax-level stuff, here's some usage.
complete :: Cont a f a -> f
complete (Cont x) = x id
amb :: [a] -> Cont (Maybe b) (Maybe (a, b)) a
amb [] = Cont (const Nothing)
amb (x : xs) = Cont $ \test -> case test x of
Nothing -> runCont (amb xs) test
Just y -> Just (x, y)
poly :: Num a => a -> a -> a -> a
poly x y z = sq x * y + sq y + z + sq z * x
where sq x = x * x
solution :: (Num a, Enum a, Eq a) => Maybe (a, (a, (a, ())))
solution = complete $ testRoot <$> amb [-5..5]
<*> amb [-10 .. -5]
<*> amb [5..10]
where testRoot x y z = case poly x y z of
0 -> Just ()
_ -> Nothing
complete completes a computation when there isn't actually a gap holding it up. amb takes a [a], and goes through each a, one by one. It passes each into the test, and searches until it finds one that succeeds. It post-processes the result of the test in two ways. It resets the result until it's a Just (or gives up), and a Just result gets up paired with the input that built it.
In solution, the complete is delimiting the extent of the continuation passed to the ambs. Each amb is passed the code that lies between it and the complete. E.g., the continuation given to the amb [-5..5] is \x -> testRoot x <*> amb [-10 .. -5] <*> amb [10..5]. This style of continuations is called shift/reset. Cont is shift, complete is reset. The idea is that amb [-5..5] is a "liar"; it "looks like" a Num a => a because it's getting passed to testRoot, but it's actually a control structure that turns everything around it inside-out. Compared to the normal Cont r a, the control structures allowed in our Cont are more powerful.
Now, here's what we need RebindableSyntax for:
(=<<) :: (a -> Cont r m b) -> Cont m f a -> Cont r f b
f =<< Cont x = Cont $ \cont -> x $ \realX -> runCont (f realX) cont
(>>=) = flip (=<<)
return :: a -> Cont r r a
return x = Cont ($ x)
(=<<) is the Monad-style function application operator. Again, our version doesn't fit the usual type. With (>>=) and return, do-notation has now been redefined to work with Cont. You can go back and rewrite solution in do-notation to see that it works.
Let's really get out there. The idea behind profunctor optics is that data structures give rise to "transformer transformers". E.g. a Lens s t a b = forall f. Functor f => (a -> f b) -> s -> f t takes a transformer between the "small" structures a and b and makes one from between the "bigger" s and t. Look what lies just a flip away...
editing :: ((a -> Identity b) -> s -> Identity t) -> s -> Cont b t a
editing optic x = Cont (runIdentity . flip optic x . (Identity .))
editing, as a control structure, takes a reference to a field inside a structure, a structure to use it on, and then mutates that structure with "the rest of the program." Using it, you can write the following:
example :: (a -> a) -> [(Bool, (a, a))] -> [(Bool, (a, a))]
example f xs = complete $ do x <- editing traversed xs
n2 <- editing _2 x
n <- case fst x of
True -> editing _1 n2
False -> editing _2 n2
return (f n)
I hope, with even these contrived examples, that you're convinced that post-processing is useful in Cont. There's nothing wrong with doing it. However, if you want to use it at its full potential, you have to break out of the existing Applicative and Monad form. This is painful, so we cripple Cont to make it fit, disabling type-changing post-processing as a trade-off.
the Cont r a type stands for a function which takes a continuation a->r and produces a result of type r. So both the continuation and the entire Cont r a produce a result of the same type r.
My question is: are the two results necessarily the same value, or can a Cont r a post-process the result from the continuation and produce a different value, albeit of the same type r?
I tried using (+1) for post-processing (note the + 1 --<--):
c1 :: Int -> Cont r Int
c1 x = let y = 2*x
in cont $ \k -> (k y) + 1 --<--
Now that doesn't typecheck, because my post-processing function (+1) only accepts an argument whose type belongs to the Num typeclass. However, I pass the result of the continuation (k y) which is of some type r that is not guaranteed to belong to the Num typeclass.
Whatever I do to (k y), it must be a function of type r->r. The only function which can do this for all r is the id function and using id for post-processing is no post-processing at all.
However, the whole thing does typecheck if I restrict r to the Num typeclass or even to the concrete type Int. It then produces the expected result:
*Main> runCont (c1 1) id
3
I am quite unsure,
if such post-processing and restricting the type of r is a normal thing to do, and if so, in what circumstances this might be useful
or if the type variable rhas to be read as for all r and restricting the type of r will lead to all sorts of trouble.
Can someone shed some light on this?
Technically, I think it's fine. Specializing Cont r a to Num r => Cont r a doesn't seem fundamentally more problematic than specializing Reader r a to Num r => Reader r a.
An implication of doing so is that the resulting CPS computation can only be run against a (final) continuation that produces a number, but that's obvious -- if you have a computation that post-processes the continuation result as a number, it can only be used with continuations that produce numbers!
As additional evidence that this is sanctioned at least to some degree, note that there's a function:
mapCont :: (r -> r) -> Cont r a -> Cont r a
If this function was to be used with no restriction on r, the only valid values for its first argument would be id or functions that don't terminate, as you have noted.
A version of your c1 using mapCont might look like:
c2 :: (Num r) => Int -> Cont r Int
c2 x = mapCont (+1) $ return (2*x)
and seems to work fine:
> runCont (c2 10) id
21
> runCont (c2 10) (const 5)
6
> runCont (c2 10) show
... No instance for (Num String) arising from a use of 'c2' ...
As for when this would be useful, I'm not sure. I can think of a few somewhat lame applications. You could define an computation that overrides the final result (provided no other kind of post-processing is used):
override x = cont (const x)
to be used like:
> runCont (return 2 >>= \x -> cont (\f -> f (x*3))) id
6
> runCont (return 2 >> override 1000 >>= \x -> cont (\f -> f (x*3))) id
1000
>
or a computation transformer that emulates a writer to add log functionality:
annotate note comp = mapCont (\(a, w) -> (a, note:w)) comp
which you might use like this:
runCont (annotate "two" (return 2)
>>= \x -> annotate "times three" (cont (\f -> f (x*3))))
(\a -> (a, []))
yielding:
(6,["two","times three"])
These don't seem like very compelling applications, though.
#KABuhr has shown that post-processing in the ordinary Cont works, but didn't find "very compelling applications". I'm going to show you how post-processing is useful, but it only works best when you generalize Cont. First, some header stuff (mostly used in the examples):
{-# LANGUAGE RebindableSyntax #-}
import Prelude(Num(..), Eq(..), Enum(..))
import Data.Bool
import Data.Function
import Data.Functor.Identity
import Data.List
import Data.Maybe
import Data.Tuple
import Control.Lens(_1, _2, traversed)
Now, a generalized Cont.
newtype Cont r f a = Cont { runCont :: (a -> r) -> f }
Your question was "is post-processing allowed in Cont?" The answer is yes. If would like it to not be so, you can use newtype ContS a = { runContS :: forall r. (a -> r) -> r } which totally disallows it. In fact, ContS a is isomorphic to a. The Cont I just defined takes the opposite position: even type-changing post-processors are allowed. We can define a standard Functorial (<$>).
infixl 1 <$>
(<$>) :: (a -> b) -> Cont r f a -> Cont r f b
f <$> Cont x = Cont $ \cont -> x $ \realX -> cont (f realX)
Before continuing, let's get an understanding of the metaphor behind Cont. A Cont r f a is a computation that can produce as. It will give you the as, but will ask you to produce rs. Once you do that, it'll make fs. It's sort of like a (r -> f, a), but with heavy restrictions on use. If we try to define an Applicative-ish operator, we see something interesting.
infixl 1 <*>
(<*>) :: Cont m f (a -> b) -> Cont r m a -> Cont r f b
Cont f <*> Cont x = Cont $ \cont -> x $ \realX -> f $ \realF -> cont (realF realX)
(<*>) is sort of doing two operations at once. It is applying the a -> b to an a to get b, but it's also composing the m -> f and r -> m aspects into a r -> f part. However, the type of (<*>) no longer fits into the normal Applicative format. This is why we use Cont r a instead of Cont r f a. The former is less powerful, but it fits into our existing framework. To get our Cont to work, we have to leave some of the established infrastructure behind.
Before we get into the RebindableSyntax-level stuff, here's some usage.
complete :: Cont a f a -> f
complete (Cont x) = x id
amb :: [a] -> Cont (Maybe b) (Maybe (a, b)) a
amb [] = Cont (const Nothing)
amb (x : xs) = Cont $ \test -> case test x of
Nothing -> runCont (amb xs) test
Just y -> Just (x, y)
poly :: Num a => a -> a -> a -> a
poly x y z = sq x * y + sq y + z + sq z * x
where sq x = x * x
solution :: (Num a, Enum a, Eq a) => Maybe (a, (a, (a, ())))
solution = complete $ testRoot <$> amb [-5..5]
<*> amb [-10 .. -5]
<*> amb [5..10]
where testRoot x y z = case poly x y z of
0 -> Just ()
_ -> Nothing
complete completes a computation when there isn't actually a gap holding it up. amb takes a [a], and goes through each a, one by one. It passes each into the test, and searches until it finds one that succeeds. It post-processes the result of the test in two ways. It resets the result until it's a Just (or gives up), and a Just result gets up paired with the input that built it.
In solution, the complete is delimiting the extent of the continuation passed to the ambs. Each amb is passed the code that lies between it and the complete. E.g., the continuation given to the amb [-5..5] is \x -> testRoot x <*> amb [-10 .. -5] <*> amb [10..5]. This style of continuations is called shift/reset. Cont is shift, complete is reset. The idea is that amb [-5..5] is a "liar"; it "looks like" a Num a => a because it's getting passed to testRoot, but it's actually a control structure that turns everything around it inside-out. Compared to the normal Cont r a, the control structures allowed in our Cont are more powerful.
Now, here's what we need RebindableSyntax for:
(=<<) :: (a -> Cont r m b) -> Cont m f a -> Cont r f b
f =<< Cont x = Cont $ \cont -> x $ \realX -> runCont (f realX) cont
(>>=) = flip (=<<)
return :: a -> Cont r r a
return x = Cont ($ x)
(=<<) is the Monad-style function application operator. Again, our version doesn't fit the usual type. With (>>=) and return, do-notation has now been redefined to work with Cont. You can go back and rewrite solution in do-notation to see that it works.
Let's really get out there. The idea behind profunctor optics is that data structures give rise to "transformer transformers". E.g. a Lens s t a b = forall f. Functor f => (a -> f b) -> s -> f t takes a transformer between the "small" structures a and b and makes one from between the "bigger" s and t. Look what lies just a flip away...
editing :: ((a -> Identity b) -> s -> Identity t) -> s -> Cont b t a
editing optic x = Cont (runIdentity . flip optic x . (Identity .))
editing, as a control structure, takes a reference to a field inside a structure, a structure to use it on, and then mutates that structure with "the rest of the program." Using it, you can write the following:
example :: (a -> a) -> [(Bool, (a, a))] -> [(Bool, (a, a))]
example f xs = complete $ do x <- editing traversed xs
n2 <- editing _2 x
n <- case fst x of
True -> editing _1 n2
False -> editing _2 n2
return (f n)
I hope, with even these contrived examples, that you're convinced that post-processing is useful in Cont. There's nothing wrong with doing it. However, if you want to use it at its full potential, you have to break out of the existing Applicative and Monad form. This is painful, so we cripple Cont to make it fit, disabling type-changing post-processing as a trade-off.
Explain about a "duplicate"
Someone point to Is this a case for foldM? as a possible duplicate. Now, I have a strong opinion that, two questions that can be answered with identical answers are not necessarily duplicates! "What is 1 - 2" and "What is i^2" both yields "-1", but no, they are not duplicate questions. My question (which is already answered, kind of) was about "whether the function iterateM exists in Haskell standard library", not "How to implement a chained monad action".
The question
When I write some projects, I found myself writing this combinator:
repeatM :: Monad m => Int -> (a -> m a) -> a -> m a
repeatM 0 _ a = return a
repeatM n f a = (repeatM (n-1) f) =<< f a
It just performs a monadic action n times, feeding the previous result into the next action. I tried some hoogle search and some Google search, and did not find anything that comes with the "standard" Haskell. Is there such a formal function that is predefined?
You can use foldM, e.g.:
import Control.Monad
f a = do print a; return (a+2)
repeatM n f a0 = foldM (\a _ -> f a) a0 [1..n]
test = repeatM 5 f 3
-- output: 3 5 7 9 11
Carsten mentioned replicate, and that's not a bad thought.
import Control.Monad
repeatM n f = foldr (>=>) pure (replicate n f)
The idea behind this is that for any monad m, the functions of type a -> m b form the Kleisli category of m, with identity arrows
pure :: a -> m a
(also called return)
and composition operator
(<=<) :: (b -> m c) -> (a -> m b) -> a -> m c
f <=< g = \a -> f =<< g a
Since were actually dealing with a function of type a -> m a, we're really looking at one monoid of the Kleisli category, so we can think about folding lists of these arrows.
What the code above does is fold the composition operator, flipped, into a list of n copies of f, finishing off with an identity as usual. Flipping the composition operator actually puts us into the dual category; for many common monads, x >=> y >=> z >=> w is more efficient than w <=< z <=< y <=< x; since all the arrows are the same in this case, it seems we might as well. Note that for the lazy state monad and likely also the reader monad, it may be better to use the unflipped <=< operator; >=> will generally be better for IO, ST s, and the usual strict state.
Notice: I am no category theorist, so there may be errors in the explanation above.
I find myself wanting this function often, I wish it had a standard name. That name however would not be repeatM - that would be for an infinite repeat, like forever if it existed, just for consistency with other libraries (and repeatM is defined in some libraries that way).
Just as another perspective from the answers already given, I point out that (s -> m s) looks a bit like an action in a State monad with state type s.
In fact, it is isomorphic to StateT s m () - an action which returns no value, because all the work it does is encapsulated in the way it changes the state. In this monad, the function you wanted really is replicateM. You can write it this way in haskell although it probably looks uglier than just writing it directly.
First convert s -> m s to the equivalent form which StateT uses, adding the information-free (), using liftM to map a function over the return type.
> :t \f -> liftM (\x -> ((),x)) . f
\f -> liftM (\x -> ((),x)) . f :: Monad m => (a -> m t) -> a -> m ((), t)
(could have used fmap but the Monad constraint seems clearer here; could have used TupleSections if you like; if you find do notation easier to read it is simply \f s -> do x <- f s; return ((),s) ).
Now this has the right type to wrap up with StateT:
> :t StateT . \f -> liftM (\x -> ((),x)) . f
StateT . \f -> liftM (\x -> ((),x)) . f :: Monad m => (s -> m s) -> StateT s m ()
and then you can replicate it n times, using the replicateM_ version because the returned list [()] from replicateM would not be interesting:
> :t \n -> replicateM_ n . StateT . \f -> liftM (\x -> ((),x)) . f
\n -> replicateM_ n . StateT . \f -> liftM (\x -> ((),x)) . f :: Monad m => Int -> (s -> m s) -> StateT s m ()
and finally you can use execStateT to go back to the Monad you were originally working in:
runNTimes :: Monad m => Int -> (s -> m s) -> s -> m s
runNTimes n act =
execStateT . replicateM_ n . StateT . (\f -> liftM (\x -> ((),x)) . f) $ act
A function for determine if a string is a palindrome can be implemented in a pointfree applicative manner via
pal1 = (==) <$> reverse <*> id
And here is a monadic version
reverse >>= (==)
How does the modadic version work with no explicit call to id? I attempted to view the poinful representation using pointful and get back the same function.
This works using the fact that x -> y can be regarded as a kind of "reader monad". If we were to say
type Reader r x = r -> x
then we have an instance of Monad (Reader r). So we can see that
reverse :: [x] -> [x]
is actually
reverse :: Reader [x] [x]
Similarly,
(==) :: [x] -> [x] -> Bool
can be written as
(==) :: [x] -> Reader [x] Bool
Then (>>=) joins the two together.
So... We start with reverse, which is a Reader action that reads a list and returns a list. We then use >>= to pass that to ==, which is a function that takes a list, and returns a Reader [x] Bool.
In short, the input list is duplicated by the action of Reader, which basically takes an input and passes it to every function in the chain. (That's what the reader monad is.)
I hope that made some kind of sense... It took me a while to figure out!
Let's have a look at the Monad instance for ((->) r):
instance Monad ((->) r) where
return = const
f >>= k = \ r -> k (f r) r
and then simply fill in your monadic code:
reverse >>= (==) = \r -> (==) (reverse r) r
which we can write in a more familiar way:
\r -> reverse r == r
To add to other answers, here is another POV on this. Let's take a definition of bind via fmap and join:
m >>= act = join (fmap act m)
The expression (==) <$> reverse has type Eq a => [a] -> [a] -> Bool and is equivalent to fmap (==) reverse. Now, we pass it to join :: m (m a) -> m a and for (->) r monad instance the type would be ([a] -> [a] -> Bool) -> ([a] -> Bool). That is, join is exactly <*> id part.
I think the easiest way to understand this is by looking at the types:
(>>=) :: Monad m => m a -> (a -> m b) -> m b
specialized to the ((->) r) instance:
(>>=) :: (r -> a) -> (a -> r -> b) -> r -> b
You are not given an a. The only way to produce one is to apply the first function r -> a to the r you are given. The only way to produce a b is to apply the second function to the r and the a you just produced. This means the only possible definition for this function* is:
f >>= g = \a -> g (f a) a
Plugging our arguments in, we get:
reverse >>= (==)
-- definition of (>>=)
= \a -> (==) (reverse a) a
-- prefix to infix
= \a -> reverse a == a
Parametricity is a powerful tool for reasoning about polymorphic functions.
* other than bottom
The other answers confirm that the two behave the same, but don't explain where the id actually went. In this answer, I will attempt to do so. The punchline is that, for Reader, we have a curious id-removing equation: id >>= return . f = f. (A more beautiful form of this equation is that (id >>=) = (>>= id); together with the monad laws the beautiful form implies the easily-usable form.) To make the explanation a bit simpler, instead of trying to convert from applicative form to monadic form, I will just take it for granted that you believe the following equation:
(==) <$> reverse <*> id
= { too annoying to do carefully }
reverse >>= \xs -> id >>= \ys -> return ((==) xs ys)
So we will start from that last line, and end at reverse >>= (==). Along the way, it will be key to observe that id is the identity for (.) -- which just so happens to be fmap for the Reader monad. Here we go:
reverse >>= \xs -> id >>= \ys -> return ((==) xs ys)
= { monad law }
reverse >>= \xs -> fmap ((==) xs) id
= { definition of fmap for Reader }
reverse >>= \xs -> (.) ((==) xs) id
= { id is the identity of fmap }
reverse >>= \xs -> (==) xs
= { eta reduction }
reverse >>= (==)
So what is the meaning of id >>= return . f = f? Well, treating functions as "indexed values", we can understand id as being the value that equals its index; and return as being the value that is the same everywhere. So id >>= return . f says "look at index x; then, (still at index x), return the value that ignores its index and has value f x". It just so happens that the index we ignore and the value we hand to f match up -- so we might as well skip all that indirection and simply say "look at index x and apply f to it". This is the meaning of the equation.