Rewrite class with fundeps in pure h98?

I thought that I should be able to write something like the toHtml function below with pure H98, but when I went to write it I ended up needing fundeps. Is there a way to express this without using any extensions? The idea was to take a remotely Dom-like tree and flatten it into a string, but not require any particular string type. Mostly I'm ripping off HStringTemplate for the fun of it. {-# OPTIONS -fglasgow-exts #-} module Control.WebWidget where import Data.Monoid import Data.String data (IsString s, Monoid s) => Dom s = Element s [Attr s] [Dom s] | Text s data (IsString s, Monoid s) => Attr s = Attr s s class (Monoid s, IsString s) => HTML d s | d -> s where toHtml :: d -> s instance (Monoid s, IsString s) => HTML (Dom s) s where toHtml (Element name attrs children) = mconcat [ fromString "<", name, mconcat $ map toHtml attrs, fromString ">", mconcat $ map toHtml children, fromString "", name, fromString ">" ] toHtml (Text s) = s instance (Monoid s, IsString s) => HTML (Attr s) s where toHtml (Attr key value) = mconcat [ fromString " '", key, fromString "'='", value, fromString "' " ] -- Darrin

Darrin Thompson wrote:
I thought that I should be able to write something like the toHtml function below with pure H98, but when I went to write it I ended up needing fundeps. Is there a way to express this without using any extensions?
The idea was to take a remotely Dom-like tree and flatten it into a string, but not require any particular string type.
data (IsString s, Monoid s) => Dom s = Element s [Attr s] [Dom s] | Text s
data (IsString s, Monoid s) => Attr s = Attr s s
class (Monoid s, IsString s) => HTML d s | d -> s where toHtml :: d -> s
instance (Monoid s, IsString s) => HTML (Dom s) s where
instance (Monoid s, IsString s) => HTML (Attr s) s where
The H98 way is to make a class for type constructors: class HTML d where toHTML :: (Monoid s, IsString s) => d s -> s instance HTML Dom where ... instance HTML Attr where ... Btw, naming the class "HTML" is feels wrong, something like Serialize is probably a better fit. Regards, apfelmus

This was how it was originally done in HStringTemplate, as I recall. The mptcs were introduced in order to maintain lookup-maps of the correct type, and particularly to allow embedding of templates within one another. There may have been some other corner-cases involved as well. However, unless you run into them, the H98 way is certainly cleaner. --Sterl On Jun 3, 2008, at 1:17 PM, apfelmus wrote:
Darrin Thompson wrote:
I thought that I should be able to write something like the toHtml function below with pure H98, but when I went to write it I ended up needing fundeps. Is there a way to express this without using any extensions? The idea was to take a remotely Dom-like tree and flatten it into a string, but not require any particular string type. data (IsString s, Monoid s) => Dom s = Element s [Attr s] [Dom s] | Text s data (IsString s, Monoid s) => Attr s = Attr s s class (Monoid s, IsString s) => HTML d s | d -> s where toHtml :: d -> s instance (Monoid s, IsString s) => HTML (Dom s) s where instance (Monoid s, IsString s) => HTML (Attr s) s where
The H98 way is to make a class for type constructors:
class HTML d where toHTML :: (Monoid s, IsString s) => d s -> s
instance HTML Dom where ...
instance HTML Attr where ...
Btw, naming the class "HTML" is feels wrong, something like Serialize is probably a better fit.
Regards, apfelmus
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (3)
-
apfelmus
-
Darrin Thompson
-
Sterling Clover