module GHC.StgToCmm.ExtCode (
CmmParse, unEC,
Named(..), Env,
loopDecls,
getEnv,
withName,
getName,
newLocal,
newLabel,
newBlockId,
newFunctionName,
newImport,
lookupLabel,
lookupName,
code,
emit, emitLabel, emitAssign, emitStore,
getCode, getCodeR, getCodeScoped,
emitOutOfLine,
withUpdFrameOff, getUpdFrameOff
)
where
import GhcPrelude
import qualified GHC.StgToCmm.Monad as F
import GHC.StgToCmm.Monad (FCode, newUnique)
import Cmm
import CLabel
import MkGraph
import BlockId
import DynFlags
import FastString
import Module
import UniqFM
import Unique
import UniqSupply
import Control.Monad (ap)
data Named
= VarN CmmExpr
| FunN UnitId
| LabelN BlockId
type Env = UniqFM Named
type Decls = [(FastString,Named)]
newtype CmmParse a
= EC { unEC :: String -> Env -> Decls -> FCode (Decls, a) }
deriving (Functor)
type ExtCode = CmmParse ()
returnExtFC :: a -> CmmParse a
returnExtFC a = EC $ \_ _ s -> return (s, a)
thenExtFC :: CmmParse a -> (a -> CmmParse b) -> CmmParse b
thenExtFC (EC m) k = EC $ \c e s -> do (s',r) <- m c e s; unEC (k r) c e s'
instance Applicative CmmParse where
pure = returnExtFC
(<*>) = ap
instance Monad CmmParse where
(>>=) = thenExtFC
instance MonadUnique CmmParse where
getUniqueSupplyM = code getUniqueSupplyM
getUniqueM = EC $ \_ _ decls -> do
u <- getUniqueM
return (decls, u)
instance HasDynFlags CmmParse where
getDynFlags = EC (\_ _ d -> do dflags <- getDynFlags
return (d, dflags))
loopDecls :: CmmParse a -> CmmParse a
loopDecls (EC fcode) =
EC $ \c e globalDecls -> do
(_, a) <- F.fixC $ \ ~(decls, _) ->
fcode c (addListToUFM e decls) globalDecls
return (globalDecls, a)
getEnv :: CmmParse Env
getEnv = EC $ \_ e s -> return (s, e)
getName :: CmmParse String
getName = EC $ \c _ s -> return (s, c)
withName :: String -> CmmParse a -> CmmParse a
withName c' (EC fcode) = EC $ \_ e s -> fcode c' e s
addDecl :: FastString -> Named -> ExtCode
addDecl name named = EC $ \_ _ s -> return ((name, named) : s, ())
addVarDecl :: FastString -> CmmExpr -> ExtCode
addVarDecl var expr = addDecl var (VarN expr)
addLabel :: FastString -> BlockId -> ExtCode
addLabel name block_id = addDecl name (LabelN block_id)
newLocal
:: CmmType
-> FastString
-> CmmParse LocalReg
newLocal ty name = do
u <- code newUnique
let reg = LocalReg u ty
addVarDecl name (CmmReg (CmmLocal reg))
return reg
newLabel :: FastString -> CmmParse BlockId
newLabel name = do
u <- code newUnique
addLabel name (mkBlockId u)
return (mkBlockId u)
newFunctionName
:: FastString
-> UnitId
-> ExtCode
newFunctionName name pkg = addDecl name (FunN pkg)
newImport
:: (FastString, CLabel)
-> CmmParse ()
newImport (name, cmmLabel)
= addVarDecl name (CmmLit (CmmLabel cmmLabel))
lookupLabel :: FastString -> CmmParse BlockId
lookupLabel name = do
env <- getEnv
return $
case lookupUFM env name of
Just (LabelN l) -> l
_other -> mkBlockId (newTagUnique (getUnique name) 'L')
lookupName :: FastString -> CmmParse CmmExpr
lookupName name = do
env <- getEnv
return $
case lookupUFM env name of
Just (VarN e) -> e
Just (FunN pkg) -> CmmLit (CmmLabel (mkCmmCodeLabel pkg name))
_other -> CmmLit (CmmLabel (mkCmmCodeLabel rtsUnitId name))
code :: FCode a -> CmmParse a
code fc = EC $ \_ _ s -> do
r <- fc
return (s, r)
emit :: CmmAGraph -> CmmParse ()
emit = code . F.emit
emitLabel :: BlockId -> CmmParse ()
emitLabel = code . F.emitLabel
emitAssign :: CmmReg -> CmmExpr -> CmmParse ()
emitAssign l r = code (F.emitAssign l r)
emitStore :: CmmExpr -> CmmExpr -> CmmParse ()
emitStore l r = code (F.emitStore l r)
getCode :: CmmParse a -> CmmParse CmmAGraph
getCode (EC ec) = EC $ \c e s -> do
((s',_), gr) <- F.getCodeR (ec c e s)
return (s', gr)
getCodeR :: CmmParse a -> CmmParse (a, CmmAGraph)
getCodeR (EC ec) = EC $ \c e s -> do
((s', r), gr) <- F.getCodeR (ec c e s)
return (s', (r,gr))
getCodeScoped :: CmmParse a -> CmmParse (a, CmmAGraphScoped)
getCodeScoped (EC ec) = EC $ \c e s -> do
((s', r), gr) <- F.getCodeScoped (ec c e s)
return (s', (r,gr))
emitOutOfLine :: BlockId -> CmmAGraphScoped -> CmmParse ()
emitOutOfLine l g = code (F.emitOutOfLine l g)
withUpdFrameOff :: UpdFrameOffset -> CmmParse () -> CmmParse ()
withUpdFrameOff size inner
= EC $ \c e s -> F.withUpdFrameOff size $ (unEC inner) c e s
getUpdFrameOff :: CmmParse UpdFrameOffset
getUpdFrameOff = code $ F.getUpdFrameOff