I don't quite understand the problem, but maybe an example involving an explicit recursion operator will help.

class Foo a where
  foo :: a

instance Foo a => Foo (Maybe a) where
  foo = Just foo

data Rec f = In (f (Rec f))

instance Foo (f (Rec f)) => Foo (Rec f) where
  foo = In foo

compile with -fglasgow-exts and -fallow-undecidable-instances,
and Rec Maybe will be an instance of Foo.

I can't find the discussion, but if I recall correctly, ghc was extended
as a result to allow regular instance deriviations rather than just
finite one. I think Simon Peyton-Jones said it just required switching
two lines.

Brandon

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.

On 6/8/06, *Greg Buchholz* < [EMAIL PROTECTED] <mailto:[EMAIL PROTECTED]>> 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 <mailto:Haskell-Cafe@haskell.org>
    http://www.haskell.org/mailman/listinfo/haskell-cafe



------------------------------------------------------------------------

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


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

Reply via email to