ADT views Re: [Haskell] Views in Haskell

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, Bulat mailto:Bulat.Ziganshin@gmail.com

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

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, Bulat mailto:Bulat.Ziganshin@gmail.com

On 1/31/07, Bulat Ziganshin
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.

J. Garrett Morris wrote (to Bulat Ziganshin):
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.
I just read this paper, in particular the part about the problems with equational reasoning that come up once you introduce (a certain form of) views. I fail to appreciate those problems. Perhaps someone can help me see them? :-) ### Polar representation Before taking on the problematic 'Half', I review the earlier example of the polar representation of complex numbers.
data Complex = Cart Float Float
view Polar of Complex = Polar Float Float where polar (Cart r i) = Polar (sqrt(r*r+i*i)) (atan2 r i)
I am slightly puzzled by this notation: the role of the extra function (?) 'polar' is unclear to me. If I leave it out, the definition makes sense: 'Cart r i' and 'Polar (sqrt(r*r+i*i)) (atan2 r i)' are declared to be the same object. Note that this definition provides only one direction of the "change of coordinates": if we define a complex number by giving its polar representation, then its cartesian components are not yet well defined. This means that the "constructor" 'Polar' is not a well defined function, unless you assume a new datatype 'Polar' (of "complex numbers in polar representation") and have 'Polar :: Float -> Float -> Polar'. This is what the proposal seems to do, but I find it very misleading: if you look at the defining equation of the view, the constructor 'Polar' takes two floating point numbers, and returns a complex number: 'Polar :: Float -> Float -> Complex'. (Said another way: when 'Polar' appears in a pattern, it must convert the original cartesian coordinates to polar ones; when it appears in an expression, it converts polar back to cartesian. The view given above only allows the first of these two.) (Maybe this is where the proposal strays from the natural "equational" meaning?) ### 'Half' OK, now we consider the following view:
view Half of Int = Half Int where half i = Half (i `div` 2)
Again, I propose to leave out the word 'half', and conclude that the integer 'i' is declared to be equal to 'Half (i `div` 2)'. (Maybe at this point my interpretation diverges from the intended meaning, but then the first example does not implement the usual polar representation of complex numbers.) Just as before, we have not specified what number 'Half n' actually is; even if we are consistent it could be either '2*n' or '2*n+1'. Therefore, if we define the function 'f' by
f (Half i) = i+1
, the only sensible way I can think of to compute 'f (Half 8)' is by pattern matching 'Half 8' against 'Half i', giving the binding 'i -> 8', and substituting this in the RHS of 'f', giving 'f (Half 8) = 8+1 = 9'. Of course this is also what you get by "replacing equals for equals", as the paper puts it. The paper however continues to state that "'f (Half 8) = 9' [...] is not true because 'f (Half 8) = 5' due to the computational part of 'Half'". ***I really don't see how one would conclude this.*** It would be strange to divide the parameter of 'Half' by 2 -- 'n' is already half of the number represented by 'Half n'. Perhaps someone can enlighten me to see the problem. I have a feeling, though, that there is no inherent problem with views, only some confusion about which way the coordinate transformations should go. In fact, I would love to see views in Haskell, but I'll save that discussion for another thread. Kind regards, Arie

Arie Peterson wrote:
J. Garrett Morris wrote (to Bulat Ziganshin):
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.
I just read this paper, in particular the part about the problems with equational reasoning that come up once you introduce (a certain form of) views.
The problems are not unsolvable - see the Pattern Matching Calculus http://www.cas.mcmaster.ca/~kahl/PMC/ for one way to re-introduce equational reasoning in pattern-matching. On another front, I am a big fan of the polar/cartesian 'view' of Complex numbers as being a fundamental test case for "full" views. In fact, that is quite restricted, one should instead be looking at the following views for R^2: bipolar, cardioid, cassinian, cartesian, elliptic, hyperbolic, invcassinian, invelliptic, logarithmic, logcosh, maxwell, parabolic, polar, rose, and tangent. In three dimensions, one then gets - bipolarcylindrical, bispherical, cardioidal, cardioidcylindrical, casscylindrical, confocalellip, confocalparab, conical, cylindrical, ellcylindrical, ellipsoidal, hypercylindrical, invcasscylindrical, invellcylindrical, invoblspheroidal, invprospheroidal, logcoshcylindrical, logcylindrical, maxwellcylindrical, oblatespheroidal, paraboloidal, paraboloidal2, paracylindrical, prolatespheroidal, rectangular, rosecylindrical, sixsphere, spherical, tangentcylindrical, tangentsphere, and toroidal. REFERENCES: Moon, P. and D.E.Spencer. "Field Theory Handbook, 2nd Ed." Berlin: Springer-Verlag, 1971. Spiegel, Murray R. "Mathematical Handbook of Formulas and Tables." New York: McGraw Hill Book Company, 1968. 126-130. Jacques

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, Bulat mailto:Bulat.Ziganshin@gmail.com

Bulat Ziganshin wrote:
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)
No. Abstractions should (and mostly do) make reasoning easier, not harder, by having clear semantics, suited to the problem domain. The ability to reason about your program is vital in about every part of the programming cycle, and is one of the things that make Haskell work. Another of those things is abstraction of data representation, you're right about that. But I think there is no conflict between those goals. In fact, all the views proposal does is to give the natural meaning to the equation
f (v x) = h x
, by letting the programmer specify a partial inverse for 'v'. Greetings, Arie

Hello Arie, Thursday, February 1, 2007, 2:08:33 PM, you wrote:
The ability to reason about your program is vital in about every part of the programming cycle, and is one of the things that make Haskell work.
when i say what i don't use reasoning, you can trust me :)
Another of those things is abstraction of data representation, you're right about that. But I think there is no conflict between those goals.
right now we are discussing such conflict, not be? :) -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Bulat Ziganshin
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 Jon.Fairbairn@cl.cam.ac.uk

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 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?
Granted. It's not necesary, but I find that it can be handy to have a bit of syntactic information about cost.
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.
I am less troubled about this than I was before, but I still don't like the implied inequivalence. I like to assume that pattern matching and guards can be translated into if statements with error, and with your syntax I'm not sure whether this is true. i.e. what happens if I 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 = if x /= 0 && y /= 0 then Polar (x*y) (x+y) -- matching else undefined -- not matching Is this an invalid bit of code, i.e. for your views syntax, are you reusing only a subset of the function syntax? Or is this valid code that causes an error when you match f (Polar r a) = ... if the argument is Coord 0 0? If we don't allow this syntax (if statement on the RHS of the matching definition), why not? The syntax you propose can be used to decribe arbitrary functions, so why not allow us coders to use the ordinary Haskell syntax to define these functions, rather than a subset thereof? I have a feeling that with complicated views, coding the entire function on the LHS could get cumbersome pretty quickly. Of course, with pattern guards, one can always get around this by defining a helper function, but I'd prefer to avoid syntax constraints that require that I define a helper function that's only used once. -- David Roundy Department of Physics Oregon State University

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
participants (6)
-
Arie Peterson
-
Bulat Ziganshin
-
David Roundy
-
J. Garrett Morris
-
Jacques Carette
-
Jón Fairbairn