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

Dan Licata drl at cs.cmu.edu
Thu Jul 26 11:28:03 EDT 2007


I think what you're describing is equivalent to making the "implicit
view function" syntax so terse that you don't write anything at all.  So
the pattern 'p' is always (view -> p).  This seems like a pretty
invasive change: 

I don't think the version with the functional dependency works (unless
you adopt some form of scoped type class instances, as you suggest
below), because then if you want to use a datatype as a view, you can no
longer pattern match on the datatype itself at all!  Even with some form
of scoping, you can't decompose the view datatype as itself and as a
view in the same scope.  

The non-functional type class will make everything very polymorphic
(e.g., where we used to infer a type based on the datatype constructors
that occurred, we will now say that it's anything that can be viewed as
that datatype).

So, this syntax affects a lot of code, existing or otherwise, that
doesn't use view patterns, which is something we're trying to avoid.

-Dan

On Jul25, Stefan O'Rear wrote:
> On Wed, Jul 25, 2007 at 09:35:32PM +0200, apfelmus wrote:
> >     Integer
> >  => (forall a . ViewInt a => a)
> > 
> > can even be done implicitly and for all types. Together with the magic
> > class View, this would give real views.
> > 
> > 
> > Jón Fairbairn wrote:
> > > It's essential to this idea that it doesn't involve any new
> > > pattern matching syntax; the meaning of pattern matching for
> > > overloaded functions should be just as transparent as for
> > > non-overloaded ones.
> > 
> > That's what the real views would do modulo the probably minor
> > inconvenience that one would need to use (:<) and (EmptyL) instead of
> > (:) and []. I doubt that the latter can be reused.
> 
> It's possible to go even simpler, and implement views via a simple
> desugaring without altering the typechecking kernel at all.
> 
> (for simplicity of exposition, assume pattern matches have already been
> compiled to flat cases using Johnsson's algorithm; in particular the
> patterns mentioned consist of exactly one constructor, not zero)
> 
> case scrut of
>   pat -> a
>   _   -> b
> 
> ==>
> 
> realcase (Prelude.view scrut) of
>   pat -> a
>   _   -> b
> 
> Where in the Prelude (or the current type environment, if
> -fno-implicit-prelude) we have:
> 
> class View a c | c -> a where
>     view :: a -> c
> 
> and we provide a deriving-form for View which generates View Foo Foo
> where view = id.
> 
> Or, a rule which does that automatically if no explicit instance of View
> _ Foo is in the current module.
> 
> Or, remove the fundep and add an instance View a a where view = id to
> the Prelude.
> 
> Option 3 makes definitions more polymorphic.  Options 1 and 2 keep the
> same level of polymorphism as before; 1 is simpler but breaks old code.
> 
> Note that none of these options supports the value input feature; we
> need new syntax to support non-binding identifiers in patterns!
> 
> Stefan



> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe



More information about the Haskell-Cafe mailing list