Factory function

From HaskellWiki
Revision as of 22:44, 2 December 2006 by Mgsloan (talk | contribs)
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.

If you need more intelligence from your constructor functions, use a real function instead. Also known as smart constructors.

Examples

Expression type

Consider the following data type:

data Expr = EAdd Expr Expr | EMult Expr Expr | EInt Int | EVar String

Keeping an expression in a relatively simplified form can be difficult if it is modified a lot. One simple way is to write replacements for the constructor functions:

eInt i = EInt i

eAdd (EInt i1) (EInt i2) = eInt (i1+i2)
eAdd (EInt 0)  e2        = e2
eAdd e1        (EInt 0)  = e1
eAdd e1        e2        = EAdd e1 e2

eMult (EInt 0) e2        = eInt 0
{- etc -}

Then if you need to construct an expression, use the factory functions:

derivative :: String -> Expr -> Expr
derivative x (EMult e1 e2)
  = eAdd (eMult (derivative x e1) e2) (eMult e1 (derivative x e2))
{- etc -}

This is actually a special kind of worker wrapper where the wrapper does more work than the worker.

The factory function idiom is especially useful when you have a data structure with invariants that you need to preserve, such as a binary search tree which needs to stay balanced.

User:AndrewBromage

Red-black trees example

This form of balanced tree is a perfect example of the use of this idiom. The type declaration for a Red-Black tree is:

data Colour = R | B
	      deriving (Eq, Show, Ord)

data RBSet a = Empty |
	     RBTip Colour (RBSet a) a (RBSet a)
		   deriving Show

However, this must satisfy these invariants:

  1. The children of a red node are black.
  2. There are the same number of black nodes on every path from root to leaf.

To do this, we create a factory function, balance that ensures the invariants are met.

balance :: Colour -> RBSet a -> a -> RBSet a -> RBSet a
balance B (RBTip R (RBTip R a x b) y c) z d 
	= RBTip R (RBTip B a x b) y (RBTip B c z d)
balance B (RBTip R a x (RBTip R b y c)) z d 
	= RBTip R (RBTip B a x b) y (RBTip B c z d)
balance B a x (RBTip R (RBTip R b y c) z d) 
	= RBTip R (RBTip B a x b) y (RBTip B c z d)
balance B a x (RBTip R b y (RBTip R  c z d)) 
	= RBTip R (RBTip B a x b) y (RBTip B c z d)
balance c a x b = RBTip c a x b

(See Red-black trees in a functional setting by Chris Okasaki)

See also