Behavior of reverse >>= (==) - haskell

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.

Related

Can I say that Monad makes it possible to see some types as isomorphic?

Monad can pass Just [1,2], which is a different type from what the original length function takes, to >>= return . length.
Just [1,2] >>= return . length
Can I say that Monad makes it possible to see Maybe [a] as isomorphic with [a] on length using (>>=, return)? (Of course they are not really isomorphic.)
Can I choose the term "isomorphic" this situation?
What your example ultimately illustrates is that Maybe is a functor: if you have some f :: a -> b, you can use fmap to turn it into fmap f :: Maybe a -> Maybe b in a way that preserves identities and composition. Monads are functors, with \f m -> m >>= return . f being the same as fmap f m. In your case, we have the length function being transformed by the Maybe functor.
can I choose term "isomorphic" this situation?
Not really. fmap for Maybe is not an isomorphism. An isomorphism requires there being a two-sided inverse that undoes it, which in this case would be something like:
unFmapMaybe :: (Maybe a -> Maybe b) -> (a -> b)
-- For it to be a two-sided inverse to `fmap`, we should have:
unFmapMaybe . fmap = id
fmap . unFmapMaybe = id
However, there are no (Maybe a -> Maybe b) -> (a -> b) functions, as there is no way to obtain a b result if the input Maybe a -> Maybe b function gives out a Nothing. While there are specific functors whose fmap is an isomorphism (Identity is one example), that is not the case in general.
[a] is isomorphic to the quotient type of Maybe [a] with Nothing and Just [] considered equivalent. Alternatively it is isomorphic to Maybe (NonEmpty a), which simply eliminates the Just [] case.
In other words, [a] can be factorized as a composition of the Maybe and NonEmpty functors.
A result of this is that you can lift any function on NonEmpty a to a function on [a]:
liftEmptyable :: (NonEmpty a -> r) -> [a] -> Maybe r
liftEmptyable _ [] = Nothing
liftEmptyable f (x:xs) = Just $ f (x:|xs)
Not sure that actually has much to do with your question though. As duplode answered, you don't really do anything but a simple functor mapping. We could at most elaborate that the monad laws ensure that the fmap really behaves as if length acted directly on the contained list:
Just [1,2] >>= return . length
≡ return [1,2] >>= return . length -- def. of `Monad Maybe`
≡ return (length [1,2]) -- left-identity monad law

Haskell instance of `bind` for a custom type

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 (>>=).

Can `(>>=)` be redeclared as `(a -> m b) -> m a -> m b`?

In Haskell Monad is declared as
class Applicative m => Monad m where
return :: a -> m a
(>>=) :: m a -> (a -> m b) -> m b
return = pure
I was wondering if it is okay to redeclare the bind operator as
(>>=) :: (a -> m b) -> m a -> m b
?
Is it correct that the second declaration makes it clearer that (>>=) maps a function of type a -> m b to a function of type m a -> m b, while the original declaration makes less clear what it means?
Will that change of declaration make something from possible to impossible, or just require some change of using monad (which seems bearable to Haskell programmers)?
Thanks.
There's one reason why >>= tends to be more useful in practice than it's flipped counterpart =<<: it plays nicely with lambda notation. Namely, \ acts as a syntactic herald, so you can continue the computation without needing any parentheses. For instance,
do x <- [1..5]
y <- [10..20]
return $ x*y
can be rewritten very easily in terms of >>= as
[1..5] >>= \x -> [10..20] >>= \y -> return $ x*y
You still have much the same “imperative flow” feel as with the do version.
Whereas with =<< it would require awkward parentheses and seem to read backwards:
(\x -> (\y -> return $ x*y) =<< [10..20]) =<< [1..5]
Ok, you might say this feels more like function application. But where that is useful, it is often more poignant to use only the applicative functor interface rather than the monadic one:
(\x y -> x*y) <$> [1..5] <*> [10..20]
or short
(*) <$> [1..5] <*> [10..20]
Note that (<*>) :: f (a->b) -> f a -> f b has essentially the order of =<< that you propose, just with the a-> inside the functor rather than outside.

How is `join` implemented in Maybe/List monad? [duplicate]

This question already has answers here:
Monads with Join() instead of Bind()
(7 answers)
Closed 3 years ago.
join can be defined implemented in terms of >>=:
join :: Monad m => m (m a) -> m a
join m = m >>= id
Specifically, how is it implemented in a Maybe and a List monad?
Is it in Maybe monad:
join Nothing = Nothing
join (Just (Just x)) = Just x
and in List monad:
join [] = []
join [[xs]] = [xs]
?
Thanks.
join is implemented exactly once, and it works for all types that are Monads.
The very point of the Monad abstraction is to enable working on different types in the same way. Once you provide >>= (and return) for your type, and make sure they follow the Monad laws, any code that is generic enough to only use those operations will work on your type correctly.
join is just a regular function, implemented in terms of the preexisting (>>=) function. You don't have to worry about which monad is used; (>>=) takes care of that.
Conversely, Monad could have been defined in a way closer to its mathematical definition:
class Monad' m where
return :: a -> m a
join :: m (m a) -> m a
with
(>>=) :: Monad' m => m a -> (a -> m b) -> m b
x >>= f = join (fmap f x)
as the regular function. Then the list-specific definition of join would just be concat :: [[a]] -> [a]:
instance Monad' [] where
return x = [x]
join = concat
join is just implemented as [src]:
join :: (Monad m) => m (m a) -> m a
join x = x >>= id
If we take a look at the monad instances of [] [src] and Maybe [src], we see:
instance Monad [] where
{-# INLINE (>>=) #-}
xs >>= f = [y | x <- xs, y <- f x]
{-# INLINE (>>) #-}
(>>) = (*>)
{-# INLINE fail #-}
fail _ = []
instance Monad Maybe where
(Just x) >>= k = k x
Nothing >>= _ = Nothing
(>>) = (*>)
fail _ = Nothing
So that means that for lists, join is equivalent to:
-- for lists
join xs
-> xs >>= id
-> [ y | x <- xs, y <- id x ]
-> concatMap id xs
-> concat xs
so for lists, the equivalent implementation is:
join_list :: [[a]] -> [a]
join_list = concat
For Maybe we can do case-analysis: the input is a Maybe (Maybe a) so there are basically three possibilities here:
-- (1)
join Nothing
-> Nothing >>= id
-> Nothing
-- (2)
join (Just Nothing)
-> Just Nothing >>= id
-> id Nothing
-> Nothing
-- (3)
join (Just (Just x))
-> Just (Just x) >>= id
-> id (Just x)
-> Just x
So that means that for Maybes the equivalent implementation is:
join_maybe :: Maybe (Maybe a) -> Maybe a
join_maybe (Just x) = x
join_maybe Nothing = Nothing
join is thus not reimplemented for list or Maybe monads, it simply uses the implementation for (>>=) for lists and Maybes, and since these differ, the behavior of join is of course different.

Why to define the constructor parameter of Reader as a function?

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.

Resources