Warning Police
[ghc-hetmet.git] / compiler / cmm / CmmOpt.hs
index 9a51215..0a6c193 100644 (file)
@@ -18,7 +18,6 @@ import Cmm
 import CmmUtils
 import CLabel
 import MachOp
-import SMRep
 import StaticFlags
 
 import UniqFM
@@ -93,7 +92,7 @@ cmmMiniInline blocks = map do_inline blocks
 
 cmmMiniInlineStmts :: UniqFM Int -> [CmmStmt] -> [CmmStmt]
 cmmMiniInlineStmts uses [] = []
-cmmMiniInlineStmts uses (stmt@(CmmAssign (CmmLocal (LocalReg u _)) expr) : stmts)
+cmmMiniInlineStmts uses (stmt@(CmmAssign (CmmLocal (LocalReg u _ _)) expr) : stmts)
   | Just 1 <- lookupUFM uses u,
     Just stmts' <- lookForInline u expr stmts
   = 
@@ -109,7 +108,7 @@ cmmMiniInlineStmts uses (stmt:stmts)
 -- Try to inline a temporary assignment.  We can skip over assignments to
 -- other tempoararies, because we know that expressions aren't side-effecting
 -- and temporaries are single-assignment.
-lookForInline u expr (stmt@(CmmAssign (CmmLocal (LocalReg u' _)) rhs) : rest)
+lookForInline u expr (stmt@(CmmAssign (CmmLocal (LocalReg u' _ _)) rhs) : rest)
   | u /= u' 
   = case lookupUFM (getExprUses rhs) u of
        Just 1 -> Just (inlineStmt u expr stmt : rest)
@@ -150,8 +149,8 @@ getStmtUses (CmmJump e _) = getExprUses e
 getStmtUses _ = emptyUFM
 
 getExprUses :: CmmExpr -> UniqFM Int
-getExprUses (CmmReg (CmmLocal (LocalReg u _))) = unitUFM u 1
-getExprUses (CmmRegOff (CmmLocal (LocalReg u _)) _) = unitUFM u 1
+getExprUses (CmmReg (CmmLocal (LocalReg u _ _))) = unitUFM u 1
+getExprUses (CmmRegOff (CmmLocal (LocalReg u _ _)) _) = unitUFM u 1
 getExprUses (CmmLoad e _) = getExprUses e
 getExprUses (CmmMachOp _ es) = getExprsUses es
 getExprUses _other = emptyUFM
@@ -161,8 +160,8 @@ getExprsUses es = foldr (plusUFM_C (+)) emptyUFM (map getExprUses es)
 inlineStmt :: Unique -> CmmExpr -> CmmStmt -> CmmStmt
 inlineStmt u a (CmmAssign r e) = CmmAssign r (inlineExpr u a e)
 inlineStmt u a (CmmStore e1 e2) = CmmStore (inlineExpr u a e1) (inlineExpr u a e2)
-inlineStmt u a (CmmCall target regs es vols)
-   = CmmCall (infn target) regs es' vols
+inlineStmt u a (CmmCall target regs es srt)
+   = CmmCall (infn target) regs es' srt
    where infn (CmmForeignCall fn cconv) = CmmForeignCall fn cconv
         infn (CmmPrim p) = CmmPrim p
         es' = [ (inlineExpr u a e, hint) | (e,hint) <- es ]
@@ -172,10 +171,10 @@ inlineStmt u a (CmmJump e d) = CmmJump (inlineExpr u a e) d
 inlineStmt u a other_stmt = other_stmt
 
 inlineExpr :: Unique -> CmmExpr -> CmmExpr -> CmmExpr
-inlineExpr u a e@(CmmReg (CmmLocal (LocalReg u' _)))
+inlineExpr u a e@(CmmReg (CmmLocal (LocalReg u' _ _)))
   | u == u' = a
   | otherwise = e
-inlineExpr u a e@(CmmRegOff (CmmLocal (LocalReg u' rep)) off)
+inlineExpr u a e@(CmmRegOff (CmmLocal (LocalReg u' rep _)) off)
   | u == u' = CmmMachOp (MO_Add rep) [a, CmmLit (CmmInt (fromIntegral off) rep)]
   | otherwise = e
 inlineExpr u a (CmmLoad e rep) = CmmLoad (inlineExpr u a e) rep
@@ -531,7 +530,7 @@ narrowS _ _ = panic "narrowTo"
   except factorial, but what the hell.
 -}
 
-cmmLoopifyForC :: CmmTop -> CmmTop
+cmmLoopifyForC :: RawCmmTop -> RawCmmTop
 cmmLoopifyForC p@(CmmProc info entry_lbl [] blocks@(BasicBlock top_id _ : _))
   | null info = p  -- only if there's an info table, ignore case alts
   | otherwise =