Safe Haskell | None |
---|---|
Language | Haskell2010 |
Documentation
data NatM_State Source #
NatM_State | |
|
mkNatM_State :: UniqSupply -> Int -> DynFlags -> Module -> ModLocation -> DwarfFiles -> LabelMap DebugBlock -> NatM_State Source #
Instances
Monad NatM # | |
Functor NatM # | |
Applicative NatM # | |
MonadUnique NatM # | |
Defined in NCGMonad getUniqueSupplyM :: NatM UniqSupply Source # getUniqueM :: NatM Unique Source # getUniquesM :: NatM [Unique] Source # | |
HasDynFlags NatM # | |
CmmMakeDynamicReferenceM NatM # | |
initNat :: NatM_State -> NatM a -> (a, NatM_State) Source #
addImportNat :: CLabel -> NatM () Source #
mapAccumLNat :: (acc -> x -> NatM (acc, y)) -> acc -> [x] -> NatM (acc, [y]) Source #
setDeltaNat :: Int -> NatM () Source #
getDeltaNat :: NatM Int Source #
getDynFlags :: HasDynFlags m => m DynFlags Source #
getDebugBlock :: Label -> NatM (Maybe DebugBlock) Source #
type DwarfFiles = UniqFM (FastString, Int) Source #