-caf-all gives "Error: symbol `Mainmain_CAF_cc_ccs' is already defined"
With this module:
module Main where
x = f [1..5] (f [2..] [3..])
f xs ys = l
where
l = [ if s then x else y | (x, y) <- zip xs ys ]
s = g xs ys
g [] _ = True
g _ [] = False
g (x:xs) (y:ys) = g xs ys
main = print (show x)
compiling with -caf-all gives:
% ghc -prof -caf-all a.hs -o a
/tmp/ghc21918_0/ghc21918_0.s: Assembler messages:
/tmp/ghc21918_0/ghc21918_0.s:3039:0:
Error: symbol `Mainmain_CAF_cc_ccs' is already defined
/tmp/ghc21918_0/ghc21918_0.s:3087:0:
Error: symbol `Mainsat_CAF_cc_ccs' is already defined
/tmp/ghc21918_0/ghc21918_0.s:3103:0:
Error: symbol `Mainsat_CAF_cc_ccs' is already defined
The failure is similar in 6.4.2 and almost-6.6.
Reported on the haskell-cafe list.
Trac metadata
Trac field | Value |
---|---|
Version | 6.5 |
Type | Bug |
TypeOfFailure | OtherFailure |
Priority | normal |
Resolution | Unresolved |
Component | Profiling |
Test case | |
Differential revisions | |
BlockedBy | |
Related | |
Blocking | |
CC | |
Operating system | Unknown |
Architecture | Unknown |