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.

On 6/8/06, Greg Buchholz < haskell@sleepingsquirrel.org> wrote:
Christophe Poucet wrote:
> 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...

    Er, I'll ignore this part.
>
> 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.

    Yeah, after a certain point of complexity with type classes, it
starts to look like C++ templates.  How about 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)

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

data Nil = Nil

instance Type MonoType Nil where
    freeVars (TyVar x) = [x]
    freeVars (TyConst _ xs) = ["???"]

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

main = print $ freeVars $
                TyConst "foo" [TyConst "bar"  [Nil],
                               TyConst "baz"  [Nil],
                               TyVar   "quux"      ]

_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe