Beginners problem with the type system

Dear Hasekellers, I am trying to build some abstractions on top of the module Control.Concurrent and run into a problem with the type system that I do not understand. In particular, I want to define two classes 'Channel' and 'Port' (see below) that define a common interface for several concrete implementations with different synchronization characteristics. The following code is a simplified excerpt that demonstrates the problem:
module Main where import Control.Concurrent.MVar
class Channel c where port :: Port p => c a -> IO (p a)
class Port p where take :: p a -> IO a put :: p a -> a -> IO ()
The problem arises when I instantiate the 'Channel' class and implement the 'port' function.
data C a = C (P a) instance Channel C where port (C p) = return p
Couldn't match expected type `p' (a rigid variable) against inferred type `P' `p' is bound by the type signature for `port' Expected type: p a Inferred type: P a In the first argument of `return', namely `p' In the expression: return p I am quite new to Haskell and my knowledge of how the type system works is fairly limited. Any help on this particular problem will be greatly appreciated, but any pointers to reading material that brings me closer to enlightenment are also very welcome. Thanks, Henrik
newC = do p <- newP return (C p)
data P a = P (MVar a)
newP = do v <- newEmptyMVar return (P v)
instance Port P where take (P mv) = takeMVar mv
main = do c <- newC p <- port c put p 1

On Mon, Oct 22, 2007 at 08:02:20PM +0200, Henrik Tramberend wrote:
Dear Hasekellers,
I am trying to build some abstractions on top of the module Control.Concurrent and run into a problem with the type system that I do not understand.
In particular, I want to define two classes 'Channel' and 'Port' (see below) that define a common interface for several concrete implementations with different synchronization characteristics.
The following code is a simplified excerpt that demonstrates the problem:
module Main where import Control.Concurrent.MVar
class Channel c where port :: Port p => c a -> IO (p a)
This type signature means that 'port' is return type overloaded - it can return ANY kind of port, and the caller gets to choose. Which I don't think is what you want. A possible solution is to hide the nature of the port, and use a record of functions: data Port a = Port { put :: a -> IO (), get :: IO a } class Channel c where port :: c a -> Port a Another possible approach, if it is vital for clients to know the nature of the port: class Port (PortOf c) => Channel c where type PortOf c :: * -> * port :: c a -> PortOf c a class Port p where get :: p a -> IO a put :: p a -> a -> IO () (Requires type family extension in GHC 6.8; an equivalent formulation using the older (2000) functional dependancies is possible) Stefan

On 22. Oct 2007, at 20:16 , Stefan O'Rear wrote:
This type signature means that 'port' is return type overloaded - it can return ANY kind of port, and the caller gets to choose. Which I don't think is what you want.
True.
(Requires type family extension in GHC 6.8; an equivalent formulation using the older (2000) functional dependancies is possible)
Thanks for mentioning functional dependencies. I tied together the C and the P types like this:
class Channel c p | c -> p where port :: c a -> IO (p a)
data C a = C (P a)
instance Channel C P where port (C p) = return p
Which works nicely. Thanks, Henrik

Hello Henrik, Monday, October 22, 2007, 10:02:20 PM, you wrote:
In particular, I want to define two classes 'Channel' and 'Port' (see below) that define a common interface for several concrete implementations with different synchronization characteristics.
may be this my code will be useful for you: class PipeElement e where getP :: e a -> IO a putP :: e a -> a -> IO () instance PipeElement MVar where getP = takeMVar putP = putMVar instance PipeElement Chan where getP = readChan putP = writeChan data PairFunc a = PairFunc (IO a) (a -> IO ()) instance PipeElement PairFunc where getP (PairFunc get_f put_f) = get_f putP (PairFunc get_f put_f) = put_f -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com
participants (3)
-
Bulat Ziganshin
-
Henrik Tramberend
-
Stefan O'Rear