The attached program works under hugs -98 but fails with GHC 5.04.2
with:

--------
Params2b.hs:6:
    No instance for `Show (r String)'
    When deriving the `Show' instance for type `S'

Params2b.hs:6:
    No instance for `Show (r Int)'
    When deriving the `Show' instance for type `S'
--------

If the `deriving` clause for `newtype S r` is replaced by the
commented-out instance declarations, both systems are happy.

Did I just get lucky with Hugs, or is GHC in error?

-- Dean

--------

{-# OPTIONS -fglasgow-exts #-}

class ByField s where
  byField :: (forall a. r1 a -> r2 a) -> s r1 -> s r2

newtype S r = S (r Int, r String)
  deriving Show
{-
instance Show (S Id) where
  show (S s) = "S " ++ show s
instance Show (S []) where
  show (S s) = "S " ++ show s
-}

instance ByField S where
  byField f (S (i,s)) = S (f i,f s)

newtype Id a = Id a
  deriving Show

twice :: S Id -> S []
twice = byField (\(Id x) -> [x,x])

main = do print s; print (twice s)
 where s = S (Id 3, Id "abc")


_______________________________________________
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to