[Haskell-cafe] Type class hell

Christophe Poucet christophe.poucet at gmail.com
Wed Jun 7 23:52:04 EDT 2006


Hello Greg,

The idea however is that MonoType is going to be used in a recursive 
way. For instance:

newtype FMT = FMT MonoType FMT

instance FMT where...

And this definition will have to reside on recursive definitions. In the 
style of how HasVars was instantiated:

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

So for Type

instance Type a => Type (MonoType a) where
...

That's where it becomes rather troublesome.

Greg Buchholz wrote:

>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
>    
>_______________________________________________
>Haskell-Cafe mailing list
>Haskell-Cafe at haskell.org
>http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>  
>


-- 
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