[Haskell] View patterns in GHC: Request for feedback

2007-07-23 Thread Dan Licata
Hi everyone,

Simon PJ and I are implementing view patterns, a way of pattern matching
against abstract datatypes, in GHC.  Our design is described here:

http://hackage.haskell.org/trac/ghc/wiki/ViewPatterns

If you have any comments or suggestions about this design, we'd love to
hear them.  You can respond to this list (and we can take it to
haskell-cafe if the thread gets long) or, if you prefer, directly to me.

Thanks!
-Dan
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] View patterns in GHC: Request for feedback

2007-07-23 Thread Stefan O'Rear
On Mon, Jul 23, 2007 at 05:09:01AM -0400, Dan Licata wrote:
> Hi everyone,
> 
> Simon PJ and I are implementing view patterns, a way of pattern matching
> against abstract datatypes, in GHC.  Our design is described here:
> 
> http://hackage.haskell.org/trac/ghc/wiki/ViewPatterns
> 
> If you have any comments or suggestions about this design, we'd love to
> hear them.  You can respond to this list (and we can take it to
> haskell-cafe if the thread gets long) or, if you prefer, directly to me.

Great work!

Two comments:

1. It might be better if zenary => used Bool rather than Maybe ().  This
   would allow existing Bool functions to be used as views; eg:

   foo (isUpper =>) = ...
   foo ((< 3) =>) = ...
   foo (ioErrors => (isEOFError =>)) = ...

2. This does introduce another point of infinite lookahead into the
   grammar.  Consider (long text... - after seeing the (, we might be
   seeing a parenthetized patern (back to pat*) or a expression for a
   view guard (go to exp).  Won't affect implementations that already
   mix the two (Language.Haskell.Parser, thus probably GHC too).

Stefan


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


Re: [Haskell] View patterns in GHC: Request for feedback

2007-07-23 Thread ajb
G'day all.

On Mon, Jul 23, 2007 at 05:09:01AM -0400, Dan Licata wrote:

> Simon PJ and I are implementing view patterns, a way of pattern matching
> against abstract datatypes, in GHC.  Our design is described here:
>
> http://hackage.haskell.org/trac/ghc/wiki/ViewPatterns

I have to agree.  Great work here, though I'm extremely dubious about
the utility of the "Maybe" patterns.

One important issue.

"We should be able to give clear rules for when the avoidance
of repeat computation is guaranteed."

This, for me, is a show stopper.  I really want to see these "clear rules".

Cheers,
Andrew Bromage
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] View patterns in GHC: Request for feedback

2007-07-24 Thread Claus Reinke

though I'm extremely dubious about the utility of the "Maybe" patterns.


actually, they are the main thing that interests me about view patterns!-)

it connects them to the existing work on first-class patterns (where 
combinators over Maybe patterns do the matching work, and view

patterns provide the syntax (a) for integrating Maybe patterns into
"dumb" patterns and (b) for binding the results of Maybe patterns to
pattern variables).

but then, i'd not so much use them as pretend views, but as abstract
deconstructors/observers in the unfoldr style. instead of constructing
real intermediate types, i'd have the implicit Maybe decide the match
and the returned subexpressions available in a tuple for further 
matching or binding. eg, the first example would become:


   type Typ

   unit :: Typ -> Maybe ()
   arrow :: Type -> Maybe (Typ,Typ)
   
   size :: Typ -> Integer

   size (unit -> ()) = 1
   size (arrow -> (t1,t2)) = size t1 + size t2

closer to ordinary patterns, with the lowercase and the '->' hinting
that there is computation before matching (well, '=>', according to
the new proposal).

claus

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


Re: [Haskell] View patterns in GHC: Request for feedback

2007-07-24 Thread Manuel Hernandez

Dear Haskellers,
   why is so difficult to define a function to compute the average of a
list of
numbers??

Warm regards!!!

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


Re: [Haskell] View patterns in GHC: Request for feedback

2007-07-24 Thread Andreas Marth
I find that the suggested view pattern produce quite obfuscated code!
I guess it sets the language barrier quite a bit higher.
Do you really think a normal progrogrammer understands:
insert x s@(has x -> Just _) = s
or:
fib (np 2 -> Just n) = fib (n + 1) + fib n
or even:
fib (np 2 => n) = fib (n + 1) + fib n

Do you really know what
fun f z [] = z
fun f z (x : fun f z -> xs) =  x `f` xs
means?
I find it really hides the most important fact that fun is recursive.
(If you didn't recognize fun: it is foldr.)

I didn't see 1 convincing excample for the "need" of view pattern in that
paper and  I didn't read the other proposals.

Kind regards
Andreas



- Original Message -
From: "Dan Licata" <[EMAIL PROTECTED]>
To: 
Sent: Monday, July 23, 2007 11:09 AM
Subject: [Haskell] View patterns in GHC: Request for feedback


> Hi everyone,
>
> Simon PJ and I are implementing view patterns, a way of pattern matching
> against abstract datatypes, in GHC.  Our design is described here:
>
> http://hackage.haskell.org/trac/ghc/wiki/ViewPatterns
>
> If you have any comments or suggestions about this design, we'd love to
> hear them.  You can respond to this list (and we can take it to
> haskell-cafe if the thread gets long) or, if you prefer, directly to me.
>
> Thanks!
> -Dan
> ___
> Haskell mailing list
> Haskell@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell

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


Re: [Haskell] View patterns in GHC: Request for feedback

2007-07-25 Thread Dan Licata
Hi everyone,

Thanks for all the helpful feedback!  It's great to see what people
think.

Let me just respond to one point at the moment:

I think that the signature
 
>type Typ
> 
>unit :: Typ -> Maybe ()
>arrow :: Type -> Maybe (Typ,Typ)

is *wrong* if what you really mean is

>type Typ
>
>data TypView = Unit | Arrow Typ Typ
>view :: Typ -> TypView

That is, if what you mean is that every Typ is either Unit or an Arrow
*and nothing else* then the latter signature should be preferred, as it
makes this fact explicit in the type system.  In former signature, it's
implicit: you have to say externally that a group of destructors, taken
together, define a total view.  When programming with the former
signature, you always have an extra case to consider, in which all of
the destructors fail.

The whole point of sum types is that they tell you exactly what cases
you have to consider.  There's a big difference between the type A and
the type A+1, and you should use the type system to track this
difference (or else you end up wiht things like null pointer exceptions
in Java).

To my mind, the syntactic considerations of which way you prefer to
write your view patterns should not outweigh this important semantic
distinction.

-Dan

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


Re: [Haskell] View patterns in GHC: Request for feedback

2007-07-25 Thread Claus Reinke

I think that the signature


   type Typ

   unit :: Typ -> Maybe ()
   arrow :: Type -> Maybe (Typ,Typ)


is *wrong* if what you really mean is


   type Typ

   data TypView = Unit | Arrow Typ Typ
   view :: Typ -> TypView


different =/= wrong !-)


That is, if what you mean is that every Typ is either Unit or an Arrow
*and nothing else* then the latter signature should be preferred, as it
makes this fact explicit in the type system.  


but that is not what you're saying there at all! you're saying that -within
view 'view' of Typ- Typ is mapped to either Unit or Arrow, if the mapping
is successfull. there can be other views of Typ, and the types do not 
guarantee that 'view' itself is exhaustive over Typ (there can be variants

of Typ that 'view' fails to map to TypView).

in the abstract deconstructor variant, this partiality is explicit in the types,
in the concrete view type variant, it is hidden from the types, implicit in
the implementation of 'view'.

In former signature, it's implicit: you have to say externally that a group 
of destructors, taken together, define a total view.  When programming 
with the former signature, you always have an extra case to consider, 
in which all of the destructors fail.


even with concrete view types, you still have to consider the case that
the mapping into that view type can be partial or non-exhaustive (if you
add a constructor to Typ, but forget to update 'view', the type system
will not complain, and matches over TypView will still be 'exhaustive'..).


The whole point of sum types is that they tell you exactly what cases
you have to consider.  There's a big difference between the type A and
the type A+1, and you should use the type system to track this
difference (or else you end up wiht things like null pointer exceptions
in Java).


one should also be careful not to expect more from a type than it
can deliver, and not to use A when dealing with A+1.

btw, it might be useful to permit association of abstract types 
with abstract deconstructors, so that an extended abstract type

(export) declaration somewhat like

   type Typ as unit -> () | arrow -> (Typ,Typ)

tells us (and the compiler) that the abstract patterns in the size 
function are exhaustive (or at least as exhaustive as clients of 
the abstract type Typ are supposed to be). the proof obligation

would be on the exporter of the abstract type, and any pattern
match failures relating to this should be reported as view failures.

doing so would declare a virtual view type, similar to the concrete 
view types used in other examples, so there might be several 'as'

clauses for a single abstract type, declaring separate sets of
exhaustive abstract deconstructors.

claus

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


Re: [Haskell] View patterns in GHC: Request for feedback

2007-07-25 Thread ajb
G'day all.

Quoting Claus Reinke <[EMAIL PROTECTED]>:

> different =/= wrong !-)

[...]

> but that is not what you're saying there at all! you're saying that -within
> view 'view' of Typ- Typ is mapped to either Unit or Arrow, if the mapping
> is successfull. there can be other views of Typ, and the types do not
> guarantee that 'view' itself is exhaustive over Typ (there can be variants
> of Typ that 'view' fails to map to TypView).

data TypView = Unit | Arrow Typ Typ | Other

I still vote for "wrong". :-)

The problem, and we've been through this before, is that it's very
tempting to use types like Maybe because it's there, when it's better
replaced with a custom algebraic data type.

Even probably 90% of uses of Bool are better replaced with a two-element
enumerated type.  I see a lot of things like this:

data Something = Something { ... leftHanded :: Bool ... }

Where this is safer, more expressive, more future-proof and more
meaningful:

data Handedness = LeftHanded | RightHanded
data Something = Something { ... handedness :: Handedness ... }

> even with concrete view types, you still have to consider the case that
> the mapping into that view type can be partial or non-exhaustive (if you
> add a constructor to Typ, but forget to update 'view', the type system
> will not complain, and matches over TypView will still be 'exhaustive'..).

There should be a compiler warning you can turn on in the implementation
of "view" which tells you if the pattern matching is exhaustive or not.

Cheers,
Andrew Bromage
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] View patterns in GHC: Request for feedback

2007-07-25 Thread Claus Reinke

The problem, and we've been through this before, is that it's very
tempting to use types like Maybe because it's there, when it's better
replaced with a custom algebraic data type.


i'm sure we have, and others before us. i was just arguing that one
is not necessarily better than the other. i'm not using Maybe because
its there, i tend to use Monad, so my code would work on either Maybe
or your custom type, if they both implement the interface that allows me
to encode and capture failure (and i need that interface, because i want
to program with patterns and match failure in ways not hardcoded into
the language syntax). of course, you might say that we shouldn't use 
Monad just because it is there, and that we should always define our

own, more descriptive class with the same semantics?-)

having descriptively named types is fine, but unless you really want
to emphasize and verify that your Maybe is different from all other 
Maybes (in which case a newtype + deriving might be more suitable

than a completely separate type), using Maybe encodes (by convention)
the intended semantics, thus making code easier to comprehend. the
question, i guess, is whether you want to communicate to readers of
your code that your type is like Maybe, but distinguishable, or that it
is an entirely new type, with some similarities to Maybe.

specific names have to be offset against reuse of general understanding,
but language features for combining both exist (if not as widely supported
as they could be; nor as expressive as one might want, eg. one can
rename constructors for expressions, but not deconstructors for patterns, 
which is why Connor keeps asking for pattern synonyms, or why i'd like 
to use view patterns for abstract deconstructors, with those funny Maybes

behind the scenes..).

claus

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


Re: [Haskell] View patterns in GHC: Request for feedback

2007-07-26 Thread Barney Hilken

I think you should add the form:

(function -> pattern) @ pattern

as well. The reason you don't need general 'pattern @ pattern' with  
normal patterns is that, if anything is going to match, the two  
patterns must have the same outermost constructor, so you can push  
the @ inside. This doesn't hold for view patterns, and you might well  
want to match against several views.


Of course you can do this with 'both', but the readability is  
terrible, especially if you want to match against more than two  
patterns. Nested 'both' gets extremely long, or do you want to define  
'allThree', 'allFour', ...


The reason I think this might be important is that you could use view  
patterns for records:


(label1 -> x)@(label2 -> y)@(label3 -> z) ...

gives a reasonable syntax for a record pattern, and it would be  
compatible with any form of extensible records.


Barney.

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