[Haskell-cafe] Type error
Alfonso Acosta
alfonso.acosta at gmail.com
Fri Apr 6 12:11:13 EDT 2007
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)
More information about the Haskell-Cafe
mailing list