After browsing through the Standard Library Proposal for Haskell 1.3 (Version 3
>from September 6, 1995), I have the following questions:

   1) The proposal for collections (sec. 4.2) mentions four different
      _libraries_ which all define identical functions. IMHO, this should
      better be a single (contructor-) _class_ . To explain this a little
      further, a small sketch of it is appendend at the end of the mail.

      Implementing collections as a class would relieve the programmer from
      changing a lot of type contexts if the undelying implementation of
      collections is changed. The same argument holds for mappings, etc.

      To make my point a little clearer, imagine the following scenario:
      A program which handles collections via ListSets (requiring Eq) turns out
      to be too slow. So the programmer decides to implement collections as
      Sets (requiring Ord) instead. This forces changing the context (Eq a) to
      (Ord a) in all places where collections are used (where a is the type of
      the elements in the collection).

   2) Trying to implement this constructor class (see below), I needed a
      constructor class with _two_ type variables. Gofer allows this, but
      Haskell 1.3 does not. Are there any serious theoretical obstacles for
      insisting on a single type variable in  a class declaration? If not,
      including Gofer's generality in Haskell would be nice.

   3) Are there ways of achieving the desired behaviour with a single type
      variable in the class declaration? If so, forget my previous
      question. :-)


---SNIP------SNIP------SNIP------SNIP------SNIP------SNIP------SNIP------SNIP---

\begin{code}
-- Collections as a constructor class

module Collections (Collection, UList, SList) where

-- Not standard Haskell 1.3, but Gofer-conformant
class Collection col a where
  empty     ::                         col a
  singleton ::                    a -> col a
  add       ::           a -> col a -> col a
  delete    :: (Eq a) => a -> col a -> col a

  singleton x = add x empty

----------------------------------------------------
-- a collection as an unsorted list without duplicates

data UList a = UList [a]

instance (Eq a) => Collection UList a where

   empty = UList []

   add e u@(UList l) | any (e ==) l = u
                     | otherwise    = UList (e:l)

   delete e (UList l) = UList (del l)
      where del []                 = []
            del (x:xs) | e == x    = xs
                       | otherwise = x:(del xs)

----------------------------------------------------
-- a collection as a sorted list without duplicates

data SList a = SList [a]

instance (Ord a) => Collection SList a where

   empty = SList []

   add e (SList l) = SList (adjoin l)
      where adjoin []                 = [e]
            adjoin ys@(x:xs) | e <  x = e:ys
                             | e == x = ys
                             | e >  x = x:(adjoin xs)

   delete e (SList l) = SList (del l)
      where del []                 = []
            del ys@(x:xs) | e <  x = ys
                          | e == x = xs
                          | e >  x = x:(del xs)

----------------------------------------------------
-- a collection as an unbalanced binary tree
--
-- data Tree a = Empty | Node a (Tree a) (Tree a)
--
-- instance (Ord a) => Collection Tree a where ...
--
-- and so on...
----------------------------------------------------
\end{code}

\begin{code}
-- And now to something completely different... ;-)
-- A module which uses the above Collection class
-- Note: All but the last type declarations are superfluous.

module Test where

import Collections

foo :: Collection col Char => col Char -> col Char
foo c = add 'a' c

bar :: (Collection col a, Eq a) => col a -> a -> col a
bar c x = delete x c

baz :: Collection a Char => a Char -> a Char
baz c = bar c 'a'

addRange :: (Enum a, Collection col a) => a -> a -> col a -> col a
addRange start end c = foldr add c [start..end]

test :: SList Char
test = addRange 'a' 'z' empty
\end{code}

---SNIP------SNIP------SNIP------SNIP------SNIP------SNIP------SNIP------SNIP---


-- 
Sven Panne                                         Tel.: +49/89/21106-90
LMU, Institut fuer Informatik                      FAX : +49/89/21106-99
LFE Programmier- und Modellierungssprachen             Wagmuellerstr. 23
mailto:[EMAIL PROTECTED]            D-80538 Muenchen



Reply via email to