Skip to content

Commit

Permalink
Remove unncessary fromIntegral calls
Browse files Browse the repository at this point in the history
  • Loading branch information
simonpj@microsoft.com committed Nov 16, 2010
1 parent 2d367f8 commit e21c922
Show file tree
Hide file tree
Showing 8 changed files with 11 additions and 11 deletions.
2 changes: 1 addition & 1 deletion compiler/cmm/CmmInfo.hs
Expand Up @@ -245,7 +245,7 @@ mkLiveness uniq live =

small_bitmap = case bitmap of
[] -> 0
[b] -> fromIntegral b
[b] -> b
_ -> panic "mkLiveness"
small_liveness =
fromIntegral (length bits) .|. (small_bitmap `shiftL` bITMAP_BITS_SHIFT)
Expand Down
2 changes: 1 addition & 1 deletion compiler/codeGen/CgCallConv.hs
Expand Up @@ -150,7 +150,7 @@ mkLiveness name size bits
= let
small_bits = case bits of
[] -> 0
[b] -> fromIntegral b
[b] -> b
_ -> panic "livenessToAddrMode"
in
return (smallLiveness size small_bits)
Expand Down
2 changes: 1 addition & 1 deletion compiler/codeGen/CgHpc.hs
Expand Up @@ -29,7 +29,7 @@ cgTickBox :: Module -> Int -> Code
cgTickBox mod n = do
let tick_box = (cmmIndex W64
(CmmLit $ CmmLabel $ mkHpcTicksLabel $ mod)
(fromIntegral n)
n
)
stmtsC [ CmmStore tick_box
(CmmMachOp (MO_Add W64)
Expand Down
2 changes: 1 addition & 1 deletion compiler/codeGen/StgCmmHpc.hs
Expand Up @@ -32,7 +32,7 @@ mkTickBox mod n
where
tick_box = cmmIndex W64
(CmmLit $ CmmLabel $ mkHpcTicksLabel $ mod)
(fromIntegral n)
n

initHpc :: Module -> HpcInfo -> FCode CmmAGraph
-- Emit top-level tables for HPC and return code to initialise
Expand Down
2 changes: 1 addition & 1 deletion compiler/codeGen/StgCmmLayout.hs
Expand Up @@ -400,7 +400,7 @@ mkLiveness name size bits
= let
small_bits = case bits of
[] -> 0
[b] -> fromIntegral b
[b] -> b
_ -> panic "livenessToAddrMode"
in
return (smallLiveness size small_bits)
Expand Down
2 changes: 1 addition & 1 deletion compiler/ghci/ByteCodeGen.lhs
Expand Up @@ -298,7 +298,7 @@ schemeER_wrk d p rhs
| Just (tickInfo, (_annot, newRhs)) <- isTickedExp' rhs = do
code <- schemeE d 0 p newRhs
arr <- getBreakArray
let idOffSets = getVarOffSets (fromIntegral d) p tickInfo
let idOffSets = getVarOffSets d p tickInfo
let tickNumber = tickInfo_number tickInfo
let breakInfo = BreakInfo
{ breakInfo_module = tickInfo_module tickInfo
Expand Down
8 changes: 4 additions & 4 deletions compiler/nativeGen/RegAlloc/Linear/PPC/FreeRegs.hs
Expand Up @@ -32,8 +32,8 @@ noFreeRegs = FreeRegs 0 0

releaseReg :: RealReg -> FreeRegs -> FreeRegs
releaseReg (RealRegSingle r) (FreeRegs g f)
| r > 31 = FreeRegs g (f .|. (1 `shiftL` (fromIntegral r - 32)))
| otherwise = FreeRegs (g .|. (1 `shiftL` fromIntegral r)) f
| r > 31 = FreeRegs g (f .|. (1 `shiftL` (r - 32)))
| otherwise = FreeRegs (g .|. (1 `shiftL` r)) f

releaseReg _ _
= panic "RegAlloc.Linear.PPC.releaseReg: bad reg"
Expand All @@ -53,8 +53,8 @@ getFreeRegs cls (FreeRegs g f)

allocateReg :: RealReg -> FreeRegs -> FreeRegs
allocateReg (RealRegSingle r) (FreeRegs g f)
| r > 31 = FreeRegs g (f .&. complement (1 `shiftL` (fromIntegral r - 32)))
| otherwise = FreeRegs (g .&. complement (1 `shiftL` fromIntegral r)) f
| r > 31 = FreeRegs g (f .&. complement (1 `shiftL` (r - 32)))
| otherwise = FreeRegs (g .&. complement (1 `shiftL` r)) f

allocateReg _ _
= panic "RegAlloc.Linear.PPC.allocateReg: bad reg"
2 changes: 1 addition & 1 deletion compiler/nativeGen/RegAlloc/Linear/X86/FreeRegs.hs
Expand Up @@ -47,7 +47,7 @@ getFreeRegs cls f = go f 0

allocateReg :: RealReg -> FreeRegs -> FreeRegs
allocateReg (RealRegSingle r) f
= f .&. complement (1 `shiftL` fromIntegral r)
= f .&. complement (1 `shiftL` r)

allocateReg _ _
= panic "RegAlloc.Linear.X86.FreeRegs.allocateReg: no reg"
Expand Down

0 comments on commit e21c922

Please sign in to comment.