
Functions in Haskell aren't distinguished as 1-arg of 2-arg functions.
Usually we don't even think of them as such -- rather we think of the type
of the function or operator.
But there is a wide array of combinators available:
K = const
I = id
B = (.)
C = flip
S = Monad.ap -- instance Monad (->) a - the Reader Monad
W = Monad.join -- also for the Reader Monad
Y = Control.Monad.Fix.fix
and the list goes on and on... Using only S and K, a great many functions
can be expressed, though it does get rather ugly.
Perhaps the most significant reason that Haskell doesn't have more
composition operators is that composing functions is the least part of what
we compose. Using some standard class functions often yields exactly what
you're looking for:
hook = liftM2 (.)
mhook = ap
fork = liftM2
dyfork = liftM2 . liftM2
compose12 = (.) (.) (.) -- as previously shown
Written in this form, the first four become far more general:
"hook" is function composition within a monad;
"mhook" is function application within a monad;
"fork" raises a function for application on monads; and
"dyfork" -- absolutely beautiful, BTW -- raises a function for application
upon nested monads.
BTW, if anyone has a reasonably concise form for a point-free compose21, I'd
like to see it.
On Fri, Jul 3, 2009 at 7:15 PM, Troy Pracy
I've just started learning Haskell and I've been wondering about this issue as well. I can usually work out a point-free version by carefullty deriving it step-by-step, but I was wondering if Haskell had composition operators/functions for dealing with the various forms of composition where a 2-arg function is involved.
I've played around with J (APL's successor) a little and noticed that J has various options for composing two functions (Ponit-free, or "implicit" style is very important in J). Some of the distinctions have to do with J's native array operations and aren't relevant here, but many are. Here are Haskell versions... (note: "monadic" below isn't used in the Haskell/CT sense - "monadic" and "dyadic" in J jsut refer to how many arguments an operator acts on)
-- hook is the J dyadic hook as a function. hook :: (a->b->c) -> (d->b) -> a -> d -> c hook f g = \x y -> f x (g y) -- J's monadic hook mhook :: (a->b->c) -> (a->b) -> a -> c mhook f g = \x -> (hook f g) x x -- J's monadic fork fork :: (a->b->c) -> (d->a) -> (d->b) -> d -> c fork f g h = \x -> f (g x) (h x) -- J's dyadic fork dyfork :: (a->b->c) -> (d->e->a) -> (d->e->b) -> d -> e -> c dyfork f g h = \x y -> f (g x y) (h x y) -- J's dyadic @ or @: - composition of 1-arg fn with 2-arg fn compose12 :: (a->b) -> (c->d->a) -> c -> d -> b compose12 f g = \x y -> f (g x y) (@:) = compose12 {- J's dyadic & or &: - composition of 2-arg fn with 1-arg fn, resulting in a 2-arg fn (f&:g) which applies g to *both* args before passing them to f. Haskell's composition operator and partial application allow a composition of such fns (f . g) where g is applied only to the first arg. -} compose21 :: (a->a->b) -> (c->a) -> c -> c -> b compose21 f g = \x y -> f (g x) (g y) (&:) = compose21
/ /I know a lot of Haskell is written in point-free style and I would have thought Haskell would have operators for some of this, but judging from the previous responses, it looks like it might not. That surprises me, since some of this seems to crop up a lot, but as I said I've just started learning Haskell, so I guess I'll have to give myself some time to absorb the Haskell way of doing things. _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners