I'm using the Reflex.Dom library, which defines a set of functions for creating HTML DOM elements
el
creates an elementel'
creates and returns an elementelAttr
creates an element with the given attributeselAttr'
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?