[Haskell-cafe] Rewrite class with fundeps in pure h98?

Darrin Thompson darrinth at gmail.com
Tue Jun 3 11:53:07 EDT 2008


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


More information about the Haskell-Cafe mailing list