[Haskell-cafe] Type class hell

Greg Buchholz haskell at sleepingsquirrel.org
Wed Jun 7 23:46:47 EDT 2006


Christophe Poucet wrote:
> What I would like to do is combine HasVars and Type (mostly because in my
> framework the two concepts shouldn't be divided from a design perspective)
> into one type class to clean it up a bit. However I fail to see how I would
> implement toType and fromType for the given instance. Is this feasible
> without resorting to ugly hacks?

{-# OPTIONS -fglasgow-exts #-}

-- Multiparameter type classes?

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)

class Type a b where
    toType   ::   b -> a b
    fromType :: a b -> b
    freeVars :: a b -> [Var]
    occurs   :: Var -> a b -> Bool
    
instance Type MonoType Int
    -- yada, yada, yada...
    
instance Type MonoType (MonoType Int) where
    freeVars (TyVar x) = [x]
    freeVars (TyConst _ xs) = nub . concatMap freeVars $ xs
    occurs x (TyVar y) = x == y
    occurs x (TyConst _ xs) = or . map (occurs x) $ xs
    


More information about the Haskell-Cafe mailing list