RE: help from the community?

2007-01-30 Thread Simon Peyton-Jones
|  I can also imagine predicates that do not mention locally-quantified
|  variables - the assumption must be that they mention variables bound on
|  the LHS of the datatype decl instead?  e.g. the Show predicate here:
| 
|  data Foo a b = Foo a b
|   | Bar (forall c . (Show b, Relation b c) = (b,c))
| 
|  Hmm, maybe a simpler version of this example would illustrate what you
|  mean by the proposal (first of the three bullets) to allow an empty
|  quantifier list:
| 
|  data Foo a b = Foo a b
|   | Bar (forall . Show b = b)
| 
|  In which case, does this even count as a polymorphic component at all?
|  Is it not rather GADT-like instead?
| 
|  data Foo a b where
|Foo :: a - b - Foo a b
|Bar :: Show b = b - Foo a b
|
| I was thinking that we should allow those special cases because I
| could not see a reason to disallow them (rather then having a
| compelling example to use them).   You make a good point though, that
| some of them might indicate an error in the program.  So, I guess, the
| main decision is: do we want to make them illegal (i.e., require an
| error) or suggest that implementations report a warning?  I have no
| strong feelings either way, but I guess we need to pick something.

I think I know what we should do on this particular point.  I've even 
documented it here:
http://www.haskell.org/ghc/dist/current/docs/users_guide/data-type-extensions.html#gadt-style

I would like to urge this design, or one close to it, for Haskell'.  Note that 
this is *not* the same as adopting GADTs.

Simon
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: help from the community?

2007-01-30 Thread Benjamin Franksen
Andres Loeh wrote:
 I cannot see how an empty list of tyvars is useful or desirable in
 practice:
 data Foo = Foo (forall . Int)
 is equivalent to just
 data Foo = Foo Int
 so why bother to permit the former?  It probably indicates some error in
 the thinking of the programmer, so the compiler should bring it to her
 attention.
 
 The only reasons that I could see in favor of allowing empty foralls
 is that it might be easier to automatically generate code. Haskell
 seems to be a bit inconsistent in how it treats empty constructs. For
 example, empty let and empty where seems to be allowed, but not an
 empty case?

Just a little remark on the side: 'If' and 'case' demand exactly one
expression. In such cases allowing zero expressions is not a generalization
but an unnecessary complication. 'Let' and 'where' allow any number of
bindings, so allowing zero bindings (instead of demanding at least one) is
a simplification.

Upshot: everywhere the syntax allows a 'list' of things, one should consider
allowing the empty list, too.

Cheers
Ben

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


Re: help from the community?

2007-01-30 Thread Andres Loeh
  The only reasons that I could see in favor of allowing empty foralls
  is that it might be easier to automatically generate code. Haskell
  seems to be a bit inconsistent in how it treats empty constructs. For
  example, empty let and empty where seems to be allowed, but not an
  empty case?
 
 Just a little remark on the side: 'If' and 'case' demand exactly one
 expression. In such cases allowing zero expressions is not a generalization
 but an unnecessary complication. 'Let' and 'where' allow any number of
 bindings, so allowing zero bindings (instead of demanding at least one) is
 a simplification.

I meant the branches of a case (the report specifies at least 1). Similarly,
the report specifies that lambdas must have at least one argument, infix
declarations must not be empty and datatype declarations must not be empty
(the latter will definitely be fixed).

Cheers,
  Andres
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: [Haskell] Views in Haskell

2007-01-30 Thread Mark Tullsen

On Jan 26, 2007, at 6:22 PM, Claus Reinke wrote:
  2) There are other reasons why I want to use Haskell-98 and  
would  like to be able to use other compilers.  Thus, I'd want a  
pattern-binder preprocessor (extending GHC is not as important to  
me).


I see. though I'd hope that as long as we keep our extensions  
simple and

general enough, the other implementations will pick them up anyway.

Here's my motivating example.  Here's a fragment for an STG   
interpreter in Haskell-98:

{{{
  rule_CASE_ELIM (Case p alts, s, h, o) =
  do
  ConApp c as - ptsTo p h
  let matchAlt (Alt c' vs e) | c == c' = Just (vs,e)
  matchAlt _   = Nothing
  (vs,e) - matchFirst matchAlt alts
  return (e `sub` (vs,as), s, h, o)
}}}


yes, abstract machines have inspired many a pattern match extension!-)

are we in Maybe, or in anything more complex?


Yep, just Maybe.

view patterns don't seem to apply, but pattern guards do, and  
lambda-match helps with the local function pattern (ignoring the  
Match type tag for the moment; given the revival of interest in  
pattern functions, eg., in view patterns, I ought to try and see  
whether I can get rid of the type tag in my library for the special  
case of Maybe):


{{{
rule_CASE_ELIM =
   (| (Case p alts, s, h, o)| ConApp c as - ptsTo p h
   , (vs,e) - matchFirst (| (Alt c' vs e) | c == c' -(vs,e) )  
alts

   - (e `sub` (vs,as), s, h, o) )
}}}

which isn't quite as abstract as the pattern binder/combinator  
version,

but at least I can see the scoping,


Thanks for showing how it looks with lambda-match, I see that lambda- 
matches use

more than patterns, they use guards too.


which I am at a loss with in the pattern
binder version:

I'd like it to have a textual form just a little more abstract, I  
can  do that with pattern binders and some appropriate combinators:

{{{
  rule_CASE_ELIM =
  { (Case p alts, s, h, o) }
   ptsTo p h === { ConApp c as  }
   alts === matchFirst { Alt #c vs e }
  .-
(e `sub` (vs,as), s, h, o)
}}}
I'll leave it as an exercise to figure out how the last is   
parenthesized ;-).


ok, I give up. there seem to be some new combinators,


yes, but nothing fancy:

 () :: (a - Maybe b) - (b - Maybe c) - a - Maybe c
 () = (.:)   -- as in the paper

 (===) :: a - (a - Maybe b) - Maybe b
 (===) a p = p a

and the pattern binder variables are no longer distinguishable (via  
$).


In this example I'm dropping the $: it's less clear what's going on  
but it looks cleaner,

more like Haskell patterns.

but unless you've changed the translation as well, the only way the  
scopes are going to come out right is if the layout is a lie, right?


The layout /is/ a lie :-( but the scope rule is pretty simple: in  
this expression

  {p} `op` e
everything bound in p scopes over all e.
So, all the variables in the {p}'s above scope to the end of the RHS  
expression.


and how does the translation apply to pattern binders not in an  
infix application, in particular, how do vs/e get to

the rhs of .-?

Claus


All the pattern binders here /are/ in an infix application, here's  
the parenthesized version:

{{{
  rule_CASE_ELIM =
  { (Case p alts, s, h, o) }
   (ptsTo p h == { ConApp c as  }
   (alts === (matchFirst ({ Alt #c vs e }
   .-
   (e `sub` (vs,as), s, h, o)
}}}
(Oops, I see I'm using # where in the paper I used =.)
I also fixed a type error (nothing like ghci to fix some design  
problems), I'm now using

an additional (rather simple) combinator:

  (==) :: Maybe a - (a - Maybe b) - Maybe b
  (==) = (=)

- Mark

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


Re: help from the community?

2007-01-30 Thread Brian Hulley

Andres Loeh wrote:

The only reasons that I could see in favor of allowing empty
foralls is that it might be easier to automatically generate
code. Haskell seems to be a bit inconsistent in how it treats empty
constructs. For example, empty let and empty where seems to be
allowed, but not an empty case?


Just a little remark on the side: 'If' and 'case' demand exactly one
expression. In such cases allowing zero expressions is not a
generalization but an unnecessary complication. 'Let' and 'where'
allow any number of bindings, so allowing zero bindings (instead of
demanding at least one) is a simplification.


I meant the branches of a case (the report specifies at least 1).


I think it's important to keep some possibility for the compiler to detect 
probable errors as syntax errors. If all syntax is inhabited by strange 
defaults then this just means simple errors will go undetected eg:


   let a = case foo of

Here, the user has probably got sidetracked into editing some other part of 
the program and just forgotten to get back to fill in the cases for the case 
construct. Allowing zero cases means the user will get a strange runtime 
error instead as the function part of the case is undefined.


   let z = \y (foo y)

Here, it seems clear that the user has just forgotten to type the - which 
means a simple syntax error would get transformed into a much more puzzling 
(esp for a newbie) type error.


The difference between the above and 'let' and 'where' is that if the 
enclosing construct (eg a binding) is complete, we know that the contents of 
the 'let' are complete (since extra local bindings added afterwards would be 
irrelevant) similarly for 'where', and if the enclosing construct is not 
complete the compiler will detect this.


Therefore I think the original choices are the best since they don't seem 
inconsistent when looked at this way.


Brian.
--
http://www.metamilk.com 


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