Defaults in datatype definitions

Marcin 'Qrczak' Kowalczyk qrczak@knm.org.pl
9 Jan 2001 18:37:03 GMT


Tue, 9 Jan 2001 09:46:31 +0100 (MET), Johannes Waldmann <joe@isun.informatik.uni-leipzig.de> pisze:

> 1) I would like to write down default values for record components

My proposal for remaking records ina more flexible way includes this.

> 2) With classes, we can do even more: in the default method,
> we can access other methods.

And this too.

> 3) I want to be able, in modules that use the type, 
> to add more components (with defaults) to the type:
> 
> This would avoid lengthy recomputations (at the cost of additional space).
> Imagine the difference between
> 
>     data Tree a = Node { key :: a, children :: [ Tree a ] }
>     size t = 1 + sum (map size (children t))
> 
> and
> 
>     data Tree a = Node { key :: a, children :: [ Tree a ]
> 			, size :: Integer
> 			, size = \ self -> 1 + sum (map size (children self)) }
> 
> when you have one large tree and frequently need sizes of subtrees.

And this too, but it's a bit tricky because a field changes the
type covariantly.

data Tree a = record
    key      :: a
    children :: [Tree a]
    children = []

-- A function working on a tree must be prepared for extensions.
-- The following function does not actually refer to the above type,
-- but can be used on Tree Int.

isInTree:: (Eq a, tree.key :: a, tree.children :: [tree])
         => a -> tree -> Bool
isInTree a tree = a == tree.key || any (isInTree a) tree.children

-- Trees extended by size cache. The type below does not refer to
-- the type Tree because the type of children has changed. Otherwise
-- it could include Tree as a field and delegate key and children to
-- this field instead of defining them itself. Well, it could do it,
-- but it would have to store children as SizedTrees somewhere too.
-- I don't know yet if it can be solved more elegantly.

data SizedTree a = record
    key      :: a
    children :: [SizedTree a]
    size     :: Int
    children = []
    size     = 1 + sum (map (.size) children)

-- Creation of a tree is the same for both kinds. A different kind of
-- context is needed to create a record than to extract its fields.
-- This context includes the context used in isInTree (except Eq a)
-- in its superclasses.

flatTree:: (tree.record {key :: a; children :: [tree]})
         => a -> [a] -> tree
flatTree root leaves = record
    key      = root
    children = [record key = leaf | leaf <- leaves]


I haven't written a complete description of the proposal yet, but
will do it in two weeks. I posted basic info here some time ago.
Some details changed since then.

-- 
 __("<  Marcin Kowalczyk * qrczak@knm.org.pl http://qrczak.ids.net.pl/
 \__/
  ^^                      SYGNATURA ZASTĘPCZA
QRCZAK