Re: [Haskell-cafe] message passing style like in Haskell?

2008-06-21 Thread Ian Lynagh
On Fri, Jun 20, 2008 at 07:57:58AM +0200, Ketil Malde wrote:
 Albert Y. C. Lai [EMAIL PROTECTED] writes:
 
  While we are kind of on this topic, what makes the characters ħ þ
  prefix operator by default, while º and most other odd ones infix?
 
  alphanumeric vs non-alphanumeric
 
 Testing this, I find that isAlpha is True also for 'º', but as the OP
 claims, Haskell will use it as a(n infix) symbol.

This is a bug in GHC. The characters = '\255' were done specially, but
incorrectly for many of those = '\128'. I'll fix it, probably by just
removing the specialisation for them.


Thanks
Ian

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


Re: [Haskell-cafe] message passing style like in Haskell?

2008-06-21 Thread jinjing
After some fiddling with this style, here is what I came up with
for the 8 queens problem in the 99 problem set. It's quite entertaining ...
( note: it's brute force and requires a combination library )

queens2 n = n.permutations.filter all_satisfied where
  all_satisfied queens = queens.diff_col  queens.diff_diag
  diff_col queens = queens.unique.is queens
  diff_diag queens =
n .combinations 2
  .map (map (subtract 1))
  .map (id  flip cherry_pick queens)
  .any same_dist.not where
same_dist (row_pair, col_pair) =
  row_pair.foldl1 (-).abs == col_pair.foldl1 (-).abs

  -- generic helper
  cherry_pick ids xs = ids.map (xs !!)
  is a b = a == b
  unique xs = nub xs

Guess this can conclude this experiment :)

jinjing

On Sun, Jun 22, 2008 at 1:10 AM, Ian Lynagh [EMAIL PROTECTED] wrote:
 On Fri, Jun 20, 2008 at 07:57:58AM +0200, Ketil Malde wrote:
 Albert Y. C. Lai [EMAIL PROTECTED] writes:

  While we are kind of on this topic, what makes the characters ħ þ
  prefix operator by default, while º and most other odd ones infix?

  alphanumeric vs non-alphanumeric

 Testing this, I find that isAlpha is True also for 'º', but as the OP
 claims, Haskell will use it as a(n infix) symbol.

 This is a bug in GHC. The characters = '\255' were done specially, but
 incorrectly for many of those = '\128'. I'll fix it, probably by just
 removing the specialisation for them.


 Thanks
 Ian

 ___
 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] message passing style like in Haskell?

2008-06-19 Thread Ketil Malde
jinjing [EMAIL PROTECTED] writes:

 Any way here's the code:

 module Dot where
 import Prelude hiding ( (.) )

 (.) :: a - (a - b) - b
 a . f = f a

 infixl 9 .

Isn't this (roughly?) the same as flip ($)?

As a side note, may I advise you to use another symbol, and leave the
poor dot alone? Overloading it as a module separator is bad enough.
If you have a keyboard that allows greater-than-ascii input, there are
plenty of options: « » ¡ £ ¥ ł € ® ª...

 comparing:

 encode xs = map (\x - (length x,head x)) (group xs)

 encode xs = xs.group.map token where token x = (x.length, x.head)

To be fair, you could write the first line as:

   encode xs = map token (group xs) where token x = (length x, head x)

I'm not normally too enthusiastic about point-free style, but when the
left and right side of the = both end with the same term, there's
really no need to name them, so:

   encode = map token . group where token x = (length x, head x)
   -- using function composition (.), not your definition

I'm not sure that would work with left-to-right composition.

 I found starting with data and working my way to a solution seems to be
 easier to think with, or maybe it's just me ...

For monadic code, there default is = and  which pass things
forward.  There's also = which goes the other way - so I guess
opinions differ.

-k
-- 
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


Re: [Haskell-cafe] message passing style like in Haskell?

2008-06-19 Thread Duncan Coutts

On Thu, 2008-06-19 at 11:33 +0800, jinjing wrote:
 Hi guys,
 
 This is my second attempt to learn Haskell :)
 
 Any way here's the code:
 
 module Dot where
 import Prelude hiding ( (.) )
 
 (.) :: a - (a - b) - b
 a . f = f a
 
 infixl 9 .

Note that if you redefine (.) composition to be backward application
(flip ($)) then nobody will understand your programs. It's also quite
probably that after reading your own code for a while that you'll not
understand the code that everyone else writes either! :-)

If you want an operator like that, I suggest picking some other symbol.


Duncan

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


Re: [Haskell-cafe] message passing style like in Haskell?

2008-06-19 Thread Gwern Branwen
On 2008.06.19 11:33:56 +0800, jinjing [EMAIL PROTECTED] scribbled 0.5K 
characters:
 Hi guys,

 This is my second attempt to learn Haskell :)

 Any way here's the code:

 module Dot where
 import Prelude hiding ( (.) )

 (.) :: a - (a - b) - b
 a . f = f a

 infixl 9 .

 So for example, 99 questions: Problem 10
 (*) Run-length encoding of a list.

 comparing:

 encode xs = map (\x - (length x,head x)) (group xs)

 to

 encode xs = xs.group.map token where token x = (x.length, x.head)

 I found starting with data and working my way to a solution seems to be
 easier to think with, or maybe it's just me ...

 What is your thought?

 Jinjing

http://cgi.cse.unsw.edu.au/~dons/blog/2007/07 sez:

encode = map (length  head) . group

decode = concatMap (uncurry replicate)

for a different twist on your approach using arrows.

--
gwern
Kerry W NAVSVS industrial Parvus NAVWAN ISM 8182 NRC Reno


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


Re: [Haskell-cafe] message passing style like in Haskell?

2008-06-19 Thread Adam Vogt
* On Thursday, June 19 2008, Ketil Malde wrote:

As a side note, may I advise you to use another symbol, and leave the
poor dot alone? Overloading it as a module separator is bad enough.
If you have a keyboard that allows greater-than-ascii input, there are
plenty of options: « » ¡ £ ¥ ł € ® ª...

And even if you have a plain us layout in hardware, you can use 
us-international layout (or whatever it is called).

So we can make haskell sort of like apl...

While we are kind of on this topic, what makes the characters ħ þ prefix 
operator by default, while º and most other odd ones infix?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] message passing style like in Haskell?

2008-06-19 Thread Chaddaï Fouché
2008/6/19 jinjing [EMAIL PROTECTED]:
 encode xs = xs.group.map token where token x = (x.length, x.head)

Working in this direction is a question of taste, but the choice of
the dot for the operator is a pretty bad idea...

On the other hand, my favourite would be :

encode = map (length  head) . group

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


Re: [Haskell-cafe] message passing style like in Haskell?

2008-06-19 Thread Brent Yorgey
On Thu, Jun 19, 2008 at 3:35 AM, Ketil Malde [EMAIL PROTECTED] wrote:

 jinjing [EMAIL PROTECTED] writes:

  Any way here's the code:

  module Dot where
  import Prelude hiding ( (.) )

  (.) :: a - (a - b) - b
  a . f = f a

  infixl 9 .

 Isn't this (roughly?) the same as flip ($)?

 As a side note, may I advise you to use another symbol, and leave the
 poor dot alone? Overloading it as a module separator is bad enough.
 If you have a keyboard that allows greater-than-ascii input, there are
 plenty of options: « » ¡ £ ¥ ł € (R) ª...


Note that there already is a standard symbol for this, () from
Control.Arrow.  Well, actually () is more general than backwards function
composition, so maybe making your own symbol is still a good idea while
you're learning.

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


Re: [Haskell-cafe] message passing style like in Haskell?

2008-06-19 Thread Albert Y. C. Lai

Adam Vogt wrote:
While we are kind of on this topic, what makes the characters ħ þ prefix 
operator by default, while º and most other odd ones infix?


alphanumeric vs non-alphanumeric


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


Re: [Haskell-cafe] message passing style like in Haskell?

2008-06-19 Thread Derek Elkins
On Thu, 2008-06-19 at 15:24 -0400, Brent Yorgey wrote:
 
 On Thu, Jun 19, 2008 at 3:35 AM, Ketil Malde [EMAIL PROTECTED] wrote:
 jinjing [EMAIL PROTECTED] writes:
 
  Any way here's the code:
 
  module Dot where
  import Prelude hiding ( (.) )
 
  (.) :: a - (a - b) - b
  a . f = f a
 
  infixl 9 .
 
 
 Isn't this (roughly?) the same as flip ($)?
 
 As a side note, may I advise you to use another symbol, and
 leave the
 poor dot alone? Overloading it as a module separator is bad
 enough.
 If you have a keyboard that allows greater-than-ascii input,
 there are
 plenty of options: « » ¡ £ ¥ ł € ® ª...

 
 Note that there already is a standard symbol for this, () from
 Control.Arrow.  Well, actually () is more general than backwards
 function composition, so maybe making your own symbol is still a good
 idea while you're learning.

Application, not composition.  Cont's return would work if it weren't
for the wrapping.  Similarly, (=) for the Id monad.
 

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


Re: [Haskell-cafe] message passing style like in Haskell?

2008-06-19 Thread Ketil Malde
Albert Y. C. Lai [EMAIL PROTECTED] writes:

 While we are kind of on this topic, what makes the characters ħ þ
 prefix operator by default, while º and most other odd ones infix?

 alphanumeric vs non-alphanumeric

Testing this, I find that isAlpha is True also for 'º', but as the OP
claims, Haskell will use it as a(n infix) symbol.  Neither does
isSymbol (all False), isLetter (all True), isMark (False), nor
isPunctuation (Fals) help to separate these.

The HR defines 

uniSymbol-  any Unicode symbol or punctuation 

but I couldn't find any clear way to identify of these.

-k
-- 
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