{- 
   Hi,
   
   Compiling the following module results in the following error message
   (with GHC 2.09, patchlevel 0, i386-linux
 
  
----------------------------------------------------------------------
   panic! (the `impossible' happened):
        getWorkerIdAndCons area2{-r3g,x-}{i}

   Please report it as a compiler bug to
[EMAIL PROTECTED]
  
----------------------------------------------------------------------

   If you replace newtype with data, everythings's ok.

   bye, 

        Joern
-}

module Impossible where

newtype Num a => Point2 a     = Point2 (a,a) deriving (Eq, Show)
--data Point2 a               = Point2 (a,a) deriving (Eq, Show)

instance Num a                => Num (Point2 a) where
    (Point2 (x,y)) + (Point2 (u,v))  = Point2 (x+u,y+v)
    (Point2 (x,y)) - (Point2 (u,v))  = Point2 (x-u,y-v)
    negate                    = undefined
    (*)                       = undefined
    abs                       = undefined
    signum                    = undefined
    fromInteger               = undefined

area2                         :: Num a => Point2 a -> Point2 a -> Point2
a -> a
area2 (Point2 (px,py)) (Point2 (qx,qy)) (Point2 (rx,ry))
                              = (px-qx) * (py-ry) - (py-qy) * (px-rx)

-- 
Joern Dinkla, Z"ulpicher Stra\ss e 56, 50674 K"oln, Germany
[EMAIL PROTECTED]                        +49-221-421723

Reply via email to