[Solved] Getting type error for generic class

Hello, I’m attempting to create a straightforward example code that encapsulates a channel implementation.

Here is code:

{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE InstanceSigs #-}
{-# LANGUAGE TypeFamilies #-}

import Control.Concurrent

data HChan a = HChan { ch :: IO (Chan a) }

class Channable a where
  data Impl a :: *

  (-->) :: Impl a -> b -> IO () -- send

instance Channable (HChan a) where
  data Impl (HChan a) = ImplChan (HChan a)

  (-->) :: Impl (HChan a) -> a -> IO ()
  (ImplChan hchan) --> val = do
    ch <- ch hchan
    writeChan ch val

The error output:

    • Couldn't match expected type ‘forall b.
                                    Impl (HChan a) -> b -> IO ()’
                  with actual type ‘Impl (HChan a) -> a -> IO ()’
    • When checking that instance signature for ‘-->’
        is more general than its signature in the class
        Instance sig: Impl (HChan a) -> a -> IO ()
           Class sig: forall b. Impl (HChan a) -> b -> IO ()
      In the instance declaration for ‘Channable (HChan a)’
   |
23 |   (-->) :: Impl (HChan a) -> a -> IO ()

The method --> signature seems not illegal in my view.

  (-->) :: Impl a -> b -> IO ()                          -- class defnition
  (-->) :: Impl (HChan a) -> a -> IO ()           -- instance definition

I believed that the second type parameter b could align with the second type parameter a in the instance definition, but it appears the compiler does not share this view. Can anyone assist me with this issue?

Edit: I accidentally edited over my initial explanation oh well click the little pencil in the top right if you want to see it again.

Oh you can do something like

class Channable c where
  data Impl c a :: Type

  f :: Impl c a -> a -> IO ()

instance Channable [] where
  data Impl [] a = ImplChan ([] a)

  f :: Impl [] a -> a -> IO ()
  f (ImplChan as) a = void $ pure (a : as)

though I dunno if this is actually works right.

Why do a and b have to be distinct in your class definition? That’s what GHC is saying

You can think of it like this:

Because you have not mentioned any b anywhere else inside either the (-->) type signature, or the class definition class Channable a where, there’s no way to know what the b will be or can be, so GHC will infer you mean forall b, such that any implementation of (-->) will need to accept that b can’t be any specific type, but can be any type.

The only valid implementation in this case would ignore the b argument, as there’s nothing you can do with it without knowing more about it (i.e. there’s also no constraints on it telling you what methods you could use on the b).

So @eddiemundo 's solution might work better to show to GHC what the second argument might be, or you’d have to add the b to the class definition, making it Channable a b, but then you can define different Channable instances for different combinations of a and b.

Another solution might be to add a type family in the class:

class Channable a where
  data Impl a :: *
  type Event a :: *
  (-->) :: Impl a -> Event a -> IO () -- send

So that you can tell what the type should be in the instance declaration:


instance Channable (HChan a) where
  data Impl (HChan a) = ImplChan (HChan a)
  type Event (HChan a) = a
  (-->) :: Impl (HChan a) -> Event (HChan a) -> IO ()
  ImplChan hchan --> val = do
    chan <- ch hchan
    writeChan chan val
1 Like

Thank you! Helped a lot :slight_smile:

1 Like