X-Git-Url: http://git.megacz.com/?p=ghc-hetmet.git;a=blobdiff_plain;f=compiler%2Fcmm%2FZipCfgCmmRep.hs;h=0f00641efd565df40d0ce2260914cf8f537d3480;hp=a64a81d548c383b33b4adc51d2650730cb644c1f;hb=edc0bafd3fcd01b85a2e8894e5dfe149eb0e0857;hpb=5dc8b425443200a5160b9d1399aca1808bfcffee diff --git a/compiler/cmm/ZipCfgCmmRep.hs b/compiler/cmm/ZipCfgCmmRep.hs index a64a81d..0f00641 100644 --- a/compiler/cmm/ZipCfgCmmRep.hs +++ b/compiler/cmm/ZipCfgCmmRep.hs @@ -1,3 +1,6 @@ +{-# OPTIONS_GHC -XNoMonoLocalBinds #-} +-- Norman likes local bindings + -- This module is pure representation and should be imported only by -- clients that need to manipulate representation and know what -- they're doing. Clients that need to create flow graphs should @@ -29,7 +32,6 @@ import CmmTx import CLabel import FastString import ForeignCall -import qualified ZipCfg as Z import qualified ZipDataflow as DF import ZipCfg import MkZipCfg @@ -37,10 +39,9 @@ import Util import BasicTypes import Maybes -import Monad +import Control.Monad import Outputable import Prelude hiding (zip, unzip, last) -import qualified Data.List as L import SMRep (ByteOff) import UniqSupply @@ -87,39 +88,61 @@ data Last -- one -> second block etc -- Undefined outside range, and when there's a Nothing | LastCall { -- A call (native or safe foreign) - cml_target :: CmmExpr, -- never a CmmPrim to a CallishMachOp! - cml_cont :: Maybe BlockId, + cml_target :: CmmExpr, -- never a CmmPrim to a CallishMachOp! + + cml_cont :: Maybe BlockId, -- BlockId of continuation (Nothing for return or tail call) - cml_args :: ByteOff, -- byte offset for youngest outgoing arg - -- (includes update frame, which must be younger) - cml_ret_args:: ByteOff, -- byte offset for youngest incoming arg - cml_ret_off :: Maybe UpdFrameOffset} - -- stack offset for return (update frames); - -- The return offset should be Nothing only if we have to create - -- a new call, e.g. for a procpoint, in which case it's an invariant - -- that the call does not stand for a return or a tail call, - -- and the successor does not need an info table. - -data MidCallTarget -- The target of a MidUnsafeCall - = ForeignTarget -- A foreign procedure - CmmExpr -- Its address - ForeignConvention -- Its calling convention - - | PrimTarget -- A possibly-side-effecting machine operation - CallishMachOp -- Which one + + cml_args :: ByteOff, + -- Byte offset, from the *old* end of the Area associated with + -- the BlockId (if cml_cont = Nothing, then Old area), of + -- youngest outgoing arg. Set the stack pointer to this before + -- transferring control. + -- (NB: an update frame might also have been stored in the Old + -- area, but it'll be in an older part than the args.) + + cml_ret_args :: ByteOff, + -- For calls *only*, the byte offset for youngest returned value + -- This is really needed at the *return* point rather than here + -- at the call, but in practice it's convenient to record it here. + + cml_ret_off :: Maybe ByteOff + -- For calls *only*, the byte offset of the base of the frame that + -- must be described by the info table for the return point. + -- The older words are an update frames, which have their own + -- info-table and layout information + + -- From a liveness point of view, the stack words older than + -- cml_ret_off are treated as live, even if the sequel of + -- the call goes into a loop. + } + +data MidCallTarget -- The target of a MidUnsafeCall + = ForeignTarget -- A foreign procedure + CmmExpr -- Its address + ForeignConvention -- Its calling convention + + | PrimTarget -- A possibly-side-effecting machine operation + CallishMachOp -- Which one deriving Eq data Convention - = Native -- Native C-- call/return + = NativeDirectCall -- Native C-- call skipping the node (closure) argument + + | NativeNodeCall -- Native C-- call including the node argument + + | NativeReturn -- Native C-- return + + | Slow -- Slow entry points: all args pushed on the stack - | Slow -- Slow entry points: all args pushed on the stack + | GC -- Entry to the garbage collector: uses the node reg! - | GC -- Entry to the garbage collector: uses the node reg! + | PrimOpCall -- Calling prim ops - | PrimOp -- Calling prim ops + | PrimOpReturn -- Returning from prim ops - | Foreign -- Foreign call/return - ForeignConvention + | Foreign -- Foreign call/return + ForeignConvention | Private -- Used for control transfers within a (pre-CPS) procedure All @@ -140,6 +163,7 @@ data ForeignSafety = Unsafe -- unsafe call | Safe BlockId -- making infotable requires: 1. label UpdFrameOffset -- 2. where the upd frame is + Bool -- is the call interruptible? deriving Eq data ValueDirection = Arguments | Results @@ -257,8 +281,8 @@ instance UserOfLocalRegs MidCallTarget where foldRegsUsed f z (ForeignTarget e _) = foldRegsUsed f z e instance UserOfSlots MidCallTarget where + foldSlotsUsed f z (ForeignTarget e _) = foldSlotsUsed f z e foldSlotsUsed _f z (PrimTarget _) = z - foldSlotsUsed f z (ForeignTarget e _) = foldSlotsUsed f z e instance (UserOfLocalRegs a) => UserOfLocalRegs (Maybe a) where foldRegsUsed f z (Just x) = foldRegsUsed f z x @@ -439,10 +463,9 @@ pprMiddle stmt = pp_stmt <+> pp_debug -- call "ccall" foo(x, y)[r1, r2]; -- ToDo ppr volatile MidForeignCall safety target results args -> - hsep [ if null results - then empty - else parens (commafy $ map ppr results) <+> equals, - ppr_safety safety, + hsep [ ppUnless (null results) $ + parens (commafy $ map ppr results) <+> equals, + ppr_safety safety, ptext $ sLit "call", ppr_call_target target <> parens (commafy $ map ppr args) <> semi] @@ -460,12 +483,19 @@ ppr_fc (ForeignConvention c args res) = doubleQuotes (ppr c) <+> text "args: " <+> ppr args <+> text " results: " <+> ppr res ppr_safety :: ForeignSafety -> SDoc -ppr_safety (Safe bid upd) = text "safe<" <> ppr bid <> text ", " <> ppr upd <> text ">" +ppr_safety (Safe bid upd interruptible) = + text (if interruptible then "interruptible" else "safe") <> + text "<" <> ppr bid <> text ", " <> ppr upd <> text ">" ppr_safety Unsafe = text "unsafe" ppr_call_target :: MidCallTarget -> SDoc ppr_call_target (ForeignTarget fn c) = ppr_fc c <+> ppr_target fn -ppr_call_target (PrimTarget op) = ppr (CmmLabel (mkForeignLabel (mkFastString (show op)) Nothing False IsFunction)) +ppr_call_target (PrimTarget op) + -- HACK: We're just using a ForeignLabel to get this printed, the label + -- might not really be foreign. + = ppr (CmmLabel (mkForeignLabel + (mkFastString (show op)) + Nothing ForeignLabelInThisPackage IsFunction)) ppr_target :: CmmExpr -> SDoc ppr_target t@(CmmLit _) = ppr t @@ -516,12 +546,15 @@ genFullCondBranch expr t f = ] pprConvention :: Convention -> SDoc -pprConvention (Native {}) = text "" -pprConvention Slow = text "" -pprConvention GC = text "" -pprConvention PrimOp = text "" -pprConvention (Foreign c) = ppr c -pprConvention (Private {}) = text "" +pprConvention (NativeNodeCall {}) = text "" +pprConvention (NativeDirectCall {}) = text "" +pprConvention (NativeReturn {}) = text "" +pprConvention Slow = text "" +pprConvention GC = text "" +pprConvention PrimOpCall = text "" +pprConvention PrimOpReturn = text "" +pprConvention (Foreign c) = ppr c +pprConvention (Private {}) = text "" pprForeignConvention :: ForeignConvention -> SDoc pprForeignConvention (ForeignConvention c as rs) = ppr c <> ppr as <> ppr rs