Re: [Haskell-cafe] 'data' syntax - a suggestion

2007-09-28 Thread Bas van Dijk
On 9/28/07, ok [EMAIL PROTECTED] wrote:
 Now there's a paper that was mentioned about a month ago in this
 mailing list which basically dealt with that by splitting each type
 into two:  roughly speaking a bit that expresses the recursion and
 a bit that expresses the choice structure.

Would you like to give a link to that paper?


(the following is a bit offtopic)

In the 1995 paper[1]: Bananas in Space: Extending Fold and Unfold to
Exponential Types, Erik Meijer and Graham Hutton showed a interesting
technique:

Your ADT:

data Expr env = Variable (Var env)
  | Constant Int
  | Unary String (Expr env)
  | Binary String (Expr env) (Expr env)

can be written without recursion by using a fixpoint newtype
combinator (not sure if this is the right name for it):

newtype Rec f = In { out :: f (Rec f) }

data Var env = Var env String

data E env e = Variable (Var env)
 | Constant Int
 | Unary String e
 | Binary String e e

type Expr env = Rec (E env)

example = In (Binary + (In (Constant 1)) (In (Constant 2)))

You can see that you don't have to name the recursive 'Expr env'
explicitly. However constructing a 'Expr' is a bit verbose because of
the 'In' newtype constructors.

regards,

Bas van Dijk

[1] http://citeseer.ist.psu.edu/293490.html
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] 'data' syntax - a suggestion

2007-09-27 Thread Thomas Conway
On 9/27/07, ok [EMAIL PROTECTED] wrote:
 I have often found myself wishing for a small extension to the syntax of
 Haskell 'data' declarations.  It goes like this:
['where' clause to allow locally defined names in type declarations]

Nice.

Quite a few times I've found myself declaring type synonyms for this
reason, but you end up  polluting the global namespace.

+1 vote.

-- 
Thomas Conway
[EMAIL PROTECTED]

Silence is the perfectest herald of joy:
I were but little happy, if I could say how much.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] 'data' syntax - a suggestion

2007-09-27 Thread jerzy . karczmarczuk


Thomas Conway writes: 


On 9/27/07, ok [EMAIL PROTECTED] wrote:

I have often found myself wishing for a small extension to the syntax of
Haskell 'data' declarations.  It goes like this:
['where' clause to allow locally defined names in type declarations] 

Nice. 


Quite a few times I've found myself declaring type synonyms for this
reason, but you end up  polluting the global namespace. 


+1 vote.


Data with where?
You haven't heard about GADTs? 


http://en.wikibooks.org/wiki/Haskell/GADT
http://www.haskell.org/haskellwiki/Generalised_algebraic_datatype 



Jerzy Karczmarczuk 



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


Re: [Haskell-cafe] 'data' syntax - a suggestion

2007-09-27 Thread Tomasz Zielonka
On 9/27/07, [EMAIL PROTECTED]
[EMAIL PROTECTED] wrote:

 Thomas Conway writes:

  On 9/27/07, ok [EMAIL PROTECTED] wrote:
  I have often found myself wishing for a small extension to the syntax of
  Haskell 'data' declarations.  It goes like this:
  ['where' clause to allow locally defined names in type declarations]
 
  Nice.
 
  Quite a few times I've found myself declaring type synonyms for this
  reason, but you end up  polluting the global namespace.
 
  +1 vote.

 Data with where?
 You haven't heard about GADTs?

I think that you haven't read the question carefully, because where
in GADTs is simply a syntactic sugar. However, this seems to be
available already with GADTs and type equality constraints:

data BST key val where
Empty   :: BST key val
Fork:: (bst ~ BST key val) = key - val - bst - bst - BST key val

It's a pity you can't use bst (or a type synonym) instead of the last
BST key val.

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


Re: [Haskell-cafe] 'data' syntax - a suggestion

2007-09-27 Thread Isaac Dupree

Tomasz Zielonka wrote:

On 9/27/07, [EMAIL PROTECTED]
[EMAIL PROTECTED] wrote:

Thomas Conway writes:


On 9/27/07, ok [EMAIL PROTECTED] wrote:

I have often found myself wishing for a small extension to the syntax of
Haskell 'data' declarations.  It goes like this:

['where' clause to allow locally defined names in type declarations]

Nice.

Quite a few times I've found myself declaring type synonyms for this
reason, but you end up  polluting the global namespace.

+1 vote.

Data with where?
You haven't heard about GADTs?


I think that you haven't read the question carefully, because where
in GADTs is simply a syntactic sugar. However, this seems to be
available already with GADTs and type equality constraints:

data BST key val where
Empty   :: BST key val
Fork:: (bst ~ BST key val) = key - val - bst - bst - BST key val

It's a pity you can't use bst (or a type synonym) instead of the last
BST key val.


Indeed.  GADT syntax looks like a type signature (except for strictness 
annotations, which presently aren't part of function syntax!) but 
apparently the (-)s and result-type aren't type-signature, because 
type-synonyms can't be used for them.  I tried.  (because there were 
several GADT constructors with slightly different signatures, so I made 
a type-synonym with an argument to try to shorten them).  It seems a 
pity to me too.


Isaac

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


Re: [Haskell-cafe] 'data' syntax - a suggestion

2007-09-27 Thread Albert Y. C. Lai

[EMAIL PROTECTED] wrote:

Data with where?
You haven't heard about GADTs?


To avoid clashing with GADT's where, I propose to rename ok's keyword 
to wherein, or wheretype, or something


data B k v = E | F b b wherein type b = B k v

data B k v = E | F b b wheretype b = B k v

(I also propose that ok should not just take an existing unrelated 
thread like Unicode string library, click reply, and herein talk 
about a new topic; but rather, should take the necessary extra effort to 
start a new thread altogether.)

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


Re: [Haskell-cafe] 'data' syntax - a suggestion

2007-09-27 Thread David Menendez
On 9/27/07, Albert Y. C. Lai [EMAIL PROTECTED] wrote:

 [EMAIL PROTECTED] wrote:
  Data with where?
  You haven't heard about GADTs?

 To avoid clashing with GADT's where, I propose to rename ok's keyword
 to wherein, or wheretype, or something

 data B k v = E | F b b wherein type b = B k v

 data B k v = E | F b b wheretype b = B k v


I'm not sure there is a clash.

data B k v where ...

is easily distinguished from

data B k v = ... where ...

-- 
Dave Menendez [EMAIL PROTECTED]
http://www.eyrie.org/~zednenem/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] 'data' syntax - a suggestion

2007-09-27 Thread Dan Weston

Thomas Conway wrote:

Although Richard's proposal was simpler, I reckon it's worth
discussing whether the where clause should allow normal
type/data/newtype declarations, effectively introducing a new scope.
There are obviously some type variable quantification and name
resolution issues that should yield several conference papers.

data RelaxedTree key val
= Leaf Bal [(key,val)]
| Node Bal [(key,RelaxedTree key val)]
where
data Bal = Balanced | Unbalanced


Is Bal visible outside data RelaxedTree? If so, why not put it at the 
top level. If not, are Balanced and Unbalanced visible? If not, then 
there is no way to construct a RelaxedTree. If so, then you could not 
give a type annotation to x = Balanced.


 data Tree key val
 = Leaf key val
 | Node BST key val BST
 where
 type BST = Tree key val

The type synonym example is much easier because it is effectively 
syntactic sugar, and although BST is not visible, Tree key val is. But 
is let allowed as well, if we want to restrict the visibility of BST to 
just the Node constructor? Type synomym of a type variable OK?


data Tree key val
= let BST = key in Leaf BST val  -- perversely called BST
| let BST = Tree key val in Node BST key val BST


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


Re: [Haskell-cafe] 'data' syntax - a suggestion

2007-09-27 Thread Thomas Conway
On 9/28/07, David Menendez [EMAIL PROTECTED] wrote:
 I'm not sure there is a clash.

 data B k v where ...

 is easily distinguished from

 data B k v = ... where ...

Indeed.

Although Richard's proposal was simpler, I reckon it's worth
discussing whether the where clause should allow normal
type/data/newtype declarations, effectively introducing a new scope.
There are obviously some type variable quantification and name
resolution issues that should yield several conference papers.

Here are a couple of examples:


data Tree key val
= Leaf key val
| Node BST key val BST
where
type BST = Tree key val


data RelaxedTree key val
= Leaf Bal [(key,val)]
| Node Bal [(key,RelaxedTree key val)]
where
data Bal = Balanced | Unbalanced

-- 
Thomas Conway
[EMAIL PROTECTED]

Silence is the perfectest herald of joy:
I were but little happy, if I could say how much.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] 'data' syntax - a suggestion

2007-09-27 Thread ok

On 28 Sep 2007, at 10:01 am, Thomas Conway wrote:

data Tree key val
= Leaf key val
| Node BST key val BST
where
type BST = Tree key val


data RelaxedTree key val
= Leaf Bal [(key,val)]
| Node Bal [(key,RelaxedTree key val)]
where
data Bal = Balanced | Unbalanced



My proposal was deliberately rather limited.
My feeling was that if there is a constructor
(like Balanced, Unbalanced)
then I want it to belong to a module-scope type name.

What I'm looking for is something that provides
(1) an easily understood way of abbreviating repeated types in a
data, type, or newtype declaration
(2) and using them *uniformly* throughout such a declaration
(which is why GADTs don't help)
(3) to reduce the incidence of errors
(4) and clarify the programmer's intent in much the same way as
field names do (but as a complementary,  not a rival technique)
(5) and above all, to simplify maintenance.

The thing that got me thinking about this is my continuing attempt
to write a compiler (to C) for a legacy language in Haskell.
I start out with a simple AST data type, adequate for testing
the grammar.  And then I start adding semantic information to the
nodes, and suddenly I find myself adding extra fields all over the
place.

Now there's a paper that was mentioned about a month ago in this
mailing list which basically dealt with that by splitting each type
into two:  roughly speaking a bit that expresses the recursion and
a bit that expresses the choice structure.  My feeling about that
was that while it is a much more powerful and general technique, it
isn't as easy to get your head around as a single level solution.

Here's a trivial example.

Parser-only version:

newtype Var
=   Var String

data Expr
   = Variable Var
   | Constant Int
   | Unary String Expr
   | Binary String Expr

Revised version:

data Var env
   = Var env String

data Expr env
   = Variable (Var env)
   | Constant Int
   | Unary String (Expr env)
   | Binary String (Expr env) (Expr env)

Now let's do Expr using my proposal:

data Expr
   = Variable var
   | Constant Int
   | Unary String expr
   | Binary String expr expr
   where type var = Var
 type expr = Expr

(obtained from the first parser-only version by lower-casing the type  
names)

becoming

*   data Expr env
   = Variable var
   | Constant Int
   | Unary String expr
   | Binary String expr expr
*  where type var = Var env
*type expr = Expr env

To my mind it's clearer to see 'expr' repeated than '(Expr env)'  
repeated,

as you don't have to keep checking that the argument is the same.

I'm not wedded to this scheme.  It's the simplest thing I can think of
that will do the job.  But the Haskell spirit is, if I may say so,
seems to be to look for the simplest thing that can do the job at hand
and a whole lot more in a principled way.

What I'm looking for in a better counter-proposal is something that
makes it this easy or easier to revise and extend a type.  Perhaps
a variation on GADTs would be the way to go.  I don't know.


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