Since there occurred problems with e-mail delivery, i am sorry,
i repeat the two bug reports for   ghc-4-i386-linux.

------------------
Sergey Mechveliani
[EMAIL PROTECTED]



*****************************************************************
1. The reduced `panic' example:    ghc -c Bug.hs

ft  does not look natural. But after `panic' is fixed, i hope the 
original program will work.
By the way, has 
           class PolLike p  where  cPMul :: Eq a => a -> p a -> p a    
                                            ----
sense? I thought, yes.


-------------------------------------------------------------------
class PolLike p  where  cPMul :: Eq a => a -> p a -> p a    

class Eq a => AddSemigroup a  where  add :: a -> a -> a

type UMon a     =  (a, Integer  )          
type Monomial a =  (a, [Integer])   
data UPol a     =  UPol [UMon a] a String [a]

instance Eq a => Eq (UPol a)   

instance PolLike UPol  where  cPMul _ _ = error ""  

instance Eq a => AddSemigroup (UPol a)


ft :: AddSemigroup k => UPol k -> [UPol k]

ft  f@(UPol _ c v d) = 
  let
    berl h =  let  b  = [cPMul c h] 
                   fr = map (const []) [cPMul c h] 
              in 
               case  head fr
               of      
                 _:_ -> let  es = map (add (UPol [] c v d)) [h]
                        in   berl h
  in
  berl f





*********************************************************************
2. Modularity bug:

-----------------------------------------------------
module T1 where
type Z = Integer
toZ    = toInteger  :: Integral a => a -> Z

-- the idea is to switch Z, toZ between Integer, Int
-----------------------------------------------------
module Main where
import List (genericTake)
import T1   (Z, toZ     )

f :: Z -> Z -> [Z] 
f    n    i =  case  toZ i  of  j -> genericTake (n+j) (repeat n)

main = let  ns = f 2 3  in   putStr (shows ns "\n")
-----------------------------------------------------------------


After   ghc -c T1.hs,  ghc -c Main.hs   

the compiler derives a contradiction for  i :: Int,  Z.

After moving the definition of toZ  to Main.hs the compiler solves
the types differently.

Reply via email to