[Haskell-cafe] Type class hell
Greg Buchholz
haskell at sleepingsquirrel.org
Thu Jun 8 17:37:29 EDT 2006
Brandon Moore wrote:
> I don't quite understand the problem, but maybe an example involving an
> explicit recursion operator will help.
-- Maybe he's looking for something like...
{-# OPTIONS -fglasgow-exts #-}
{-# OPTIONS -fallow-undecidable-instances #-}
import List
type Var = String
type Const = String
data MonoType mt = TyVar Var
| TyConst Const [mt] deriving (Eq, Show)
newtype Fix f = In { out :: f (Fix f) }
class Types a where
freeVars :: a -> [Var]
instance Types (a (Fix a)) => Types (Fix a) where
freeVars (In x) = freeVars x
instance Types a => Types (MonoType a) where
freeVars (TyVar x) = [x]
freeVars (TyConst _ xs) = nub . concatMap freeVars $ xs
main = do
print $ freeVars
(TyConst
"foo"
[(In (TyVar "abc")),
(In (TyVar "123")),
(In (TyConst
"bar"
[(In (TyVar "www"))]))]))
More information about the Haskell-Cafe
mailing list