
I find myself often writing this pattern: someFun x y z = ... fun y z = runFun $ someFun someDefault y z
or, alternatively: fun y = runFun . someFun someDefault y
The second option approaches the ideal pointfreeness (or pointlessness if you prefer), but I'd like to go farther: (...) :: (c -> d) -> (a -> b -> c) -> a -> b -> d
(...) f g x y = f (g x y) infixr 9 ...
fun = runFun ... someFun someDefault
There, that's better. More points for fewer points (which means I should really change the name from fun to pun). Does anybody else care about this? What are some alternative solutions? I'd love to have something like this available in the Prelude or a library. (I have no strong feelings about the particular operator.) Regards, Sean

Sean Leather wrote:
I find myself often writing this pattern:
someFun x y z = ...
fun y z = runFun $ someFun someDefault y z
or, alternatively:
fun y = runFun . someFun someDefault y
I very often write this too (wanting function composition, but with a two-argument function on the right hand side). The trick I picked up from somewhere is to do: fun = (runFun .) . someFun someDefault I'm not too keen on that, as it seems clumsy. I often end up writing the operator that you describe, but have never settled on a consistent name (since the obvious one to me, (..), is taken). Thanks, Neil.

On Wed, 17 Feb 2010, Neil Brown wrote:
I very often write this too (wanting function composition, but with a two-argument function on the right hand side). The trick I picked up from somewhere is to do:
fun = (runFun .) . someFun someDefault
I'm not too keen on that, as it seems clumsy. I often end up writing the operator that you describe, but have never settled on a consistent name (since the obvious one to me, (..), is taken).
Maybe helpful: http://www.haskell.org/haskellwiki/Composing_functions_with_multiple_values

That signature is the `oo` "specs" combinator in Data.Aviary:
fun = runFun `oo` someFun someDefault
-md begin Sean Leather quotation:
I find myself often writing this pattern:
someFun x y z = ...
fun y z = runFun $ someFun someDefault y z
or, alternatively:
fun y = runFun . someFun someDefault y
The second option approaches the ideal pointfreeness (or pointlessness if you prefer), but I'd like to go farther:
(...) :: (c -> d) -> (a -> b -> c) -> a -> b -> d
(...) f g x y = f (g x y) infixr 9 ...
fun = runFun ... someFun someDefault
There, that's better. More points for fewer points (which means I should really change the name from fun to pun).
Does anybody else care about this? What are some alternative solutions? I'd love to have something like this available in the Prelude or a library. (I have no strong feelings about the particular operator.)
Regards, Sean
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On 17 February 2010 15:41, Mike Dillon
That signature is the `oo` "specs" combinator in Data.Aviary:
Hi Mike Thanks - indeed, I was just looking up the thread that covered them a month or two ago: http://www.haskell.org/pipermail/haskell-cafe/2009-December/071392.html I wouldn't recommend writing code that depends on Data.Aviary, but some of the combinators are often worth copy/pasting out of it. Best wishes Stephen

begin Stephen Tetley quotation:
On 17 February 2010 15:41, Mike Dillon
wrote: That signature is the `oo` "specs" combinator in Data.Aviary:
Hi Mike
Thanks - indeed, I was just looking up the thread that covered them a month or two ago:
http://www.haskell.org/pipermail/haskell-cafe/2009-December/071392.html
I wouldn't recommend writing code that depends on Data.Aviary, but some of the combinators are often worth copy/pasting out of it.
Are you kidding me? I love writing code like this: ooooo = bunting bunting cardinal thrush blackbird :) -md

On 17 February 2010 16:05, Mike Dillon
Are you kidding me? I love writing code like this:
ooooo = bunting bunting cardinal thrush blackbird
:)
Hi Mike Thanks! - it took me a surprising amount of time to get from this (where I cheated and used an online 'combinator calculator'): psi :: (b -> b -> c) -> (a -> b) -> a -> a -> c psi = c (b s (b (b c) (b (b (b b)) (c (b b (b b i)) (c (b b i) i))))) (c (b b i) i) where c = cardinal b = bluebird s = starling i = idiot ... to this: psi :: (b -> b -> c) -> (a -> b) -> a -> a -> c psi = cardinal (bluebird starling (bluebird cardinalstar dovekie)) applicator

begin Stephen Tetley quotation:
On 17 February 2010 16:05, Mike Dillon
wrote: ... Are you kidding me? I love writing code like this:
ooooo = bunting bunting cardinal thrush blackbird
:)
Hi Mike
Thanks! - it took me a surprising amount of time to get from this (where I cheated and used an online 'combinator calculator'):
psi :: (b -> b -> c) -> (a -> b) -> a -> a -> c psi = c (b s (b (b c) (b (b (b b)) (c (b b (b b i)) (c (b b i) i))))) (c (b b i) i) where c = cardinal b = bluebird s = starling i = idiot
... to this:
psi :: (b -> b -> c) -> (a -> b) -> a -> a -> c psi = cardinal (bluebird starling (bluebird cardinalstar dovekie)) applicator
I just typed a bunch of bird names together, saw that the signature appeared to be "ooooo", and ran a quick test to confirm :) -md

On Wed, Feb 17, 2010 at 16:48, Stephen Tetley wrote:
On 17 February 2010 15:41, Mike Dillon
wrote: That signature is the `oo` "specs" combinator in Data.Aviary:
Nice! I wouldn't recommend writing code that depends on Data.Aviary, but
some of the combinators are often worth copy/pasting out of it.
On the contrary, I think the specs combinators and perhaps others in Data.Aviary (probably not Data.Aviary.*) have potential. We could even generalize oo and the others to categories and add it to Control.Category (which is, after all, looking rather empty). import Control.Category
import Prelude hiding ((.))
-- oo :: (c -> d) -> (a -> b -> c) -> a -> b -> d oo :: (Category cat) => cat c d -> (a -> cat b c) -> a -> cat b d oo = (.) . (.)
-- ooo :: (d -> e) -> (a -> b -> c -> d) -> a -> b -> c -> e ooo :: (Category cat) => cat d e -> (a -> b -> cat c d) -> a -> b -> cat c e ooo = (.) . (.) . (.)
-- oooo :: (e -> f) -> (a -> b -> c -> d -> e) -> a -> b -> c -> d -> f oooo :: (Category cat) => cat e f -> (a -> b -> c -> cat d e) -> a -> b -> c -> cat d f oooo = (.) . (.) . (.) . (.)
Is it necessary? Maybe not. I'm guessing that the names oo, etc. do not have a commonly accepted meaning, so I like them. I'd like to have a module (e.g. Control.Pointfree) containing these and other useful general combinators from the community. Sean

Hi Sean Thanks for the comment. David Menendez pointed out on the other thread that they generalize nicely to functors: http://www.haskell.org/pipermail/haskell-cafe/2009-December/071428.html Typographically they are a pun on ML's composition operator (o), if you don't define o - (aka 'monocle' - little need as we've already got (.) ) then I'd imagine there won't be too many name clashes with people's existing code. 'Specs' was an obvious name for the family once you use them infix. Many of the combinator 'birds' that aren't already used by Haskell seem most useful for permuting other combinator birds rather than programming with - their argument orders not being ideal. The most useful ones I've found that expand to higher arities have the first argument as a 'combiner' (combining all the intermediate results), one or more 'functional' arguments (producing intermediate results from the 'data' arguments), then the 'data' arguments themselves. The liftM and liftA family are of this form, considering the functional type instances ((->) a): liftA :: (a -> ans) -> (r -> a) -> r -> ans liftA2 :: (a -> b -> ans) -> (r -> a) -> (r -> b) -> r -> ans liftA3 :: (a -> b -> c -> ans) -> (r -> a) -> (r -> b) -> (r -> c) -> r -> ans ... or the full general versions: liftA :: Applicative f => (a -> b) -> f a -> f b liftA2 :: Applicative f => (a -> b -> c) -> f a -> f b -> f c liftA3 :: Applicative f => (a -> b -> c -> d) -> f a -> f b -> f c -> f d liftA for functions is bluebird liftA2 for functions is phoenix or starling' or Big Phi ---- An arity family of Starlings can be quite nice for manipulating records. starling :: (a -> b -> c) -> (a -> b) -> a -> c star :: (a -> r -> ans) -> (r -> a) -> r -> ans star2 :: (a -> b -> r -> ans) -> (r -> a) -> (r -> b) -> r -> ans star3 :: (a -> b -> c -> r -> ans) -> (r -> a) -> (r -> b) -> (r -> c) -> r -> ans star4 :: (a -> b -> c -> d -> r -> ans) -> (r -> a) -> (r -> b) -> (r -> c) -> (r -> d) -> r -> ans star5 :: (a -> b -> c -> d -> e -> r -> ans) -> (r -> a) -> (r -> b) -> (r -> c) -> (r -> d) -> (r -> e) -> r -> ans An example - tracking the source position in a parser: data SrcPos = SrcPos { src_line :: Int, src_column :: Int, src_tab_stop :: Int } incrCol :: SrcPos -> SrcPos incrCol = star (\i s -> s { src_column=i+1 }) src_column incrTab :: SrcPos -> SrcPos incrTab = star2 (\i t s -> s { src_column=i+t }) src_column src_tab_stop incrLine :: SrcPos -> SrcPos incrLine = star (\i s -> s { src_line =i+1, src_column=1 }) src_line ---- Permuted variants of cardinal-prime can be useful for adapting a function to a slightly different type. I originally called them combfi etc. 'f' to indicate where a function was applied, and 'i' where identity was applied; but I'm no so happy with the name now: combfi :: (c -> b -> d) -> (a -> c) -> a -> b -> d combfii :: (d -> b -> c -> e) -> (a -> d) -> a -> b -> c -> e combfiii :: (e -> b -> c -> d -> f) -> (a -> e) -> a -> b -> c -> d -> f I've sometimes used them to generalize a function's interface, e.g a pretty printer: f1 :: Doc -> Doc -> Doc adapted_f1 :: Num a => a -> Doc -> Doc adapted_f1 = f1 `combfi` (int . fromIntegral) ... not particularly compelling I'll admit. Slowly I'm synthesizing sets of 'em when they seem to apply to an interesting use. Actually finding valid uses and coining good names is harder than defining them. The 'specs' were lucky in that they pretty much named themselves. Best wishes Stephen

On Wed, Feb 17, 2010 at 10:23 PM, Sean Leather
-- oo :: (c -> d) -> (a -> b -> c) -> a -> b -> d oo :: (Category cat) => cat c d -> (a -> cat b c) -> a -> cat b d oo = (.) . (.)
I think at NL-FP day 2008 at Utrecht somebody called '(.) . (.)' the 'boob' operator... it was late and we had a few beers... oh wel, Bas

Am Mittwoch 17 Februar 2010 16:31:16 schrieb Sean Leather:
I find myself often writing this pattern:
someFun x y z = ...
fun y z = runFun $ someFun someDefault y z
or, alternatively:
fun y = runFun . someFun someDefault y
The second option approaches the ideal pointfreeness (or pointlessness if you prefer), but I'd like to go farther:
(...) :: (c -> d) -> (a -> b -> c) -> a -> b -> d
(...) f g x y = f (g x y)
(...) = (.) . (.)
infixr 9 ...
fun = runFun ... someFun someDefault
There, that's better. More points for fewer points (which means I should really change the name from fun to pun).
Does anybody else care about this? What are some alternative solutions?
o = (.) oo = (.) . (.) ooo = (.) . (.) . (.) -- etc. runFun `oo` someFun someDefault I've also seen (.:) = (.) . (.) runFun .: someFun someDefault I don't particularly like (...), it's too much like an ellipsis (and bad to count if you continue on that route), I prefer the 'spectacles' or (∘) = (.) (∘∘) = (.) . (.)
I'd love to have something like this available in the Prelude or a library. (I have no strong feelings about the particular operator.)
Regards, Sean

Sean Leather wrote:
The second option approaches the ideal pointfreeness (or pointlessness if you prefer), but I'd like to go farther:
(...) :: (c -> d) -> (a -> b -> c) -> a -> b -> d
(...) f g x y = f (g x y) infixr 9 ...
I go with infixl 8 personally. It seems to play better with some of the other composition combinators. In a somewhat different vein than Oleg's proposed general composition, I've particularly enjoyed Matt Hellige's pointless fun combinators[0]. I have a version which also adds a strict application combinator in my desiderata package[1] so we can say things like: foo $:: bar ~> baz !~> bif which translates to: \a b -> bif (foo (bar a) (baz $! b)) These combinators are especially good when you don't just have a linear chain of functions. [0] http://matt.immute.net/content/pointless-fun [1] http://community.haskell.org/~wren/wren-extras/src/Data/Function/Pointless.h... -- Live well, ~wren

On Fri, Feb 19, 2010 at 10:42 PM, wren ng thornton
Sean Leather wrote:
The second option approaches the ideal pointfreeness (or pointlessness if you prefer), but I'd like to go farther:
(...) :: (c -> d) -> (a -> b -> c) -> a -> b -> d
(...) f g x y = f (g x y) infixr 9 ...
I go with infixl 8 personally. It seems to play better with some of the other composition combinators.
In a somewhat different vein than Oleg's proposed general composition, I've particularly enjoyed Matt Hellige's pointless fun combinators[0]. I have a version which also adds a strict application combinator in my desiderata package[1] so we can say things like:
foo $:: bar ~> baz !~> bif
which translates to:
\a b -> bif (foo (bar a) (baz $! b))
These combinators are especially good when you don't just have a linear chain of functions.
Thanks! I'm glad to know that people have found this approach useful. In cases where it works, I find it somewhat cleaner than families of combinators with (what I find to be) rather obscure names, or much worse, impenetrable sections of (.). We can write the original example in this style: fun = someFun someDefault $:: id ~> id ~> runFun but unfortunately, while it's both pointfree and fairly clear, it isn't really an improvement over the pointful version, IMHO. Matt

Matt Hellige wrote:
Thanks! I'm glad to know that people have found this approach useful. In cases where it works, I find it somewhat cleaner than families of combinators with (what I find to be) rather obscure names, or much worse, impenetrable sections of (.). We can write the original example in this style: fun = someFun someDefault $:: id ~> id ~> runFun but unfortunately, while it's both pointfree and fairly clear, it isn't really an improvement over the pointful version, IMHO.
For something this simple it's not too helpful. But, one of the places it really shines is when dealing with newtypes in order to clean up the wrapping/unwrapping so they don't obscure the code. -- Live well, ~wren
participants (9)
-
Bas van Dijk
-
Daniel Fischer
-
Henning Thielemann
-
Matt Hellige
-
Mike Dillon
-
Neil Brown
-
Sean Leather
-
Stephen Tetley
-
wren ng thornton