RE: [Haskell-cafe] Point-free style

Ketil Malde wrote:
(.) . (.) .(.)
I entered it into GHCi, and got
:: forall a a b c a. (b -> c) -> (a -> a -> a -> b) -> a -> a -> a -> c
I spent a minute or so attempting to intuit the type signature of this, before cheating and entering it into ghci also. Is there a straightforward technique by which type signatures can be "hand calculated", or does one end up needing to run the whole inference algorithm in one's head? Tim

G'day all. Ketil Malde wrote:
(.) . (.) .(.)
I entered it into GHCi, and got
:: forall a a b c a. (b -> c) -> (a -> a -> a -> b) -> a -> a -> a -> c
I got this:
Prelude> :t (.) . (.) . (.)
(.) . (.) . (.) :: forall a a1 b c a2.
(b -> c) -> (a -> a1 -> a2 -> b) -> a -> a1 -> a2 -> c
Quoting Tim Docker
Is there a straightforward technique by which type signatures can be "hand calculated", or does one end up needing to run the whole inference algorithm in one's head?
For this case, yes, but you need to expand the point-free style first. Using the combinator B to represent (.): (.) . (.) . (.) = \f -> B (B (B f)) = \f g x -> B (B (B f)) g x = \f g x -> B (B f) (g x) = \f g x y -> B (B f) (g x) y = \f g x y -> B f (g x y) = \f g x y z -> f (g x y z) The type should now be obvious. However, it's probably easier in this case to get the expanded lambda expression directly from the type's "free theorem". Cheers, Andrew Bromage

Am Montag, 14. Februar 2005 01:24 schrieb Tim Docker:
Ketil Malde wrote:
(.) . (.) .(.)
I entered it into GHCi, and got
:: forall a a b c a.
(b -> c) -> (a -> a -> a -> b) -> a -> a -> a -> c
I spent a minute or so attempting to intuit the type signature of this, before cheating and entering it into ghci also.
Is there a straightforward technique by which type signatures can be "hand calculated", or does one end up needing to run the whole inference algorithm in one's head?
Tim
An aside first: Shiqi Cao confused left and right, for (.) is infixr 9 -- it's associative in fact, so it doesn't matter for the result. I'd just phrase the derivation differently: In (.) . (.), the first (to be applied, that is, the right) (.) has -- what else ? -- the type (b -> c) -> ((a -> b) -> (a -> c)). A) The type of the left (.) is an instance of the general type (y -> z) -> ((x -> y) -> (x -> z)), with the input type (y -> z) being the output type of the right (.), so we find y -> z === (a -> b) -> (a -> c), i.e. y = a -> b z = a -> c and x completely arbitrary, hence the type of (.) . (.) is inputTypeOfRight(.) -> OutputTypeOfLeft(.), (b -> c) -> ((x -> y) -> (x -> z)), which we determined as (b -> c) -> ((x -> (a -> b)) -> (x -> (a -> c))). Now rename and drop unnecessary parentheses to get the type (b -> c) -> (a1 -> a -> b) -> (a1 -> a -> c). To get the type of (.) . (.) . (.), insert this type into A) to find y = a -> a1 -> b z = a -> a1 -> c, hence the type of (.) .(.) . (.) is (b -> c) -> (a2 -> a1 -> a -> b) -> (a2 -> a1 -> a -> c). -- here is the point where nested parentheses would really obscure rather than clarify, in handwriting or LaTeX, different sizes could take care of that. Now iteration of the process should be clear. A question for the point-free society: Is there any advantage of defining (.<) = (.) . (.) rather than f .< g = \x y -> f (g x y) -- or f $ g x y ? Analogous question for (.) . (.) . (.) etc. And could one define \f g h x y -> f (g x) (h y) point-free? I can get rid of x and y by co2 f g h = flip (flip (f . g) . h), but that's not satisfactory. Daniel

Am Montag, 14. Februar 2005 13:45 schrieb Thomas Jäger:
On Mon, 14 Feb 2005 11:07:48 +0100, Daniel Fischer > And could one define
\f g h x y -> f (g x) (h y)
point-free?
sure, ((flip . ((.) .)) .) . (.)
Thomas
Cool! But I must say, I find the pointed version easier to read (and define). So back to the question before this one, is there a definite advantage of point-free style? I tend to use semi-point-free style, but I might be argued away from that. Daniel

Hi, On Mon, 14 Feb 2005 14:40:56 +0100, Daniel Fischer wrote:
\f g h x y -> f (g x) (h y) ((flip . ((.) .)) .) . (.)
Cool!
But I must say, I find the pointed version easier to read (and define). It certainly is. In fact, I transformed it automatically using a toy lambdabot plugin, i've recently been writing.
So back to the question before this one, is there a definite advantage of point-free style?
I tend to use semi-point-free style, but I might be argued away from that. Yes, me too. I think obscure point-free style should only be used if a type signature makes it obvious what is going on. Occasionally, the obscure style is useful, though, if it is clear there is exactly one function with a specific type, but tiresome to work out the details using lambda expressions. For example to define a map function for the continuation monad cmap :: (a -> b) -> Cont r a -> Cont r b One knows that it must look like cmap f = Cont . foo . runCont where foo is some twisted composition with f, so successively trying the usual suspects ((f.).), ((.f).), ... will finally lead to the only type-checking and thus correct version (.(.f)), even though I can't tell what exactly that does without looking at the type or eta-expanding it.
Thomas

Thomas Jäger
On Mon, 14 Feb 2005 11:07:48 +0100, Daniel Fischer > And could one define
\f g h x y -> f (g x) (h y)
point-free? sure, ((flip . ((.) .)) .) . (.)
That occurence of flip cannot (AFAIK) be removed, indicating that as far as natural composition is concerned, that function above is not quite 'right'. On the other hand \f g x h y -> f (g x) (h y) corresponds to (((.) .) .) . (.) Clearly better, no? ;-) Reducing the 'complexity' by one level, the symmetric version ((.) .) . (. (.)) has the same type as \f g h x -> f (\f1 y -> g (f1 y)) (h x) I am curious if the function above has been 'seen' in an application before? Jacques

Daniel Fischer wrote:
And could one define
\f g h x y -> f (g x) (h y)
point-free? Any definition can be made point free if you have a complete combinator base at your disposal, e.g., S and K.
Haskell has K (called const), but lacks S. S could be defined as spread f g x = f x (g x) Given that large set of Haskell prelude functions I would not be surprised if spread could already be defined point free in Haskell. :) -- Lennart

On Mon, Feb 14, 2005 at 03:55:01PM +0100, Lennart Augustsson wrote:
Any definition can be made point free if you have a complete combinator base at your disposal, e.g., S and K.
Haskell has K (called const), but lacks S. S could be defined as spread f g x = f x (g x)
Given that large set of Haskell prelude functions I would not be surprised if spread could already be defined point free in Haskell. :)
-- Lennart
I hope this won't be considered cheating... import Control.Monad.Reader k :: a -> b -> a k = return s :: (a -> r -> b) -> (a -> r) -> a -> b s = flip (>>=) . flip Greetings, Remi -- Nobody can be exactly like me. Even I have trouble doing it.

Remi Turk wrote:
import Control.Monad.Reader
k :: a -> b -> a k = return
s :: (a -> r -> b) -> (a -> r) -> a -> b s = flip (>>=) . flip
Greetings, Remi
Oh, a little bit of cheating. ;) But neat. It can be done without importing anything. (Except the implicit Prelude import, of course.) -- Lennart

On Mon, 14 Feb 2005 16:46:17 +0100, Lennart Augustsson
Remi Turk wrote:
import Control.Monad.Reader
k :: a -> b -> a k = return
s :: (a -> r -> b) -> (a -> r) -> a -> b s = flip (>>=) . flip This can be even written as s = ap.
It can be done without importing anything. (Except the implicit Prelude import, of course.) It can, but is it possible to do it much easier than s' = flip flip (span ((0 ==) . fst) . zip [0..] . repeat) . ((.) .) . (id .) . (uncurry .) . flip ((.) . flip (.) . (. (snd . head))) . (. (snd . head)) ?
Thomas

On Monday 14 February 2005 17:08, Thomas Jäger wrote:
s' = flip flip (span ((0 ==) . fst) . zip [0..] . repeat) . ((.) .) . (id .) . (uncurry .) . flip ((.) . flip (.) . (. (snd . head))) . (. (snd . head))
This one is a little bit shorter and somewhat more 'elementary': s = (.) (flip (.) (head . uncurry zip . splitAt 1 . replicate 2) . uncurry) . (flip (.) (flip (.)) . flip (.)) The really hard part was to find a nice & short point-less version of \x -> (x,x) i.e. head . uncurry zip . splitAt 1 . replicate 2 This stuff is really crazy =8-))) Ben

Benjamin Franksen wrote:
This one is a little bit shorter and somewhat more 'elementary':
s = (.) (flip (.) (head . uncurry zip . splitAt 1 . replicate 2) . uncurry) . (flip (.) (flip (.)) . flip (.))
And with less flips: s = (((. head . uncurry zip . splitAt 1 . repeat) . uncurry) .) . (.) . flip /Stephan

Lennart Augustsson wrote (on Mon, 14 Feb 2005 at 14:55): > Any definition can be made point free if you have a > complete combinator base at your disposal, e.g., S and K.
> Haskell has K (called const), but lacks S. S could be > defined as > spread f g x = f x (g x) > Given that large set of Haskell prelude functions I would > not be surprised if spread could already be defined point > free in Haskell. :) It sometimes surprises me the prelude doesn't have diag f x = f x x (aka W. It already has B, C, K and I: (.), flip, const and id.) Peter Hancock

Joe Fasel argued for the inclusion of S or W in the prelude on the grounds that a complete combinator base would be "neat". But the majority of the Haskell committee didn't buy that. -- Lennart Peter G. Hancock wrote:
Lennart Augustsson wrote (on Mon, 14 Feb 2005 at 14:55):
> Any definition can be made point free if you have a > complete combinator base at your disposal, e.g., S and K.
> Haskell has K (called const), but lacks S. S could be > defined as > spread f g x = f x (g x)
> Given that large set of Haskell prelude functions I would > not be surprised if spread could already be defined point > free in Haskell. :)
It sometimes surprises me the prelude doesn't have
diag f x = f x x
(aka W. It already has B, C, K and I: (.), flip, const and id.)
Peter Hancock _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Lennart Augustsson wrote:
Daniel Fischer wrote:
And could one define
\f g h x y -> f (g x) (h y)
point-free?
Any definition can be made point free if you have a complete combinator base at your disposal, e.g., S and K.
Haskell has K (called const), but lacks S. S could be defined as spread f g x = f x (g x)
Given (you guessed it) class Idiom i where ii :: x -> i x (<%>) :: i (s -> t) -> i s -> i t I tend to write instance Idiom ((->) r) where ii = const (<%>) rst rs r = rst r (rs r) or instance Idiom ((->) r) where ii = return (<%>) = ap The idiom bracket notation (implemented by ghastly hack) gives iI f is1 ... isn Ii = ii f <%> is1 <%> .. <%> isn :: i t when f :: s1 -> .. -> sn -> t is1 :: i s1 .. isn :: i sn The point is to turn higher-order/effectful things into first-order applicative things, so eval :: Expr -> [Int] -> Int eval (Var j) = (!! j) eval (Add e1 e2) = iI (+) (eval e1) (eval e2) Ii -- and so on The above is a bit pointwise, a bit point-free: the components of the expression get named explicitly, the plumbing of the environment is hidden. I get the plumbing for free from the structure of the computations, which I really think of as first-order things in the environment idiom, rather than higher-order things in the identity idiom. Thomas Jäger wrote:
Yes, me too. I think obscure point-free style should only be used if a type signature makes it obvious what is going on. Occasionally, the obscure style is useful, though, if it is clear there is exactly one function with a specific type, but tiresome to work out the details using lambda expressions. For example to define a map function for the continuation monad
cmap :: (a -> b) -> Cont r a -> Cont r b
Correspondingly, if I were developing the continuation monad, I'd probably write the monad instance itself in quite a pointy way, with suggestive (not to say frivolous) identifiers data Cont a x = Cont {runCont :: (x -> a) -> a} instance Monad (Cont a) where return x = Cont $ \ uputX -> uputX x ugetS >>= ugetTfromS = Cont $ \ uputT -> runCont ugetS $ \ s -> runCont (ugetTfromS s) $ \ t -> uputT t And then I already have the map operator, liftM. But more generally, if I wanted to avoid ghastly plumbing or overly imperative-looking code, I'd perform my usual sidestep instance Idiom (Cont a) where ii = return (<%>) = ap and now I've got a handy first-order notation. If I didn't already have map, I could write mapI :: Idiom i => (s -> t) -> i s -> i t mapI f is = iI f is Ii although mapI = (<%>) . ii is perhaps too tempting for an old sinner like me. My rule of thumb is that tunes should be pointwise, rhythms point-free. And you know the old gag about drummers and drum machines... Conor -- http://www.cs.nott.ac.uk/~ctm

On Feb 14, 2005, at 2:07 AM, Daniel Fischer wrote:
A question for the point-free society: Is there any advantage of defining
(.<) = (.) . (.)
rather than
f .< g = \x y -> f (g x y) -- or f $ g x y ?
Analogous question for (.) . (.) . (.) etc.
Well, from the fact that you even pose the question, and notwithstanding wise remarks from Simon Marlow, I'm guessing that "out of sheer impish delight" or "to tickle the aesthetic sense the way a bump to the elbow tickles the funny bone" are not the sort of answers you're looking for :) . (Note that others have since risen to the occasion in this vein. And remember that all these "dotted dots" were Jerzy's fault, not mine, and that beer was at hand ... .) More seriously, however, the generalization to n raises some interesting issues. For surely we are tempted to something like this, in a half-imagined syntax (read the LHS as "dot sub n"): (. _ n) = foldl1 (.) (replicate n (.)) And, just as surely, we shouldn't be satisfied with the answer "Hindley-Milner don't do dat" * . Rather, we should seek out ways to extend the type system and the language so that we could make this abstraction, and others like it, which are compelling at some basic level. The point being, this generalization might not occur to us (and drive us to new heights, etc.) if we didn't express it in the more "precious" style. -- Fritz PS: Which is not to say that the Haskell type system can't be wrenched (coerced, cajoled, gently plied with sweet whispers ...) into doing things *similar* to this, using type-level natural numbers, or perhaps existentially-quantified data constructors. I'm sure that "extreme typists" like Oleg and Ken do this sort of thing to warm up in the morning, the way other typists (the mundane sort) lace their fingers together and stretch them out before settling in to their 60-words-per-minute day. But perhaps someone else should post some code along these lines, lest Oleg and Ken despair too much of having wasted their efforts on us. I promise to try out a few ideas myself when I get the chance. * (take no offense: just a reference to the old "In Living Color" variety show)

Am Dienstag, 15. Februar 2005 00:42 schrieben Sie:
On Feb 14, 2005, at 2:07 AM, Daniel Fischer wrote:
A question for the point-free society: Is there any advantage of defining
(.<) = (.) . (.)
rather than
f .< g = \x y -> f (g x y) -- or f $ g x y ?
Analogous question for (.) . (.) . (.) etc.
Well, from the fact that you even pose the question, and notwithstanding wise remarks from Simon Marlow, I'm guessing that "out of sheer impish delight" or "to tickle the aesthetic sense the way a bump to the elbow tickles the funny bone" are not the sort of answers you're looking for :) .
No, although I appreciate them and often do things (among them point-freeing my code -- I've not reached mastery in that department yet) for exactly these reasons, what I was looking for, were reasons such as - Oh, indeed this gives better performance, - Well, it makes no difference in performance, but it's easier to handle for the compiler, or whatever else there might be. L'art pour l'art is great, but as Simon Marlow pointed out, it's valuable to write code so that you (and other people) can understand it when you read it some time later. And there I think that point-freeing has a tendency to require more extensive comments.
(Note that others have since risen to the occasion in this vein. And remember that all these "dotted dots" were Jerzy's fault, not mine, and that beer was at hand ... .)
Why "fault"?, I find all this quite interesting.
More seriously, however, the generalization to n raises some interesting issues. For surely we are tempted to something like this, in a half-imagined syntax (read the LHS as "dot sub n"):
(. _ n) = foldl1 (.) (replicate n (.))
And, just as surely, we shouldn't be satisfied with the answer "Hindley-Milner don't do dat" * . Rather, we should seek out ways to extend the type system and the language so that we could make this abstraction, and others like it, which are compelling at some basic level.
The point being, this generalization might not occur to us (and drive us to new heights, etc.) if we didn't express it in the more "precious" style.
-- Fritz
This is the sort of reason for point-free style that I was looking for.
PS: Which is not to say that the Haskell type system can't be wrenched (coerced, cajoled, gently plied with sweet whispers ...) into doing things *similar* to this, using type-level natural numbers, or perhaps existentially-quantified data constructors. I'm sure that "extreme typists" like Oleg and Ken do this sort of thing to warm up in the morning, the way other typists (the mundane sort) lace their fingers together and stretch them out before settling in to their 60-words-per-minute day.
But perhaps someone else should post some code along these lines, lest Oleg and Ken despair too much of having wasted their efforts on us. I promise to try out a few ideas myself when I get the chance.
* (take no offense: just a reference to the old "In Living Color" variety show)
I don't know that, so the pun's wasted on me, pity. Daniel
participants (12)
-
ajb@spamcop.net
-
Benjamin Franksen
-
Conor McBride
-
Daniel Fischer
-
Fritz Ruehr
-
hancock@spamcop.net
-
Jacques Carette
-
Lennart Augustsson
-
Remi Turk
-
Stephan Hohe
-
Thomas Jäger
-
Tim Docker