[Haskell-cafe] type and class problems compiling code on GHC 6.6

Albert Lai trebla at vex.net
Mon Jan 29 19:22:13 EST 2007


José Miguel Vilaça <jmvilaca at di.uminho.pt> writes:

> I had used some code which worked fine on GHC 6.4 and now it don’t compile
> on GHC 6.6.

I am unable to reproduce your problem.  It is saddening that everyone
neglects to provide self-contained code for others to reproduce the
alleged problems.

I have cooked up a small resemblance to demonstrate the lack of
problems.  It is accepted by GHC 6.6 just fine.  It is self-contained,
so you can reproduce the same success too.

> instance InfoKind a b => InfoKind (Maybe a) b where
[...]

{-# OPTIONS_GHC -fglasgow-exts #-}

class InfoKind a b where
    info :: a -> b -> Bool

instance InfoKind Int Double where
    info x y = fromIntegral x == y

instance InfoKind a b => InfoKind (Maybe a) b where
    info Nothing y = False
    info (Just x) y = info x y

testInfoKind = [ info (45::Int) (45::Double),
                 info (Nothing::Maybe Int) (45::Double),
                 info (Just 45::Maybe Int) (45::Double)
               ]

> multiListViewGetTSelections :: MultiListView x () -> IO [x]
> multiListViewGetTSelections multiListView =
>  do { Just ((model, _) :: (Var [x], x -> String)) <-
> unsafeObjectGetClientData multiListView
[...]

{-# OPTIONS_GHC -fglasgow-exts #-}

data Multi a = Multi (IO (Maybe ([a], a->String)))
deMulti (Multi x) = x

multiGetList :: Multi x -> IO [x]
multiGetList m =
    do { Just ((list,_) :: ([x],x->String)) <- deMulti m
       ; return list
       }


More information about the Haskell-Cafe mailing list