[Haskell] Views in Haskell
Mark Tullsen
tullsen at galois.com
Tue Jan 30 21:16:20 EST 2007
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
More information about the Haskell-prime
mailing list