[Haskell-cafe] Type class hell

Greg Buchholz haskell at sleepingsquirrel.org
Thu Jun 8 13:06:48 EDT 2006


Christophe Poucet wrote:
> I'm not certain but I think this will still fail for exactly the piece that
> you ignored, which is the crux of the problem.

-- You're not looking for this solution, right?

import List

type Var = String
type Const = String

data MonoType mt = TyVar Var
                 | TyConst Const [mt] deriving (Eq, Show)

data PolyType mt = TyPoly [Var] mt deriving (Show)

newtype FMT = FMT (MonoType FMT)

class Types a where
    freeVars :: a -> [Var]

instance Types FMT where    
    freeVars (FMT (TyVar x)) = [x]
    freeVars (FMT (TyConst _ xs)) = nub . concatMap freeVars $ xs

main = print $ freeVars 
    (FMT (TyConst 
            "foo" 
            [(FMT (TyVar "abc")),
             (FMT (TyVar "123")),
             (FMT (TyConst 
                     "bar"
                      [(FMT (TyVar "www"))]))])) 


More information about the Haskell-Cafe mailing list