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

Jonathan Cast jcast at ou.edu
Wed Jul 25 12:17:36 EDT 2007


On Wednesday 25 July 2007, Jon Fairbairn wrote:
> Simon Marlow <simonmarhaskell at gmail.com> writes:
> > Dan Licata wrote:
> > > Simon PJ and I are implementing view patterns, a way of
> > > pattern matching against abstract datatypes, in GHC.
> >
> > At the risk of being a spoil-sport, I have a somewhat
> > negative take on view patterns.  Not because I think they're
> > particularly bad, but because I don't think they're
> > significantly useful enough to warrant adding to the
> > language, at least if we also have pattern guards.
>
> I wholeheartedly agree.
>
> I'd rather see a slightly different question addressed: how
> to permit the definition of overloaded functions using
> pattern matching (and I mean pattern matching with exactly
> the same syntax as anywhere else). In other words, if I write
>
> > f [] = e
> > f (a:b) g a b
>
> I currently only get f :: [t] -> something, so if I later
> discover that I need to change the input representation to
> be more efficient than lists, I have to rewrite f. Wouldn't
> it be so much nicer if I could simply add a declaration
>
> > f:: Stream s => s t -> something
>
> and get a function that works on anything in the Stream
> class?
>
> The core of the idea would be to allow classes to include
> constructors (and associated destructors) so the definition
> of Stream would include something for ":" and "[]" and their
> inverses, though I've no real idea of the details; can
> anyone come up with a plan?
>
>
> * * *
>
> 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.

I don't have a formal specification, but I think this does that:

-- | Minimal complete definition: either 'empty', 'unit', and 'append' or '[]'
-- and '(:)' + pattern matching
algebraic class Stream s where
  empty :: s t
  unit :: t -> s t
  append :: s t -> s t -> s t
  [] :: s t
  (:) :: t -> s t -> s t
  empty = []
  unit x = x : []
  append (x:xn) ys = x : (xn `append` ys)
  [] = empty
  x : xn = unit x `append` xn

De-sugars into:

data StreamView s t
  = []
  | (:) t (s t)

data Stream s = Stream{
  empty :: forall t. s t,
  unit :: forall t. t -> s t,
  append :: forall t. t -> s t,
  nil :: forall t. s t,
  cons :: forall t. t -> s t,
  viewStream :: forall t. s t -> StreamView s t}

defaultEmpty s = nil s
defaultUnit s x = cons s x (nil s)
defaultAppend s xn ys = case viewStream s xn of
  [] -> ys
  x : xn' -> cons s x (defaultAppend s xn' ys)
defaultNil s = empty s
defaultCons s x xn = append s (unit s x) xn

Case evaluation proceeds by case analysis of viewStream.

data List t
  = Nil
  | Cons t (List t)

instance Stream List where
  [] = Nil
  (:) = Cons
  Nil = []
  Cons = (:)

De-sugars into:

streamList = Stream{
  empty = defaultEmpty streamList,
  unit = defaultUnit streamList,
  append = defaultAppend streamList,
  nil = Nil,
  cons = Cons,
  viewStream = \ xn -> case xn of
    Nil -> []
    Cons x xn -> x : xn}

While

data Tsil t
  = Lin
  | Snoc (Tsil t) t

instance Stream Tsil where
  empty = Lin
  unit x = Snoc Lin x
  xn `append` Lin = xn
  xn `append` Snoc ys y = (xn `append` ys) `Snoc` y
  Lin = []
  Snoc xn x = flip fix (x, Lin, xn) $ \ loop (x, ys, xn) -> case xn of
    Lin -> x : ys
    Snoc xn' x' -> loop (x', x : ys, xn')

De-sugars into

streamTsil = Stream{
  empty = Lin,
  unit = Snoc Lin,
  append = \ xn ys -> case ys of
    Lin -> xn
    Snoc ys' y -> (append streamTsil xn ys') `Snoc` y,
  nil = defaultNil streamTsil,
  cons = defaultCons streamTsil,
  viewStream = \ xn -> case xn of
    Lin -> []
    Snoc xn' x -> flip fix (x, Lin, xn) $ \ loop (x, ys, xn) -> case xn of
      Lin -> x : ys
      Snoc xn' x' -> loop (x', cons streamTsil x ys, xn')}

The best part is that you can have multiple data types to a view and multiple 
views of a data type, and the fact that pattern-matching proceeds one level 
at a time; the worst part is the rather syntactic way e.g. (:) as a 
view-constructor is distinguished from (:) as a class method.  They can't be 
distinguished type-wise (e.g., by a dictionary passing mechanism) because 
their types aren't unifiable; I think you'd have to define a tail context 
within viewStream and replace (:) with the constructor there only.  Or change 
the view type to

data StreamView t
  = []
  | t : StreamView t

Jonathan Cast
http://sourceforge.net/projects/fid-core
http://sourceforge.net/projects/fid-emacs
-- 
Jonathan Cast
http://sourceforge.net/projects/fid-core
http://sourceforge.net/projects/fid-emacs
-------------- next part --------------
A non-text attachment was scrubbed...
Name: not available
Type: application/pgp-signature
Size: 189 bytes
Desc: not available
Url : http://www.haskell.org/pipermail/haskell-cafe/attachments/20070725/8ed04dd3/attachment-0001.bin


More information about the Haskell-Cafe mailing list