[Haskell-cafe] Trying to implement this code

Scott Turner p.turner at computer.org
Mon Apr 18 23:15:15 EDT 2005


On 2005 April 18 Monday 16:57, Dmitry Vyal wrote:
> Am not sure about the relevance of this approach as i have very little
> experience with Haskell and FP. So it would be great if someone offers
> better solution.
It's a valid approach.  Rather than declare an Updateable class, I'd just have 
the update function be a parameter of ins_in_tree.  Also, the key and value 
types can be independent parameters of BinTree.

> Why doesnt translator automatically deduce constraints in type of
> ins_in_tree and flat_tree functions so i need to explicitly define them?
It deduces not just the constraints, but the entire type. You don't have to 
state the types of ins_in_tree or flat_tree at all.   The following types are 
distinct
    (Ord a, Updateable a) => BinTree a -> a -> BinTree a
    BinTree a -> a -> BinTree a
because the latter type has no constraints, and names having the latter type 
can be used in more contexts than the former.  If
    foo :: BinTree a -> a -> BinTree a
meant that foo might or might not have constraints, then there would be no way 
to tell the translator that foo has no constraints.

> ---------------
> data (Ord a, Updateable a) => BinTree a =
>      Leaf | Node (BinTree a) a (BinTree a)
>
> class Updateable a where
>      update :: a -> a
>
> data Word_stat = Word_stat String Int deriving Show
>
> instance Eq (Word_stat) where
>      (==) (Word_stat s1 _) (Word_stat s2 _) = s1 == s2
>
> instance Ord (Word_stat) where
>      (Word_stat s1 _) < (Word_stat s2 _) = s1<s2
>
> instance Updateable (Word_stat) where
>      update (Word_stat s i) = Word_stat s (i+1)
> -- inserts new element in the tree or updates existing one
> ins_in_tree :: (Ord a, Updateable a) => BinTree a -> a -> BinTree a
> ins_in_tree Leaf el = Node Leaf el Leaf
> ins_in_tree (Node left cur right) el
>
>      | el < cur = Node (ins_in_tree left el) cur right
>      | el == cur = Node left (update cur) right
>      | otherwise = Node left cur (ins_in_tree right el)
>
> -- loads list of strings in the tree
> ins_list :: [String] -> BinTree Word_stat
> ins_list lst = foldl ins_in_tree  Leaf (map wrap lst)
>      where wrap :: String -> Word_stat
> 	  wrap s = Word_stat s 1
> --traverses the tree
> flat_tree :: (Ord a, Updateable a) => BinTree a -> [a]
> flat_tree Leaf = []
> flat_tree (Node left el right) =
>      (flat_tree left) ++ [el] ++ (flat_tree right)
>
> -- function you probably need
> summary :: [String] -> [Word_stat]
> summary lst  = flat_tree $ ins_list lst


More information about the Haskell-Cafe mailing list