Re: [Haskell-cafe] Implicit concatenation in list comprehensions

2009-07-21 Thread Duncan Coutts
On Sun, 2009-07-19 at 23:07 +0100, Thomas Schilling wrote:
 2009/7/19 Max Bolingbroke batterseapo...@hotmail.com
 
  Dear Cafe,
 
  For fun, I spent a few hours yesterday implement support for this
  syntax in GHC, originally propsed by Koen Claessen:
 
   [k, =, v,   | (k, v) - [(foo, 1), (bar, 2)]
  [foo, =, 1,  , bar, =, 2,  ]
 
 Given that this can easily be simulated via:
 
  [ x | (k, v) - [(foo, 1), (bar, 2)], x - [k, =, v,  ]]
 [foo,=,1, ,bar,=,2, ]
 
 I believe that the added syntax (which every complete tool operating
 on Haskell code would have to support) is not worth its price.

Except that it's ugly compared to the proposed extension. With the
extension you can put things in the same, right place:

renderGhcOptions opts =
 ghcOptExtraPre opts

  -- source search path
  ++ [ -i  | not (null (ghcOptSearchPath opts)) ]
  ++ [ -i, dir | dir - ghcOptSearchPath opts ]

or using your syntax:

  ++ [ opt | dir - ghcOptSearchPath opts
   | opt - [ -i, dir ] ]

or another not-so-nice alternative:

  ++ concat
 [ [ -i, dir ] | dir - ghcOptSearchPath opts ]


When looking down a bunch of these cases, using the extension means we
can put the most important bit --- the flag names and arguments --- in
the same position rather than sometime having to put them at the end in
an extra generator, or having to use extra brackets and a concat.

So yes you can certainly simulate it but it does not read nearly so
well.

Duncan

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


Re: [Haskell-cafe] Implicit concatenation in list comprehensions

2009-07-21 Thread Neil Mitchell
 Except that it's ugly compared to the proposed extension. With the
 extension you can put things in the same, right place:

 renderGhcOptions opts =
     ghcOptExtraPre opts

  -- source search path
  ++ [ -i      | not (null (ghcOptSearchPath opts)) ]
  ++ [ -i, dir | dir - ghcOptSearchPath opts ]

Following the discussions, I now support this extension too - I keep
seeing more and more places in my code where it would be very useful.

Thanks

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


Re: [Haskell-cafe] Implicit concatenation in list comprehensions

2009-07-21 Thread Thomas Schilling
I'm not convinced ugly is a good reason to add more complexity to
the language syntax.  I am not aware of a good metric to measure the
costs/beneficts of new syntactic constructs.  Part of the costs are
the number of tools that need to be adapted and the extend of their
loss of utility if they are not adopted.  Granted, we don't have that
many tools working on Haskell code, but perhaps the feature-creep is
part of the reason (cf. HaRe).  Sure, the eagerness of new features
added to Haskell (well, GHC mostly) is part reason of Haskell's
success.  Since we don't have an objective measure, all I can do is to
ask people to consider that new syntax is not as cheap as it many seem
to think it is.

2009/7/20 Duncan Coutts duncan.cou...@worc.ox.ac.uk:
 On Sun, 2009-07-19 at 23:07 +0100, Thomas Schilling wrote:
 2009/7/19 Max Bolingbroke batterseapo...@hotmail.com
 
  Dear Cafe,
 
  For fun, I spent a few hours yesterday implement support for this
  syntax in GHC, originally propsed by Koen Claessen:
 
   [k, =, v,   | (k, v) - [(foo, 1), (bar, 2)]
  [foo, =, 1,  , bar, =, 2,  ]

 Given that this can easily be simulated via:

  [ x | (k, v) - [(foo, 1), (bar, 2)], x - [k, =, v,  ]]
 [foo,=,1, ,bar,=,2, ]

 I believe that the added syntax (which every complete tool operating
 on Haskell code would have to support) is not worth its price.

 Except that it's ugly compared to the proposed extension. With the
 extension you can put things in the same, right place:

 renderGhcOptions opts =
     ghcOptExtraPre opts

  -- source search path
  ++ [ -i      | not (null (ghcOptSearchPath opts)) ]
  ++ [ -i, dir | dir - ghcOptSearchPath opts ]

 or using your syntax:

  ++ [ opt | dir - ghcOptSearchPath opts
           | opt - [ -i, dir ] ]

 or another not-so-nice alternative:

  ++ concat
     [ [ -i, dir ] | dir - ghcOptSearchPath opts ]


 When looking down a bunch of these cases, using the extension means we
 can put the most important bit --- the flag names and arguments --- in
 the same position rather than sometime having to put them at the end in
 an extra generator, or having to use extra brackets and a concat.

 So yes you can certainly simulate it but it does not read nearly so
 well.

 Duncan





-- 
Push the envelope.  Watch it bend.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Implicit concatenation in list comprehensions

2009-07-21 Thread Dan Weston

Bulat Ziganshin wrote:

Hello Neil,

Tuesday, July 21, 2009, 1:26:55 PM, you wrote:


 ++ [ -i  | not (null (ghcOptSearchPath opts)) ]
 ++ [ -i, dir | dir - ghcOptSearchPath opts ]



Following the discussions, I now support this extension too - I keep
seeing more and more places in my code where it would be very useful.



 ++[ -i| not (null (ghcOptSearchPath opts)) ]
 ++ concat [ [-i, dir] | dir - ghcOptSearchPath opts ]


 [a   | c ] = concat $ do { c; return [a] }
 [a,b | c ]  = concat $ do { c; return [a,b] }

This would mean that

 [   | c ] = concat $ do { c; return [] }

The right is legal Haskell and gives []. The left is (not yet) legal. 
Should it be?


Dan

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


Re: [Haskell-cafe] Implicit concatenation in list comprehensions

2009-07-21 Thread Felipe Lessa
On Tue, Jul 21, 2009 at 12:29:18PM -0700, Dan Weston wrote:
 This would mean that

  [   | c ] = concat $ do { c; return [] }

 The right is legal Haskell and gives []. The left is (not yet)
 legal. Should it be?

Please, please, do not allow that.
People wanting [] should write [].

Thanks!

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


Re: [Haskell-cafe] Implicit concatenation in list comprehensions

2009-07-20 Thread Roel van Dijk
I think the tuple sections are a great idea! It also makes tuple types
and constructors more alike:

x :: (,) String Double
x = (,) Pi 3.14159

I can also see some uses in writing pointfree code. I would definitely
want this in a future GHC (or any other Haskell compiler/interpreter)
release.

I'm not so sure about the list comprehension concatenation. Like
Thomas Schilling wrote, it is only a bit shorter then writing it with
the current syntax. So I'm not sure if it is worth the cost.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Implicit concatenation in list comprehensions

2009-07-20 Thread Roel van Dijk
On Mon, Jul 20, 2009 at 1:27 PM, Roel van Dijkvandijk.r...@gmail.com wrote:
 I think the tuple sections are a great idea! It also makes tuple types
 and constructors more alike:

 x :: (,) String Double
 x = (,) Pi 3.14159

I just realised this is already in GHC :-) But does you patch also add
the equivalent for tuple type annotations?

x :: (String, ) Double
x = (Pi, ) 3.14159

I am also wondering what the following would/should mean:

  (1, , ( , 2), ) 'a' 'b' 'c'

Should this mean
  (1, 'a', ('b', 2), 'c')
or
  (1, 'a', ('c', 2), 'b')

Intuitively I would expect the first option. Just reading from left to
right. But it doesn't look entirely trivial.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Implicit concatenation in list comprehensions

2009-07-20 Thread Sittampalam, Ganesh
Roel van Dijk wrote:
 On Mon, Jul 20, 2009 at 1:27 PM, Roel van
 Dijkvandijk.r...@gmail.com wrote: 
 I think the tuple sections are a great idea! It also makes tuple
 types and constructors more alike: 
 
 x :: (,) String Double
 x = (,) Pi 3.14159
 
 I just realised this is already in GHC :-) But does you patch also
 add the equivalent for tuple type annotations? 
 
 x :: (String, ) Double
 x = (Pi, ) 3.14159
 
 I am also wondering what the following would/should mean:
 
   (1, , ( , 2), ) 'a' 'b' 'c'

I would expect it to be a type error, since I think the following is the
only sane type the tuple can have (assuming numeric literals :: Int):

(1, , ( , 2), ) :: a - b - (Int, a, c - (c, Int), b)

Ganesh

=== 
 Please access the attached hyperlink for an important electronic 
communications disclaimer: 
 http://www.credit-suisse.com/legal/en/disclaimer_email_ib.html 
 
=== 
 
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Implicit concatenation in list comprehensions

2009-07-20 Thread Roel van Dijk
 I am also wondering what the following would/should mean:

   (1, , ( , 2), ) 'a' 'b' 'c'

 I would expect it to be a type error, since I think the following is the
 only sane type the tuple can have (assuming numeric literals :: Int):

 (1, , ( , 2), ) :: a - b - (Int, a, c - (c, Int), b)

 Ganesh

Ah you're completely right! I would be applying a tuple to a Char
which is nonsense.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Implicit concatenation in list comprehensions

2009-07-20 Thread Max Bolingbroke
2009/7/20 Roel van Dijk vandijk.r...@gmail.com:
 I just realised this is already in GHC :-) But does you patch also add
 the equivalent for tuple type annotations?

 x :: (String, ) Double
 x = (Pi, ) 3.14159

It doesn't, and indeed it would only work in the special case where
your only missing type arguments are on the right (since we lack
type-level lambda, we can only accept eta-reduced forms). So it
probably wouldn't be worth it - it wouldn't allow you to write
anything significantly shorter than the existing form (,) String.

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


Re: [Haskell-cafe] Implicit concatenation in list comprehensions

2009-07-20 Thread Nicolas Pouillard
Excerpts from Max Bolingbroke's message of Sun Jul 19 16:58:08 +0200 2009:
 Dear Cafe,
 
 For fun, I spent a few hours yesterday implement support for this
 syntax in GHC, originally propsed by Koen Claessen:
 

[...]

 P.S. I also implemented tuple sections
 (http://hackage.haskell.org/trac/ghc/ticket/3377#comment:3) which are
 a lot more useful:

I vote for both extensions.

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


Re: [Haskell-cafe] Implicit concatenation in list comprehensions

2009-07-20 Thread porges

2009/7/21 Roel van Dijk vandijk.r...@gmail.com:

I am also wondering what the following would/should mean:

  (1, , ( , 2), ) 'a' 'b' 'c'


I would expect it to be a type error, since I think the following is the
only sane type the tuple can have (assuming numeric literals :: Int):

(1, , ( , 2), ) :: a - b - (Int, a, c - (c, Int), b)

Ganesh


Ah you're completely right! I would be applying a tuple to a Char
which is nonsense.


You can kind of do it if you indicate which 'field' is to be applied:

 import Control.Applicative

 newtype Fst b a = Fst (a,b) deriving (Show)
 newtype Snd a b = Snd (a,b) deriving (Show)

 instance Functor (Fst b) where
fmap f (Fst (a,b)) = Fst (f a,b)

 instance Functor (Snd a) where
fmap f (Snd (a,b)) = Snd (a,f b)

 f $$ x = ($x) $ f

...


Fst ((,)1,3) $$ 2 -- no section, don't have the patch ;)

Fst ((1,2),3)

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


Re: [Haskell-cafe] Implicit concatenation in list comprehensions

2009-07-19 Thread Neil Mitchell
Hi Max,

 For fun, I spent a few hours yesterday implement support for this
 syntax in GHC, originally propsed by Koen Claessen:

 [k, =, v,   | (k, v) - [(foo, 1), (bar, 2)]
 [foo, =, 1,  , bar, =, 2,  ]

 This is a generalisation of list comprehensions that allows several
 items to be concatenated onto the result list at once, by having
 several comma-separated items before the pipe.

I like the power this feature gives, and if it was already in Haskell
98 I'd certainly have used it a few times. I can't think of anything
else the syntax could mean, so I don't see a potential for it stealing
syntax that might otherwise be reused. However, it doesn't seem that
discoverable or natural - I'm not sure I'd have ever guessed that such
a feature might exist.

 P.S. I also implemented tuple sections
 (http://hackage.haskell.org/trac/ghc/ticket/3377#comment:3) which are
 a lot more useful:

Yay! Discoverable, useful and really common in practice - a brilliant
extension :-)

Thanks

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


Re: [Haskell-cafe] Implicit concatenation in list comprehensions

2009-07-19 Thread Thomas Hartman
I vote for tuple sections. Very nice!

I don't really see immediate places where I would use the list
comprehension improvement so I guess I don't vote for that.

2009/7/19 Neil Mitchell ndmitch...@gmail.com:
 Hi Max,

 For fun, I spent a few hours yesterday implement support for this
 syntax in GHC, originally propsed by Koen Claessen:

 [k, =, v,   | (k, v) - [(foo, 1), (bar, 2)]
 [foo, =, 1,  , bar, =, 2,  ]

 This is a generalisation of list comprehensions that allows several
 items to be concatenated onto the result list at once, by having
 several comma-separated items before the pipe.

 I like the power this feature gives, and if it was already in Haskell
 98 I'd certainly have used it a few times. I can't think of anything
 else the syntax could mean, so I don't see a potential for it stealing
 syntax that might otherwise be reused. However, it doesn't seem that
 discoverable or natural - I'm not sure I'd have ever guessed that such
 a feature might exist.

 P.S. I also implemented tuple sections
 (http://hackage.haskell.org/trac/ghc/ticket/3377#comment:3) which are
 a lot more useful:

 Yay! Discoverable, useful and really common in practice - a brilliant
 extension :-)

 Thanks

 Neil
 ___
 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] Implicit concatenation in list comprehensions

2009-07-19 Thread Robin Green
I really like tuple sections and I've wanted them for years. I never use
comprehensions though, so I abstain from the other vote.
-- 
Robin

On Sun, 19 Jul 2009 08:18:48 -0700
Thomas Hartman tphya...@gmail.com wrote:

 I vote for tuple sections. Very nice!
 
 I don't really see immediate places where I would use the list
 comprehension improvement so I guess I don't vote for that.
 
 2009/7/19 Neil Mitchell ndmitch...@gmail.com:
  Hi Max,
 
  For fun, I spent a few hours yesterday implement support for this
  syntax in GHC, originally propsed by Koen Claessen:
 
  [k, =, v,   | (k, v) - [(foo, 1), (bar, 2)]
  [foo, =, 1,  , bar, =, 2,  ]
 
  This is a generalisation of list comprehensions that allows several
  items to be concatenated onto the result list at once, by having
  several comma-separated items before the pipe.
 
  I like the power this feature gives, and if it was already in
  Haskell 98 I'd certainly have used it a few times. I can't think of
  anything else the syntax could mean, so I don't see a potential for
  it stealing syntax that might otherwise be reused. However, it
  doesn't seem that discoverable or natural - I'm not sure I'd have
  ever guessed that such a feature might exist.
 
  P.S. I also implemented tuple sections
  (http://hackage.haskell.org/trac/ghc/ticket/3377#comment:3) which
  are a lot more useful:
 
  Yay! Discoverable, useful and really common in practice - a
  brilliant extension :-)
 
  Thanks
 
  Neil
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Implicit concatenation in list comprehensions

2009-07-19 Thread Thomas Schilling
2009/7/19 Max Bolingbroke batterseapo...@hotmail.com

 Dear Cafe,

 For fun, I spent a few hours yesterday implement support for this
 syntax in GHC, originally propsed by Koen Claessen:

  [k, =, v,   | (k, v) - [(foo, 1), (bar, 2)]
 [foo, =, 1,  , bar, =, 2,  ]

Given that this can easily be simulated via:

 [ x | (k, v) - [(foo, 1), (bar, 2)], x - [k, =, v,  ]]
[foo,=,1, ,bar,=,2, ]

I believe that the added syntax (which every complete tool operating
on Haskell code would have to support) is not worth its price.


 This is a generalisation of list comprehensions that allows several
 items to be concatenated onto the result list at once, by having
 several comma-separated items before the pipe. One situation where I
 have found this to be useful is when you are writing Haskell programs
 that call lots of external programs and you need to set the flags
 based on some tests, like so:

 rawSystem myProgram $
  [foo | fooing_enabled] ++
  [bar1, bar2 | baring_enabled]

 I have submitted a ticket to GHC HQ with the patch
 (http://hackage.haskell.org/trac/ghc/ticket/3380#comment:5), but as it
 is just a small convenience it most likely won't make it in unless
 there is more demand for the feature. So, now is the time to speak up
 in favour of (or indeed, against) the added syntax!

 All the best,
 Max

 P.S. I also implemented tuple sections
 (http://hackage.haskell.org/trac/ghc/ticket/3377#comment:3) which are
 a lot more useful:

They are indeed, and here I would be inclined to consider the added
cost worth it.


--
Push the envelope.  Watch it bend.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe