[Haskell] Empty instance declaration

ajb at spamcop.net ajb at spamcop.net
Fri Dec 28 22:24:13 EST 2007


G'day all.

Quoting Hugo Macedo <hmacedo at di.uminho.pt>:

> After checking the Haskell98 grammar I found out that this is allowed
> syntactically and probably semantically too. Is there any reason to do that?

One thing that hasn't come up yet is that empty instance declarations are
the only decent option (that I know of) that we have in the absence of
real class aliases.  Here's an example from Dfa.lhs, which could probably
be written slightly more simply now:

> {-# OPTIONS -fglasgow-exts #-}
> {-# OPTIONS -fallow-undecidable-instances #-}

> import Control.Monad.Identity
> import Control.Monad.Reader
> import Control.Monad.State

> data (Ord t) => ReRead t
>  = {- detail unimportant -}

> data (Ord t) => ReState t
>  = {- detail unimportant -}

> type ReM m t a = StateT (ReState t) (ReaderT (ReRead t) m) a

> class (Monad m, Ord t) => ReVars m t where { }
> instance (Monad m, Ord t) => ReVars m t where { }

> remNullSet :: (ReVars m t) => ReM m t (SimplRe t)
{- etc -}

> class (ReVars m t, MonadIO m, Show t) => ReVarsIO m t where { }
> instance (ReVars m t, MonadIO m, Show t) => ReVarsIO m t where { }

> remDump :: (ReVarsIO m t) => ReM m t ()
{- etc -}

Cheers,
Andrew Bromage


More information about the Haskell mailing list