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



_______________________________________________
Haskell-Cafe mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to