Re: [Haskell-cafe] Re: Why is $ right associative instead ofleftassociative?

2006-02-08 Thread Jan-Willem Maessen


On Feb 8, 2006, at 1:34 AM, Stefan Monnier wrote:

The trouble with monad comprehensions was that it became far too  
easy to
write ambiguous programs, even when you thought you were just  
working with

lists.


One solution was already suggested: to make the comprehension  
syntax be pure
syntactic sugar whose semantics depends on the semantics of the  
identifiers

the syntactic sugar expands into.


OK.  Which identifiers?  I happen to want a version which always uses  
"concatMap" (or, equivalently, monadic bind), and never, ever the  
direct "efficient" translation.  To get the efficient translation for  
lists a la Wadler, though, this requires either a wrapper, so that  
the comprehension runs at the type ([a] -> [a]) and gets applied to  
[] at the very end, or it requires heavy lifting from the compiler  
(foldr/build and its kin as seen in GHC, phc, etc.).


When it was all tied to lists, it was easy to gloss over the details  
of the machinery.


-Jan-Willem Maessen

So you could keep the current list-only comprehension as default,  
and allow
monad comprehension by providing a library (which the users need to  
import

so as to hide the Prelude's definition).


Stefan

___
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


[Haskell-cafe] Re: Why is $ right associative instead ofleftassociative?

2006-02-07 Thread Stefan Monnier
> The trouble with monad comprehensions was that it became far too easy to
> write ambiguous programs, even when you thought you were just working with
> lists.

One solution was already suggested: to make the comprehension syntax be pure
syntactic sugar whose semantics depends on the semantics of the identifiers
the syntactic sugar expands into.

So you could keep the current list-only comprehension as default, and allow
monad comprehension by providing a library (which the users need to import
so as to hide the Prelude's definition).


Stefan

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


Re: [Haskell-cafe] Re: Why is $ right associative instead ofleftassociative?

2006-02-05 Thread John Meacham
On Sun, Feb 05, 2006 at 06:50:57PM +, Ben Rudiak-Gould wrote:
> Paul Hudak wrote:
> >Minor point, perhaps, but I should mention that : is not special syntax 
> >-- it is a perfectly valid infix constructor.
> 
> But Haskell 98 does treat it specially: you can't import Prelude hiding 
> ((:)), or rebind it locally, or refer to it as Prelude.:. In fact I've 
> always wondered why it was done this way. Can anyone enlighten me? Of 
> course it might be confusing if it were rebound locally, but no more 
> confusing than the fact that [f x | x <- xs] is not the same as (map f xs).
> 
> It might be kind of nice if the list type were actually defined in the 
> Prelude as
> 
> data List a = Nil | a : List a
> 
> and all of the special [] syntax defined by a desugaring to this (entirely 
> ordinary) datatype, e.g. [1,2] -> 1 Prelude.: 2 Prelude.: Prelude.Nil.

it would probably be simpler just to declare [] to be a data
constructor. that is what jhc does, it parses the same as any
capitalized name. so you can do

import Prelude hiding([])

data Foo a = [] | Foo | Bar

and list syntax desugars into whatever (:) and [] are in scope.

similarly, (x,y) is just sugar for (,) x y and (,) is a standard data
constructor and can be hidden, redefined, etc just like any other one.

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Why is $ right associative instead ofleftassociative?

2006-02-05 Thread Paul Hudak

Ben Rudiak-Gould wrote:

Paul Hudak wrote:
Minor point, perhaps, but I should mention that : is not special 
syntax -- it is a perfectly valid infix constructor.


But Haskell 98 does treat it specially: you can't import Prelude hiding 
((:)), or rebind it locally, or refer to it as Prelude.:. In fact I've 
always wondered why it was done this way. Can anyone enlighten me?


I think that originally it was because various primitives were defined 
(via "Translations" in the Haskell Report) in terms of lists.  But with 
qualified imports I'm also not sure why this is necessary.


Of course it might be confusing if it were rebound locally, but no more 
confusing than the fact that [f x | x <- xs] is not the same as (map f xs).


It's not?  Hmmm... why not?  (At one time list comprehensions were 
another way to write do notation -- i.e. they were both syntactic sugar 
for monads -- in which case these would surely be different, but that's 
not the case in Haskell 98, as far as I know.)


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


[Haskell-cafe] Re: Why is $ right associative instead ofleftassociative?

2006-02-05 Thread Ben Rudiak-Gould

Paul Hudak wrote:
Minor point, perhaps, but I should mention that : is not special syntax 
-- it is a perfectly valid infix constructor.


But Haskell 98 does treat it specially: you can't import Prelude hiding 
((:)), or rebind it locally, or refer to it as Prelude.:. In fact I've 
always wondered why it was done this way. Can anyone enlighten me? Of course 
it might be confusing if it were rebound locally, but no more confusing than 
the fact that [f x | x <- xs] is not the same as (map f xs).


It might be kind of nice if the list type were actually defined in the 
Prelude as


data List a = Nil | a : List a

and all of the special [] syntax defined by a desugaring to this (entirely 
ordinary) datatype, e.g. [1,2] -> 1 Prelude.: 2 Prelude.: Prelude.Nil.


-- Ben

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