[Haskell-cafe] type-class and subclasses

Dominik Schrempf dominik.schrempf at gmail.com
Thu Apr 10 03:23:02 UTC 2025


Hi!

I am not doing too much type-fu, but I think you can pull the type
variables into the class definitions so you can access them for adding
constraints when defining the instances. Then, you do not need any
special extension (GHC2021). I hope this helps! (I also separated your
Pair class into the Pair and CombinablePair classes).

Dominik

    import Prelude hiding (fst, snd)

    class Pair pt u v where
      fst :: pt u v -> u
      snd :: pt u v -> v

    class CombinablePair pt u v w where
      f :: pt u v -> pt v w -> pt u w

    class (Pair pt u v, Num u, u ~ v) => PairNum pt u v where
      total :: pt u v -> u

    --------
    -- Ptype

    data Ptype u v = ConsPtype !u !v deriving (Show)

    instance Pair Ptype u v where
      fst (ConsPtype x _) = x
      snd (ConsPtype _ y) = y

    instance CombinablePair Ptype u v w where
      f (ConsPtype a _) (ConsPtype _ d) = ConsPtype a d

    fromPairNum :: (Pair pt u v) => pt u v -> Ptype u v
    fromPairNum pn = ConsPtype (fst pn) (snd pn)

    ---------
    -- PNtype

    data PNtype u v = (Num u, Num v) => ConsPNtype !u !v

    instance Pair PNtype u v where
      fst (ConsPNtype x _) = x
      snd (ConsPNtype _ y) = y

    instance (u ~ v, v ~ w) => CombinablePair PNtype u v w where
      f (ConsPNtype a b) (ConsPNtype c d) = ConsPNtype (a + c) (b + d)

    instance (Num u, u ~ v) => PairNum PNtype u v where
      total (ConsPNtype x y) = x + y


lloyd allison <proflandy at gmail.com> writes:

> I have a general question:
> I would like to have a type-class C in which types that are instances of C have
> some type parameters and then a subclass S of C where some of the type
> parameters of an instance of S are more constrained in some way -- perhaps by
> being equal and/or being instances of some other class.
>
> I have an entirely artificial example (att.) that illustrates this situation and
> struggled (it's a while since I wrote much Haskell) to get it past the ghc type
> checker until stumbling across GADTs which do seem to do the trick, so I could
> leave it at that but...
>  ...I am very far from sure that this is the correct way to look at the problem
> and am hoping for some illumination.
>
> regards
> Lloyd.


More information about the Haskell-Cafe mailing list