
Many of the fmap fmaps I've seen come from (fmap f) . g = (fmap f) `fmap` g = fmap (fmap f) g = (fmap (fmap f)) g = ((fmap.fmap) f) g = (fmap.fmap) f g But... to me the former is much clearer than the latter... It is less abstract since it uses (.) instead of fmap. However, I also see (fmap.fmap.fmap), so Conal must have seen a pattern here? Of course one could also write (fmap `fmap` fmap `fmap` fmap) instead of (fmap.fmap.fmap). Or as was already mentioned with the generic replacement (.) = fmap, (fmap.fmap.fmap) can be written as ( (.) . (.) . (.) ) But besides this all being very Haskelly Hackery - and maybe ASCII art that needs to be censured - I don't see the light yet :) Could somebody enlighten me?

I see fmap as a "penetration" of one box.
fmap.fmap as a "penetration" of two boxes, and so on.
So, if you have (UI -> Behavior (Blah, a)), then the value "a" is "buried"
inside a (UI->) box, then inside a Behavior box, and then inside a (Blah,)
box.
To change the value of "a" you can thus use: (fmap.fmap.fmap) aToB
To access (Blah, a), instead, just use (fmap.fmap) and penetrate just 2
boxes instead of 3.
Additionally, this "trick" also works nicely with liftA2. If you have two
values that are buried inside the same 2 boxes (For example, two values of
type: UI -> Behavior a -- the boxes here are a (UI->) reader, and a
Behavior), then you can apply f to the "a" inside both via:
(liftA2.liftA2) f doublyBoxedA doublyBoxedB
And as usual, (liftA2.liftA2.liftA2) when the values are wrapped in 3 boxes,
and so on.
Eyal
2008/11/19 Peter Verswyvelen
Many of the fmap fmaps I've seen come from (fmap f) . g = (fmap f) `fmap` g = fmap (fmap f) g = (fmap (fmap f)) g = ((fmap.fmap) f) g = (fmap.fmap) f g
But... to me the former is much clearer than the latter... It is less abstract since it uses (.) instead of fmap.
However, I also see (fmap.fmap.fmap), so Conal must have seen a pattern here?
Of course one could also write (fmap `fmap` fmap `fmap` fmap) instead of (fmap.fmap.fmap).
Or as was already mentioned with the generic replacement (.) = fmap, (fmap.fmap.fmap) can be written as ( (.) . (.) . (.) )
But besides this all being very Haskelly Hackery - and maybe ASCII art that needs to be censured - I don't see the light yet :)
Could somebody enlighten me?
_______________________________________________ Reactive mailing list Reactive@haskell.org http://www.haskell.org/mailman/listinfo/reactive

In my blog I wrote comment with a pretty short explanation. (BTW, I
love the box penetration metaphor).
http://netsuperbrain.com/blog/posts/introducing-reactive-events/
David
2008/11/18 Peter Verswyvelen
Many of the fmap fmaps I've seen come from (fmap f) . g = (fmap f) `fmap` g = fmap (fmap f) g = (fmap (fmap f)) g = ((fmap.fmap) f) g = (fmap.fmap) f g
But... to me the former is much clearer than the latter... It is less abstract since it uses (.) instead of fmap. However, I also see (fmap.fmap.fmap), so Conal must have seen a pattern here? Of course one could also write (fmap `fmap` fmap `fmap` fmap) instead of (fmap.fmap.fmap). Or as was already mentioned with the generic replacement (.) = fmap, (fmap.fmap.fmap) can be written as ( (.) . (.) . (.) ) But besides this all being very Haskelly Hackery - and maybe ASCII art that needs to be censured - I don't see the light yet :)
Could somebody enlighten me?
-- David Sankel Sankel Software

Thanks for the feedback. Let's see if I get this by writing a little newbie tutorial for myself using literal Haskell syntax. I will import Control.Arrow since fmap on a pairs transforms the second coordinate value, and when transforming pairs, I sometimes need to transform the first coordinate value...
import Control.Arrow
To understand the (fmap.fmap.fmap) thing, I will create a simple tutorial, mainly for myself to get a better understanding. Suppose we have a pair:
p :: (Bool, [Char])
E.g.
p = (True,"Reactive")
The "type graph" (pardon my lack of knowledge of correct terminology) of p is (,) / \ Bool [] | Char Since fmap is about transforming a structure into another structure, let's suppose that - given any "instance" with a type signature like p - we want to create a new instance p' at runtime that transforms the string (at the second coordinate) into its length. That's easy; we can use fmap (or Arrow.second) to do that: < instance Functor ((,) a) where < fmap f (x,y) = fmap (x, f y)
tp :: (Bool,[Char]) -> (Bool,Int) tp = fmap length
p' = tp p
fmap on pairs basically transforms the rightmost branch of our graph. (,) (,) / \ / \ Bool [] --> Bool Int | Char fmap always transforms the rightmost branch in the graph, since the kind of Functor is * -> *. For example lets define an fmap on triples:
instance Functor ((,,) a b) where fmap f (x,y,z) = (x,y,f z)
< fmap :: (c->d) -> (a,b,c) -> (a,b,d) (,,) (,,) / | \ --> / | \ a b c a b d To continue the (fmap.fmap.fmap) story, suppose we now nest p in a Maybe:
m :: Maybe (Bool, [Char]) m = Just (True, "Reactive")
Maybe | (,) / \ Bool [] | Char Again we want to transform the string into its length. To do that we can use the fmap Maybe instance: < fmap f Nothing = Nothing < fmap f (Just x) = Just (f x) The function we need to fmap on m is just tp!
tm :: Maybe (Bool,[Char]) -> Maybe (Bool,Int) tm = fmap tp
m' = tm m
So again this fmap transforms the rightmost branch underneath the Maybe (which is the one and only branch underneath the unary Maybe type) If we expand tm we get < tm = fmap (fmap length) = (fmap . fmap) length So here we have the first magical (fmap . fmap): - the first fmap transforms the branch underneath the Maybe with (fmap (fmap length)), - the second fmap transforms the right branch underneath the pair (,) with (fmap length). We can also do this for functions. Suppose we now have
f :: Char -> Maybe (Bool, [Char]) f c = Just (c=='a', "Reactive")
The type graph of f is (->) / \ Char Maybe | (,) / \ Bool [] | Char But function application also has an fmap instance! It is just the same as function composition: < instance Functor ((<-) a) where < fmap f g = f . g < fmap :: (b->c) -> (a->b) -> (a->c) (->) (->) / \ -> / \ a b a c Again the rightmost branch is transformed... So to transform the string into its length but now in the f graph, we do
tf :: (Char -> Maybe (Bool, [Char])) -> (Char -> Maybe (Bool, Int)) tf = fmap tm
f' = tf f
Expanding this gives
tf' = (fmap . fmap . fmap) length f'' = tf' f
So the expression ((fmap.fmap.fmap) g) performs deep transformation on the 3 rightmost branches of any type graph (that has fmap instances) To transform a leftmost branch, we can use Arrow.first, for example:
tf'' :: (Char -> Maybe (Bool,[Char])) -> (Char -> Maybe (String,[Char])) tf'' = (fmap . fmap . first) show
f''' = tf'' f
Demo:
main = mapM_ putStrLn [ showT p $ fmap length , showT m $ (fmap.fmap) length , showF f $ (fmap.fmap.fmap) length , showF f $ (fmap.fmap.first) show ]
showT x t = show x ++ " ==> " ++ (show $ t x) showF f t = "\'a' -> "++show (f 'a') ++ " ==> \'a' -> " ++ show ((t f) 'a')
|(True,"Reactive") ==> (True,8) | Just (True,"Reactive") ==> Just (True,8) | 'a' -> Just (True,"Reactive") ==> 'a' -> Just (True,8) | 'a' -> Just (True,"Reactive") ==> 'a' -> Just ("True","Reactive") I think I learned something cool here: being able to perform deep transformations without writing a lot of boiler plate code. Thank you!

You got it, Peter!
There's a different generalization axis I've gotten a lot of mileage from,
hinted at by the types of first and second. Generalize function fmap to
arrows beyond (->). I called the generalized method "result", because it
says to edit in the result of a function, just as first and second say to
edit in the first and second components of a pair.
This pattern emerged for me while working on the Eros (
http://conal.net/papers/Eros/) project and is captured in the DeepArrow
library (http://haskell.org/haskellwiki/DeepArrow). The Eros paper shows
applications for interactive composition of values, code, and UIs.
Even without the generalization to deep arrows, defining result = (.), and
using first, second, and result gives a nice concrete reading, in addition
to uses of fmap. For instance, (first.result.second) says how to walk down
the type graph: take the first half of a pair, then the result part of a
function, then the second part of a pair.
- Conal
2008/11/20 Peter Verswyvelen
Thanks for the feedback. Let's see if I get this by writing a little newbie tutorial for myself using literal Haskell syntax.
I will import Control.Arrow since fmap on a pairs transforms the second coordinate value, and when transforming pairs, I sometimes need to transform the first coordinate value...
import Control.Arrow
To understand the (fmap.fmap.fmap) thing, I will create a simple tutorial, mainly for myself to get a better understanding.
Suppose we have a pair:
p :: (Bool, [Char])
E.g.
p = (True,"Reactive")
The "type graph" (pardon my lack of knowledge of correct terminology) of p is
(,) / \ Bool [] | Char
Since fmap is about transforming a structure into another structure, let's suppose that - given any "instance" with a type signature like p - we want to create a new instance p' at runtime that transforms the string (at the second coordinate) into its length.
That's easy; we can use fmap (or Arrow.second) to do that:
< instance Functor ((,) a) where < fmap f (x,y) = fmap (x, f y)
tp :: (Bool,[Char]) -> (Bool,Int) tp = fmap length
p' = tp p
fmap on pairs basically transforms the rightmost branch of our graph.
(,) (,) / \ / \ Bool [] --> Bool Int | Char
fmap always transforms the rightmost branch in the graph, since the kind of Functor is * -> *.
For example lets define an fmap on triples:
instance Functor ((,,) a b) where fmap f (x,y,z) = (x,y,f z)
< fmap :: (c->d) -> (a,b,c) -> (a,b,d)
(,,) (,,) / | \ --> / | \ a b c a b d
To continue the (fmap.fmap.fmap) story, suppose we now nest p in a Maybe:
m :: Maybe (Bool, [Char]) m = Just (True, "Reactive")
Maybe | (,) / \ Bool [] | Char
Again we want to transform the string into its length.
To do that we can use the fmap Maybe instance:
< fmap f Nothing = Nothing < fmap f (Just x) = Just (f x)
The function we need to fmap on m is just tp!
tm :: Maybe (Bool,[Char]) -> Maybe (Bool,Int) tm = fmap tp
m' = tm m
So again this fmap transforms the rightmost branch underneath the Maybe (which is the one and only branch underneath the unary Maybe type)
If we expand tm we get
< tm = fmap (fmap length) = (fmap . fmap) length
So here we have the first magical (fmap . fmap): - the first fmap transforms the branch underneath the Maybe with (fmap (fmap length)), - the second fmap transforms the right branch underneath the pair (,) with (fmap length).
We can also do this for functions. Suppose we now have
f :: Char -> Maybe (Bool, [Char]) f c = Just (c=='a', "Reactive")
The type graph of f is
(->) / \ Char Maybe | (,) / \ Bool [] | Char
But function application also has an fmap instance!
It is just the same as function composition:
< instance Functor ((<-) a) where < fmap f g = f . g < fmap :: (b->c) -> (a->b) -> (a->c)
(->) (->) / \ -> / \ a b a c
Again the rightmost branch is transformed...
So to transform the string into its length but now in the f graph, we do
tf :: (Char -> Maybe (Bool, [Char])) -> (Char -> Maybe (Bool, Int)) tf = fmap tm
f' = tf f
Expanding this gives
tf' = (fmap . fmap . fmap) length f'' = tf' f
So the expression ((fmap.fmap.fmap) g) performs deep transformation on the 3 rightmost branches of any type graph (that has fmap instances)
To transform a leftmost branch, we can use Arrow.first, for example:
tf'' :: (Char -> Maybe (Bool,[Char])) -> (Char -> Maybe (String,[Char])) tf'' = (fmap . fmap . first) show
f''' = tf'' f
Demo:
main = mapM_ putStrLn [ showT p $ fmap length , showT m $ (fmap.fmap) length , showF f $ (fmap.fmap.fmap) length , showF f $ (fmap.fmap.first) show ]
showT x t = show x ++ " ==> " ++ (show $ t x) showF f t = "\'a' -> "++show (f 'a') ++ " ==> \'a' -> " ++ show ((t f) 'a')
|(True,"Reactive") ==> (True,8) | Just (True,"Reactive") ==> Just (True,8) | 'a' -> Just (True,"Reactive") ==> 'a' -> Just (True,8) | 'a' -> Just (True,"Reactive") ==> 'a' -> Just ("True","Reactive")
I think I learned something cool here: being able to perform deep transformations without writing a lot of boiler plate code.
Thank you!
_______________________________________________ Reactive mailing list Reactive@haskell.org http://www.haskell.org/mailman/listinfo/reactive

As interesting as the fmap.fmap.fmap thread is to me, I'm wondering if folks on the reactive list are getting annoyed with it. And I'm sorry that most haskell folks are missing it. How about follow-ups to haskell-cafe? - Conal
participants (4)
-
Conal Elliott
-
David Sankel
-
Eyal Lotem
-
Peter Verswyvelen