Search code examples
haskellreflex

How do you define a Haskell typeclass with a type that cannot be deduced?


I'm using the Reflex.Dom library, which defines a set of functions for creating HTML DOM elements

  • el creates an element
  • el' creates and returns an element
  • elAttr creates an element with the given attributes
  • elAttr' creates and returns an element with the given attributes
  • etc

I'm making my own widget library and I don't want to define all those variations for every widget. So I wrote a typeclass that uses the same names, but defines all the functions in terms of one another, leaving only one of them to be defined in each instance:

{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}

module ElMaker where

import Data.Map (Map)
import qualified Data.Map as Map
import qualified Reflex.Dom as D

-- el: type of element to create
-- input: input parameter
-- output: return value
class (D.MonadWidget t m) => ElMaker t m el input output where
  el :: el -> input -> m output
  el e = elAttr e Map.empty

  elAttr :: el -> Map Text Text -> input -> m output
  elAttr e attrs input = snd <$> elAttr' e attrs input

  el' :: el -> input -> m (D.El t, output)
  el' e = elAttr' e Map.empty

  -- This is the only one to implement, yay!
  elAttr' :: el -> Map Text Text -> input -> m (D.El t, output)

I created an instance that uses the original elAttr' to test it out. It worked:

import Data.Text (Text)
import qualified Reflex.Dom as D

instance (D.MonadWidget t m) => ElMaker t m Text (m output) output where
  elAttr' = D.elAttr'

And then I created a Button widget instance that returns an event for when the button is clicked. It worked:

data Button = Button
instance (MonadWidget t m) => ElMaker t m Button (m input) (Event t ()) where
  elAttr' _ attrs contents = do
    (e, _) <- D.el' "button" contents
    return $ (e, D.domEvent D.Click e)

I'd like to be able to compose widgets, so I tried rewriting the Button instance to use the Text instance of ElMaker to create the element. But it fails to compile:

data Button = Button
instance (MonadWidget t m) => ElMaker t m Button (m input) (Event t ()) where
  elAttr' _ attrs contents = do
    (e, _) <- el' ("button" :: Text) contents
    return $ (e, D.domEvent D.Click e)

Compiler output:

MDL.hs:119:15: error:
    • Could not deduce (ElMaker t m Text (m input) output0)
        arising from a use of ‘el'’
      from the context: MonadWidget t m
        bound by the instance declaration at MDL.hs:116:10-71
      The type variable ‘output0’ is ambiguous
      Relevant bindings include
        contents :: m input (bound at MDL.hs:117:19)
        elAttr' :: Button
                   -> Map.Map Text Text -> m input -> m (D.El t, Event t ())
          (bound at MDL.hs:117:3)
      These potential instance exist:
        instance MonadWidget t m => ElMaker t m Text (m output) output
          -- Defined in ‘ElMaker’
    • In a stmt of a 'do' block:
        (e, _) <- el' ("button" :: Text) contents
      In the expression:
        do { (e, _) <- el' ("button" :: Text) contents;
             return $ (e, D.domEvent D.Click e) }
      In an equation for ‘elAttr'’:
          elAttr' _ attrs contents
            = do { (e, _) <- el' ("button" :: Text) contents;
                   return $ (e, D.domEvent D.Click e) }

I think this is because the function doesn't do anything with the value that would constrain its type, and the compiler really wants it to have a concrete type. But this typeclass doesn't care what the value of that type parameter is. Is there any way to compile this anyway?


Solution

  • What you probably want to do (and this is something you very often want to do; it's becoming something of a FAQ) is replace a constructor on the right side of => with an equality constraint on the left side.

    {-# LANGUAGE GADTs #-}
    
    instance (D.MonadWidget t m, input ~ m output)
       => ElMaker t m Text input output where ...
    
    instance (D.MonadWidget t m, input' ~ m input, output ~ Event t ())
       => ElMaker t m Button input' output where ...
    

    Once you know you're building Text or Button, you want to commit to a particular instance, and then to certain class parameters having particular shapes. Putting those in the instance constraints lets you do that.

    For the particular case here, once you know that you're dealing with Text, you know which instance you want to use, and that you can calculate output by matching on input. You want GHC to know that, rather than wondering if some other Text instance will have a different input/output relationship.

    Note: it's generally best for the critical class parameter that determines others to go last. So I'd make el the last parameter of ElMaker. This is good for newtype deriving, and is also conventional.