module StgCmmExtCode (
CmmParse, unEC,
Named(..), Env,
loopDecls,
getEnv,
newLocal,
newLabel,
newBlockId,
newFunctionName,
newImport,
lookupLabel,
lookupName,
code,
emit, emitLabel, emitAssign, emitStore,
getCode, getCodeR,
emitOutOfLine,
withUpdFrameOff, getUpdFrameOff
)
where
import qualified StgCmmMonad as F
import StgCmmMonad (FCode, newUnique)
import Cmm
import CLabel
import MkGraph
import BlockId
import DynFlags
import FastString
import Module
import UniqFM
import Unique
import Control.Monad (liftM, ap)
import Control.Applicative (Applicative(..))
data Named
= VarN CmmExpr
| FunN PackageId
| LabelN BlockId
type Env = UniqFM Named
type Decls = [(FastString,Named)]
newtype CmmParse a
= EC { unEC :: Env -> Decls -> FCode (Decls, a) }
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 $ \e s -> do (s',r) <- m e s; unEC (k r) e s'
instance Functor CmmParse where
fmap = liftM
instance Applicative CmmParse where
pure = return
(<*>) = ap
instance Monad CmmParse where
(>>=) = thenExtFC
return = returnExtFC
instance HasDynFlags CmmParse where
getDynFlags = EC (\_ d -> do dflags <- getDynFlags
return (d, dflags))
loopDecls :: CmmParse a -> CmmParse a
loopDecls (EC fcode) =
EC $ \e globalDecls -> do
(_, a) <- F.fixC (\ ~(decls, _) -> fcode (addListToUFM e decls) globalDecls)
return (globalDecls, a)
getEnv :: CmmParse Env
getEnv = EC $ \e s -> return (s, e)
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)
newBlockId :: CmmParse BlockId
newBlockId = code F.newLabelC
newFunctionName
:: FastString
-> PackageId
-> 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 rtsPackageId 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 $ \e s -> do
((s',_), gr) <- F.getCodeR (ec e s)
return (s', gr)
getCodeR :: CmmParse a -> CmmParse (a, CmmAGraph)
getCodeR (EC ec) = EC $ \e s -> do
((s', r), gr) <- F.getCodeR (ec e s)
return (s', (r,gr))
emitOutOfLine :: BlockId -> CmmAGraph -> CmmParse ()
emitOutOfLine l g = code (F.emitOutOfLine l g)
withUpdFrameOff :: UpdFrameOffset -> CmmParse () -> CmmParse ()
withUpdFrameOff size inner
= EC $ \e s -> F.withUpdFrameOff size $ (unEC inner) e s
getUpdFrameOff :: CmmParse UpdFrameOffset
getUpdFrameOff = code $ F.getUpdFrameOff