ghc-6.12.3: The GHC APISource codeContentsIndex
NCGMonad
Documentation
data NatM_State Source
Constructors
NatM_State
natm_us :: UniqSupply
natm_delta :: Int
natm_imports :: [CLabel]
natm_pic :: Maybe Reg
natm_dflags :: DynFlags
mkNatM_State :: UniqSupply -> Int -> DynFlags -> NatM_StateSource
data NatM result Source
show/hide Instances
initNat :: NatM_State -> NatM a -> (a, NatM_State)Source
addImportNat :: CLabel -> NatM ()Source
getUniqueNat :: NatM UniqueSource
mapAccumLNat :: (acc -> x -> NatM (acc, y)) -> acc -> [x] -> NatM (acc, [y])Source
setDeltaNat :: Int -> NatM ()Source
getDeltaNat :: NatM IntSource
getBlockIdNat :: NatM BlockIdSource
getNewLabelNat :: NatM CLabelSource
getNewRegNat :: Size -> NatM RegSource
getNewRegPairNat :: Size -> NatM (Reg, Reg)Source
getPicBaseMaybeNat :: NatM (Maybe Reg)Source
getPicBaseNat :: Size -> NatM RegSource
getDynFlagsNat :: NatM DynFlagsSource
Produced by Haddock version 2.6.1