Hi,

I'm sending this to g-h-bugs because there is certainly a ghc bug,
however any answer may also be interesting to readers of g-h-user so
consider cc-ing them if appropriate.

I am running GHC-4.01 (compiled by myself with GHC 4.01) on a linux
box.

I am trying to create a polymorphic list,  each item in the list can
be of different types but the type must be an instance of
PictureObject so I know I can invoke PictureObject's methods on the
elements of the list.  Assuming I am on the right track,  is there any 
way of getting the same result with the latest release of hugs?

I thought I could do this with existential types,  however my test
program below has problems.  Firstly,  if compiled with -DDUMPCORE
then the executable dumps core (Is there any way I can get useful
information from this core?)

Secondly,  if compiled without -DDUMPCORE I get the following error
messages: 


exist.hs:73:
    My brain just exploded.
    I can't handle pattern bindings for existentially-quantified constructors.
    In the binding group
        MkGenPic obj = item
    In a pattern binding:
        main
            = do putStr $ (getPictureName obj)
            where
                item = head obj_list
                MkGenPic obj = item
 
exist.hs:67:
    Ambiguous type variable(s) `pot'
        in the constraint `PictureObject pot'
        arising from use of `getPictureName' at exist.hs:67


Compilation had errors

(btw. whose brain? :-)

Thanks for any help.

Kevin

module Main where

data Coordinate3D = Coord3D {cx, cy, cz::Double} 
                    deriving (Eq, Show)

-- We Represent a line by two coordinates which it passes through.
data Line = MkLine Coordinate3D Coordinate3D 


class PictureObject pot where

      -- Returns ordered (rel to 0 0 0) of points where the object
      -- intersects the given line. 
      intersectLineObject :: pot -> Line -> [Coordinate3D]

      getPictureName :: pot -> String

data Sphere = 
   Sphere Coordinate3D                  -- Centre
          Double                        -- Radius
          Double                        -- ambient coeff
          Double                        -- diffuse coeff
          Double                        -- specular coeff
          Double                        -- phong specular exponent
   deriving (Eq, Show)

intersectLineSphere :: Sphere -> Line -> [Coordinate3D]
intersectLineSphere sp line = []

instance PictureObject Sphere where
         intersectLineObject = intersectLineSphere
         getPictureName _ = "Sphere"

data Cube = 
   Cube Coordinate3D            -- Origin corner 
        Coordinate3D            -- Opposite corner
        Double                  -- ambient coeff
        Double                  -- diffuse coeff
        Double                  -- specular coeff
        Double                  -- phong specular exponent
   deriving (Eq, Show)

intersectLineCube :: Cube -> Line -> [Coordinate3D]
intersectLineCube cube line = []

instance PictureObject Cube where
         intersectLineObject = intersectLineCube
         getPictureName _ = "Cube"


sphere :: Sphere
sphere = Sphere (Coord3D 1 1 1) 1 1 1 1 1

cube :: Cube
cube = Cube (Coord3D 1 1 1) (Coord3D 2 2 2) 1 1 1 1

data GenPic = forall pot. (PictureObject pot) => MkGenPic pot

obj_list:: [GenPic] 
obj_list = [MkGenPic sphere, MkGenPic cube]

putName :: PictureObject pot => pot -> IO ()
putName x = putStr $ getPictureName x


main :: IO ()
main = do
#ifdef DUMPCORE
        sequence $ map (\(MkGenPic el) -> putStr $ getPictureName el) obj_list
#else
        putStr $ getPictureName obj
        where MkGenPic obj = item
              item = head obj_list
#endif

Reply via email to