> {- 
>    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}


Thanks.  You've tickled a small but dark corner of the compiler.
If you have a source release you can replace the defn of getWorkerIdAndCons
in stranal/WorkWrap.lhs with the defn below.  Otherwise wait for 2.10.

Simon


getWorkerIdAndCons wrap_id wrapper_fn
  = go wrapper_fn
  where
    go (Lam _ body)                       = go body
    go (Case _ (AlgAlts [(con,_,rhs)] _)) = let (wrap_id, cons) = go rhs
                                            in  (wrap_id, cons `addOneToIdSet` con)
    go (Let (NonRec _ (Coerce (CoerceOut con) _ _)) body) 
                                          = let (wrap_id, cons) = go body
                                            in  (wrap_id, cons `addOneToIdSet` con)
    go other                              = (get_work_id other, emptyIdSet)

    get_work_id (App fn _)    = get_work_id fn
    get_work_id (Var work_id) = work_id
    get_work_id other         = pprPanic "getWorkerIdAndCons" (ppr wrap_id)


Reply via email to