| $ ghc -c Formula.hs -fallow-overlapping-instances \
| -fallow-undecidable-instances -fglasgow-exts
|
| panic! (the `impossible' happened):
| applyTy
Excellent bug! Thank you.
Turns out that it happens when there are join points combined
with existential constructors. The latter came along after the former
were implemented.
Solution: replace the tail end of Simplify.mkDupableAlt with the code below.
Simon M is going to commit this to the ghc-407-banch of the repository,
but I don't know if he's done so yet.
It'll be fixed in 4.08.2, which we'll put out soon.
QUESTION FOR EVERYONE
Is anyone stuck becuase of a bug in 4.08.1 that they
can't work around by changing the source or slurping the
draft 4.08.2 from teh repository?
Simon
================ STUFF TO PUT AT END OF Simplify.lhs
-- See comment about "$j" name above
newId SLIT("$j") (foldr mkPiType rhs_ty' final_bndrs') $ \
join_bndr ->
-- Notice the funky mkPiType. If the contructor has existentials
-- it's possible that the join point will be abstracted over
-- type varaibles as well as term variables.
-- Example: Suppose we have
-- data T = forall t. C [t]
-- Then faced with
-- case (case e of ...) of
-- C t xs::[t] -> rhs
-- We get the join point
-- let j :: forall t. [t] -> ...
-- j = /\t \xs::[t] -> rhs
-- in
-- case (case e of ...) of
-- C t xs::[t] -> j t xs
let
-- We make the lambdas into one-shot-lambdas. The
-- join point is sure to be applied at most once, and doing so
-- prevents the body of the join point being floated out by
-- the full laziness pass
really_final_bndrs = map one_shot final_bndrs'
one_shot v | isId v = setOneShotLambda v
| otherwise = v
in
returnSmpl ([NonRec join_bndr (mkLams really_final_bndrs rhs')],
(con, bndrs, mkApps (Var join_bndr) final_args))
_______________________________________________
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs