ADT views Re: [Haskell] Views in Haskell

Bulat Ziganshin bulat.ziganshin at gmail.com
Wed Jan 31 09:53:08 EST 2007


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 at gmail.com



More information about the Haskell-prime mailing list