Re: [Haskell-cafe] Point-free style in guards

2008-07-31 Thread Henning Thielemann

On Tue, 22 Jul 2008, L29Ah wrote:

 outStanza | (isMessage) = outMessage
 | (isPresence) = outPresence
 | (isIQ) = outIQ

 Why such a style doesn't work, so I must write ugly code like that:

 outStanza a | (isMessage a) = outMessage a
 | (isPresence a) = outPresence a
 | (isIQ a) = outIQ a

 so, guards can't be useful in point-free function definitions in any way

It's sad that syntactic sugar makes people want even more syntactic sugar
(some people thus call it syntactic heroin).

You can easily achieve the wanted effect by a function like 'select'
  http://www.haskell.org/haskellwiki/Case
 and that way you can also avoid guards in many cases.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Point-free style in guards

2008-07-22 Thread L29Ah
outStanza | (isMessage) = outMessage
| (isPresence) = outPresence
| (isIQ) = outIQ

Why such a style doesn't work, so I must write ugly code like that:

outStanza a | (isMessage a) = outMessage a
| (isPresence a) = outPresence a
| (isIQ a) = outIQ a

so, guards can't be useful in point-free function definitions in any way
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Point-free style in guards

2008-07-22 Thread Neil Mitchell
Hi

 Why such a style doesn't work, so I must write ugly code like that:

 outStanza a | (isMessage a) = outMessage a
  | (isPresence a) = outPresence a
 | (isIQ a) = outIQ a

You can make it slightly prettier, since the brackets are not necessary:

outStanza a | isMessage a = outMessage a
 | isPresence a = outPresence a
| isIQ a = outIQ a

Although I suspect that outMessage crashes if isMessage returns False?
And perhaps outMessage is written as outMessage (Message a b) = ...

In which case, I'd write:

outStanza (Message a b) = ...

And then the code no longer looks ugly, uses pattern matching nicely,
requires no is... functions and won't crash if things like
outMessage are called incorrectly.

[Note, everything beyond the no need for brackets is a bit of a guess,
just possible ideas to think about]

Thanks

Neil
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Point-free style in guards

2008-07-22 Thread Brandon S. Allbery KF8NH


On Jul 22, 2008, at 13:18 , L29Ah wrote:


outStanza | (isMessage) = outMessage
| (isPresence) = outPresence
| (isIQ) = outIQ

Why such a style doesn't work, so I must write ugly code like that:



Because the Haskell 98 Report specifies that guards are rewritten in a  
specific way, which in your case produces invalid code.  See http://haskell.org/onlinereport/decls.html#pattern-bindings 
 for details.


--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] [EMAIL PROTECTED]
system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
electrical and computer engineering, carnegie mellon universityKF8NH


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Point-free style in guards

2008-07-22 Thread Evan Laforge
On Tue, Jul 22, 2008 at 10:27 AM, Neil Mitchell [EMAIL PROTECTED] wrote:
 Hi

 Why such a style doesn't work, so I must write ugly code like that:

 outStanza a | (isMessage a) = outMessage a
  | (isPresence a) = outPresence a
 | (isIQ a) = outIQ a

 You can make it slightly prettier, since the brackets are not necessary:

 outStanza a | isMessage a = outMessage a
 | isPresence a = outPresence a
| isIQ a = outIQ a

Also, if it really is in that format, maybe you can write something like:

switch v pairs = maybe (error no match) ($v) (lookupWith ($v) pairs)

And then you can write the list point-free, though you don't get the
nice guard syntax.  I guess lookupWith must be one of my local
functions, but it's easy to write too.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Point-free style in guards

2008-07-22 Thread Claus Reinke

outStanza | (isMessage) = outMessage
   | (isPresence) = outPresence
   | (isIQ) = outIQ

Why such a style doesn't work, so I must write ugly code like that:

outStanza a | (isMessage a) = outMessage a
   | (isPresence a) = outPresence a
   | (isIQ a) = outIQ a

so, guards can't be useful in point-free function definitions in any way


You just have to avoid all those pointless language constructs
that let mere Haskellers deal with points, and define your own:

   import Control.Monad
   import Data.Maybe
   import Control.Arrow(())

   g |= rhs = uncurry () . ((guard . g)  (return . rhs))
   a +++ b  = uncurry mplus . (a  b)
   (=|) = (fromJust .)

   outStanza = (=|) (((==m) |= (message: ++))
+++  ((==p) |= (presence: ++))
+++  ((==i) |= (iq: ++)) )

Sorry about mentioning those Strings, but then the names shouldn't
really mention the points (Stanza/Message/..), either, right? Or have
I missed the point of this exercise?-)

Claus

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Point-free style in guards

2008-07-22 Thread J.N. Oliveira

On Jul 22, 2008, at 6:32 PM, Brandon S. Allbery KF8NH wrote:


On Jul 22, 2008, at 13:18 , L29Ah wrote:


outStanza | (isMessage) = outMessage
| (isPresence) = outPresence
| (isIQ) = outIQ

Why such a style doesn't work, so I must write ugly code like that:



Because the Haskell 98 Report specifies that guards are rewritten  
in a specific way, which in your case produces invalid code.  See  
http://haskell.org/onlinereport/decls.html#pattern-bindings for  
details.


You may mimic the syntax you wish by writing your own PF combinators,  
eg. by declaring


outStanza =
(isMessage  .=  outMessage .|
(isPresence .=  outPresence .|
(isIQ  .=  outIQ .| ... )))

once you've defined combinators

(p .= f) x = if p x then (f .Left) x else (f. Right) x

and

(f .| g) (Left a) = f a
(f .| g) (Right b) = g b

with appropriate infix priorities ( .| higher than .= ).

But you still need the extra parentheses...

jno



Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe




smime.p7s
Description: S/MIME cryptographic signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Point-free style in guards

2008-07-22 Thread Luke Palmer
2008/7/22 J.N. Oliveira [EMAIL PROTECTED]:
 But you still need the extra parentheses...

Not so!

infixl 0 .|
infixl 0 .|...  -- 'otherwise' construct
infix 1 .=

(.=) :: (a - Bool) - (a - b) - (a - Maybe b)
(.|) :: (a - Maybe b) - (a - Maybe b) - (a - Maybe b)
(.|...) :: (a - Maybe b) - (a - b) - (a - b)
-- implementations left as exercise for the reader

outStanza = isMessage .= outMessage
 .| isPresence .= outPresence
 .| isIQ   .= outIQ
 .|...const 42

Hooray for abusing operators!

Luke
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Point-free style

2005-02-16 Thread Stephan Hohe
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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Point-free style (Was: Things to avoid)

2005-02-16 Thread Bernard Pope
On Mon, 2005-02-14 at 15:56 +, Simon Marlow wrote:
 
 I don't think a general things to avoid section should be advocating
 not naming things... in fact I would advocate the reverse.  Name as many
 things as possible, at least until you have a good feel for how much
 point-freeness is going to result in code that you can read again in 6
 months time.

Another reason to name more things is that it can make debugging easier,
especially in something like buddha where it tells you:

   name args = result

Also, avoiding excessive higher-order code can make debugging easier
too.

Cheers,
Bernie.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Point-free style (Was: Things to avoid)

2005-02-15 Thread Graham Klyne
[I drafted this response some time ago, but didn't send it, so apologies if 
I am re-covering old ground...]

At 09:23 10/02/05 -0500, Jan-Willem Maessen wrote:
If you're trying to avoid obscurity, why advocate point-free style?
Some time ago, I asked an experienced Haskell programmer about the extent 
to which they used point-free style in day-to-day programming, and the 
response I got was to the effect that they use point-full style a fair amount.

The ...er... point, I think, is that it is easier to reason equationally 
with point-free programs, even if the intended computation is often easier 
for mere mortals to see when named values are used.  So point-free style 
helps when trying to apply program transformation techniques, and 
translation to make greater use of point-free idioms may be a useful 
precursor to transforming a program.

Something I have noticed is that, as one gets more used to using higher 
order functions, it is often more elegant to express a computation by 
composition of functions, but in so doing one has to discard preconceived 
notions of what makes an efficient program.

I think it comes down to this: learn to be comfortable with both styles, 
and be prepared to use the one that best expressed the intended solution 
(and is easiest to understand) in any given context.

#g
--
At 09:23 10/02/05 -0500, Jan-Willem Maessen wrote:
If you're trying to avoid obscurity, why advocate point-free style?
I ask this question to be deliberately provocative; I'm not trying to 
single you out in particular.  So, to everybody: What's so great about 
point-free style?

Is it really clear or obvious what
 map . (+)
means?  Contrast this with
 \n - map (+n)
or
 \n xs - map (+n) xs
I submit that, while it is possible to develop a reading knowledge of 
point-free style, non-trivial use of point-free 
computations---compositions of functions with arity greater than 1, as 
above, compositions of sections of composition or application, arrow 
notation without the sugar, and so forth---will always be more difficult 
to read and understand than the direct version.  I submit that this is 
true even if one is familiar with point-free programming and skilled in 
its use.
Even something as simple as eta-reduction (as in the second and third 
functions above) can seriously obscure the meaning of program code by 
concealing the natural arity of a function.

-Jan-Willem Maessen
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Graham Klyne
For email:
http://www.ninebynine.org/#Contact
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Point-free style

2005-02-15 Thread Daniel Fischer
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

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Point-free style

2005-02-14 Thread Daniel Fischer
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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Point-free style

2005-02-14 Thread 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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Point-free style

2005-02-14 Thread Daniel Fischer
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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Point-free style

2005-02-14 Thread Thomas Jäger
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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Point-free style

2005-02-14 Thread Lennart Augustsson
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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Point-free style

2005-02-14 Thread Remi Turk
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.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Point-free style

2005-02-14 Thread 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
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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Point-free style (Was: Things to avoid)

2005-02-14 Thread Simon Marlow
On 10 February 2005 14:23, Jan-Willem Maessen wrote:

 If you're trying to avoid obscurity, why advocate point-free style?
 
 I ask this question to be deliberately provocative; I'm not trying to
 single you out in particular.  So, to everybody: What's so great about
 point-free style?

I completely agree.  I find myself tending towards pointfull-style these
days, perhaps because I'm getting lazy and find it easier to read code
when lots of things have names.  I use explicit function definitions and
lambda bindings a lot more than I used to - at some point I figured out
that the number of characters in my source code isn't the right target
for optimisation :-)

I don't think a general things to avoid section should be advocating
not naming things... in fact I would advocate the reverse.  Name as many
things as possible, at least until you have a good feel for how much
point-freeness is going to result in code that you can read again in 6
months time.

Cheers,
Simon
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Point-free style

2005-02-14 Thread Peter G. Hancock

 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


Re: [Haskell-cafe] Point-free style

2005-02-14 Thread Thomas Jäger
On Mon, 14 Feb 2005 16:46:17 +0100, Lennart Augustsson
[EMAIL PROTECTED] wrote:
 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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Point-free style

2005-02-14 Thread Lennart Augustsson
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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Point-free style

2005-02-14 Thread Jacques Carette
Thomas Jäger [EMAIL PROTECTED] wrote:
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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Point-free style

2005-02-14 Thread Conor McBride
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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Point-free style

2005-02-14 Thread Fritz Ruehr
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)

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Point-free style

2005-02-13 Thread 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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Fwd: [Haskell-cafe] Point-free style

2005-02-13 Thread shiqi cao
-- Forwarded message --
From: shiqi cao [EMAIL PROTECTED]
Date: Sun, 13 Feb 2005 21:25:56 -0500
Subject: Re: [Haskell-cafe] Point-free style
To: Tim Docker [EMAIL PROTECTED]


On Mon, 14 Feb 2005 11:24:12 +1100, Tim Docker [EMAIL PROTECTED] wrote:
 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?

Hi Ketil,

I think the type signatures can be derived by hand.

First let us take a look the type of (.)

(.) :: forall c a b. (b - c) - (a - b) - a - c

one thing need to be taken into account is  (.) is left associative,
but composition of two functions , like f(g(x)),  brings the inner
function into our mind first intuitively.

Since we know the type of (.) calculating the (.).(.) is algebra
manipulation, but be careful.

The left hand (.) and right hand (.) are not identical in terms of
type. Let us call the left one (.)_1, right one (.)_2 and the middle
one (.)_3. Let us type (.)_2 first since the type of (.)_1 is based on
(.)_2

(.)_2 :: (b - c) - (a-b) - (a - c)
 X   -Y--

Let X =  (b - c) and Y = (a-b) - (a - c)

(.)_2 :: X - Y

Then (.)_3 must be (Y - Z) - (X - Y) - (X - Z)

Then (.)_2 must be (Y - Z)

Since (.)_3 is derived (.).(.) has type (X-Z), we need to find out what Z is.

(.)_2 :: (Y - Z)
=  (.)_2 :: ((a-b) - (a - c)) - Z   [1]

(.) :: forall C A B. (B - C) - (A - B) - (A - C)
=  (.)_2 :: ((a-b) - (a - c)) - (d - (a - b)) - (d - (a - c))   [2]
There d is an arbitrary type.

[1] and [2]
=  Z = (d - (a - b)) - (d - (a - c))
=  (.).(.) :: (X - Z) = (b - c)  -  (d - (a - b)) - (d - (a - c))

GHCi result is
(.).(.) :: forall a b c a1.
   (b - c) - (a - a1 - b) - a - a1 - c


Shiqi Cao
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Point-free style

2005-02-13 Thread ajb
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 [EMAIL PROTECTED]:

 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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Point-free style

2005-02-11 Thread Fritz Ruehr
Hmm, Hugs gives me this:
(.) . (.) . (.) :: (a - b) - (c - d - e - a) - c - d - e - b
which I think is correct, if still not transparent in its meaning. 
(ghci gives me a slightly re-named and explicitly quantified 
variation).

Basically, the idea is that this sort of expression, with n occurrences 
of *parenthesized* dots (and n-1 unparenthesized ones interspersed) is 
the compose a 1-argument function with an n-argument function variant 
of the composition operator (in the obvious way). For small n, this 
allows one to get around the limitations of (.) for some points-free 
applications: for large n, it probably isn't worth it. (Appropriate 
definitions of small and large tend to vary :) ).

  --  Fritz
Example nicked from the file I attached to the last message:
(.) = (.) . (.)
stutter = concat . replicate
Here the use of the  symbol is onomatopoeic (or the graphical 
homologue of that): the two arms of the symbol, branching out to the 
right, suggest that this variant of the composition operator, (.), 
takes a 2-argument function on the right.

On Feb 11, 2005, at 12:00 AM, Ketil Malde wrote:
...  Type signatures help, of course.  E.g. with
the previously mentioned and rather cryptic function
(.) . (.) .(.)
I entered it into GHCi, and got
:: forall a a b c a.
  (b - c) - (a - a - a - b) - a - a - a - c
and it suddenly is much clearer what it does.
-kzm
--
If I haven't seen further, it is by standing in the footprints of 
giants
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Point-free style (Was: Things to avoid)

2005-02-10 Thread Jan-Willem Maessen
On Feb 10, 2005, at 6:50 AM, Henning Thielemann wrote:
On Thu, 10 Feb 2005, [ISO-8859-1] Thomas Jäger wrote:
Altogether, the spirit of the page seems to be use as little
syntactic sugar as possible which maybe appropriate if it is aimed at
newbies, who often overuse syntactic sugar (do-notation).
This overuse is what I observed and what I like to reduce. There are 
many
people advocating Haskell just because of the sugar, which let 
interested
people fail to see what's essential for Haskell. When someone says to 
me
that there is a new language which I should know of because it supports
definition of infix operators and list comprehension, I shake my head 
and
wonder why he don't simply stick to Perl, Python, C++ or whatever.
If you're trying to avoid obscurity, why advocate point-free style?
I ask this question to be deliberately provocative; I'm not trying to 
single you out in particular.  So, to everybody: What's so great about 
point-free style?

Is it really clear or obvious what
 map . (+)
means?  Contrast this with
 \n - map (+n)
or
 \n xs - map (+n) xs
I submit that, while it is possible to develop a reading knowledge of 
point-free style, non-trivial use of point-free 
computations---compositions of functions with arity greater than 1, as 
above, compositions of sections of composition or application, arrow 
notation without the sugar, and so forth---will always be more 
difficult to read and understand than the direct version.  I submit 
that this is true even if one is familiar with point-free programming 
and skilled in its use.
Even something as simple as eta-reduction (as in the second and third 
functions above) can seriously obscure the meaning of program code by 
concealing the natural arity of a function.

-Jan-Willem Maessen
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Point-free style (Was: Things to avoid)

2005-02-10 Thread Matthew Roberts
I have to agree (although I suspect few others will :))
matt
On 11/02/2005, at 1:23 AM, Jan-Willem Maessen wrote:
On Feb 10, 2005, at 6:50 AM, Henning Thielemann wrote:
On Thu, 10 Feb 2005, [ISO-8859-1] Thomas Jäger wrote:
Altogether, the spirit of the page seems to be use as little
syntactic sugar as possible which maybe appropriate if it is aimed 
at
newbies, who often overuse syntactic sugar (do-notation).
This overuse is what I observed and what I like to reduce. There are 
many
people advocating Haskell just because of the sugar, which let 
interested
people fail to see what's essential for Haskell. When someone says to 
me
that there is a new language which I should know of because it 
supports
definition of infix operators and list comprehension, I shake my head 
and
wonder why he don't simply stick to Perl, Python, C++ or whatever.
If you're trying to avoid obscurity, why advocate point-free style?
I ask this question to be deliberately provocative; I'm not trying to 
single you out in particular.  So, to everybody: What's so great about 
point-free style?

Is it really clear or obvious what
 map . (+)
means?  Contrast this with
 \n - map (+n)
or
 \n xs - map (+n) xs
I submit that, while it is possible to develop a reading knowledge of 
point-free style, non-trivial use of point-free 
computations---compositions of functions with arity greater than 1, as 
above, compositions of sections of composition or application, arrow 
notation without the sugar, and so forth---will always be more 
difficult to read and understand than the direct version.  I submit 
that this is true even if one is familiar with point-free programming 
and skilled in its use.
Even something as simple as eta-reduction (as in the second and third 
functions above) can seriously obscure the meaning of program code by 
concealing the natural arity of a function.

-Jan-Willem Maessen
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe