the alternative I'm aiming for, as exhibited in the consP example, would be
to build patterns systematically from view patterns used as abstract
de-constructors, composed in the same way as one would compose the
abstract constructors to build the abstract data structure.

This would cause an awful lot of kludging to get around the fact you need to declare a new ADT to declare new abstract deconstructors, and requires an additional extension for abstract deconstructors to be typeclass methods - something abstract constructors can do for free. Neither seems gainful to me.

I don't understand? you can define deconstructors for concrete types as well,
as many as you like; it is just that when the representation is not hidden in an
ADT, noone hinders me from bypassing your deconstructors and go for the
concrete representation instead of the abstract representation. and how did additional extensions or typeclasses get into the picture??

perhaps a concrete example will help. as I used the lists-as-arrays example
for lambda-match, here it is again for view patterns (implementation not
repeated, List made abstract, untested..):

   module ListArray(List(),nilA,nullA  , nilAP
                           ,consA,headA,tailA  , consAP
                           ,snocA,initA,tailA  , snocAP
                           ) where
   ..imports..

   -- our own array list variant
   data List a = List (Array Int a)

   -- constructors, tests, selectors; cons and snoc view
   nilA :: List a
   nullA :: List a -> Bool

   consA :: a -> List a -> List a
   headA :: List a -> a
   tailA :: List a -> List a

   snocA :: List a -> a -> List a
   lastA :: List a -> a
   initA :: List a -> List a

   -- we also define our own pattern constructors
nilAP = guard . nullA consAP l = do { guard $ not (nullA l); return ( headA l, tailA l ) }
   snocAP l = do { guard $ not (nullA l); return ( initA l, lastA l ) }


   module Examples where
   import ListArray

   anA = consA 1 $ consA 2 $ consA 3 $ consA 4 nilA

   mapA f (nilAP -> ()) = nilA
   mapA f (consAP -> (h,t)) = consA (f h) (mapA f t)

   foldA  f n (nilAP     -> ())    = n
foldA f n (consAP -> (h,t)) = f h (foldA f n t)
   foldA' f n (nilAP     -> ())   = n
   foldA' f n (snocAP -> (i,l)) = f (foldA' f n i) l

   palindrome (nilAP -> ()) = True
   palindrome (consAP -> (_, nilAP -> () ) = True
   palindrome (consAP -> (h, snocAP -> (m,l))) = (h==l) && palindrome m

no need for typeclasses so far. we use abstract data and pattern constructors
for adts, just as we use concrete data and pattern constructors for concrete
types. we choose what view to take of our data simply by choosing what
pattern constructors we use (no need for type-based overloaded in/out).
and since our pattern constructors are simply functions, we get pattern
synonyms as well.

we could, I guess, try to package data and pattern constructors together,
either by typeclasses:

   class Cons t where cons :: t
   instance Cons (a->List a->List a) where cons = ListArray.cons
   instance Cons (List a->(a,List a)) where cons = ListArray.consP

or by declaring consP as the deconstructor corresponding to the cons
constructor, as Mark suggested:

   cons :: a -> List a -> List a
   cons# :: List a -> (a,List a)

both versions could then be used to select the pattern or data constructor,
depending on whether cons was used in a pattern or expression context.
but neither of these seems strictly necessary to get the benefit of views.

if view patterns turn out to be practical, one could then go on to redefine
the meaning of data type declarations as implicitly introducing both
data and pattern constructors, so

   f (C x (C y N) = C y (C x N)

might one day stand for

   f (cP -> (x, cP -> (y, nP))) = c y (c x n)

but it seems a bit early to discuss such far-reaching changes when we haven't got any experience with view patterns yet. in the mean-time, one
might want to extend the refactoring from concrete to abstract types
(HaRe has such a refactoring), so that it uses view patterns instead of eliminating pattern matching.

since others have raised similar concerns about needing type-classes,
I seem to be missing something. could someone please explain what?

Claus

_______________________________________________
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime

Reply via email to