#4189: Add (<.>) operator (generalizing (.) to Functor)

The proposal is to add (<.>) function to Data.Functor/Control.Applicative: (<.>) :: (b -> c) -> (a -> f b) -> a -> f c f <.> g = fmap f . g -- (<.>) = (.) . fmap In intend it is related to <$> in the same way as (.) is related to $: (a . b . c) d = a $ b $ c $ d (a <.> b <.> c) d = a <$> b <$> c <$> d a is not specialized to f a to allow such chaining: const 1 <.> print <=< (read :: String -> Int) <.> readFile :: (Num t) => FilePath -> IO t Discussion deadline: 31th August 2010

On 01/08/10 16:05, Felipe Lessa wrote:
+1
What should be its fixity?
I guess right: \a b c -> a <.> b <.> c :: (Functor f) => (a1 -> b) -> (a11 -> a1) -> (a -> f a11) -> a -> f b As opposed to: \a b c -> a <.> b <.> c :: (Functor f, Functor f1) => (a1 -> b) -> (a11 -> f a1) -> (a -> f1 a11) -> a -> f1 (f b) Regards

On Sun, Aug 1, 2010 at 11:25 AM, Maciej Marcin Piechotka
On 01/08/10 16:05, Felipe Lessa wrote:
+1
What should be its fixity?
I guess right:
I mean, how tightly should it bind? We currently have infixr 9 . infixr 0 $ infixr 4 <$> infirl 4 <$ infixl 4 <*> infixr 1 >=> Hmmm... -- Felipe.

-1 Personal preference against the name - regular compose (.) has symmetry in what composes, this combinator doesn't.

On Sun, Aug 01, 2010 at 09:15:33PM +0100, Stephen Tetley wrote:
blackbirdA ?
For the function instance of Applicative its the blackbird combinator, unless I made a miscalculation when rewriting the signature.
Then clearly we should use this as the operator.
.--. ." o \__ _.-" ,( ` _.-" ,;;| _.-=" _," ,,;;;' .-"`_.-"``-..,,;;;;:' `"'` `\`\ /^\\\
We will just have to tweak the layout rule a little to accept it.. John -- John Meacham - ⑆repetae.net⑆john⑈ - http://notanumber.net/

On Sun, 1 Aug 2010, John Meacham wrote:
Then clearly we should use this as the operator.
.--. ." o \__ _.-" ,( ` _.-" ,;;| _.-=" _," ,,;;;' .-"`_.-"``-..,,;;;;:' `"'` `\`\ /^\\\
We will just have to tweak the layout rule a little to accept it..
That's the best proposal for an infix operator I have ever seen! However, I'm afraid that GHC will reject it since the bird's eye is a letter.

On 01/08/10 22:15, Stephen Tetley wrote:
On 1 August 2010 20:57, Maciej Marcin Piechotka
wrote: Hmm. Do you have an idea for better name?
blackbirdA ?
For the function instance of Applicative its the blackbird combinator, unless I made a miscalculation when rewriting the signature.
Hmm. Looks like that but: - blackbirdA does not save much space - f `blackbirdA` g is *more* confusing then (f <$>) . g/ fmap f . g: const 1 <.> print <=< (read :: String -> Int) <.> readFile fmap (const 1) . print <=< fmap (read :: String -> Int) . readFile (const 1 <$>) . print <=< ((read :: String -> Int) <$>) . readFile const 1 `blackbirdA` print <=< (read :: String -> Int) `blackbirdA` readFile First shows the nearly-normal Haskell function pipeline. It's nearly: const 1 . print . read . readFile from non-pure languages (with added pureness) The last one is IMHO unreadable. It is much longer and does not 'graphically' represent flow of information. - blackbird is rather not widely known reference. Regards PS. I know, I know...

Well, blackbirdA wasn't entirely a serious contender, I'd still prefer a word name rather than an operator. Note, that you naming as an infix operator a 3 parameter function, with the intention that the third parameter will generally be elided by programming in a point-free style. I don't think there are any other examples in Prelude plus Control.Monad / Applicative / Category / Arrow of this. Many of the operators expand to three parameters for the function instance, but their general signature is still two params plus result. (<.>) :: Functor f => (b -> c) -> (a -> f b) -> a -> f c f <.> g = fmap f . g

On 2 August 2010 13:53, Stephen Tetley
I don't think there are any other examples in Prelude plus Control.Monad / Applicative / Category / Arrow of this.
Correcting myself - the Kleisli fish [1] in Control.Monad are 3 param. I still don't think its a good precedent though. [1] aka (>=>) & (<=<)

On Mon, 2 Aug 2010, Stephen Tetley wrote:
On 2 August 2010 13:53, Stephen Tetley
wrote: I don't think there are any other examples in Prelude plus Control.Monad / Applicative / Category / Arrow of this.
Correcting myself - the Kleisli fish [1] in Control.Monad are 3 param. I still don't think its a good precedent though.
(.) from Prelude (not Category) is another such example.

On 02/08/10 14:53, Stephen Tetley wrote:
Well, blackbirdA wasn't entirely a serious contender, I'd still prefer a word name rather than an operator.
I know (the "I know" at the end was meant to mean that... well I know).
Note, that you naming as an infix operator a 3 parameter function, with the intention that the third parameter will generally be elided by programming in a point-free style. I don't think there are any other examples in Prelude plus Control.Monad / Applicative / Category / Arrow of this.
As self-corrected (<=<), (.) and (>=>) so exactly the operators it is suppose to be used with. Regards

On Monday 02 August 2010 9:30:12 am Maciej Marcin Piechotka wrote:
As self-corrected (<=<), (.) and (>=>) so exactly the operators it is suppose to be used with.
(f &&& g) x = (f x, g x) (f *** g) (x, y) = (f x, g y) (f ||| g) (Left x) = f x (f ||| g) (Right y) = g y (f +++ g) (Left x) = Left (f x) (f +++ g) (Right y) = Right (g y) They may be Arrow-related functions, and so not all instances behave this way. But (->) is an Arrow after all. The point of all of these is that we don't conceptualize them as "three parameter functions." They are two parameter functions, with the two parameters being functions, and the result being a function. And when thought of in that way, they can be nice ways of structuring programs, by building up larger functions out of smaller components. I can even go on. :) (m >>= f) r = f (m r) r -- reader monad (m >>= f) s = let (s', a) = m s in f a s' -- state monad (m >>= f) k = m $ \a -> f a k -- cont monad Those (except the first) get obscured by newtypes, though. -- Dan

On 2 August 2010 14:59, Dan Doel
The point of all of these is that we don't conceptualize them as "three parameter functions." They are two parameter functions, with the two parameters being functions, and the result being a function.
For sure, we don't conceptualize them as 3 parameter functions because they're more general. But Maciej Piechotka's (<.>) is just a function so not its as general as the arrow operators. My point was that in Prelude + subset of Base, infix symbol names are used for binary functions, not arbitrary combinators like `on` (vis the three exceptions listed). Whether this is a worthwhile principle or even whether its just an accident and not a principle is open to debate. My opinion is that its worth airing it now, as granting a place in Base for (<.>) would feel like a precedent.

On Monday 02 August 2010 12:30:01 pm Stephen Tetley wrote:
For sure, we don't conceptualize them as 3 parameter functions because they're more general. But Maciej Piechotka's (<.>) is just a function so not its as general as the arrow operators.
So what? 99% of the uses I've ever seen of (&&&), (|||), etc. are with the Arrow instance for (->). I'd, at least, consider them worth adding even specialized to that instance if they didn't already exist in their more general forms. And I'd still think of the specialized versions as binary, because using combinators that accept and return functions is one of the perks of using a functional language.
My point was that in Prelude + subset of Base, infix symbol names are used for binary functions, not arbitrary combinators like `on` (vis the three exceptions listed). Whether this is a worthwhile principle or even whether its just an accident and not a principle is open to debate. My opinion is that its worth airing it now, as granting a place in Base for (<.>) would feel like a precedent.
on is named on because uses like compare `on` fst read nicely, and are suggestive of their meaning. And then there are div, elem, max, etc. which are frequently used infix, but are alphabetic binary functions. I'm not sure how enthusiastic I am about (<.>). But this rule about naming (which as far as I know, has not informed any previous decisions; (<=<) and (>=>) are not very old; they were added in GHC 6.8/base 3) is not a good argument against it. -- Dan

On Sun, Aug 1, 2010 at 9:52 AM, Maciej Marcin Piechotka
The proposal is to add (<.>) function to Data.Functor/Control.Applicative: (<.>) :: (b -> c) -> (a -> f b) -> a -> f c f <.> g = fmap f . g -- (<.>) = (.) . fmap
In intend it is related to <$> in the same way as (.) is related to $: (a . b . c) d = a $ b $ c $ d (a <.> b <.> c) d = a <$> b <$> c <$> d
I'm not convinced. "fmap f . g" isn't that much longer than "f <.> g"
and requires no new combinators.
I'd argue that "fmap f . fmap g . h" is better style, since it's
obvious that this should be rewritten as "fmap (f . g) . h". In the
example above, "a <$> b <$> c <$> d" is best transformed to "a . b . c
<$> d".
--
Dave Menendez

On Mon, 2 Aug 2010, David Menendez wrote:
On Sun, Aug 1, 2010 at 9:52 AM, Maciej Marcin Piechotka
wrote: The proposal is to add (<.>) function to Data.Functor/Control.Applicative: (<.>) :: (b -> c) -> (a -> f b) -> a -> f c f <.> g = fmap f . g -- (<.>) = (.) . fmap
In intend it is related to <$> in the same way as (.) is related to $: (a . b . c) d = a $ b $ c $ d (a <.> b <.> c) d = a <$> b <$> c <$> d
I'm not convinced. "fmap f . g" isn't that much longer than "f <.> g" and requires no new combinators.
'f' and 'g' might be infix expressions. Depending on the precedence we had to compare "fmap (f) . g" with "f <.> g" or "fmap (f) . (g)" with "f <.> g" .
I'd argue that "fmap f . fmap g . h" is better style, since it's obvious that this should be rewritten as "fmap (f . g) . h". In the example above, "a <$> b <$> c <$> d" is best transformed to "a . b . c <$> d".
I am also happy with fmap f . fmap g . h and a . b . c <$> d .

On 02/08/10 18:44, Henning Thielemann wrote:
On Mon, 2 Aug 2010, David Menendez wrote:
On Sun, Aug 1, 2010 at 9:52 AM, Maciej Marcin Piechotka
wrote: The proposal is to add (<.>) function to Data.Functor/Control.Applicative: (<.>) :: (b -> c) -> (a -> f b) -> a -> f c f <.> g = fmap f . g -- (<.>) = (.) . fmap
In intend it is related to <$> in the same way as (.) is related to $: (a . b . c) d = a $ b $ c $ d (a <.> b <.> c) d = a <$> b <$> c <$> d
I'm not convinced. "fmap f . g" isn't that much longer than "f <.> g" and requires no new combinators.
'f' and 'g' might be infix expressions. Depending on the precedence we had to compare "fmap (f) . g" with "f <.> g" or "fmap (f) . (g)" with "f <.> g" .
Well - even for other expressions (not necessary infix: fmap (div 5) . read vs div 5 <.> read fmap (f . g) . h vs. f . g <.> h
I'd argue that "fmap f . fmap g . h" is better style, since it's obvious that this should be rewritten as "fmap (f . g) . h". In the example above, "a <$> b <$> c <$> d" is best transformed to "a . b . c <$> d".
I am also happy with
fmap f . fmap g . h
and
a . b . c <$> d
.
The "a <$> b <$> c <$> d" was done to show the relation between $/. and <$>/<.>. Some random usage in my files:
in Reactive e s a' (accumR' a' <.> n) r
= Reactive ef (sf <> ev <> sv) v ((`filterR` rv) <.> nf) (ff *> fv)
f `fmap` Behavior b = Behavior $ fmap f <.> b
accumB b = Behavior $ accumR <.> unBeh b
show = unsafePerformIO . (decode <.> peekArray0 0 <=< toString)
lookupQuark = guardQuark <.> flip (withArray0 0) tryString . encode
peek = Boolean . ((==0) :: GBoolean -> Bool) <.> peek . castPtr
show = unsafePerformIO . (decode <.> peekArray0 0 <=< typeName
typeFromName = typeCheck <.> flip (withArray0 0) fromName . encode
typeAncestors = unfoldr ((id &&& id) <.> typeParent)
vs.
in Reactive e s a' (fmap (accumR' a') . n) r
= Reactive ef (sf <> ev <> sv) v (fmap (`filterR` rv) . nf) (ff *> fv)
f `fmap` Behavior b = Behavior $ fmap (fmap f) . b
accumB b = Behavior $ fmap accumR . unBeh b
show = unsafePerformIO . (fmap decode . peekArray0 0 <=< toString
lookupQuark = fmap guardQuark . flip (withArray0 0) tryString . encode
peek = fmap (Boolean . ((==0) :: GBoolean -> Bool)) . peek . castPtr
show = unsafePerformIO . (fmap decode . peekArray0 0 <=< typeName)
typeFromName = fmap typeCheck . flip (withArray0 0) fromName . encode
typeAncestors = unfoldr (fmap (id &&& id) . typeParent)
Regards

Maciej Marcin Piechotka wrote:
The "a <$> b <$> c <$> d" was done to show the relation between $/. and <$>/<.>.
Yes, but (.) _is_ (<$>) for (a->). Therefore, trying to make (.) and ($) opposing conceptions and then extending it to (<.>) and (<$>) doesn't necessarily make sense. Personally, I think being explicit about the use of fmap here makes code a lot clearer overall. One prime example has already been raised where it makes it clear that (fmap f . fmap g . h) should be written (fmap(f . g) . h) instead. This isn't a case like (<=<) or (<<<) where we are actually generalizing composition in Hask to composition in another category. I'm not a big fan of making a composition operator that crosses between categories; it just doesn't feel like a clean abstraction. The notation of (<$>) for fmap is a clean abstraction in the context of Applicative because it vs (<*>) captures the semantic differences between the spaces in (f x y). Outside of the applicative setting, use of (<$>) instead of fmap tends to obfuscate code rather than improve legibility, IMO. -- Live well, ~wren

On 03/08/10 07:11, wren ng thornton wrote:
Maciej Marcin Piechotka wrote:
The "a <$> b <$> c <$> d" was done to show the relation between $/. and <$>/<.>.
Yes, but (.) _is_ (<$>) for (a->). Therefore, trying to make (.) and ($) opposing conceptions and then extending it to (<.>) and (<$>) doesn't necessarily make sense.
I'm not sure I quite follow. I haven't stated that ($) and (.) are opposite - I stated they are connected. You may say that <.> is <$> for Compose ((->) a) f without the newtype & co.
Personally, I think being explicit about the use of fmap here makes code a lot clearer overall. One prime example has already been raised where it makes it clear that (fmap f . fmap g . h) should be written (fmap(f . g) . h) instead. This isn't a case like (<=<) or (<<<) where we are actually generalizing composition in Hask to composition in another category. I'm not a big fan of making a composition operator that crosses between categories; it just doesn't feel like a clean abstraction.
For existing examples of such mixture:
(^<<) :: (Arrow a) => (c -> d) -> a b c -> a b d (<<^) :: (Arrow a) => a c d -> (b -> c) -> a b d (>>^) :: (Arrow a) => a b c -> (c -> d) -> a b d (^>>) :: (Arrow a) => (b -> c) -> a c d -> a b d
Regards

Maciej Marcin Piechotka wrote:
Personally, I think being explicit about the use of fmap here makes code a lot clearer overall. One prime example has already been raised where it makes it clear that (fmap f . fmap g . h) should be written (fmap(f . g) . h) instead. This isn't a case like (<=<) or (<<<) where we are actually generalizing composition in Hask to composition in another category. I'm not a big fan of making a composition operator that crosses between categories; it just doesn't feel like a clean abstraction.
For existing examples of such mixture:
(^<<) :: (Arrow a) => (c -> d) -> a b c -> a b d (<<^) :: (Arrow a) => a c d -> (b -> c) -> a b d (>>^) :: (Arrow a) => a b c -> (c -> d) -> a b d (^>>) :: (Arrow a) => (b -> c) -> a c d -> a b d
Yeah, I don't like any of those either :) -- Live well, ~wren

On Mon, Aug 02, 2010 at 10:52:21AM -0400, David Menendez wrote:
On Sun, Aug 1, 2010 at 9:52 AM, Maciej Marcin Piechotka
wrote: The proposal is to add (<.>) function to Data.Functor/Control.Applicative: (<.>) :: (b -> c) -> (a -> f b) -> a -> f c f <.> g = fmap f . g -- (<.>) = (.) . fmap
I'd argue that "fmap f . fmap g . h" is better style, since it's obvious that this should be rewritten as "fmap (f . g) . h".
I think that's a convincing argument against. The proposed operator doesn't save much typing, but you need to remember new laws to use it effectively.

In case no one has already mentioned it, (<.>) = fmap.fmap, or more specifically, result.fmap (where 'result' comes from TypeCompose or DeepArrow). Usually I prefer this explicit style over ad hoc infix operators, as the explicit style illustrates and hints toward a more general situation, made up of compositions of first, second, result, fmap, etc. See http://conal.net/blog/posts/semantic-editor-combinators/ . - Conal On Sun, Aug 1, 2010 at 6:52 AM, Maciej Marcin Piechotka < uzytkownik2@gmail.com> wrote:
The proposal is to add (<.>) function to Data.Functor/Control.Applicative: (<.>) :: (b -> c) -> (a -> f b) -> a -> f c f <.> g = fmap f . g -- (<.>) = (.) . fmap
In intend it is related to <$> in the same way as (.) is related to $: (a . b . c) d = a $ b $ c $ d (a <.> b <.> c) d = a <$> b <$> c <$> d
a is not specialized to f a to allow such chaining: const 1 <.> print <=< (read :: String -> Int) <.> readFile :: (Num t) => FilePath -> IO t
Discussion deadline: 31th August 2010
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
participants (10)
-
Conal Elliott
-
Dan Doel
-
David Menendez
-
Felipe Lessa
-
Henning Thielemann
-
John Meacham
-
Maciej Marcin Piechotka
-
Ross Paterson
-
Stephen Tetley
-
wren ng thornton