[Haskell-cafe] F# active patterns versus GHC's view

John Van Enk vanenkj at gmail.com
Thu Jan 15 18:23:04 EST 2009


I've often thought having constructor "views" would be handy.

data Foo = Foo A B C D E F G H I
view Bar = (Foo A _ C _ _ _ G _ I) => Bar A C G I

This does bring up problems with case alternatives though.

I think the correct answer for these kinds of views is with the record
pattern matching syntax, though, I wish there was a more terse way to notate
it.

data Foo = {
  a :: A,
  b :: B,
  c :: C,
  d :: D,
  e :: E,
  f :: F,
  g :: G
}

f (Foo {a = var_a, g = var_g}) = ...

/jve


2009/1/15 Peter Verswyvelen <bugfact at gmail.com>

> When I first read about active patterns in F#, I found it really cool idea,
> since it allows creating fake data constructors that can be used for pattern
> matching, giving many views to a single piece of data, and allowing
> backwards compatibility when you completely change or hide a data structure.
> So for example one could define a Polar pattern and a Rect pattern that
> give different views of a Complex number, e.g (pseudo code follows)
>
> pattern Polar c = (mag c, phase c)
> pattern Rect c = (real c, imag c)
>
> This seems handy:
>
> polarMul (Polar m1 p1) (Polar m2 p2) = mkComplexFromPolar (m1*m2) (p1+p2)
>
> However, I think it is flawed, since the following
>
> case c of
>      Polar _ _ -> "it's polar!"
>      Rect _ _ -> "it's rect!"
>
> seems like valid code but does not make any sense.
>
> So I think the GHC extension of view patterns is better than the active
> patterns in F#?
>
> A good coding style is to provide constructor functions and hide data
> constructors. But then one looses the ability to perform pattern matching,
> which is so cool in Haskell. Would I have to conclude that it would be good
> coding style to use view patterns as much as possible in Haskell,
> creating auxiliary data constructors to expose the "public members" of the
> hidden data constructors?
>
>
>
>
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20090115/1ee13952/attachment.htm


More information about the Haskell-Cafe mailing list