[Haskell-beginners] Re: Data.Tree computation

Heinrich Apfelmus apfelmus at quantentunnel.de
Fri Feb 12 05:48:00 EST 2010


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



More information about the Beginners mailing list