
Peter Jones wrote:
Actually, the problem is with your `symbolToConstructor' function. It needs to look like this:
symbolToConstructor :: (Foo a) => String -> a
Then symbolToInfixLevel can be:
symbolToInfixLevel :: String -> Int
Sorry, I have not been able to write an example with your proposition. Might you give more informations? In the meantime, I have been able to write a working example proposing two variants: ------------------------------ {-# LANGUAGE ScopedTypeVariables #-} data Exp = Plus Exp Exp | Minus Exp Exp | Atom String deriving Show class Foo a where symbolToConstructor :: String -> ( a -> a -> a ) infixLevel :: a -> Int -- The second argument is only used to indicate the type of the -- intermediary result (i.e. the type of the result of -- symbolToConstructor). symbolToInfixLevel :: String -> a -> Int symbolToInfixLevel s u = infixLevel $ (((symbolToConstructor s) undefined undefined)::a) instance Foo Exp where symbolToConstructor e = case e of "+" -> Plus "-" -> Minus infixLevel e = case e of Plus _ _ -> 6 Minus _ _ -> 7 main = do -- First variant print $ infixLevel $ (((symbolToConstructor "+") undefined undefined)::Exp) print $ infixLevel $ (((symbolToConstructor "-") undefined undefined)::Exp) -- Second variant print $ symbolToInfixLevel "+" (undefined::Exp) print $ symbolToInfixLevel "-" (undefined::Exp) ------------------------------