
Hi all, I have a type problem in my code which I dont know how to solve (and I'm not really sure why is caused). I have made a simplified example, can anyone have a look at it? Thanks in advance, The error is: Example.hs:24:47: Ambiguous type variable `a' in the constraint: `HDPrimType a' arising from use of `supplySig' at Example.hs:24:47-55 Probable fix: add a type signature that fixes these type variable(s) Here is the code --- module Example where data HDSignal a = HDSignal class HDPrimType a where class PortIndex a where class SourcePort s where -- Plug an external signal to the port plugSig :: (HDPrimType a, PortIndex ix) => ix -> s -> (HDSignal a -> b) -> b class DestPort d where -- Supply a signal to the port supplySig :: (PortIndex ix, HDPrimType a) => HDSignal a -> ix -> d -> d -- Connect providing indexes connectIx :: (SourcePort s, PortIndex six, DestPort d, PortIndex dix) => six -> s -> dix -> d -> d -- This can seem ugly, -- it would be easier for us having different types for plugSig and supplySig -- but the final user would find it much more difficult to deal with -- supplysig connectIx six s dix d = plugSig six s $ (push2 supplySig) dix d push2 :: (a -> b -> c -> d) -> b -> c -> a -> d push2 f = (\b c a -> f a b c)

I'll explain a little bit. Consider (show (read "13")). The compiler has no way to know what the type "a" produced by read should be. It must be an instance of (Read a) and (Show a), but the compiler cannot generate any actual code! Alfonso Acosta wrote:
Hi all,
I have a type problem in my code which I dont know how to solve (and I'm not really sure why is caused). I have made a simplified example, can anyone have a look at it?
Thanks in advance,
The error is:
Example.hs:24:47: Ambiguous type variable `a' in the constraint: `HDPrimType a' arising from use of `supplySig' at Example.hs:24:47-55 Probable fix: add a type signature that fixes these type variable(s)
Here is the code
I have further simplified the example, removing and reordering parameters.
--- module Example where
data HDSignal a = HDSignal
The above lets you use constructor HDSignal to create type (HDSignal a) for any type "a".
class HDPrimType a where class PortIndex a where
class SourcePort s where -- Plug an external signal to the port plugSig :: (HDPrimType a) => s -> (HDSignal a -> b) -> b
The above is odd, in that the plugSig can internally produce (HDPrimType a => HDSignal a) for any "a" that satisfies the constraint. Perhaps you want to use a functional dependency?
class SourcePort s a | s -> a where
Or perhaps you need an existential forall ?
plugSig :: s -> (forall a. HDPrimType a=> HDSignal a -> b) -> b
class DestPort d where -- Supply a signal to the port supplySig :: (PortIndex ix, HDPrimType a) => ix -> d -> HDSignal a -> d
The above is odd, in that the DestPort can take (HDPrimType a => HDSignal a) for any "a" that satisfies the constraint. Perhaps you really want the type "d" in (DestPort d) to imply a specific type "a" with a functional dependency?
class DestPort d a | d -> a where
Or perhaps you need a forall?
supplySig :: (PortIndex ix) => ix -> d -> (forall. HDPrimType a => HDSignal a) -> d
-- Connect providing indexes connectIx :: (SourcePort s, DestPort d, PortIndex dix) => s -> dix -> d -> d -- This can seem ugly, -- it would be easier for us having different types for plugSig and supplySig -- but the final user would find it much more difficult to deal with -- supplysig connectIx s dix d = plugSig s (supplySig dix d)
The above produced the error because the compiler has no clue what the type "a" is in the signatures for supplySig and plugSit.

Thanks for your answer, The functional dependencies solution doesn't
help because my instances cannot satisfy them (there are various
DestPort and SourcePort instances with are required to support various
HDSignals). I tried with existentials, but I'm still getting an error
(I'm not that comfortable working with existentials yet :)).
Example.hs:24:41:
Couldn't match expected type `forall a.
(HDPrimType a) =>
HDSignal a -> b'
against inferred type `(forall a. (HDPrimType a) => HDSignal a)
-> d'
In the second argument of `($)', namely `(push2 supplySig) dix d'
In the expression: (plugSig six s) $ ((push2 supplySig) dix d)
In the definition of `connectIx':
connectIx six s dix d = (plugSig six s) $ ((push2 supplySig) dix d)
Here is the code
module Example where
data HDSignal a = HDSignal
class HDPrimType a where
class PortIndex a where
class SourcePort s where
-- Plug an external signal to the port
plugSig :: (HDPrimType a, PortIndex ix) => ix -> s -> (forall
a.HDPrimType a => HDSignal a -> b) -> b
class DestPort d where
-- Supply a signal to the port
supplySig :: (PortIndex ix, HDPrimType a) => (forall a. HDPrimType a
=> HDSignal a) -> ix -> d -> d
-- Connect providing indexes
connectIx :: (SourcePort s, PortIndex six, DestPort d, PortIndex dix) =>
six -> s -> dix -> d -> d
-- This can seem ugly,
-- it would be easier for us having different types for plugSig and supplySig
-- but the final user would find it much more difficult to deal with
-- supplysig
connectIx six s dix d = plugSig six s $ (push2 supplySig) dix d
push2 :: (a -> b -> c -> d) -> b -> c -> a -> d
push2 f = (\b c a -> f a b c)
On 4/6/07, Chris Kuklewicz
I'll explain a little bit.
Consider (show (read "13")). The compiler has no way to know what the type "a" produced by read should be. It must be an instance of (Read a) and (Show a), but the compiler cannot generate any actual code!
Alfonso Acosta wrote:
Hi all,
I have a type problem in my code which I dont know how to solve (and I'm not really sure why is caused). I have made a simplified example, can anyone have a look at it?
Thanks in advance,
The error is:
Example.hs:24:47: Ambiguous type variable `a' in the constraint: `HDPrimType a' arising from use of `supplySig' at Example.hs:24:47-55 Probable fix: add a type signature that fixes these type variable(s)
Here is the code
I have further simplified the example, removing and reordering parameters.
--- module Example where
data HDSignal a = HDSignal
The above lets you use constructor HDSignal to create type (HDSignal a) for any type "a".
class HDPrimType a where class PortIndex a where
class SourcePort s where -- Plug an external signal to the port plugSig :: (HDPrimType a) => s -> (HDSignal a -> b) -> b
The above is odd, in that the plugSig can internally produce (HDPrimType a => HDSignal a) for any "a" that satisfies the constraint.
Perhaps you want to use a functional dependency?
class SourcePort s a | s -> a where
Or perhaps you need an existential forall ?
plugSig :: s -> (forall a. HDPrimType a=> HDSignal a -> b) -> b
class DestPort d where -- Supply a signal to the port supplySig :: (PortIndex ix, HDPrimType a) => ix -> d -> HDSignal a -> d
The above is odd, in that the DestPort can take (HDPrimType a => HDSignal a) for any "a" that satisfies the constraint.
Perhaps you really want the type "d" in (DestPort d) to imply a specific type "a" with a functional dependency?
class DestPort d a | d -> a where
Or perhaps you need a forall?
supplySig :: (PortIndex ix) => ix -> d -> (forall. HDPrimType a => HDSignal a) -> d
-- Connect providing indexes connectIx :: (SourcePort s, DestPort d, PortIndex dix) => s -> dix -> d -> d -- This can seem ugly, -- it would be easier for us having different types for plugSig and supplySig -- but the final user would find it much more difficult to deal with -- supplysig connectIx s dix d = plugSig s (supplySig dix d)
The above produced the error because the compiler has no clue what the type "a" is in the signatures for supplySig and plugSit.

Hello Alfonso, Friday, April 6, 2007, 9:33:45 PM, you wrote:
(I'm not that comfortable working with existentials yet :)).
probably you may benefit from looking at http://haskell.org/haskellwiki/OOP_vs_type_classes and original Wadler's paper mentioned there -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Alfonso Acosta wrote: I have a type problem in my code which I dont know how to solve
data HDSignal a = HDSignal class HDPrimType a where class PortIndex a where
class SourcePort s where -- Plug an external signal to the port plugSig :: (HDPrimType a, PortIndex ix) =>ix -> s ->(HDSignal a -> b) -> b
class DestPort d where -- Supply a signal to the port supplySig :: (PortIndex ix, HDPrimType a) => HDSignal a -> ix -> d -> d
-- Connect providing indexes connectIx :: (SourcePort s, PortIndex six, DestPort d, PortIndex dix) => six -> s -> dix -> d -> d connectIx six s dix d = plugSig six s $ (push2 supplySig) dix d
I'm afraid the example may be a bit too simplified. The first question: what is the role of the |HDPrimType a| constraint in plugSig and supplySig? Do the implementations of those functions invoke some methods of the class HDPrimType? Or the |HDPrimType a| constraint is just to declare that the parameter |a| of HDSignal is a member of HDPrimType? If it is the latter, that intention is better declared
data HDPrimType a => HDSignal a = HDSignal
Any function constructing the value HDSignal has to prove to the typechecker that the type |a| satisfied the HDPrimType constraint. Once we ensured that only properly constrained HDSignal can be constructed, the HDPrimType constraint can be removed from the signature of plugSig and supplySig, and the example compiles. It compiles because plugSig requires a supplicant that can process any HDSignal, and supplySig promises to be exactly this supplicant, which is able to process HDSignal without looking at it. With the original HDPrimType constraint, the meaning is the same. Although neither plugSig or supplySig care about which particular instance of HDPrimType is chosen, the typechecker must chose some instance. Alas, there is no information in the signature of connectIx to help the typechecker chose the instance. There is no defaulting. If plugSig and supplySig do use the methods of HDPrimType, one could use existentials:
data HDSignal' = forall a. HDPrimType a => HDSignal' (HDSignal a) class SourcePort s where plugSig :: (PortIndex ix) => ix -> s -> (HDSignal' -> b) -> b
class DestPort d where supplySig :: (PortIndex ix) => HDSignal' -> ix -> d -> d
That works too.

Hi oleg,
On 4/9/07, oleg@pobox.com
Alfonso Acosta wrote:
I have a type problem in my code which I dont know how to solve
data HDSignal a = HDSignal class HDPrimType a where class PortIndex a where
class SourcePort s where -- Plug an external signal to the port plugSig :: (HDPrimType a, PortIndex ix) =>ix -> s ->(HDSignal a -> b) -> b
class DestPort d where -- Supply a signal to the port supplySig :: (PortIndex ix, HDPrimType a) => HDSignal a -> ix -> d -> d
-- Connect providing indexes connectIx :: (SourcePort s, PortIndex six, DestPort d, PortIndex dix) => six -> s -> dix -> d -> d connectIx six s dix d = plugSig six s $ (push2 supplySig) dix d
I'm afraid the example may be a bit too simplified. The first question: what is the role of the |HDPrimType a| constraint in plugSig and supplySig? Do the implementations of those functions invoke some methods of the class HDPrimType?
Yes, I added the |HDPrimType a| constraint beacuse I realized I'm forced to call a function from that class withoin supplySig . Actually all the code was working smothly before adding the constraint which has been te cause of my problem.
Or the |HDPrimType a| constraint is just to declare that the parameter |a| of HDSignal is a member of HDPrimType?
Unfortunately not
If plugSig and supplySig do use the methods of HDPrimType, one could use existentials:
I tried the existential approach when it was previously suggested by Chris, but the problem is that, for some Source instances calling methods from HDPrimType within supplySig is not enough. Thus, it doesn't work with existentials due to their limitations. I'm definitively stuck wit this problem :S Cheers, Fons

Alfonso Acosta wrote:
I tried the existential approach when it was previously suggested by Chris, but the problem is that, for some Source instances calling methods from HDPrimType within supplySig is not enough. Thus, it doesn't work with existentials due to their limitations.
I see. The typechecker is right then: one can't write
supplySig :: (PortIndex ix, HDPrimType a) => HDSignal a -> ix -> d -> d
because supplySig is not parametric in 'a': supplySig needs to know more than just the membership of 'a' in HDPrimType. It needs a more refined constraint. So, the class hierarchy has to change, for example, as follows
data HDSignal a = HDSignal data HDSignal' d = forall a. DestPort' d a => HDSignal' (HDSignal a) class HDPrimType a where class PortIndex a where
class SourcePort s where -- Plug an external signal to the port plugSig :: (PortIndex ix, DestPort d) =>ix -> s -> (HDSignal' d -> b) -> b
class DestPort d where supplySig :: (PortIndex ix) => HDSignal' d -> ix -> d -> d supplySig (HDSignal' sig) = supplySig' sig
class HDPrimType a => DestPort' d a where -- Supply a signal to the port supplySig' :: (PortIndex ix) => HDSignal a -> ix -> d -> d
-- Connect providing indexes
connectIx :: (SourcePort s, PortIndex six, DestPort d, PortIndex dix) => six -> s -> dix -> d -> d connectIx six s dix d = plugSig six s $ (push2 supplySig) dix d
push2 :: (a -> b -> c -> d) -> b -> c -> a -> d push2 f = (\b c a -> f a b c)
participants (4)
-
Alfonso Acosta
-
Bulat Ziganshin
-
Chris Kuklewicz
-
oleg@pobox.com