summaryrefslogtreecommitdiff
path: root/compiler/GHC/Cmm/Node.hs
diff options
context:
space:
mode:
Diffstat (limited to 'compiler/GHC/Cmm/Node.hs')
-rw-r--r--compiler/GHC/Cmm/Node.hs12
1 files changed, 6 insertions, 6 deletions
diff --git a/compiler/GHC/Cmm/Node.hs b/compiler/GHC/Cmm/Node.hs
index 40b268931d..841c726b14 100644
--- a/compiler/GHC/Cmm/Node.hs
+++ b/compiler/GHC/Cmm/Node.hs
@@ -74,7 +74,7 @@ data CmmNode e x where
CmmAssign :: !CmmReg -> !CmmExpr -> CmmNode O O
-- Assign to register
- CmmStore :: !CmmExpr -> !CmmExpr -> CmmNode O O
+ CmmStore :: !CmmExpr -> !CmmExpr -> !AlignmentSpec -> CmmNode O O
-- Assign to memory location. Size is
-- given by cmmExprType of the rhs.
@@ -322,7 +322,7 @@ instance UserOfRegs LocalReg (CmmNode e x) where
{-# INLINEABLE foldRegsUsed #-}
foldRegsUsed platform f !z n = case n of
CmmAssign _ expr -> fold f z expr
- CmmStore addr rval -> fold f (fold f z addr) rval
+ CmmStore addr rval _ -> fold f (fold f z addr) rval
CmmUnsafeForeignCall t _ args -> fold f (fold f z t) args
CmmCondBranch expr _ _ _ -> fold f z expr
CmmSwitch expr _ -> fold f z expr
@@ -337,7 +337,7 @@ instance UserOfRegs GlobalReg (CmmNode e x) where
{-# INLINEABLE foldRegsUsed #-}
foldRegsUsed platform f !z n = case n of
CmmAssign _ expr -> fold f z expr
- CmmStore addr rval -> fold f (fold f z addr) rval
+ CmmStore addr rval _ -> fold f (fold f z addr) rval
CmmUnsafeForeignCall t _ args -> fold f (fold f z t) args
CmmCondBranch expr _ _ _ -> fold f z expr
CmmSwitch expr _ -> fold f z expr
@@ -474,7 +474,7 @@ mapExp _ m@(CmmComment _) = m
mapExp _ m@(CmmTick _) = m
mapExp f (CmmUnwind regs) = CmmUnwind (map (fmap (fmap f)) regs)
mapExp f (CmmAssign r e) = CmmAssign r (f e)
-mapExp f (CmmStore addr e) = CmmStore (f addr) (f e)
+mapExp f (CmmStore addr e align) = CmmStore (f addr) (f e) align
mapExp f (CmmUnsafeForeignCall tgt fs as) = CmmUnsafeForeignCall (mapForeignTarget f tgt) fs (map f as)
mapExp _ l@(CmmBranch _) = l
mapExp f (CmmCondBranch e ti fi l) = CmmCondBranch (f e) ti fi l
@@ -505,7 +505,7 @@ mapExpM _ (CmmComment _) = Nothing
mapExpM _ (CmmTick _) = Nothing
mapExpM f (CmmUnwind regs) = CmmUnwind `fmap` mapM (\(r,e) -> mapM f e >>= \e' -> pure (r,e')) regs
mapExpM f (CmmAssign r e) = CmmAssign r `fmap` f e
-mapExpM f (CmmStore addr e) = (\[addr', e'] -> CmmStore addr' e') `fmap` mapListM f [addr, e]
+mapExpM f (CmmStore addr e align) = (\[addr', e'] -> CmmStore addr' e' align) `fmap` mapListM f [addr, e]
mapExpM _ (CmmBranch _) = Nothing
mapExpM f (CmmCondBranch e ti fi l) = (\x -> CmmCondBranch x ti fi l) `fmap` f e
mapExpM f (CmmSwitch e tbl) = (\x -> CmmSwitch x tbl) `fmap` f e
@@ -558,7 +558,7 @@ foldExp _ (CmmComment {}) z = z
foldExp _ (CmmTick {}) z = z
foldExp f (CmmUnwind xs) z = foldr (maybe id f) z (map snd xs)
foldExp f (CmmAssign _ e) z = f e z
-foldExp f (CmmStore addr e) z = f addr $ f e z
+foldExp f (CmmStore addr e _) z = f addr $ f e z
foldExp f (CmmUnsafeForeignCall t _ as) z = foldr f (foldExpForeignTarget f t z) as
foldExp _ (CmmBranch _) z = z
foldExp f (CmmCondBranch e _ _ _) z = f e z