Skip to content
Snippets Groups Projects
Commit 0484fa82 authored by Sven Tennie's avatar Sven Tennie :smiley_cat:
Browse files

Fix getAmode: Only signed 12bit immediates

The symptom to find this was a too big immediate in a LW instruction in
test arr020:
    Error: illegal operands `lw t0,4016(t0)'
parent 5d7d4217
No related branches found
No related tags found
2 merge requests!10486Draft: RISCV64 Sync,!10367Draft: RISCV-NCG
......@@ -1032,28 +1032,21 @@ truncateReg w w' r =
-- The 'Amode' type: Memory addressing modes passed up the tree.
data Amode = Amode AddrMode InstrBlock
-- | Provide the value of a `CmmExpr` with an `Amode`
--
-- N.B. this function should be used to provide operands to load and store
-- instructions with signed 12bit wide immediates (S & I types). For other
-- immediate sizes and formats (e.g. B type uses multiples of 2) this function
-- would need to be adjusted.
getAmode :: Platform
-> Width -- ^ width of loaded value
-> CmmExpr
-> NatM Amode
-- TODO: Specialize stuff we can destructure here.
-- OPTIMIZATION WARNING: Addressing modes.
-- Addressing options:
-- LDUR/STUR: imm9: -256 - 255
getAmode platform _ (CmmRegOff reg off) | -256 <= off, off <= 255
= return $ Amode (AddrRegImm reg' off') nilOL
where reg' = getRegisterReg platform reg
off' = ImmInt off
-- LDR/STR: imm12: if reg is 32bit: 0 -- 16380 in multiples of 4
getAmode platform W32 (CmmRegOff reg off)
| 0 <= off, off <= 16380, off `mod` 4 == 0
= return $ Amode (AddrRegImm reg' off') nilOL
where reg' = getRegisterReg platform reg
off' = ImmInt off
-- LDR/STR: imm12: if reg is 64bit: 0 -- 32760 in multiples of 8
getAmode platform W64 (CmmRegOff reg off)
| 0 <= off, off <= 32760, off `mod` 8 == 0
-- LDR/STR: Immediate can be represented with 12bits
getAmode platform w (CmmRegOff reg off)
| w <= W64, fitsIn12bitImm off
= return $ Amode (AddrRegImm reg' off') nilOL
where reg' = getRegisterReg platform reg
off' = ImmInt off
......@@ -1063,12 +1056,12 @@ getAmode platform W64 (CmmRegOff reg off)
-- E.g. a CmmStoreOff really. This can be translated to `str $expr2, [$expr, #n ]
-- for `n` in range.
getAmode _platform _ (CmmMachOp (MO_Add _w) [expr, CmmLit (CmmInt off _w')])
| -256 <= off, off <= 255
| fitsIn12bitImm off
= do (reg, _format, code) <- getSomeReg expr
return $ Amode (AddrRegImm reg (ImmInteger off)) code
getAmode _platform _ (CmmMachOp (MO_Sub _w) [expr, CmmLit (CmmInt off _w')])
| -256 <= -off, -off <= 255
| fitsIn12bitImm (-off)
= do (reg, _format, code) <- getSomeReg expr
return $ Amode (AddrRegImm reg (ImmInteger (-off))) code
......@@ -1077,6 +1070,12 @@ getAmode _platform _ expr
= do (reg, _format, code) <- getSomeReg expr
return $ Amode (AddrReg reg) code
fitsIn12bitImm :: (Num a, Ord a) => a -> Bool
fitsIn12bitImm off = off >= intMin12bit && off <= intMax12bit
where
intMin12bit = -2048
intMax12bit = 2047
-- -----------------------------------------------------------------------------
-- Generating assignments
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment