fonction in a typeclass that does not mention the type variable

Hi, I have a simple test case containing a typeclass Foo with one type variable a. The goal is to write once and for all a function symbolToInfixLevel function that combines two other functions defined in the typeclass: ----------------------- class Foo a where symbolToConstructor :: String -> ( a -> a -> a ) infixLevel :: a -> Int symbolToInfixLevel :: String -> Int symbolToInfixLevel s = infixLevel $ (symbolToConstructor s) undefined undefined ----------------------- This yields an error because there is no "a" in the type signature for symbolToInfixLevel: $ runghc test_typeclass_without_typevariable.hs test_typeclass_without_typevariable.hs:1:1: The class method `symbolToInfixLevel' mentions none of the type variables of the class Foo a When checking the class method: symbolToInfixLevel :: String -> Int In the class declaration for `Foo' Now, if I define symbolToInfixLevel out of the typeclass: ----------------------- class Foo a where symbolToConstructor :: String -> ( a -> a -> a ) infixLevel :: a -> Int symbolToInfixLevel :: String -> Int symbolToInfixLevel s = infixLevel $ (symbolToConstructor s) undefined undefined ----------------------- Now, I obtain: $ runghc test_typeclass_without_typevariable.hs test_typeclass_without_typevariable.hs:7:24: No instance for (Foo a0) arising from a use of `infixLevel' In the expression: infixLevel In the expression: infixLevel $ (symbolToConstructor s) undefined undefined In an equation for `symbolToInfixLevel': symbolToInfixLevel s = infixLevel $ (symbolToConstructor s) undefined undefined How to get rid from this situation? Thanks in advance, TP

Maybe I don't fully understand what you are trying to achieve, but I don't
think what you are trying to do makes sense. infixLevel and
symbolToConstructor will have different implementations for each instance
of Foo, and the compiler cannot possibly know which implementations you
mean. If the implementation of symbolToInfixLevel is independent of the
implementations of infixLevel and symbolToConstructor then it shouldn't
need them in its definition.
Peter
On 21 August 2013 17:39, TP
Hi,
I have a simple test case containing a typeclass Foo with one type variable a. The goal is to write once and for all a function symbolToInfixLevel function that combines two other functions defined in the typeclass:
----------------------- class Foo a where
symbolToConstructor :: String -> ( a -> a -> a ) infixLevel :: a -> Int
symbolToInfixLevel :: String -> Int symbolToInfixLevel s = infixLevel $ (symbolToConstructor s) undefined undefined -----------------------
This yields an error because there is no "a" in the type signature for symbolToInfixLevel:
$ runghc test_typeclass_without_typevariable.hs test_typeclass_without_typevariable.hs:1:1: The class method `symbolToInfixLevel' mentions none of the type variables of the class Foo a When checking the class method: symbolToInfixLevel :: String -> Int In the class declaration for `Foo'
Now, if I define symbolToInfixLevel out of the typeclass:
----------------------- class Foo a where
symbolToConstructor :: String -> ( a -> a -> a ) infixLevel :: a -> Int
symbolToInfixLevel :: String -> Int symbolToInfixLevel s = infixLevel $ (symbolToConstructor s) undefined undefined -----------------------
Now, I obtain:
$ runghc test_typeclass_without_typevariable.hs test_typeclass_without_typevariable.hs:7:24: No instance for (Foo a0) arising from a use of `infixLevel' In the expression: infixLevel In the expression: infixLevel $ (symbolToConstructor s) undefined undefined In an equation for `symbolToInfixLevel': symbolToInfixLevel s = infixLevel $ (symbolToConstructor s) undefined undefined
How to get rid from this situation?
Thanks in advance,
TP
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

Peter Hall wrote:
Maybe I don't fully understand what you are trying to achieve, but I don't think what you are trying to do makes sense. infixLevel and symbolToConstructor will have different implementations for each instance of Foo, and the compiler cannot possibly know which implementations you mean.
Indeed, my question was stupid. This is obvious in the second implementation (which instance to choose?), and it is also true in the first one because even if symbolToInfixLevel of one considered instance uses infixLevel and symbolToConstructor of this same instance (what I am not sure of), at the location where I use this function the compiler cannot known which instance I mean.
If the implementation of symbolToInfixLevel is independent of the implementations of infixLevel and symbolToConstructor then it shouldn't need them in its definition.
No, they are not independent: it is really a function that "composes" functions infixLevel and symbolToConstructor. See my proposition in my answer to Peter Jones.

TP
symbolToInfixLevel :: String -> Int symbolToInfixLevel s = infixLevel $ (symbolToConstructor s) undefined
Now, I obtain:
$ runghc test_typeclass_without_typevariable.hs test_typeclass_without_typevariable.hs:7:24: No instance for (Foo a0) arising from a use of `infixLevel' In the expression: infixLevel In the expression: infixLevel $ (symbolToConstructor s) undefined undefined In an equation for `symbolToInfixLevel': symbolToInfixLevel s = infixLevel $ (symbolToConstructor s) undefined undefined
How to get rid from this situation?
Your `symbolToConstructor' function is too specific for both cases you describe. You'd need to change the `String' argument to `a' and put it back in the type class or write it like this: symbolToInfixLevel :: (Foo a) => a -> Int symbolToInfixLevel s = infixLevel $ (symbolToConstructor s) undefined -- Peter Jones, Founder, Devalot.com Defending the honor of good code

Peter Jones
Your `symbolToConstructor' function is too specific for both cases you describe. You'd need to change the `String' argument to `a' and put it back in the type class or write it like this:
symbolToInfixLevel :: (Foo a) => a -> Int symbolToInfixLevel s = infixLevel $ (symbolToConstructor s) undefined
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 -- Peter Jones, Founder, Devalot.com Defending the honor of good code

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) ------------------------------
participants (3)
-
Peter Hall
-
Peter Jones
-
TP