[Haskell-cafe] Type class hell

Christophe Poucet christophe.poucet at gmail.com
Wed Jun 7 19:05:29 EDT 2006


Dear,

I am writing a compiler (as you may have gathered from some previous 
messages). Anyways I am stuck with a small monadic issue. I mostly use 
indirect composite as this gives me the most flexibility with regards 
taking out parts of the AST, or decorating at whim. Basically the 
question regards how to implement a certain instance. Currently I have 
the code that can be seen below. 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?

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

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

class Type mt where
toType :: mt -> MonoType mt
fromType :: MonoType mt -> mt

class HasVars a where
freeVars :: a -> [Var]
occurs :: Var -> a -> Bool

toPoly :: (HasVars a) => a -> PolyType a
toPoly x = TyPoly (freeVars x) x

instance HasVars a => HasVars (MonoType a) 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

Cheers,
Christophe(vincenz)

-- 
Christophe Poucet
Ph.D. Student
Phone:+32 16 28 87 20
E-mail: Christophe (dot) Poucet (at) imec (dot) be
Website: http://notvincenz.com/  
IMEC vzw – Register of Legal Entities Leuven VAT BE 0425.260.668 – Kapeldreef 75, B-3001 Leuven, Belgium – www.imec.be
*****DISCLAIMER*****
This e-mail and/or its attachments may contain confidential information. It is intended solely for the intended addressee(s).
Any use of the information contained herein by other persons is prohibited. IMEC vzw does not accept any liability for the contents of this e-mail and/or its attachments.
**********



More information about the Haskell-Cafe mailing list