[Haskell-beginners] Data.Tree computation
Stephen Tetley
stephen.tetley at gmail.com
Fri Feb 12 05:48:57 EST 2010
Hello
One idiom is to avoid Data.Tree unless you really have a "rose tree" -
Haskell's algebraic data types model trees.
Note this one is a binary tree rather than a "rose tree" - _plus_
doesn't work quite the same as it did in your original.
(+ 1 2 3 4) == (+ 1 (+ 2 (+ 3 4)))
data Val = VInt Int
| VDbl Double
deriving (Eq,Ord,Show)
data Op = Plus | Minus | Mult | Div
deriving (Eq,Ord,Show)
-- Note this is a binary tree
-- Data.Tree is a "rose tree"
data Tree = Tree { operator :: Op
, left_branch :: Tree
, right_branch :: Tree }
| Leaf { value :: Val }
deriving (Eq,Show)
-- Or whithout field labels:
-- data Tree = Tree Op Tree Tree
-- | Leaf Val
calc :: Tree -> Double
calc (Leaf v) = val v
calc (Tree Plus l r) = calc l + calc r
calc (Tree Minus l r) = calc l - calc r
calc (Tree Mult l r) = calc l * calc r
calc (Tree Div l r) = calc l / calc r
val :: Val -> Double
val (VInt i) = fromIntegral i
val (VDbl d) = d
-- "wrapped" constructors
dblLeaf :: Double -> Tree
dblLeaf d = Leaf $ VDbl d
intLeaf :: Int -> Tree
intLeaf i = Leaf $ VInt i
-- simulates: (+ a b c ... n)
--
plus :: [Tree] -> Tree
plus [] = error "Bad plus"
plus [a] = a
plus (a:as) = Tree Plus a (plus as)
-- (/ (+ 5 5 (- 10 100)) 10) - calc Should return -8.0
aTree :: Tree
aTree = Tree Div (plus [ intLeaf 5
, intLeaf 5
, Tree Minus (intLeaf 10) (intLeaf 100) ])
(intLeaf 10)
demo1 = calc aTree
-----------------------------------------------------------------
Once you've made the tree type concrete there are other variations you
can consider.
E.g, a polymorphic tree - leaf type is a parameter:
data Tree a = Tree Op (Tree a) (Tree a)
| Leaf a
deriving (Eq,Show)
Or you could really wanted a multiple argument plus:
data Op2 = Minus' | Mult' | Div'
deriving (Eq,Ord,Show)
data Tree2 = Tree Op2 Tree Tree
| MultiPlus [Tree]
| Leaf Val
... although once things start going irregular, they often cause problems later.
Best wishes
Stephen
More information about the Beginners
mailing list