Monadic alteration to tuple - haskell

I am looking for a function with type similar to:
Monad m => (a, b) -> (b -> m c) -> m (a, c)
It appears to me as some combination of bind (>>=) and a lens operation.
I am aware that I can solve this with a pattern match after a bind, but my gut tells me there is a "simpler" way to write this by leveraging lenses.
Is there any such operation?

This is definitely lensy. The monad is actually just a bit of a distraction because all you need is a functor:
changesecond (a, b) f = fmap (a,) (f b)
I'm pretty sure the _2 lens can be made to do your bidding with a basic lens thing like maybe over but I'm not too familiar with the library yet.
Edit
No combinator is really needed. You can write
changesecond pair f = _2 f pair
You should be able to work this out from the general definition of the Lens type.
Edit 2
This simple example demonstrates the main theme of Van Laarhoven lens construction:
Extract the focus from the context.
Apply the given function to produce a functorful of results.
Use fmap to restore the contexts to the results.
Ed Kmett's lens library elaborates on this theme in various ways. Sometimes it strengthens the functor constraint. Sometimes it generalizes the function to a profunctor. In the case of Equality, it removes the functor constraint. It just turns out that the same basic type shape can express a lot of different ideas.

Your function is just forM = flip mapM, or for = flip traverse if you relax the Monad constraint to Applicative. The Functor being traversed is (,) a.
Prelude> let foo :: Applicative f => (a, b) -> (b -> f c) -> f (a, c); foo p k = traverse k p
Prelude> :t foo
foo :: Applicative f => (a, b) -> (b -> f c) -> f (a, c)
Prelude> foo (1,2) (\x -> [x,2*x])
[(1,2),(1,4)]
(Also, as dfeuer points out, you don't even need Applicative in this specific case.)

Related

What is the 'minimum' needed to make an Applicative a Monad?

The Monad typeclass can be defined in terms of return and (>>=). However, if we already have a Functor instance for some type constructor f, then this definition is sort of 'more than we need' in that (>>=) and return could be used to implement fmap so we're not making use of the Functor instance we assumed.
In contrast, defining return and join seems like a more 'minimal'/less redundant way to make f a Monad. This way, the Functor constraint is essential because fmap cannot be written in terms of these operations. (Note join is not necessarily the only minimal way to go from Functor to Monad: I think (>=>) works as well.)
Similarly, Applicative can be defined in terms of pure and (<*>), but this definition again does not take advantage of the Functor constraint since these operations are enough to define fmap.
However, Applicative f can also be defined using unit :: f () and (>*<) :: f a -> f b -> f (a, b). These operations are not enough to define fmap so I would say in some sense this is a more minimal way to go from Functor to Applicative.
Is there a characterization of Monad as fmap, unit, (>*<), and some other operator which is minimal in that none of these functions can be derived from the others?
(>>=) does not work, since it can implement a >*< b = a >>= (\ x -> b >>= \ y -> pure (x, y)) where pure x = fmap (const x) unit.
Nor does join since m >>= k = join (fmap k m) so (>*<) can be implemented as above.
I suspect (>=>) fails similarly.
I have something, I think. It's far from elegant, but maybe it's enough to get you unstuck, at least. I started with join :: m (m a) -> ??? and asked "what could it produce that would require (<*>) to get back to m a?", which I found a fruitful line of thought that probably has more spoils.
If you introduce a new type T which can only be constructed inside the monad:
t :: m T
Then you could define a join-like operation which requires such a T:
joinT :: m (m a) -> m (T -> a)
The only way we can produce the T we need to get to the sweet, sweet a inside is by using t, and then we have to combine that with the result of joinT somehow. There are two basic operations that can combine two ms into one: (<*>) and joinT -- fmap is no help. joinT is not going to work, because we'll just need yet another T to use its result, so (<*>) is the only option, meaning that (<*>) can't be defined in terms of joinT.
You could roll that all up into an existential, if you prefer.
joinT :: (forall t. m t -> (m (m a) -> m (t -> a)) -> r) -> r

Exercise with functor, applicative and monads in Haskell

I'm doing exercises from the book "Programming in Haskell (2nd Edition)" and I have some problems in understanding the following:
"Given the following type of expressions
data Expr a = Var a | Val Int | Add (Expr a) (Expr a)
deriving Show
that contain variables of some type a, show how to make this type into instances of the Functor, Applicative and Monad classes. With the aid of an example, explain what the >>= operator for this type does."
I found a solution to the first question, which is the same as here: https://github.com/evturn/programming-in-haskell/blob/master/12-monads-and-more/12.05-exercises.hs (ex. 7), that is type correct.
The problem is that I cannot find out the sense of this exercise and the meaning of what this solution actually does.
To understand the solution, you need to get an intuition over a Functor, an Applicative and a Monad.
That being said fmap, <*> and >>= is just a way for one to be able to transform a data within an arbitrary F in your case that's an Expr from a -> b
Take a look at the Type class definitions of Functor, Applicative and Monad for example.
class Functor f where
fmap :: (a -> b) -> f a -> f b
class Functor f => Applicative f where
<*> :: f (a -> b) -> f a -> f b
class Applicative m => Monad m where
>>= :: m a -> (a -> m b) -> m b
Though on the bigger picture, these functions also execute effects of the algebraic datatype that have the type class instances for it.
For example, I will provide the rough definition of the Maybe monad.
instance Monad Maybe where
(Just something) >>= f = f something
Nothing >>= _ = Nothing
In this context, the bind or >>= combinator returns Nothing if there is Nothing for the input else it applies the arbitrary f on something such that f is a transformation from a -> Maybe b which satisfies the definition of the >>= combinator which is m a -> (a -> m b) -> m b where m is the Maybe datatype.

Monad more powerful than Applicative?

I looked at past discussion but could not see why any of the answers are actually correct.
Applicative
<*> :: f (a -> b) -> f a -> f b
Monad
(>>=) :: m a -> (a -> m b) -> m b
So if I get it right, the claim is that >>= cannot be written by only assuming the existence of <*>
Well, let's assume I have <*>.
And I want to create >>=.
So I have f a.
I have f (a -> b).
Now when you look at it, f (a -> b) can be written as (a -> b) (if something is a function of x, y , z - then it's also a function of x, y).
So from the existence of <*> we get (a -> b) -> f a -> f b which again can be written as ((a -> b) -> f a) -> f b, which can be written as (a -> f b).
So we have f a, we have (a -> f b), and we know that <*> results in f b, so we get:
f a -> (a -> f b) -> f b
which is a monad.
Actually, in a more intuitive language: when implementing <*>, I extract (a -> b) out of f(a -> b), I extract a out of f a, and then I apply (a -> b) on a and get b which I wrap with f to finally get f b.
So I do almost the same to create >>=. After applying (a -> b) on a and getting b, do one more step and wrap it with f, so I return f b, hence I know I have a function (a -> f b).
Now when you look at it, f(a -> b) can be written as (a -> b)
No. It can't. Your intuition is (dangerously) far off at this point. That's like saying a hammer is perfect for driving screws in, since it already works for a nail*. You can't simply drop f here, it's part of the type**.
Instead, let's get the facts straight. An Applicative has three associated functions, counting Functor's fmap:
fmap :: Functor f => (a -> b) -> f a -> f b
pure :: Applicative f => a -> f a
(<*>) :: Applicative f => f (a -> b) -> f a -> f b
Here's another fact: you can define bind ((>>=)) in terms of join and vice versa:
join :: Monad m => m (m a) -> m a
join k = k >>= id
(>>=) :: Monad m => m a -> (a -> m b) -> m b
k >>= f = join (fmap f k)
are the implementations of join and bind you provided here part of the Monad definition, or are only join and bind signatures part of the Monad definition? [...] So now I ask myself why would they bother.
Those aren't the official definitions of course, since they would never terminate. You have to define (>>=) for your type if you want to make it a a monad:
instance Monad YourType where
k >>= f = ...
Also, your join definition uses id which is not in the Monad interface, why is it mathematically legitimate?
First of all, id :: a -> a is defined for any type. Second, the mathematical definition of a monad is actually via join. So it's "more"*** legitimate. But most important of all, we can define the monad laws in terms of join (exercise).
If we created join via Applicative, we could also create bind. If we cannot create join via Applicative methods, neither can we derive bind. And join's type actually makes it obvious that we cannot derive it from Applicative:
join :: Monad m => m (m a) -> m a
-- ^ ^ ^
Join is able to drop one of the m layers. Let's check whether it's possible to do the same in the other methods:
fmap :: Functor f => (a -> b) -> f a -> f b
^ ^
0 here 1 here
pure :: Applicative f => a -> f a
^ | ^
0 here | 1 here
(<*>) :: Applicative f => f (a -> b) -> f a -> f b
^ ^
1 here 1 here
The answer is no: none of the tools we're given by Applicative enables us collapse multiple m's into a single one. And that's also what is written in the Typeclassopedia right after the cited paragraph in the other question:
To see the increased power of Monad from a different point of view, let’s see what happens if we try to implement (>>=) in terms of fmap, pure, and (<*>). We are given a value x of type m a, and a function k of type a -> m b, so the only thing we can do is apply k to x. We can’t apply it directly, of course; we have to use fmap to lift it over the m. But what is the type of fmap k? Well, it’s m a -> m (m b). So after we apply it to x, we are left with something of type m (m b)—but now we are stuck; what we really want is an m b, but there’s no way to get there from here. We can add m’s using pure, but we have no way to collapse multiple m’s into one.
Note that join doesn't make it possible to get rid of m completely, that would be a total extraction, and—depending on some other functions—a feature of a comonad. Either way, make sure that you don't let your intuition go astray; trust and use the types.
* That comparison is a little bit bad, because you could actually try to dive a screw in with a hammer into a piece of wood. So think of a plastic screw, a rubber hammer and a carbon steel plate you want to drive the nail in. Good luck.
** Well, you can drop it, but then the type changes drastically.
*** Given that (>>=) and join are equivalent of power and any (>>=) using formula can be transformed to one only using join, they are of course both mathematical sound.
Now when you look at it, f (a -> b) can be written as (a -> b)
Everyone has already contributed explaining that this is not a fact. Let me prove it to you.
If we genuinely had what you state then we should be able to write a function
expose :: f (a -> b) -> (a -> b)
Moreover, for any concrete data type we like, call it F, we ought to be able to write
expose_F :: F (a -> b) -> (a -> b)
expose_F = expose
Let's worry only about writing expose_F since if we can show that expose_F cannot be written for some F then we have surely shown that expose cannot be written.
Let me provide us a test F. It will certainly be non-intuitive feeling as I'm intending to use it to break intuition, but I'm happy to confirm all day long that there is nothing funny at all about
data F a = F
Indeed, it is a Functor
instance Functor F where
fmap _ F = F
and an Applicative for that matter
instance Applicative F where
pure _ = F
F <*> F = F
even a Monad
instance Monad F where
return _ = F
F >>= _ = F
You can verify yourself that all of these typecheck. There's nothing wrong at all about F.
So what's just right about, F? Why did I choose it? Well F is interesting in that values of F a fail to contain anything related at all to a within them. Often people like to talk about data types (or Functors) as "containers" or "boxes". F forces us to remember that in a certain sense a box that's 0 inches deep is still a box. [0]
So surely we cannot write
expose_F :: F (a -> b) -> (a -> b)
There are a number of ways of proving this. The easiest is to appeal to my supposition that you, for instance, believe that there is no coerce function. But, if we had expose_F there would be!
coerce :: a -> b
coerce = expose_F F
More specifically, let me introduce another pathological type (which I again assure you is totally fine)
data Void
There are zero constructors of Void and we like to say therefore that Void has no members. It cannot be made to exist. But we can make one with expose_F.
void :: Void
void = expose_F F ()
In Haskell we're not technically sound enough to execute the above proofs. If you dislike the way I talk about impossibility then you can conjure up whatever types you like with a convenient infinite loop, casual call to
error "Madness rides the star-wind... claws and teeth sharpened on centuries of corpses... dripping death astride a bacchanale of bats from nigh-black ruins of buried temples of Belial..."
or perhaps an unassuming undefined. But these are all on the path of madness.
There is no expose_F and therefore there is no expose.
[0] And to be completely clear, thinking of data types as boxes at all is often flawed. Instances of Functor tend to be "box-like", but here's another interesting data type which is difficult to think of as a box
data Unbox a = Unbox (a -> Bool)
unless perhaps you consider Unbox a to be a box containing a Bool and a negative a or something like that. Perhaps an IOU a.

An example of a Foldable which is not a Functor (or not Traversable)?

A Foldable instance is likely to be some sort of container, and so is likely to be a Functor as well. Indeed, this says
A Foldable type is also a container (although the class does not technically require Functor, interesting Foldables are all Functors).
So is there an example of a Foldable which is not naturally a Functor or a Traversable? (which perhaps the Haskell wiki page missed :-) )
Here's a fully parametric example:
data Weird a = Weird a (a -> a)
instance Foldable Weird where
foldMap f (Weird a b) = f $ b a
Weird is not a Functor because a occurs in a negative position.
Here's an easy example: Data.Set.Set. See for yourself.
The reason for this should be apparent if you examine the types of the specialized fold and map functions defined for Set:
foldr :: (a -> b -> b) -> b -> Set a -> b
map :: (Ord a, Ord b) => (a -> b) -> Set a -> Set b
Because the data structure relies on a binary search tree internally, an Ord constraint is needed for elements. Functor instances must allow any element type, so that's not viable, alas.
Folding, on the other hand, always destroys the tree to produce the summary value, so there's no need to sort the intermediate results of the fold. Even if the fold is actually building a new Set, the responsibility for satisfying the Ord constraint lies on the accumulation function passed to the fold, not the fold itself.
The same will probably apply to any container type that's not fully parametric. And given the utility of Data.Set, this makes the remark you quoted about "interesting" Foldables seem a bit suspect, I think!
Reading Beautiful folding
I realized that any Foldable can be made a Functor by wrapping it into
data Store f a b = Store (f a) (a -> b)
with a simple smart contructor:
store :: f a -> Store f a a
store x = Store x id
(This is just a variant of the Store comonad data type.)
Now we can define
instance Functor (Store f a) where
fmap f (Store x g) = Store x (f . g)
instance (F.Foldable f) => F.Foldable (Store f a) where
foldr f z (Store x g) = F.foldr (f . g) z x
This way, we can make both Data.Set.Set and Sjoerd Visscher's Weird a functor. (However, since the structure doesn't memoize its values, repeatedly folding over it could be very inefficient, if the function that we used in fmap is complex.)
Update: This also provides an example of a structure that is a functor, foldable but not traversable. To make Store traversable, we would need to make (->) r traversable. So we'd need to implement
sequenceA :: Applicative f => (r -> (f a)) -> f (r -> a)
Let's take Either b for f. Then we'd need to implement
sequenceA' :: (r -> Either b a) -> Either b (r -> a)
Clearly, there is no such function (you can verify with Djinn). So we can neither realize sequenceA.

Does a function like this already exist? (Or, what's a better name for this function?)

I've written code with the following pattern several times recently, and was wondering if there was a shorter way to write it.
foo :: IO String
foo = do
x <- getLine
putStrLn x >> return x
To make things a little cleaner, I wrote this function (though I'm not sure it's an appropriate name):
constM :: (Monad m) => (a -> m b) -> a -> m a
constM f a = f a >> return a
I can then make foo like this:
foo = getLine >>= constM putStrLn
Does a function/idiom like this already exist? And if not, what's a better name for my constM?
Well, let's consider the ways that something like this could be simplified. A non-monadic version would I guess look something like const' f a = const a (f a), which is clearly equivalent to flip const with a more specific type. With the monadic version, however, the result of f a can do arbitrary things to the non-parametric structure of the functor (i.e., what are often called "side effects"), including things that depend on the value of a. What this tells us is that, despite pretending like we're discarding the result of f a, we're actually doing nothing of the sort. Returning a unchanged as the parametric part of the functor is far less essential, and we could replace return with something else and still have a conceptually similar function.
So the first thing we can conclude is that it can be seen as a special case of a function like the following:
doBoth :: (Monad m) => (a -> m b) -> (a -> m c) -> a -> m c
doBoth f g a = f a >> g a
From here, there are two different ways to look for an underlying structure of some sort.
One perspective is to recognize the pattern of splitting a single argument among multiple functions, then recombining the results. This is the concept embodied by the Applicative/Monad instances for functions, like so:
doBoth :: (Monad m) => (a -> m b) -> (a -> m c) -> a -> m c
doBoth f g = (>>) <$> f <*> g
...or, if you prefer:
doBoth :: (Monad m) => (a -> m b) -> (a -> m c) -> a -> m c
doBoth = liftA2 (>>)
Of course, liftA2 is equivalent to liftM2 so you might wonder if lifting an operation on monads into another monad has something to do with monad transformers; in general the relationship there is awkward, but in this case it works easily, giving something like this:
doBoth :: (Monad m) => ReaderT a m b -> ReaderT a m c -> ReaderT a m c
doBoth = (>>)
...modulo appropriate wrapping and such, of course. To specialize back to your original version, the original use of return now needs to be something with type ReaderT a m a, which shouldn't be too hard to recognize as the ask function for reader monads.
The other perspective is to recognize that functions with types like (Monad m) => a -> m b can be composed directly, much like pure functions. The function (<=<) :: Monad m => (b -> m c) -> (a -> m b) -> (a -> m c) gives a direct equivalent to function composition (.) :: (b -> c) -> (a -> b) -> (a -> c), or you can instead make use of Control.Category and the newtype wrapper Kleisli to work with the same thing in a generic way.
We still need to split the argument, however, so what we really need here is a "branching" composition, which Category alone doesn't have; by using Control.Arrow as well we get (&&&), letting us rewrite the function as follows:
doBoth :: (Monad m) => Kleisli m a b -> Kleisli m a c -> Kleisli m a (b, c)
doBoth f g = f &&& g
Since we don't care about the result of the first Kleisli arrow, only its side effects, we can discard that half of the tuple in the obvious way:
doBoth :: (Monad m) => Kleisli m a b -> Kleisli m a c -> Kleisli m a c
doBoth f g = f &&& g >>> arr snd
Which gets us back to the generic form. Specializing to your original, the return now becomes simply id:
constKleisli :: (Monad m) => Kleisli m a b -> Kleisli m a a
constKleisli f = f &&& id >>> arr snd
Since regular functions are also Arrows, the definition above works there as well if you generalize the type signature. However, it may be enlightening to expand the definition that results for pure functions and simplify as follows:
\f x -> (f &&& id >>> arr snd) x
\f x -> (snd . (\y -> (f y, id y))) x
\f x -> (\y -> snd (f y, y)) x
\f x -> (\y -> y) x
\f x -> x.
So we're back to flip const, as expected!
In short, your function is some variation on either (>>) or flip const, but in a way that relies on the differences--the former using both a ReaderT environment and the (>>) of the underlying monad, the latter using the implicit side-effects of the specific Arrow and the expectation that Arrow side effects happen in a particular order. Because of these details, there's not likely to be any generalization or simplification available. In some sense, the definition you're using is exactly as simple as it needs to be, which is why the alternate definitions I gave are longer and/or involve some amount of wrapping and unwrapping.
A function like this would be a natural addition to a "monad utility library" of some sort. While Control.Monad provides some combinators along those lines, it's far from exhaustive, and I could neither find nor recall any variation on this function in the standard libraries. I would not be at all surprised to find it in one or more utility libraries on hackage, however.
Having mostly dispensed with the question of existence, I can't really offer much guidance on naming beyond what you can take from the discussion above about related concepts.
As a final aside, note also that your function has no control flow choices based on the result of a monadic expression, since executing the expressions no matter what is the main goal. Having a computational structure independent of the parametric content (i.e., the stuff of type a in Monad m => m a) is usually a sign that you don't actually need a full Monad, and could get by with the more general notion of Applicative.
Hmm, I don't think constM is appropriate here.
map :: (a -> b) -> [a] -> [b]
mapM :: (Monad m) => (a -> m b) -> [a] -> m b
const :: b -> a -> b
So perhaps:
constM :: (Monad m) => b -> m a -> m b
constM b m = m >> return b
The function you are M-ing seems to be:
f :: (a -> b) -> a -> a
Which has no choice but to ignore its first argument. So this function does not have much to say purely.
I see it as a way to, hmm, observe a value with a side effect. observe, effect, sideEffect may be decent names. observe is my favorite, but maybe just because it is catchy, not because it is clear.
I don't really have a clue this exactly allready exists, but you see this a lot in parser-generators only with different names (for example to get the thing inside brackets) - there it's normaly some kind of operator (>>. and .>> in fparsec for example) for this. To really give a name I would maybe call it ignore?
There's interact:
http://hackage.haskell.org/packages/archive/haskell98/latest/doc/html/Prelude.html#v:interact
It's not quite what you're asking for, but it's similar.

Resources