decodeDouble_Int64 rewrite rule is incorrect (core lint error - compiling AD)
module Double
(
eexponent
) where
-- spine lazy, value strict list of doubles
data List
= Nil
| {-# UNPACK #-} !Double :! List
infixr 5 :!
newtype TowerDouble = Tower { getTower :: List }
primal :: TowerDouble -> Double
primal (Tower (x:!_)) = x
primal _ = 0
eexponent :: TowerDouble -> Int
eexponent = exponent . primal
> ~/head.hackage/ghc/bin/ghc Double.hs -O -dcore-lint
*** Core Lint errors : in result of Simplifier ***
Double.hs:20:1: warning:
Argument value doesn't match argument type:
Expected arg type: Int64#
Actual arg type: Int#
Arg: 0#
In the RHS of eexponent :: TowerDouble -> Int
In the body of lambda with binder x_aSF :: TowerDouble
In the body of letrec with binders $j_sTw :: Double# -> Int
In a case alternative: (Nil)
Substitution: <InScope = {}
IdSubst = []
TvSubst = []
CvSubst = []>
Which we note is because of this incorrect rule firing:
Rule fired
Rule: decodeDouble_Int64#
Module: (BUILTIN)
Before: GHC.Prim.decodeDouble_Int64# ValArg 0.0##
After: (# 0#, 0# #)
Cont: Select nodup ds_aTq
Stop[BoringCtxt] GHC.Types.Int
but the first part of the tuple should be an Int64.
primop DoubleDecode_Int64Op "decodeDouble_Int64#" GenPrimOp
Double# -> (# Int64#, Int# #)
{Decode 'Double#' into mantissa and base-2 exponent.}
with out_of_line = True
Edited by sheaf