
Hi guys, I've tried to use Data.Tree as a computation tree (each node is numerical function, each leaf is a terminal) It kinda works, but the code seems very verbose. How can it made more concise ? I am sure I missed a lot of shortcuts and idioms. -- file t.hs import qualified Data.Tree as T data Term = TInt Int| TDouble Double deriving (Show, Eq) data Func = Plus | Minus | Mult | Div deriving (Show, Eq) data ANode = GFunc Func | GTerm Term deriving (Show, Eq) fNode :: Func -> T.Forest ANode-> T.Tree ANode fNode f = T.Node (GFunc f) tNode:: Term -> T.Tree ANode tNode t = T.Node (GTerm t) [] calc :: T.Tree ANode -> Double calc (T.Node (GTerm (TInt n))[]) = fromIntegral n :: Double calc (T.Node (GFunc Plus) xs ) = foldl1 (+) (map calc xs) calc (T.Node (GFunc Minus) xs ) = foldl1 (-) (map calc xs) calc (T.Node (GFunc Mult) xs ) = foldl1 (*) (map calc xs) calc (T.Node (GFunc Div) xs ) = foldl1 (/) (map calc xs) -- (/ (+ 5 5 (- 10 100)) 10) - calc Should return -8.0 aTree = fNode Div [fNode Plus [tNode $ TInt 5,tNode $ TInt 5, fNode Minus [tNode $ TInt 10,tNode $ TInt 100]], tNode (TInt 10)] Regards, Gabi http://bugspy.net

Gabi wrote:
I've tried to use Data.Tree as a computation tree (each node is numerical function, each leaf is a terminal) It kinda works, but the code seems very verbose. How can it made more concise ? I am sure I missed a lot of shortcuts and idioms.
-- file t.hs import qualified Data.Tree as T
data Term = TInt Int| TDouble Double deriving (Show, Eq)
data Func = Plus | Minus | Mult | Div deriving (Show, Eq)
data ANode = GFunc Func | GTerm Term deriving (Show, Eq)
fNode :: Func -> T.Forest ANode-> T.Tree ANode fNode f = T.Node (GFunc f)
tNode:: Term -> T.Tree ANode tNode t = T.Node (GTerm t) []
calc :: T.Tree ANode -> Double calc (T.Node (GTerm (TInt n))[]) = fromIntegral n :: Double calc (T.Node (GFunc Plus) xs ) = foldl1 (+) (map calc xs) calc (T.Node (GFunc Minus) xs ) = foldl1 (-) (map calc xs) calc (T.Node (GFunc Mult) xs ) = foldl1 (*) (map calc xs) calc (T.Node (GFunc Div) xs ) = foldl1 (/) (map calc xs)
How about calc :: T.Tree ANode -> Double calc (T.Node (GTerm sym) []) = term sym where term (TInt n) = fromIntegral n term (TDouble d) = d calc (T.Node (GFunc sym) xs) = foldl1 (op sym) (map calc xs) where op Plus = (+) op Minus = (-) op Mult = (*) op Div = (/) By the way, Data.Tree is not used very often, people usually roll their own syntax trees because it's so easy. data Expr = V Value | App Fun [Expr] data Value = VInt Int | VDouble Double data Fun = Plus | Minus | Mult | Div eval :: Expr -> Double eval (V (VInt n)) = fromIntegral n eval (V (VDouble d)) = d eval (App sym xs ) = foldl1 (op sym) (map eval xs) where op Plus = ... Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com

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

The reason I wanted to use Data.Tree instead of my own is that I hoped to serliaze it using Data.Binary (which supposed to support Data.Tree) Alas, It doesn't work. Need to figure it out yet.. *Main Data.Binary Data.Tree> :m +Data.Binary *Main Data.Binary Data.Tree> encode aTree <interactive>:1:0: No instance for (Binary ANode) arising from a use of `encode' at <interactive>:1:0-11 Possible fix: add an instance declaration for (Binary ANode) In the expression: encode aTree In the definition of `it': it = encode aTree -- Regards, Gabi http://bugspy.net

Hello Gabi
The docs for Data.Binary use a binary tree as an example - see about
half way down the page...
http://hackage.haskell.org/packages/archive/binary/0.5.0.2/doc/html/Data-Bin...
On 12 February 2010 14:30, Gabi
The reason I wanted to use Data.Tree instead of my own is that I hoped to serliaze it using Data.Binary (which supposed to support Data.Tree) Alas, It doesn't work. Need to figure it out yet..
participants (3)
-
Gabi
-
Heinrich Apfelmus
-
Stephen Tetley