Concrete view

From HaskellWiki
Revision as of 02:22, 4 January 2008 by AndrewBromage (talk | contribs)
(diff) ← Older revision | Latest revision (diff) | Newer revision → (diff)
Jump to navigation Jump to search
The printable version is no longer supported and may have rendering errors. Please update your browser bookmarks and please use the default browser print function instead.

It is sometimes not obvious how to implement an operation on some data structure. Using an intermediate concrete data type can help simplify the case analysis.


Simple example - complex numbers

Suppose you're implementing complex numbers (which you wouldn't do, since it's already in the standard library):

data Complex = Complex Double Double

instance Num Complex where
    (Complex r1 i1) + (Complex r2 i2) = Complex (r1+r2) (i1+i2)
    {- etc etc -}

Some operations (e.g. complex roots) are easier in polar form. So make a "view" of your complex number type which projects the numbers into polar form:

data ComplexPolarView = ComplexPolarView Double Double

complexPolarView :: Complex -> ComplexPolarView
complexPolarView (Complex r i) = {- detail omitted -}

operationThatWouldBeEasierInPolarForm :: Complex -> Something
operationThatWouldBeEasierInPolarForm c
    = case complexPolarView c of
        ComplexPolarView radius theta -> {- whatever -}

Use as a design tool

The technique is also valuable as a design tool. While trying to work out how a data type should be implemented, appropriate use of concrete views can help streamline the design process.

A good example of this is due to User:RalfHinze in his paper, A fresh look at binary search trees. He notes that binary search tree deletion is much more difficult than insertion. His solution is to use a concrete view of the tree which simplifies the operation, and as a result, comes up with a new representation which makes the operation much easier to understand.

Here is a simple binary search tree type:

data Tree a = Leaf | Branch (Tree a) a (Tree a)

Suppose that we had a view of the binary search tree which looked like this:

data TreeView a
    = EmptyTree
    | SingletonTree a
    | ConsTree (Tree a) (Tree a)

treeView :: Tree a -> TreeView a

And the following operations:

-- Return the maximum value in the tree
treeMax :: Tree a -> a

-- These are the "converses" of the TreeView
emptyTree :: Tree a
singletonTree :: a -> Tree a
consTree :: Tree a -> Tree a -> Tree a

(The "converse" operations are basically smart constructors.)

Then you can implement tree insertion like this:

insert :: (Ord a) => a -> Tree a -> Tree a
insert x t
    = case treeView t of
        EmptyTree   -> singletonTree x
        SingletonTree a
            | x < a   -> consTree (singletonTree x) (singletonTree a)
            | x == a  -> singletonTree x
            | x > a   -> consTree (singletonTree a) (singletonTree x)
        ConsTree l r
            | x < treeMax l -> consTree (insert x l) r
            | otherwise     -> consTree l (insert x r)

And you could implement tree deletion like this:

delete :: (Ord a) => a -> Tree a -> Tree a
delete x t
    = case treeView t of
        EmptyTree -> emptyTree
        SingletonTree a
            | x == a    -> emptyTree
            | otherwise -> singletonTree a
        ConsTree l r
            | x <= treeMax l -> consTree (delete x l) r
            | otherwise      -> consTree l (delete x r)


Implementing the view and the operations in terms of Tree is straightforward, and it allows you to start with a simple data structure and make it more sophisticated as needed. With the view, you can change the implementation of Tree without the algorithms changing. Basically, you're using an abstract data type within a module at the micro-design level.

Once the algorithms have stabilised, then you can change your implementation (here of Tree) to be optimised for the view and operations and refactor out the abstraction layer if you want.

In this case, redesigning the data structure is simple. Simply pull the maximum element out to the top level:

data Tree a
    = Empty
    | NonEmpty (Tree' a) a

data Tree' a
    = Leaf
    | Branch (Tree' a) a (Tree' a)

treeView :: Tree a -> TreeView a
treeView Empty = EmptyTree
treeView (NonEmpty Leaf a) = SingletonTree a
treeView (NonEmpty (Branch l x r) a) = ConsTree (NonEmpty l x) (NonEmpty r a)

maxTree :: Tree a -> a
maxTree (NonEmpty _ a) = a

-- Implementing emptyTree, singletonTree and consTree are left as an exercise

The TreeView data structure can then be refactored out if desired.

As part of a module interface

Concrete views are also valuable at the module interface level. Rather than providing a number of accessor functions to get data out of some type...

module Complex (
    Complex,
    -- stuff omitted
    radius, theta
) where

radius :: Complex -> Double
theta :: Complex -> Double

{- etc etc -}

...provide a concrete view instead.

module Complex (
    Complex,
    -- stuff omitted
    ComplexPolarView(..),
    complexPolarView
) where

{- etc etc -}

Efficiency

View operations are excellent candidates for declaring inline.

Remember that Haskell data structures are lazily evaluated. Only as much of the view as the client needs will actually be computed, and if there is any shared work between different parts of the view, it will only be computed once. Accessor functions, by comparison, may do strictly more work than views.

History

Views were briefly considered as a language extension, but never really caught on. A more recent proposal is the View Pattern proposal.

User:AndrewBromage