G. Elia Jergensen
G. Elia Jergensen

Reputation: 23

Annotating ambiguous type variable for MultiParamTypeClasses

I am working with a type class where I can "measure" some property of type v on an object of type a. For instance, consider the definitions below:

{-# LANGUAGE MultiParamTypeClasses #-}

data SizedElem a =
  SizedElem
    { getSize :: Size
    , getElem :: Elem a
    }

newtype Size =
  Size Integer

newtype Elem a =
  Elem a

class Measured a v where
  measureTypeClass :: a -> v

instance Measured (Elem a) (SizedElem a) where
  measureTypeClass (Elem a) = SizedElem (Size 1) (Elem a)

Attempting to combine the functions for measuring the element and then extracting the size like so

broken :: Elem a -> Size
broken = getSize . measureTypeClass

results in a complaint from GHC:

Ambiguous type variable ‘a0’ arising from a use of ‘measureTypeClass’
prevents the constraint ‘(Measured
                            (Elem a) (SizedElem a0))’ from being solved.
...
Probable fix: use a type annotation to specify what ‘a0’ should be.
These potential instance exist:
  instance Measured (Elem a) (SizedElem a)

Naively, I simply tried to annotate the type which I expect in the middle:

broken' :: Elem a -> Size
broken' xs =
  let meas = measureTypeClass xs :: SizedElem a
   in getSize meas

However, this results in a slightly different error:

No instance for (Measured (Elem a) (SizedElem a2))
  arising from a use of ‘measureTypeClass’
In the expression: measureTypeClass xs :: SizedElem a
In an equation for ‘meas’:
    meas = measureTypeClass xs :: SizedElem a

If I understand correctly, this means that the a interpreted from the annotation :: SizedElem a is not same type as the one in the type signature. How can I tell the compiler that these should be the same type variable? Simply applying {-# LANGUAGE ScopedTypeVariables #-} didn't solve the problem.

As an aside, everything works fine for a particular type, e.g.

specificWorks :: Elem Char -> Size
specificWorks xs =
  let meas = measureTypeClass xs :: SizedElem Char
   in getSize meas

or if the type signature has the same type variable for both the input and output

elemWorks :: Elem a -> Elem a
elemWorks = getElem . measureTypeClass

Additionally, forgoing the type class entirely also works, but for my actual application, I need the type class for other reasons:

measureDirect :: Elem a -> SizedElem a
measureDirect (Elem a) = SizedElem (Size 1) (Elem a)

directWorks :: Elem a -> Size
directWorks = getSize . measureDirect

Upvotes: 2

Views: 65

Answers (1)

Li-yao Xia
Li-yao Xia

Reputation: 33464

To use the extension ScopedTypeVariables, add a forall quantifier to the function's signature:

getSize' :: forall a. Elem a -> Size
getSize' xs =
  let meas = measureTypeClass xs :: SizedElem a
  in getSize meas

Another technique that's applicable here is the "constraint trick". A rule of thumb is to never have an instance head (to the right of =>) where a variable occurs twice, and to use an equality constraint instead.

instance (a ~ b) => Measured (Elem a) (SizedElem b) where
  measureTypeClass (Elem a) = SizedElem (Size 1) (Elem a)

Upvotes: 4

Related Questions