-- Inspired by Chris Okasaki's reference to Ross Patterson's AVL
-- trees as a nested datatype, here are (I think) red-black trees
-- as a nested datatype.
-- ref: http://www.haskell.org/pipermail/haskell/2003-April/011693.html

module RedBlackTree where

{-
 Red-black trees satisfy the following conditions,
 according to Wikipedia:

  1. A node is either red or black.
  2. The root is black.
  3. All leaves are black.
  4. Both children of every red node are black.
  5. Every simple path from a node to a descendant leaf contains the
     same number of black nodes.
-}

data Node a n = Node n a n


{- a is the carrier type: the type of the values contained in the
  nodes.
  r0 and b0 are red and black trees with one more level of black
  nodes than r1 and b1.
-}
data Tree a r0 b0 r1 b1 =
   Zero b1 -- The top node of a tree is black
   -- We recurse by adding one to the number of levels of black nodes
 | Succ (Tree a
                {- Red trees have black children and reduce the count
                   of black nodes to the descendent leaves by 0 -}
                (Node a b0)
                {- Black trees have children of either color and reduce
                   the count of black nodes to the descendent leaves by 1 -}
                (Node a (Either r1 b1))
                r0
                b0)

-- The type for black-rooted trees with two levels of black nodes.
type Black2 a  = Node a (Maybe a)

type RedBlackTree a =
   Tree a
   -- A red tree with two levels of black nodes is just a red node on
   -- top of two black nodes.
   (Node (Black2 a) a) (Black2 a) a ()

-- Jim Apple
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to