RULE left-hand side too complicated to desugar
GHC reports multiple "RULE left-hand side too complicated to desugar" warnings for the fast-math
package.
Here is an testcase, extracted from fast-math/Numeric/FastMath/Approximation.hs
:
{-# LANGUAGE MagicHash #-}
module T10555 where
import GHC.Exts
{-# RULES
"double /,+ distribute" forall x y1 y2. (y1 /## x) +## (y2 /## x)
= (y1 +## y2) /## x
"double /,- distribute" forall x y1 y2. (y1 /## x) -## (y2 /## x)
= (y1 -## y2) /## x
"float /,- distribute" forall x y1 y2. (y1 `divideFloat#` x) `minusFloat#` (y2 `divideFloat#` x)
= (y1 `minusFloat#` y2) `divideFloat#` x
#-}
2$ ghc-7.10.2 T10555.hs -fforce-recomp
[1 of 1] Compiling T10555 ( T10555.hs, T10555.o )
T10555.hs:8:1: Warning:
RULE left-hand side too complicated to desugar
Optimised lhs: case /## y2 x of wild_00 { __DEFAULT ->
(case /## y1 x of wild_X2 { __DEFAULT -> +## wild_X2 }) wild_00
}
Orig lhs: case /## y2 x of wild_00 { __DEFAULT ->
(case /## y1 x of wild_00 { __DEFAULT -> +## wild_00 }) wild_00
}
T10555.hs:11:1: Warning:
RULE left-hand side too complicated to desugar
Optimised lhs: case /## y2 x of wild_00 { __DEFAULT ->
(case /## y1 x of wild_X2 { __DEFAULT -> -## wild_X2 }) wild_00
}
Orig lhs: case /## y2 x of wild_00 { __DEFAULT ->
(case /## y1 x of wild_00 { __DEFAULT -> -## wild_00 }) wild_00
}
T10555.hs:14:1: Warning:
RULE left-hand side too complicated to desugar
Optimised lhs: case divideFloat# y2 x of wild_00 { __DEFAULT ->
(case divideFloat# y1 x of wild_X2 { __DEFAULT ->
minusFloat# wild_X2
})
wild_00
}
Orig lhs: case divideFloat# y2 x of wild_00 { __DEFAULT ->
(case divideFloat# y1 x of wild_00 { __DEFAULT ->
minusFloat# wild_00
})
wild_00
}
Edited by Thomas Miedema