> instance (EmbedAsChild m c, m1 ~ m) => EmbedAsChild m (XMLGenT m1 c)

That looked to me like a long-winded way of saying:

> instance (EmbedAsChild m c) => EmbedAsChild m (XMLGenT m c)

Unless I'm missing something?

These two instances are not equivalent:
- the first matches even if m and m1 differ, causing a type-error.
- the second matches only if m~m1

Claus

{-# LANGUAGE OverlappingInstances #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE MultiParamTypeClasses #-}

class C a b    where c :: a -> b -> Bool
instance C a a where c _ _ = True
instance C a b where c _ _ = False

class D a b         where d :: a -> b -> Bool
instance a~b=>D a b where d _ _ = True
-- instance      D a b where d _ _ = False -- would be a duplicate instance

{-
*Main> c () ()
True
*Main> c () True
False
*Main> d () ()
True
*Main> d () True

<interactive>:1:0:
   Couldn't match expected type `Bool' against inferred type `()'
   When generalising the type(s) for `it'
-} _______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to