summaryrefslogtreecommitdiff
path: root/compiler/cmm/CmmNode.hs
diff options
context:
space:
mode:
Diffstat (limited to 'compiler/cmm/CmmNode.hs')
-rw-r--r--compiler/cmm/CmmNode.hs46
1 files changed, 20 insertions, 26 deletions
diff --git a/compiler/cmm/CmmNode.hs b/compiler/cmm/CmmNode.hs
index 61c0b80179..47811bcd7f 100644
--- a/compiler/cmm/CmmNode.hs
+++ b/compiler/cmm/CmmNode.hs
@@ -4,13 +4,6 @@
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE UndecidableInstances #-}
-{-# OPTIONS -fno-warn-tabs #-}
--- The above warning supression flag is a temporary kludge.
--- While working on this module you are encouraged to remove it and
--- detab the module (please do the detabbing in a separate patch). See
--- http://hackage.haskell.org/trac/ghc/wiki/Commentary/CodingStyle#TabsvsSpaces
--- for details
-
module CmmNode (
CmmNode(..), CmmFormal, CmmActual,
UpdFrameOffset, Convention(..),
@@ -50,13 +43,13 @@ data CmmNode e x where
-- Assign to memory location. Size is
-- given by cmmExprType of the rhs.
- CmmUnsafeForeignCall :: -- An unsafe foreign call;
- -- see Note [Foreign calls]
- -- Like a "fat machine instruction"; can occur
- -- in the middle of a block
- ForeignTarget -> -- call target
- [CmmFormal] -> -- zero or more results
- [CmmActual] -> -- zero or more arguments
+ CmmUnsafeForeignCall :: -- An unsafe foreign call;
+ -- see Note [Foreign calls]
+ -- Like a "fat machine instruction"; can occur
+ -- in the middle of a block
+ ForeignTarget -> -- call target
+ [CmmFormal] -> -- zero or more results
+ [CmmActual] -> -- zero or more arguments
CmmNode O O
-- Semantics: clobbers any GlobalRegs for which callerSaves r == True
-- See Note [foreign calls clobber GlobalRegs]
@@ -124,12 +117,13 @@ data CmmNode e x where
} -> CmmNode O C
CmmForeignCall :: { -- A safe foreign call; see Note [Foreign calls]
- -- Always the last node of a block
+ -- Always the last node of a block
tgt :: ForeignTarget, -- call target and convention
res :: [CmmFormal], -- zero or more results
args :: [CmmActual], -- zero or more arguments; see Note [Register parameter passing]
succ :: ULabel, -- Label of continuation
- updfr :: UpdFrameOffset, -- where the update frame is (for building infotable)
+ ret_args :: ByteOff, -- same as cml_ret_args
+ ret_off :: ByteOff, -- same as cml_ret_off
intrbl:: Bool -- whether or not the call is interruptible
} -> CmmNode O C
@@ -143,14 +137,14 @@ instruction". In particular, they do *not* kill all live registers,
just the registers they return to (there was a bit of code in GHC that
conservatively assumed otherwise.) However, see [Register parameter passing].
-Safe ones are trickier. A safe foreign call
+Safe ones are trickier. A safe foreign call
r = f(x)
ultimately expands to
- push "return address" -- Never used to return to;
- -- just points an info table
+ push "return address" -- Never used to return to;
+ -- just points an info table
save registers into TSO
call suspendThread
- r = f(x) -- Make the call
+ r = f(x) -- Make the call
call resumeThread
restore registers
pop "return address"
@@ -354,7 +348,7 @@ instance DefinerOfRegs GlobalReg (CmmNode e x) where
-----------------------------------
-- mapping Expr in CmmNode
-mapForeignTarget :: (CmmExpr -> CmmExpr) -> ForeignTarget -> ForeignTarget
+mapForeignTarget :: (CmmExpr -> CmmExpr) -> ForeignTarget -> ForeignTarget
mapForeignTarget exp (ForeignTarget e c) = ForeignTarget (exp e) c
mapForeignTarget _ m@(PrimTarget _) = m
@@ -374,7 +368,7 @@ mapExp _ l@(CmmBranch _) = l
mapExp f (CmmCondBranch e ti fi) = CmmCondBranch (f e) ti fi
mapExp f (CmmSwitch e tbl) = CmmSwitch (f e) tbl
mapExp f n@CmmCall {cml_target=tgt} = n{cml_target = f tgt}
-mapExp f (CmmForeignCall tgt fs as succ updfr intrbl) = CmmForeignCall (mapForeignTarget f tgt) fs (map f as) succ updfr intrbl
+mapExp f (CmmForeignCall tgt fs as succ ret_args updfr intrbl) = CmmForeignCall (mapForeignTarget f tgt) fs (map f as) succ ret_args updfr intrbl
mapExpDeep :: (CmmExpr -> CmmExpr) -> CmmNode e x -> CmmNode e x
mapExpDeep f = mapExp $ wrapRecExp f
@@ -404,10 +398,10 @@ mapExpM f (CmmUnsafeForeignCall tgt fs as)
= case mapForeignTargetM f tgt of
Just tgt' -> Just (CmmUnsafeForeignCall tgt' fs (mapListJ f as))
Nothing -> (\xs -> CmmUnsafeForeignCall tgt fs xs) `fmap` mapListM f as
-mapExpM f (CmmForeignCall tgt fs as succ updfr intrbl)
+mapExpM f (CmmForeignCall tgt fs as succ ret_args updfr intrbl)
= case mapForeignTargetM f tgt of
- Just tgt' -> Just (CmmForeignCall tgt' fs (mapListJ f as) succ updfr intrbl)
- Nothing -> (\xs -> CmmForeignCall tgt fs xs succ updfr intrbl) `fmap` mapListM f as
+ Just tgt' -> Just (CmmForeignCall tgt' fs (mapListJ f as) succ ret_args updfr intrbl)
+ Nothing -> (\xs -> CmmForeignCall tgt fs xs succ ret_args updfr intrbl) `fmap` mapListM f as
-- share as much as possible
mapListM :: (a -> Maybe a) -> [a] -> Maybe [a]
@@ -430,7 +424,7 @@ mapExpDeepM f = mapExpM $ wrapRecExpM f
-----------------------------------
-- folding Expr in CmmNode
-foldExpForeignTarget :: (CmmExpr -> z -> z) -> ForeignTarget -> z -> z
+foldExpForeignTarget :: (CmmExpr -> z -> z) -> ForeignTarget -> z -> z
foldExpForeignTarget exp (ForeignTarget e _) z = exp e z
foldExpForeignTarget _ (PrimTarget _) z = z