I've got a prob with the Function toHeap. It return an argument with an undefined type. Well, I think that's got something to do with why I can`t get it to work. OK, for it's input, it takes a list of some datatype, so I try at the hugs console.... toHeap "hello" ERROR - Unresolved overloading *** Type : Heap a => a Char *** Expression : toHeap "hello" How do I get round this prob? The fact that this code compiles fine, makes me think that it's me not using it right, rather than the code not being right *** module Heap where class Heap h where empty :: Ord a => h a isEmpty :: Ord a => h a -> Bool insert :: Ord a => a -> h a -> h a merge :: Ord a => h a -> h a -> h a findMin :: Ord a => h a -> Maybe a deleteMin :: Ord a => h a -> h a toHeap :: (Ord a, Heap h) => [a] -> h a toHeap xs = foldr insert empty xs data Way = L | R deriving (Eq, Show) data Tree a = Nil | Node Way a (Tree a) (Tree a) deriving Show isNil :: Tree a -> Bool isNil Nil = True isNil _ = False isNode :: Tree a -> Bool isNode = not . isNil leftSub :: Tree a -> Tree a leftSub Nil = error "leftSub" leftSub (Node _ _ lt _) = lt rightSub :: Tree a -> Tree a rightSub Nil = error "rightSub" rightSub (Node _ _ _ rt) = rt root :: Tree a -> a root Nil = error "root" root (Node _ v _ _) = v insTree :: Ord a => a -> Tree a -> Tree a insTree val Nil = Node L val Nil Nil -- L is an arbitrary choice insTree val (Node way v lt rt) | v==val = Node way v lt rt -- no change, value in tree | val < v = if (way==L) then Node R val (insTree v lt) rt else Node L val lt (insTree v rt) | v < val = if (way==L) then Node R v (insTree val lt) rt else Node L v lt (insTree val rt) minTree :: Ord a => Tree a -> Maybe a minTree t | isNil t = Nothing | otherwise = Just(root t) deleteM :: Ord a => Tree a -> Tree a deleteM Nil = error "deleteM" deleteM (Node _ _ lt rt) = join lt rt join :: Ord a => Tree a -> Tree a -> Tree a join t Nil = t join Nil t = t join lt@(Node way1 v1 lt1 rt1) rt@(Node way2 v2 lt2 rt2) | v1 <= v2 = Node L v1 lt1 (join rt1 rt) | v2 < v1 = Node R v2 (join lt lt2) rt2 --instance (Show a) => Show (Tree a) where -- show Tree Nil = "as" instance Heap Tree where empty = Nil isEmpty = isNil insert = insTree merge = join findMin = minTree deleteMin = deleteM __________________________________________________ Yahoo! Plus For a better Internet experience http://www.yahoo.co.uk/btoffer
James Grist writes: | I've got a prob with the Function toHeap. It return an | argument with an undefined type. Well, I think that's | got something to do with why I can`t get it to work. | OK, for it's input, it takes a list of some datatype, | so I try at the hugs console.... | | toHeap "hello" | | ERROR - Unresolved overloading | *** Type : Heap a => a Char | *** Expression : toHeap "hello" | | How do I get round this prob? Say which Heap instance you want. It won't automatically default to Tree, even though that's the only Heap instance in scope. toHeap "hello" :: Tree Char
participants (2)
-
James Grist -
Tom Pledger