Re: ADT views Re: [Haskell] Views in Haskell

2007-02-01 Thread David Roundy
On Thu, Feb 01, 2007 at 09:12:02AM -0800, David Roundy wrote:
> On Wed, Jan 31, 2007 at 09:28:30PM +0300, Bulat Ziganshin wrote:
> > Next, i don't think that ability to use any functions in view buy
> > something important. pattern guards can be used for arbitrary
> > functions, or such function can be used in view definition. view,
> > imho, is not a function - it's a two-way conversion between abstract
> > and real data representation which has one or more alternative
> > variants - just like Algebraic Data Types. so, when defining a view, i
> > want to have ability to define exactly all variants alternative to
> > each other. for another representation, another view should be
> > created. so
> 
> But you *are* using functions in views, that's what they are.  And the
> two-way conversion, while pretty, is likely to be a fiction.  It'll be too
> easy (and useful) for someone to define
> 
> view RegexpMatch String of String where
> string | matchesRegexp regexp string = RegexpMatch regexp
> RegexpMatch regexp = undefined

Never mind.  I see that this won't work, and it's not so easy to usefully
get around your restrictions.  But I must admit that this power was one of
the nicest things in Simon's proposal.  You'd still be in danger of me
subverting your proposal with something like

view Odd of Int where
 i | isOdd i = Odd
 Odd = undefined

but I'll admit that this isn't particularly powerful.  It's allowing
arguments to the match (e.g. the regexp I was trying to sneak through) that
gives Simon's views their power.  It's also what forces the syntactic
complexity of the -> in the matches, since you need a way to distinguish
the arguments from the patterns in something like

f (foomatch "x" "y" "z")
-- 
David Roundy
Department of Physics
Oregon State University
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: ADT views Re: [Haskell] Views in Haskell

2007-02-01 Thread David Roundy
On Wed, Jan 31, 2007 at 09:28:30PM +0300, Bulat Ziganshin wrote:
> Wednesday, January 31, 2007, 7:12:05 PM, you wrote:
> >> data Coord = Coord Float Float
> >> view of Coord = Polar Float Float where
> >>   Polar r d=   Coord (r*d) (r+d)-- construction
> >>   Coord x y   | x/=0 || y/=0   =   Polar (x*y) (x+y)-- matching
> 
> > This is somewhat pretty, but in spite of your desire to avoid creating new
> > syntax, you have just done so, and in the process made views more limited.
> > Pattern matching sytax remains the same, but a new declaration syntax has
> > been added.  And now in order to pattern match on a function it needs to
> > explicitely be declared as a "view".
> 
> yes. among the possible uses for views i clearly prefers the following:
> definition of abstract data views that may differ from actual type
> representation. moreover, i think that this facility should be
> syntactically indistinguishable from ordinary data constructor patterns
> in order to simplify learning and using of language. *defining* view is a
> rare operation, using it - very common so my first point is that views
> should be used in just the same way as ordinary constructors, both on
> left and right side:
>
> f (Polar r a) = Polar (r*2) a

I guess your assumption that views will rarely be defined is rather in
conflict with the proposal of Simon, which was to create considerably more
powerful views, I presume.

> Next, i don't think that ability to use any functions in view buy
> something important. pattern guards can be used for arbitrary
> functions, or such function can be used in view definition. view,
> imho, is not a function - it's a two-way conversion between abstract
> and real data representation which has one or more alternative
> variants - just like Algebraic Data Types. so, when defining a view, i
> want to have ability to define exactly all variants alternative to
> each other. for another representation, another view should be
> created. so

But you *are* using functions in views, that's what they are.  And the
two-way conversion, while pretty, is likely to be a fiction.  It'll be too
easy (and useful) for someone to define

view RegexpMatch String of String where
string | matchesRegexp regexp string = RegexpMatch regexp
RegexpMatch regexp = undefined

f (RegexpMatch "foo.+bar") = "It has foo bar in it"
f s@(RegexpMatch "baz.+bar") = s ++ " has baz bar in it"

You can pretend that noone will do this, but it's a nice syntax for pattern
guards, which allows us to stick the guard right next to the data being
guarded, which is often handy.

So I guess you can see this as a promise to subvert your two-way conversion
views immediately after they're created.  It's worth considering whether
one should try to make the syntax friendlier to such uses.  One option
which is sort of in between would be something like:

view regexpMatch String of String where
string | matchesRegexp regexp string = regexpMatch regexp

f (regexpMatch "foo.+bar") = "It has foo bar in it"
f s@(regexpMatch "baz.+bar") = s ++ " has baz bar in it"

where the lowercaseness of "regexpMatch" indicates that this is a one-way
matching function.  I believe this would work just fine, and then we'd have
a bit of new syntax for "function-like" views, and your constructor-like
syntax for "constructor-like" views.  And noone would be tempted to subvert
your constructor-like views.  And good programmers would have a policy that
constructor-like views would really be invertible, for some definition of
invertible, analogous to the monad laws, which aren't enforced, but
reasonable programmers obey.

> view Polar Float Float of Coord where
>   constructor (Polar r a) means (Coord (r*sin a) (r*cos a))
>   match pattern (Polar (sqrt(x*x+y*y)) (atan(y/x))) for (Coord x y) where x/=0
> (Polar y (pi/2))for (Coord x y) where y>0
> (Polar (-y) (-pi/2))for (Coord x y) where y<0
> 
> of course, my syntax is cumbersome. that is important is that view
> definition should be explicit (no arbitrary functions), it should
> mention all possible alternatives and provide a way to use the same
> constructor name both for construction of new values and matching
> existing ones. this all together should allow to transparently use ADT
> views instead of plain ADTs

I definitely agree that being able to transparently switch a library
between views and exported constructors would be handy, but don't think
it's necesary, provided the view syntax is sufficiently elegant (which I'm
not convinced Simon's proposed syntax is).  If views have a distinct--but
pretty--syntax, people can just move to always using views, and that's
that.

> > And unless you are planning to allow one-way views (you don't give any
> > examples of that), "view functions" must be invertible, which greatly
> > weakens their power.  If you choose to allow one-way views (non-invertible
> > functions), then I'd v

A view of views -- something classy? Re: [Haskell] Views in Haskell

2007-02-01 Thread Jón Fairbairn

Bulat Ziganshin
<[EMAIL PROTECTED]>
writes:
> > Yes - you've reiterated Wadler's original design, with
> > an automatic problems with equational reasoning raised
> > by this approach.
> 
> ok, i can live without it. i mean reasoning :)

That's probably not good, but I don't follow that problem
yet.  I'm afraid I've not had the stamina to follow this
thread properly, and I doubt if I'll get any more stamina
soon, so let me make a proposal not too disimilar to Bulat's
and just hope that people find it appealing enough to flesh
it out.

The idea I'm presenting is simple enough: allow data
constructors as members of classes.  (Sure, David, this does
have the problem of hiding potentially expensive operations
as straightforward pattern matches, but that's abstraction
for you). So

class Sequence s where
   (some other stuff)
   Cons:: a -> s a -> s a
   Nil:: s a

Here Cons and Nil both stand for two things: a constructor
and a deconstructor. The question is how to specify the
values of the two parts when giving an instance. The easiest
way is just to give it in terms of something that already
has the two aspects:

instance Sequence [] where
...
Cons = (::)
Nil = []

And so a definition like

f Nil = ...
f (Cons a l) = ...

gets a type like Sequence s => s a -> ...

But we also want it to work for cases where the type we are
viewing doesn't already have a constructor that does what we
want, such as giving a list instance for another member of
Sequence:

class Sequence s where
   Snoc:: s a -> a -> s a
   (some other stuff)

The idea here would be to announce that all data
constructors really do have two parts and they are accessed
via qualified names. So the Snoc part of the list instance
would look like this:

   ...
   Snoc.construct l x = l ++ [x]
   Snoc.deconstruct f g [] = g
   Snoc.deconstruct f g l = f (init l) (last l)

(We can of course argue about the precise type used for
deconstructors and there is endless bikeshed painting to be
done for the names construct and deconstruct, but I hope
this gives the general idea).


I think this proposal is simpler than the earlier ones
presented -- enough that someone in better shape than me
could work out the details and implement it. There's no
exciting new syntax, just an extension of some current
syntax to a new area, and functions declared using a "view"
are automatically overloaded for everything that shares the
view.  As far as equational reasoning goes, I think the
approach would be to specify what laws Foo.construct and
Foo.deconstruct have to follow to preserve it, and leave
them up to the programmer to respect (in the same way that
the monad laws aren't tested by the compiler).

-- 
Jón Fairbairn [EMAIL PROTECTED]


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


Re[4]: ADT views Re: [Haskell] Views in Haskell

2007-02-01 Thread Bulat Ziganshin
Hello J.,

Thursday, February 1, 2007, 1:36:33 AM, you wrote:

> Yes - you've reiterated Wadler's original design, with an automatic

> problems with equational reasoning raised by this approach.

ok, i can live without it. i mean reasoning :)

i guess that anything more complex than Turing machine makes reasoning
harder. 18 years ago Haskell fathers chosen to simpilfy language in
order to make reasoning easier. may be now we can change this
decision? that i've proposed is made on basis of my 15 years of
software development experience and i'm sure that abstraction of data
representation is very important issue (and much more important than
reasoning for practical programming)

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: Re[2]: ADT views Re: [Haskell] Views in Haskell

2007-01-31 Thread J. Garrett Morris

On 1/31/07, Bulat Ziganshin <[EMAIL PROTECTED]> wrote:


i hope that now my idea is clear


Yes - you've reiterated Wadler's original design, with an automatic
creation of a type class.  Erwig and Peyton-Jones, _Pattern Guards and
Transformational Patterns_
(http://research.microsoft.com/~simonpj/Papers/pat.htm) mentions
problems with equational reasoning raised by this approach.

/g

--
It is myself I have never met, whose face is pasted on the underside of my mind.
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re[2]: ADT views Re: [Haskell] Views in Haskell

2007-01-31 Thread Bulat Ziganshin
Hello David,

Wednesday, January 31, 2007, 7:12:05 PM, you wrote:

>> data Coord = Coord Float Float
>> view of Coord = Polar Float Float where
>>   Polar r d=   Coord (r*d) (r+d)-- construction
>>   Coord x y   | x/=0 || y/=0   =   Polar (x*y) (x+y)-- matching

> This is somewhat pretty, but in spite of your desire to avoid creating new
> syntax, you have just done so, and in the process made views more limited.
> Pattern matching sytax remains the same, but a new declaration syntax has
> been added.  And now in order to pattern match on a function it needs to
> explicitely be declared as a "view".

yes. among the possible uses for views i clearly prefers the
following: definition of abstract data views that may differ from
actual type representation. moreover, i think that this facility
should be syntactically indistinguishable from ordinary data
constructor patterns in order to simplify learning and using of
language. *defining* view is a rare operation, using it - very common

so my first point is that views should be used in just the same way as
ordinary constructors, both on left and right side:

f (Polar r a) = Polar (r*2) a

Next, i don't think that ability to use any functions in view buy
something important. pattern guards can be used for arbitrary
functions, or such function can be used in view definition. view,
imho, is not a function - it's a two-way conversion between abstract
and real data representation which has one or more alternative
variants - just like Algebraic Data Types. so, when defining a view, i
want to have ability to define exactly all variants alternative to
each other. for another representation, another view should be
created. so

view Polar Float Float of Coord where
  constructor (Polar r a) means (Coord (r*sin a) (r*cos a))
  match pattern (Polar (sqrt(x*x+y*y)) (atan(y/x))) for (Coord x y) where x/=0
(Polar y (pi/2))for (Coord x y) where y>0
(Polar (-y) (-pi/2))for (Coord x y) where y<0

of course, my syntax is cumbersome. that is important is that view
definition should be explicit (no arbitrary functions), it should
mention all possible alternatives and provide a way to use the same
constructor name both for construction of new values and matching
existing ones. this all together should allow to transparently use ADT
views instead of plain ADTs

> And unless you are planning to allow one-way views (you don't give any
> examples of that), "view functions" must be invertible, which greatly
> weakens their power.  If you choose to allow one-way views (non-invertible
> functions), then I'd vote for not allowing two-way views, as it adds
> complexity without adding any appreciable gain.

> I don't like your use of capital letters for ordinary functions, I enjoy
> having the syntax tell me whether (Foo 1) might or might not be an
> expensive operation.

the whole idea of abstraction is to not give users any knowledge aside
from algorithmic specifications. when you write (x+y) you don't know
whether this (+) will end in ADD instruction or sending expedition to
Mars :)  why you need low-level control over data matchers exported by
library but not over its functions?

> Finally, you've replaced Simon's explicit incomplete function using Maybe
> with an implicit incomplete function that returns _|_ when the view doesn't
> match.

it's an independent idea that can be used for Simon's syntax or don't
used at all. really, we need Prolog-like backtracking mechanism, i.e.
way to say "this pattern don't match input value, please try the next
alternative". Simon emulated backtracking with Maybe, one can does the
same with return/fail, i figured out one more way - just allow
recursive use of function guards. Here, if all alternatives for Polar
pattern fails, then the whole Polar pattern don't match and we should
try the next alternative. so, the following:

f (Polar r a) = Polar (r*2) a
f (Coord 0 0) = Coord 0 0

should be translated into:

f (Coord x y) | x/=0 = Coord (r*2*sin a) (r*2*cos a)
 where r = sqrt(x*x+y*y)
   a = atan(y/x)
f (Coord x y) | y>0  = Coord (r*2*sin a) (r*2*cos a)
 where r = y
   a = pi/2
f (Coord x y) | y<0  = Coord (r*2*sin a) (r*2*cos a)
 where r = -y
   a = -pi/2
f (Coord 0 0) = Coord 0 0

> I find this rather unappealing.  I certainly prefer *intentionally*
> incomplete functions to return Maybe somthing, rather than just bombing out
> when given invalid input.  I suppose you'll point out that the view Coord
> is a function that you can never explicitely call, but to me that just
> makes things even more confusing.  Now we're defining functions that we can
> only use in pattern matching, but can never call.

i hope that now my idea is clear


-- 
Best regards,
 Bulatmailto:[EMAIL PROTE

Re: ADT views Re: [Haskell] Views in Haskell

2007-01-31 Thread David Roundy
On Wed, Jan 31, 2007 at 05:53:08PM +0300, Bulat Ziganshin wrote:
> something like this:
> 
> data Coord = Coord Float Float
> view of Coord = Polar Float Float where
>   Polar r d=   Coord (r*d) (r+d)-- construction
>   Coord x y   | x/=0 || y/=0   =   Polar (x*y) (x+y)-- matching

This is somewhat pretty, but in spite of your desire to avoid creating new
syntax, you have just done so, and in the process made views more limited.
Pattern matching sytax remains the same, but a new declaration syntax has
been added.  And now in order to pattern match on a function it needs to
explicitely be declared as a "view".

And unless you are planning to allow one-way views (you don't give any
examples of that), "view functions" must be invertible, which greatly
weakens their power.  If you choose to allow one-way views (non-invertible
functions), then I'd vote for not allowing two-way views, as it adds
complexity without adding any appreciable gain.

I don't like your use of capital letters for ordinary functions, I enjoy
having the syntax tell me whether (Foo 1) might or might not be an
expensive operation.

Finally, you've replaced Simon's explicit incomplete function using Maybe
with an implicit incomplete function that returns _|_ when the view doesn't
match.  I find this rather unappealing.  I certainly prefer *intentionally*
incomplete functions to return Maybe somthing, rather than just bombing out
when given invalid input.  I suppose you'll point out that the view Coord
is a function that you can never explicitely call, but to me that just
makes things even more confusing.  Now we're defining functions that we can
only use in pattern matching, but can never call.
-- 
David Roundy
http://www.darcs.net
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


ADT views Re: [Haskell] Views in Haskell

2007-01-31 Thread Bulat Ziganshin
Hello Simon,

Monday, January 22, 2007, 5:57:27 PM, you wrote:

> adding "view patterns" to Haskell.

many of us was attracted to Haskell because it has clear and simple
syntax. but many Hugs/GHC extensions done by independent developers
differ in the syntax they used, because these developers either has
their own taste or just don't bother with syntax issues. you may
remember my examples of how the guards syntax may be reused for GADTs
and class declarations:

data T a =  C1 a | Show a
 || C2 a | Read a
instance Binary a | Storable a where ...

but unfortunately we've finished with 3 different syntax for the same
things

i'm sorry for so big introduction but this shows why i don't like the
*syntax* you've proposed. you wrote "The key feature of this proposal
is its modesty, rather than its ambition..." that means that this
proposal is great for you as implementor - you should write a minimal
amount of code to add this to GHC. but let's look at this from viewpoint
of one who learn and then use Haskell: first, he should learn two
syntax to do matching instead of one. second, he should learn how to
implement them both. third, he need to make decision of whether to
provide abstract interface to his datatypes or not. if he make a bad
decision, he will end either in rewriting lot of code (and change is
not s///-style !) or having a lots of trivial definitions like

data List a = Nil | Cons a (List a)
nil Nil = Just Nil
nil _   = Nothing
cons (Cons a b) = Just (a,b)
cons _  = Nothing

then IDEs will automate this code generation and "refactoring" of
code, etc, etc :)

>On the other hand, view patterns can do arbitrary computation,
>perhaps expensive. So it's good to have a syntactically-distinct
>notation that reminds the programmer that some computation beyond
>ordinary pattern matching may be going on.

*you* said :)  are you don't know that explicit control of generated
code is "advantage" of low-level languages? we use higher-level
languages exactly to avoid dealing with implementation details. as far
as we can describe algorithm in some form understandable by computer,
we are done. lazy evaluation, classes and even plain functions are the
tools to describe algorithm without having any guarantees about its
efficiency

so, i propose to define views in a way that
1) preserves syntax compatibility with existing patterns
2) allow to define "class of views" to provide common interface to all
sequences, for example
3) old-good guards may be used instead of Nothing to provide
"backtacking" (are you don't think that we already have full Prolog
power between "|" and "="? :)


something like this:

data Coord = Coord Float Float
view of Coord = Polar Float Float where
  Polar r d=   Coord (r*d) (r+d)-- construction
  Coord x y   | x/=0 || y/=0   =   Polar (x*y) (x+y)-- matching

f :: Coord -> Float
f (Polar r _) = r
f (Coord 0 0) = error "..."


class ListLike c e where
  head :: c -> e
  tail :: c -> c
class view of ListLike where
  Cons :: e -> e -> c
  Nil  :: c

instance ListLike [a] a where
  head (x:xs) = x
  tail (x:xs) = xs
instance view ListLike [a] a where
  Cons x xs = x:xs -- for constructing new values using Cons
  (x:xs)= Cons x xs-- used to match Cons in patterns
  Nil   = xs
  xs  | null xs = Nil
  
i know that this is longer way (and probably will be never
implemented) but the language should remain orthogonal. otherwise it
will dead in terrible tortures :)


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re[2]: [Haskell] Views in Haskell

2007-01-31 Thread Bulat Ziganshin
Hello Rene,

Wednesday, January 24, 2007, 10:49:06 PM, you wrote:

> Going by the traffic over the previous months, I think that class aliases or
> extensible records would be higher on most peoples lists than views.

i think that proper views is a must for Haskell - "We are keen on
abstraction, but pattern matching is so convenient that we break
abstractions all the time. It's our dirty little secret. "

we need views in order to stop dealing with concrete datatypes and
start writing polymorphic functions. just imagine that the following
definition

sum [x]= x
sum (x:xs) = x + sum xs

may deal with *anything*, from strict list to patricia tree. isn't that
great?


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

___
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: [Haskell] Views in Haskell

2007-01-29 Thread Claus Reinke

   mapA f (nilAP -> ()) = nilA
   mapA f (consAP -> (h,t)) = consA (f h) (mapA f t)

   foldA  f n (nilAP -> ())= n
   foldA  f n (consAP -> (h,t)) = f h (foldA f n t)


yes, maps and folds are likely to be parts of the ADT interface, rather than
defined on top of it. I just used them as simple and familiar examples, so
that we have something to compare them with. 

To me this exactly illustrates why view patterns are a bad idea: 


whether or not an ADT interface is well designed, according to some metric, 
does not tell us whether or not the language features used in the code are 
good or not. hiding the internal representation always raises questions of
whether the exposed interface is still expressive enough or allows efficient 
code to be written, even without view patterns. 

in other words, ADTs do not only conflict with the ease of pattern matching, 
but also with other possible advantages of using the internal representation 
directly. view patterns help to address the convenience/readability issue, but

the other issues remain to be addressed by careful interface design.

in this particular case, I believe that separate compilation is the main 
concern standing in the way of optimizing the abstract view away.


Claus

you've taken some concrete type, abstracted it to replace the actual structure 
by a list structure, then defined map and fold over the list structure. This 
means that map and fold can't take advantage of the actual concrete 
structure and are therefore condemned to use the inefficient linear 
structure imposed by the list abstraction.


For example implementing map over a tree directly, gives the possibility of 
parallel execution since different subtrees can be mapped independently. But 
when you view the tree abstractly as a list, no such parallel execution can 
take place. Therefore surely it is better that map and fold are defined for 
each ADT separately, with the separate definitions hidden behind a type 
class, than to attempt to define them "outside" the definition of the ADT 
using view patterns?


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

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


Re: [Haskell] Views in Haskell

2007-01-29 Thread Brian Hulley

Claus Reinke wrote:


   mapA f (nilAP -> ()) = nilA
   mapA f (consAP -> (h,t)) = consA (f h) (mapA f t)

   foldA  f n (nilAP -> ())= n
   foldA  f n (consAP -> (h,t)) = f h (foldA f n t)


To me this exactly illustrates why view patterns are a bad idea: you've 
taken some concrete type, abstracted it to replace the actual structure by a 
list structure, then defined map and fold over the list structure. This 
means that map and fold can't take advantage of the actual concrete 
structure and are therefore condemned to use the inefficient linear 
structure imposed by the list abstraction.


For example implementing map over a tree directly, gives the possibility of 
parallel execution since different subtrees can be mapped independently. But 
when you view the tree abstractly as a list, no such parallel execution can 
take place. Therefore surely it is better that map and fold are defined for 
each ADT separately, with the separate definitions hidden behind a type 
class, than to attempt to define them "outside" the definition of the ADT 
using view patterns?


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


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


Re: [Haskell] Views in Haskell

2007-01-27 Thread Claus Reinke

the alternative I'm aiming for, as exhibited in the consP example, would be
to build patterns systematically from view patterns used as abstract
de-constructors, composed in the same way as one would compose the
abstract constructors to build the abstract data structure. 


This would cause an awful lot of kludging to get around the fact you need 
to declare a new ADT to declare new abstract deconstructors, and requires 
an additional extension for abstract deconstructors to be typeclass 
methods - something abstract constructors can do for free. Neither seems 
gainful to me.


I don't understand? you can define deconstructors for concrete types as well,
as many as you like; it is just that when the representation is not hidden in an
ADT, noone hinders me from bypassing your deconstructors and go for the
concrete representation instead of the abstract representation. and how did 
additional extensions or typeclasses get into the picture??


perhaps a concrete example will help. as I used the lists-as-arrays example
for lambda-match, here it is again for view patterns (implementation not
repeated, List made abstract, untested..):

   module ListArray(List(),nilA,nullA  , nilAP
   ,consA,headA,tailA  , consAP
   ,snocA,initA,tailA  , snocAP
   ) where
   ..imports..

   -- our own array list variant
   data List a = List (Array Int a)

   -- constructors, tests, selectors; cons and snoc view
   nilA :: List a
   nullA :: List a -> Bool

   consA :: a -> List a -> List a
   headA :: List a -> a
   tailA :: List a -> List a

   snocA :: List a -> a -> List a
   lastA :: List a -> a
   initA :: List a -> List a

   -- we also define our own pattern constructors
   nilAP  = guard . nullA 
   consAP l = do { guard $ not (nullA l); return ( headA l, tailA l ) }

   snocAP l = do { guard $ not (nullA l); return ( initA l, lastA l ) }


   module Examples where
   import ListArray

   anA = consA 1 $ consA 2 $ consA 3 $ consA 4 nilA

   mapA f (nilAP -> ()) = nilA
   mapA f (consAP -> (h,t)) = consA (f h) (mapA f t)

   foldA  f n (nilAP -> ())= n
   foldA  f n (consAP -> (h,t)) = f h (foldA f n t) 


   foldA' f n (nilAP -> ())   = n
   foldA' f n (snocAP -> (i,l)) = f (foldA' f n i) l

   palindrome (nilAP -> ()) = True
   palindrome (consAP -> (_, nilAP -> () ) = True
   palindrome (consAP -> (h, snocAP -> (m,l))) = (h==l) && palindrome m

no need for typeclasses so far. we use abstract data and pattern constructors
for adts, just as we use concrete data and pattern constructors for concrete
types. we choose what view to take of our data simply by choosing what
pattern constructors we use (no need for type-based overloaded in/out).
and since our pattern constructors are simply functions, we get pattern
synonyms as well.

we could, I guess, try to package data and pattern constructors together,
either by typeclasses:

   class Cons t where cons :: t
   instance Cons (a->List a->List a) where cons = ListArray.cons
   instance Cons (List a->(a,List a)) where cons = ListArray.consP

or by declaring consP as the deconstructor corresponding to the cons
constructor, as Mark suggested:

   cons :: a -> List a -> List a
   cons# :: List a -> (a,List a)

both versions could then be used to select the pattern or data constructor,
depending on whether cons was used in a pattern or expression context.
but neither of these seems strictly necessary to get the benefit of views.

if view patterns turn out to be practical, one could then go on to redefine
the meaning of data type declarations as implicitly introducing both
data and pattern constructors, so

   f (C x (C y N) = C y (C x N)

might one day stand for

   f (cP -> (x, cP -> (y, nP))) = c y (c x n)

but it seems a bit early to discuss such far-reaching changes when we 
haven't got any experience with view patterns yet. in the mean-time, one

might want to extend the refactoring from concrete to abstract types
(HaRe has such a refactoring), so that it uses view patterns instead of 
eliminating pattern matching.


since others have raised similar concerns about needing type-classes,
I seem to be missing something. could someone please explain what?

Claus

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


Re: [Haskell] Views in Haskell

2007-01-26 Thread Claus Reinke
  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? 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, 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, and the pattern 
binder variables are no longer distinguishable (via $). 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? 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

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


RE: [Haskell] Views in Haskell

2007-01-26 Thread Simon Peyton-Jones
| > In my opinion, views are going to make more Haskell more complicated, and
| > from what I have seen so far, for little gain.
|
| We need some kind of pattern extension *now* for bytestring
| matching/views and bit parsing, though. Stuff that's used in large, real
| world Haskell programs :)

Would you care to elaborate?   After all, pattern guards get quite a lot of the 
way.

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


Re: [Haskell] Views in Haskell

2007-01-25 Thread Donald Bruce Stewart
Rene_de_Visser:
> In my opinion, views are going to make more Haskell more complicated, and 
> from what I have seen so far, for little gain.

We need some kind of pattern extension *now* for bytestring
matching/views and bit parsing, though. Stuff that's used in large, real
world Haskell programs :)

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


Re: [Haskell] Views in Haskell

2007-01-25 Thread Mark Tullsen

On Jan 25, 2007, at 6:40 AM, Claus Reinke wrote:

Strangely, for other reasons, I'm planning, within a week or so,  
to  start implementing the "pattern-binder" syntax I discussed in  
the paper (either in GHC or as a pre-processor).


I'm somewhat surprised to read this. Between view patterns, lambda- 
match,

and Control.Monad.Match, I thought we were approaching a situation in
which we have all the essential aspects covered (perhaps apart from  
the fact that your combinators come in both left-right and right- 
left variants), with slightly more convenience and better  
integration with existing pattern match facilities

Especially the pattern-binder syntax and translation strike me as more
complicated (so much so that I would rather use a simplified form  
of the translation result than all that machinery) and no more  
general than combining view patterns with pattern functions. But  
perhaps that is a

question of personal style (and my own use of type-classes to lift
mplus to pattern-functions has also been classed as complicated by
others;-).

Is there anything specific you find missing, or a those other  
reasons the

motivation with going for your own version?

Claus



Good question.  It's not that I think there is some "essential aspect"
which isn't covered: View patterns will definitely add some useful  
expressiveness,
and ditto for lambda-match and Control.Monad.Match (though I haven't  
yet had time
to fully assimilate this stuff: I didn't start following this thread  
till yesterday).


First Class Patterns are radical enough and are so far from meshing  
with the
pattern language of Haskell that I don't really consider them a  
"competing proposal".


My motivations for implementing "pattern-binder" syntax are as follows
  1) I have a special need for some significant syntactic sugar for  
which pattern binders
 perfectly fit the bill.  (For general programming I use my  
pattern combinators and

 the 'do' notation.)
  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).

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)
}}}

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 ;-).


- Mark

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


Re: [Haskell] Views in Haskell

2007-01-25 Thread Mark Tullsen

On Jan 25, 2007, at 3:49 AM, Claus Reinke wrote:
but as far as Haskell is concerned, I am perhaps less radical in my  
approach than Mark is: Haskellers have invested an awful lot of  
work in those conventional patterns, in readibility, in  
optimisations, and in linking them with other extensions (eg., type  
system extensions).


I actually would agree.  The purist in me would want to use a  
language with a simple exhaustive case construct
and pattern-binders and no more; but the pragmatist in me does,  
usually, go with the flow of the language and use some of

the more complex pattern-matching constructs.

However, I did edit the web page to include an improved description  
of First Class Patterns, for a point of

reference and comparison.

- Mark



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


Re: [Haskell] Views in Haskell

2007-01-25 Thread Claus Reinke
Strangely, for other reasons, I'm planning, within a week or so, to  
start implementing the "pattern-binder" syntax I discussed in the paper 
(either in GHC or as a pre-processor).


I'm somewhat surprised to read this. Between view patterns, lambda-match,
and Control.Monad.Match, I thought we were approaching a situation in
which we have all the essential aspects covered (perhaps apart from the 
fact that your combinators come in both left-right and right-left variants), 
with slightly more convenience and better integration with existing pattern 
match facilities 


Especially the pattern-binder syntax and translation strike me as more
complicated (so much so that I would rather use a simplified form of the 
translation result than all that machinery) and no more general than 
combining view patterns with pattern functions. But perhaps that is a

question of personal style (and my own use of type-classes to lift
mplus to pattern-functions has also been classed as complicated by
others;-).

Is there anything specific you find missing, or a those other reasons the
motivation with going for your own version?

Claus


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


Re: [Haskell] Views in Haskell

2007-01-25 Thread Claus Reinke
I'm not quite sure whether it all means you think view patterns are good; or that 
they would be good with a tweak; or that something else would be better.


probably because my opinion has been changing;-) at first, I wasn't convinced,
now I think it depends on the details. as Mark said, such syntactic extensions 
of
conventional patterns are not strictly necessary since we know how to avoid them
completely (using data parsing). so for a new functional language, I too would 
like to drop patterns as built-ins, providing their functionality via sugar and libraries.


but as far as Haskell is concerned, I am perhaps less radical in my approach 
than Mark is: Haskellers have invested an awful lot of work in those conventional 
patterns, in readibility, in optimisations, and in linking them with other extensions 
(eg., type system extensions). 

that is why I proposed the lambda-match construct to complement the library 
Control.Monad.Match, so that conventional patterns could be used within the 
data parsing framework. and that is why I think view patterns are useful: they 
allow us to embed data parsing into conventional patterns, reusing existing 
syntax for binding pattern variables while still allowing us to define our own 
pattern constructors.


so I'd like to have both lambda-match and view patterns, supported by 
Control.Monad.Match, and well integrated. but if suggestions to make Maybe 
explicit in view patterns, or to drop it alltogether, carry the day, I might lose 
interest. also, I'd like the syntax to stay close to conventional constructors, 
rather than close to pattern guards.


regarding first-class abstractions/terminology: for myself, I have settled on 
using
"first-class matches" (or "first-class match alternatives") for the likes of the
lambda-match construct (left-hand side pattern, right-hand side expression), 
and "first-class patterns" for proposals that actually allow to abstract over the 
left-hand sides of matches. both first-class matches and first-class patterns 
tend to use the common framework of MonadPlus instances for match failure 
and fall-through, as a generalisation of the good old monadic combinator 
parsers on strings. for this framework I use the term "monadic data parsing".


regarding syntax for view patterns: I like the prefix form, but agree that the 
use
of "->" is unfortunate. If it wasn't for pattern constants, I'd probably just 
use
application (lower case identifiers in function position in a pattern can only 
be
views, unless someone suggests other uses for that syntax; and the last 
parameter of a view has to be a pattern). The next best thing, to emphasize 
that we're essentially computing patterns, would be to borrow TH's notation 
for splicing, using


   $(view p1..pn) pattern

instead of

   view p1..pn -> pattern

Claus

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


RE: [Haskell] Views in Haskell

2007-01-25 Thread Simon Peyton-Jones
| is that clearer?

yes, thanks.  I'm not quite sure whether it all means you think view patterns 
are good; or that they would be good with a tweak; or that something else would 
be better.

Do feel free to edit the wiki to articulate any design alternatives that you 
think deserve consideration.

Regardless of whether any of this gets implemented, I think the wiki page can 
usefully summarise a description of at least a local part of the design space.

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


RE: [Haskell] Views in Haskell

2007-01-25 Thread Simon Peyton-Jones
| First, I'm not clear what Simon meant by "first class abstractions"
| in this comment
|
| > Several proposals suggest first class abstractions rather that
| > first-class patterns. Here are the ones I know of ...

Sorry to have been un-clear.  By a "first class abstraction" I mean a value of 
type
something -> something
with a syntax something like
\ pattern -> body

The abstraction includes both the pattern and the result.  In contrast, view 
patterns tackle only the syntax of patterns; the pattern of a first-class 
abstraction.  I'll update the wiki

A first-class *pattern*, on the other hand, really ought to be something like 
(a,b), where a and b are *binders*.  This is what Barry Jay means by a 
first-class pattern in his very interesting work (which I should reference from 
the wiki).  See "The Patten Calculus" 
http://www-staff.it.uts.edu.au/~cbj/Publications/chronological.html

Still, I think it's likely that I'm exaggerating, and that view patterns and 
first-class abstractions are tied up together somehow.  But I don't grok 
exactly how.

Simon

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


Re: [Haskell] Views in Haskell

2007-01-24 Thread Mark Tullsen

On Jan 22, 2007, at 6:57 AM, Simon Peyton-Jones wrote:
> I'm thinking of implementing it in GHC, so I'd be interested in  
feedback of the form

>- how desirable is it to have a feature of this general form?

While it looks like a useful extension with a lot of bang for the buck,
I think I'd prefer to live without it; two reasons:
 1) I'm a minimalist
 2) I find that using my pattern combinators
  (http://citeseer.ist.psu.edu/tullsen00first.html)
  and do-notation I get by very well without using any of the advanced
  features of patterns.  OK, I guess I'm a little biased.

>- can this particular proposal be improved?

I definitely agree with Claus's comment:

> 5 possible extension 1 smells of superfluous complexity. There is  
almost no gain
>compared to using tuples, but there's a lot to pay in added  
types and rules.m



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


[Haskell] Views in Haskell

2007-01-24 Thread Mark Tullsen

Sorry to enter the discussion a little late ...

First, I'm not clear what Simon meant by "first class abstractions"  
in this comment


Several proposals suggest first class abstractions rather that  
first-class patterns. Here are the ones I know of ...


Second, I completely agree with Claus in his comment here that my  
"First Class Patterns"

paper is definitely related to, and not orthogonal to view patterns:

  The "big idea" of my paper was to stop the growing complexity of  
the pattern-language
  of Haskell.  The idea was to use the abstraction capabilities of  
the language along

  with some simple syntactic sugar to give us 'pattern omnipotence'.

  However, my approach could be seen as orthogonal in that I did not  
propose
  to change Haskell patterns.  Instead, I suggested some additional  
syntax that could

  serve as a replacement for complicated uses of patterns.

Strangely, for other reasons, I'm planning, within a week or so, to  
start implementing
the "pattern-binder" syntax I discussed in the paper (either in GHC  
or as a pre-processor).


- Mark

Claus Reinke wrote:
3 what you call first class abstractions are not entirely  
orthogonal to view patterns.

taking Tullsen's and my own proposal as examples:

- the way patterns and alternatives are handled needs to fit  
together. that doesn't
seem to be a problem since your and our proposals agree on  
using what I call
a monadic data parsing framework (using a MonadPlus such as  
Maybe to handle

pattern match failure and alternatives)

- all three proposals have discussed how to handle patterns as  
well. For Tullsen,
that is central to his proposal, for me, it was only one of the  
more advanced

examples because I wanted to focus on match alternatives first.

Tullsen first builds his pattern combinators, then outlines a  
point-free style that
avoids the need for pattern variables althogether but does not  
seem to scale well,
then suggests syntactic sugar for translating patterns with  
variables into applications
of his combinators. So that last part is closely related to, if  
different from, your

proposal.

In my example, I build up patterns from de-constructors (which  
use tests and
selectors), so that a cons pattern takes a head pattern and a  
tail pattern as
parameters and applies them to the head and tail if it is  
applied to a non-empty
list. To handle variables, I use an old trick from the early  
functional logic
languages, namely that logic variables can be passed unbound,  
then bound to
values later, just what we need for pattern variables. Since  
Haskell doesn't
have logic variables, I have to simulate them, which is the  
only awkward bit

of the example:
http://www.haskell.org/pipermail/haskell-prime/2006-November/ 
001915.html


 as long as Haskell doesn't support logic variables, some syntactic  
sugar for
 variables in nested patterns, such as Tullsen's or your's, is  
probably inevitable.

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


Re: [Haskell] Views in Haskell

2007-01-24 Thread Philippa Cowderoy
On Wed, 24 Jan 2007, Claus Reinke wrote:

> the alternative I'm aiming for, as exhibited in the consP example, would be
> to build patterns systematically from view patterns used as abstract
> de-constructors, composed in the same way as one would compose the
> abstract constructors to build the abstract data structure. in other words,
> you define your pattern constructors once, with the adt, and export them;
> and anytime you want to match somethind of that abstract type, you simply
> compose your pattern from those abstract pattern constructors.
> 

This would cause an awful lot of kludging to get around the fact you need 
to declare a new ADT to declare new abstract deconstructors, and requires 
an additional extension for abstract deconstructors to be typeclass 
methods - something abstract constructors can do for free. Neither seems 
gainful to me.

-- 
[EMAIL PROTECTED]

Performance anxiety leads to premature optimisation
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: [Haskell] Views in Haskell

2007-01-24 Thread Claus Reinke
I don't think view patterns are non-linear at all!  They are just as linear as Haskell's 
existing patterns.  Definitely no implicit use of equality, for example.


interesting point. the left-hand sides are non-linear, in that variables may appear 
several times, but the context distinguishes between pattern-variables and expression

variables in view patterns, and the parts concerned with matching are linear, so
every pattern-variable will still only have a single point of definition.

perhaps that is sufficient to avoid confusion. 


but the idea that bindings have a left to right bias is new to Haskell patterns,
and switching formal and actual parameters can now be statically different,
not just dynamically different. Unless the plan is to treat the following two 
as equivalent?


   let { f1 p (p -> ()) = () } in f1 return ()
   let { f2 (p -> ()) p = () } in f2 () return

I've added a section called "Nesting". 


it certainly makes the point. the part I didn't get at once was that I can build
up abstract patterns from view patterns as I would build up abstract data from
abstract constructors, and still be able to bind sub-structures to variables.


| 3 what you call first class abstractions are not entirely orthogonal to view 
patterns.
| taking Tullsen's and my own proposal as examples:
I'm afraid I don't follow this.  I think they are entirely orthogonal.


true first-class patterns, in whatever form, include the functionality provided
by view patterns as a subset. only the syntax differs, and the means of variable 
binding. since we are aiming for a smooth integration with the rest of current
Haskell, these differences are important, but they don't make the approaches 
orthogonal.


Tullsen has the pattern binder construct (Section 4.1), which includes the ability 
to apply any pattern function (functions of type a->Maybe b) anywhere inside a 
pattern using the % construct. The result is matched against a pattern, which can

be a variable. which covers the two aspects of view patterns.

and as I've shown for the lambda-match library, one can compose pattern 
functions in the same way as one builds up a pattern from constructors, ie

every part of the pattern is a pattern function. since I don't have syntactic
sugar for variable binding, that second aspect of view patterns is a little more
awkward. but it can be done in at least two ways, using the logic variable
emulation I showed, or something similar to the result of Tullsen's translation 
of pattern binders. again covering both aspects of view patterns, without 
additional extensions.



| 4 whether to use view patterns inside ordinary patterns, or whether to build 
up
| patterns from abstract de-constructors (just as expressions are built from
| abstract constructors) may seem only a question of style. but if your aim 
is
| to encourage people to transition from exporting concrete data types to
| exporting abstract types only, the latter approach seems more consistent
| to me.
Again, I didn't follow


I wasn't very clear, as I was still trying to get a handle on what view patterns
can do. Sorry about that. Perhaps my second mail has already clarified my 
misconception, but let me try again:


concrete data structures are built from concrete data constructors.
concrete patterns are built from concrete data constructors (which thereby
double as data de-constructors).

abstract data structures are built from abstract data constructors, hiding the
concrete representation.
abstract patterns are built from abstract data-deconstructors (in our current
context, that means pattern functions of type a -> Maybe b, for some a,b).

my concern was whether it makes sense to use view patterns as abstract
de-constructors inside otherwise concrete patterns, or whether one should
encourage a wholesale switch to abstract patterns. as long as I can do the
latter, I don't mind if the former is also possible.


I think I must be missing what you mean by a "compositional abstract pattern".


most of the examples suggested that view patterns are used one a case by
case basis, to select components from an adt part of a parameter.

the alternative I'm aiming for, as exhibited in the consP example, would be
to build patterns systematically from view patterns used as abstract 
de-constructors, composed in the same way as one would compose the

abstract constructors to build the abstract data structure. in other words,
you define your pattern constructors once, with the adt, and export them;
and anytime you want to match somethind of that abstract type, you simply
compose your pattern from those abstract pattern constructors.

is that clearer?

Claus

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


RE: [Haskell] Views in Haskell

2007-01-24 Thread Simon Peyton-Jones
| 1 I am a bit concerned about the use of non-linear patterns in your examples.
| There are good arguments for non-linear patterns, and Haskellers have 
made good
| arguments against non-linear patterns. But you seem to suggest allowing 
non-linear
| patterns in some cases (related to view patterns), but not in others 
(general patterns).
| That is likely to be confusing.

I don't think view patterns are non-linear at all!  They are just as linear as 
Haskell's existing patterns.  Definitely no implicit use of equality, for 
example.

| 2 view patterns nicely separate expressions in patterns from pattern 
variables. But I
| didn't realize at first that view patterns can be used nested inside 
other patterns.
|
| Yet this variable binding during nested matching is the essential 
contribution, and
| the only reason why the extra syntactic sugar is justified. Perhaps this 
point could
| be repeated and emphasized in "The proposal more formally", for people 
like me?-)

I've added a section called "Nesting".   You can readily edit it (since I moved 
the page) to amplify if you think it would help.

| 3 what you call first class abstractions are not entirely orthogonal to view 
patterns.
| taking Tullsen's and my own proposal as examples:

I'm afraid I don't follow this.  I think they are entirely orthogonal.

| 4 whether to use view patterns inside ordinary patterns, or whether to build 
up
| patterns from abstract de-constructors (just as expressions are built from
| abstract constructors) may seem only a question of style. but if your aim 
is
| to encourage people to transition from exporting concrete data types to
| exporting abstract types only, the latter approach seems more consistent
| to me.

Again, I didn't follow

| 5 possible extension 1 smells of superfluous complexity. There is almost no 
gain
| compared to using tuples, but there's a lot to pay in added types and 
rules.

You may well be right.

| 6 possible extension 2 seems a non-starter if we want compositional abstract
| patterns, and I certainly do want them. Imagine the example in (4) with
| explicit Maybe.
|
| Being able to have compositional abstract patterns would be the make-or-break
| criterion for me. Without them, new syntactic sugar wouldn't be justified, 
with
| them, their precise form is a matter of convenience.

I think I must be missing what you mean by a "compositional abstract pattern".


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


Re: [Haskell] Views in Haskell

2007-01-24 Thread Rene de Visser
In my opinion, views are going to make more Haskell more complicated, and 
from what I have seen so far, for little gain.

Maybe a poll should be made to see what features the average Haskeller feels 
the most in need of. Or what their greatest problems are.

Going by the traffic over the previous months, I think that class aliases or 
extensible records would be higher on most peoples lists than views.

Rene. 



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


Re: [Haskell] Views in Haskell

2007-01-24 Thread Claus Reinke
   -- abstract list deconstructors / list pattern constructors 
   -- (consP takes h/t sub-patterns as parameters)

   consP h t l = do { guard $ not (null l); hr <- h (head l); tr <- t (tail l); 
return (hr,tr) }
   nilP l = do { guard $ null l; return () }
   
   -- wildcard and variable patterns

   wildP l = return ()
   varP = return

   -- extract the head of the tail of the parameter list, if that list has two 
elements
   f (consP wildP (consP varP nilP) -> (_,(x,_))) = x


hmm, the above was probably guided too much by thinking about my own proposal
(and this style could be translated back to it fairly easily, I think). the following would 
make better use of view patterns, and be a lot simpler:


   -- cons pattern/deconstructor
   consP l = do { guard $ not (null l); return (head l, tail l) }

   -- extract head of tail of two-element list
   f (consP -> (_, consP -> (x, []) ) ) = x

btw, lambda-match and view patterns complement each other:
- the sugar in lambda-match embeds classical matches in data parsing
- the sugar in view patterns embeds data parsing in classical patterns

In view of this, I was wondering: if you do not limit yourself to Maybe, but 
allow other MonadPlus instances, wouldn't that give you or-patterns?


also, view patterns give us local guards:

   g ( xs@( guard . not . null -> () ) ) ys = xs++ys

if we combine these two, we could presumably do things like using
the list MonadPlus for backtracking matches, as proposed in some other
functional languages (also assuming non-linearity of patterns here):

   select :: Eq a => a -> Map a b -> b
   select key ( toList -> ( (guard . (key==) ) ,value) ) = value

claus

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


Re: [Haskell] Views in Haskell

2007-01-24 Thread Ross Paterson
On Mon, Jan 22, 2007 at 02:57:27PM +, Simon Peyton-Jones wrote:
> This proposal is a very lightweight (and hence, I hope, cost-effective)
> proposal for a view-like mechanism.
> 
> http://hackage.haskell.org/trac/haskell-prime/wiki/ViewPatterns

This could be considered a generalization of field matching (minus the
data constructor), so you'd presumably want similar syntax for the two.

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


Re: [Haskell] Views in Haskell

2007-01-24 Thread Brian Hulley

On Wednesday, January 24, 2007 10:02 AM, Dinko Tenev wrote:

On 1/24/07, Brian Hulley <[EMAIL PROTECTED]> wrote:

A possible syntax could represent the
value being matched explicitly, say using ? to represent the value 
currently

being matched, then the pattern could be written as an equation:

   f (prodSize ? = Small) = ...
   f (prodSize ? = Medium) = ...
   f (prodSize ? = Big) = ...


...or maybe (Small = prodSize ?), etc., to be consistent with let 
bindings?


I like it!
Just to fix a minor error in one of my previous examples, and to show it in 
let-compatible form:


   -- "n+3" pattern matching against 2nd element
   j (_ : (n = ? - 3) : _ = toList ?) = ...

Also, perhaps the "binding" could be optional for "True = ", so that:

   test (True = isAlpha ?) = ...

could just be written as:

   test (isAlpha ?) = ...

(The presence of '?' in the pattern is enough to specify that it's an 
"active" pattern)


Here is another example, in current syntax and in "new" syntax:

   old (n + 3) | 0 < n = ...-- using idiosyncratic n+k pattern

   new (n = ? - 3) | 0 < n = ...-- rational reconstruction
or
   new (n @ (0 < ?) = ? - 3) = ... -- moving guard into pattern

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


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


Re: [Haskell] Views in Haskell

2007-01-24 Thread Dinko Tenev

On 1/24/07, Brian Hulley <[EMAIL PROTECTED]> wrote:


A possible syntax could represent the
value being matched explicitly, say using ? to represent the value
currently
being matched, then the pattern could be written as an equation:

f (prodSize ? = Small) = ...
f (prodSize ? = Medium) = ...
f (prodSize ? = Big) = ...



...or maybe (Small = prodSize ?), etc., to be consistent with let bindings?
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: [Haskell] Views in Haskell

2007-01-23 Thread Brian Hulley

Simon Peyton-Jones wrote:


http://hackage.haskell.org/trac/haskell-prime/wiki/ViewPatterns

I'm thinking of implementing it in GHC, so I'd be interested in
feedback of the form
- how desirable is it to have a feature of this general form?
- can this particular proposal be improved?


Regarding the syntax, I don't like the use of ->, because I think it is 
confusing to write


   even -> n

when even is the function itself. In all other places in Haskell, A -> B 
represents a function from A to B whereas in the proposal A -> B represents 
the function A applied to the thing currently being matched which may return 
a value wrapped up in Maybe which matches B.


There are 2 things - the inconsistent use of -> and the implicit Maybe.

I'd rather the Maybe was not implicit (as described in extension 2), and a 
more consistent syntax was found. A possible syntax could represent the 
value being matched explicitly, say using ? to represent the value currently 
being matched, then the pattern could be written as an equation:


   f (prodSize ? = Small) = ...
   f (prodSize ? = Medium) = ...
   f (prodSize ? = Big) = ...

or simulating an n + k pattern:

   g (? - 3 = n) = ...

or a function which checks its arg satisfies an arbitrary expression:

   h (? - (3 * ?) = 10) = ...

or an "n+k" against the second element of a list

   j ( toList ? = (_ : (? - 3 = n : _))) = ...

Regarding the problem itself, I'm still not sure why views are needed. For 
example in (f) above, why not just write as:


   f :: Product -> ...
   f prod = k (prodSize prod) where k = ...

Best regards, Brian.
--
http://www.metamilk.com 


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


Re: [Haskell] Views in Haskell

2007-01-23 Thread Claus Reinke

   http://hackage.haskell.org/trac/haskell-prime/wiki/ViewPatterns

I'm thinking of implementing it in GHC, so I'd be interested in feedback of the 
form
   - how desirable is it to have a feature of this general form?
   - can this particular proposal be improved?


IMHO, getting a handle on the ADT vs pattern matching issues is overdue, so 
thanks
for raising this again. a few first comments:

1 I am a bit concerned about the use of non-linear patterns in your examples. 
   There are good arguments for non-linear patterns, and Haskellers have made good

   arguments against non-linear patterns. But you seem to suggest allowing 
non-linear
   patterns in some cases (related to view patterns), but not in others 
(general patterns).
   That is likely to be confusing.

2 view patterns nicely separate expressions in patterns from pattern variables. But I 
   didn't realize at first that view patterns can be used nested inside other patterns.


   Yet this variable binding during nested matching is the essential 
contribution, and
   the only reason why the extra syntactic sugar is justified. Perhaps this 
point could
   be repeated and emphasized in "The proposal more formally", for people like 
me?-)

3 what you call first class abstractions are not entirely orthogonal to view 
patterns.
   taking Tullsen's and my own proposal as examples:

- the way patterns and alternatives are handled needs to fit together. that doesn't 
   seem to be a problem since your and our proposals agree on using what I call
   a monadic data parsing framework (using a MonadPlus such as Maybe to handle 
   pattern match failure and alternatives)


- all three proposals have discussed how to handle patterns as well. For 
Tullsen,
   that is central to his proposal, for me, it was only one of the more advanced 
   examples because I wanted to focus on match alternatives first.


   Tullsen first builds his pattern combinators, then outlines a point-free 
style that
   avoids the need for pattern variables althogether but does not seem to scale well, 
   then suggests syntactic sugar for translating patterns with variables into applications 
   of his combinators. So that last part is closely related to, if different from, your

   proposal.

   In my example, I build up patterns from de-constructors (which use tests and 
   selectors), so that a cons pattern takes a head pattern and a tail pattern as 
   parameters and applies them to the head and tail if it is applied to a non-empty
   list. To handle variables, I use an old trick from the early functional logic 
   languages, namely that logic variables can be passed unbound, then bound to

   values later, just what we need for pattern variables. Since Haskell doesn't
   have logic variables, I have to simulate them, which is the only awkward bit
   of the example:
   http://www.haskell.org/pipermail/haskell-prime/2006-November/001915.html

as long as Haskell doesn't support logic variables, some syntactic sugar for
variables in nested patterns, such as Tullsen's or your's, is probably 
inevitable.

4 whether to use view patterns inside ordinary patterns, or whether to build up
   patterns from abstract de-constructors (just as expressions are built from 
   abstract constructors) may seem only a question of style. but if your aim is 
   to encourage people to transition from exporting concrete data types to

   exporting abstract types only, the latter approach seems more consistent
   to me. In my example, a cons de-constructor would be as simple as

   -- the cons view of array lists is a higher-order pattern that takes
   -- patterns for the head and tail components, and applies them after
   -- checking whether the list parameter is a non-empty list
   consAP h t l = do { Match $ guard $ not (isNilA l); h (headA l); t (tailA l) 
}

   but that relies on the scoping of (simulated) logic variables, and it does 
   not translate directly to your view patterns, as the h and t pattern parameters

   would have their own scope for their pattern variables. It would be 
instructive
   to have something equivalent to pattern constructors/abstract deconstructors
   for view patterns, if only to see whether view patterns can support a fully 
   abstract style of nested matches easily. I am not entirely sure they do, but 
   here is a first attempt:


   -- abstract list deconstructors / list pattern constructors 
   -- (consP takes h/t sub-patterns as parameters)

   consP h t l = do { guard $ not (null l); hr <- h (head l); tr <- t (tail l); 
return (hr,tr) }
   nilP l = do { guard $ null l; return () }
   
   -- wildcard and variable patterns

   wildP l = return ()
   varP = return

   -- extract the head of the tail of the parameter list, if that list has two 
elements
   f (consP wildP (consP varP nilP) -> (_,(x,_))) = x

   It seems a bit awkward to have to specify the structure of the parameter 
twice,
   once to build up the pattern, then again to match sub-express

RE: [Haskell] Views in Haskell

2007-01-23 Thread Simon Peyton-Jones
[Redirecting to haskell-prime]

| In the related work, the "Active Patterns" proposal by Palao et at is missing:
|
| http://portal.acm.org/citation.cfm?id=232641&coll=portal&dl=ACM
|
| I thought this work should be included in the list because, I believe,
| they were the first to point out that computation should take place
| before matching, which was not the case in Wadler's and Burton's
| proposals?  They also proposed  types for patterns.

Good point. I've added them.  I think the Wadler/Burton stuff did allow for 
arbitrary computation; it's just that there was no way to do the value-input 
thing.  (Pattern synonyms, on the other hand, do not.)

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


Re: [Haskell] Views in Haskell

2007-01-22 Thread David Roundy
On Mon, Jan 22, 2007 at 02:57:27PM +, Simon Peyton-Jones wrote:
> Dear Haskellers
> 
> Provoked by a discussion with Don Syme, and after some helpful
> conversations at POPL, I have finally written up a proposal for adding
> "view patterns" to Haskell.  We've wanted views for a long time, but they
> have never made it, into GHC at any rate.  This proposal is a very
> lightweight (and hence, I hope, cost-effective) proposal for a view-like
> mechanism.
> 
> http://hackage.haskell.org/trac/haskell-prime/wiki/ViewPatterns
> 
> I'm thinking of implementing it in GHC, so I'd be interested in feedback of 
> the form
> - how desirable is it to have a feature of this general form?
> - can this particular proposal be improved?

It looks pretty cool to me, and simple enough to be reasonable.

One feature that would be particularly interesting would be to add some
sort of annotation mechanism to describe a possible "complete" set of views
(with respect to improving warnings about inexhaustive pattern matching).
I wonder if you could have something like:

data Foo = FooBar Bar | FooBaz Baz

foobar :: Foo -> Maybe Bar
foobaz :: Foo -> Maybe Baz

{-# COMPREHENSIVE_VIEWS Foo : foobar, foobaz #-}

which tells the compiler that for any Foo, one of foobar and foobaz will
return a non-Nothing result.  It'd allow us--at least in the simple views
case--to retain the existing level of warnings, and ought also to be useful
in somewhat trickier case as well.

Another idea is whether the syntax could be extended to indicate a failure
to match? This would actually be useful even without views, but it's
particularly useful with views (and especially so in the context of the
above warnings).  I'd imagine something like (with stupidly chosen syntax
of !!!)

foo (_:_) = True
foo _ = False

foo' !!![] = True
foo' _ = False

Here I've defined two identical functions to describe what I mean by "!!!".
I didn't gain anything in this case, but might gain some clarity if there
are multiple constructors.  But more to the point, if we're using views (of
the vanilla Maybe-always variety), we could gain some efficiency this way.

foo ([], view -> a, []) = foo1 a
foo (x, !!! view ->, []) = foo2 x
foo (_, view -> a, y) = foo3 a y

This isn't a very good example, but the point is I'd like to be able to
match on Nothing and get the same benefits you mention about the compiler
being assumed to optimize by calling view only once.  We could achieve this
by reordering the patterns, but I believe (although I failed to come up
with one above) that there are sets of pattern matches that aren't
reducible in that way, which it'd be nice to be able to express succinctly
by matching on failure to match a pattern.

Maybe this should be

foo (x, view /->, []) = foo2 x

or something like that, to indicate failure, that view doesn't match?
-- 
David Roundy
Department of Physics
Oregon State University
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime