Hi all,

(Using ghc-4.08)

consider the following program...

As it stands it will cause 'undefined' to be evaluated.
However if we replace 'broken fragment' by the
'working fragment' then it will work correctly.

The reason is straightforward: in 'broken fragment'
it obviously tries to construct the tuple so that it can do
the pattern match, and constructing the tuple will cause the
list to be evaluated slightly and thus call 'undefined'...

Is this too strict? It never uses the tuple or its arguments yet
tries to construct the tuple anyway.

Maybe the compiler code for pattern matching needs to be modified to
handle the case when there only exists one pattern?

-------------CUT---------------
module Main(main) where

class Typeable a where
  typeOf :: a -> String

instance Typeable Bool where
  typeOf _ = "B"

instance Typeable a => Typeable [a] where
  typeOf x = "["++(typeOf (see x))++"]"
    where
      see :: [a] -> a
      see = undefined 

{-
-- working fragment
instance (Typeable a, Typeable b) => Typeable (a,b) where
  typeOf tu = "("++(typeOf (fst tu))++ ","++(typeOf (snd tu))++")"
    where
      fst :: (a,b) -> a
      fst = undefined
      snd :: (a,b) -> b
      snd = undefined
-}

-- broken fragment
instance (Typeable a, Typeable b) => Typeable (a,b) where
  typeOf (x,y) = "("++(typeOf x)++ ","++(typeOf y)++")"
--

main = do
        
        let x = [(True,False),(True,True)]
        
        putStrLn (typeOf x)
------------------------CUT-----------------------------------------

P.S. The answer we want: [(B,B)]


___                 
][_)              | +44 (0)131 451 3328
]| \obert Pointon | http://www.cee.hw.ac.uk/~rpointon
------------------+------------------------------
Dept of Computing & Electrical Eng.
Heriot-Watt University
Riccarton
Edinburgh, EH14 4AS



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

Reply via email to