Safe Haskell | None |
---|---|
Language | Haskell2010 |
A monad for C code generation
Synopsis
- data Flags = Flags
- data CEnv = CEnv {
- _flags :: Flags
- _unique :: !Integer
- _modules :: Map String [Definition]
- _includes :: Set String
- _typedefs :: [Definition]
- _prototypes :: [Definition]
- _globals :: [Definition]
- _aliases :: Map Integer String
- _params :: [Param]
- _args :: [Exp]
- _locals :: [InitGroup]
- _items :: [BlockItem]
- _finalItems :: [BlockItem]
- _usedVars :: Set Id
- _funUsedVars :: Map String (Set Id)
- usedVars :: Lens' CEnv (Set Id)
- unique :: Lens' CEnv Integer
- typedefs :: Lens' CEnv [Definition]
- prototypes :: Lens' CEnv [Definition]
- params :: Lens' CEnv [Param]
- modules :: Lens' CEnv (Map String [Definition])
- locals :: Lens' CEnv [InitGroup]
- items :: Lens' CEnv [BlockItem]
- includes :: Lens' CEnv (Set String)
- globals :: Lens' CEnv [Definition]
- funUsedVars :: Lens' CEnv (Map String (Set Id))
- flags :: Lens' CEnv Flags
- finalItems :: Lens' CEnv [BlockItem]
- args :: Lens' CEnv [Exp]
- aliases :: Lens' CEnv (Map Integer String)
- defaultCEnv :: Flags -> CEnv
- type MonadC m = (Functor m, Applicative m, Monad m, MonadState CEnv m, MonadException m, MonadFix m)
- newtype CGenT t a = CGenT {
- unCGenT :: StateT CEnv (ExceptionT t) a
- type CGen = CGenT Identity
- runCGenT :: Monad m => CGenT m a -> CEnv -> m (a, CEnv)
- runCGen :: CGen a -> CEnv -> (a, CEnv)
- cenvToCUnit :: CEnv -> [Definition]
- prettyCGenT :: Monad m => CGenT m a -> m [(String, Doc)]
- prettyCGen :: CGen a -> [(String, Doc)]
- freshId :: MonadC m => m Integer
- gensym :: MonadC m => String -> m String
- touchVar :: (MonadC m, ToIdent v) => v -> m ()
- setUsedVars :: MonadC m => String -> Set Id -> m ()
- addInclude :: MonadC m => String -> m ()
- addLocalInclude :: MonadC m => String -> m ()
- addSystemInclude :: MonadC m => String -> m ()
- addTypedef :: MonadC m => Definition -> m ()
- addPrototype :: MonadC m => Definition -> m ()
- addGlobal :: MonadC m => Definition -> m ()
- addGlobals :: MonadC m => [Definition] -> m ()
- withAlias :: MonadC m => Integer -> String -> m a -> m a
- addParam :: MonadC m => Param -> m ()
- addParams :: MonadC m => [Param] -> m ()
- addArg :: MonadC m => Exp -> m ()
- addLocal :: MonadC m => InitGroup -> m ()
- addItem :: MonadC m => BlockItem -> m ()
- addLocals :: MonadC m => [InitGroup] -> m ()
- addStm :: MonadC m => Stm -> m ()
- addStms :: MonadC m => [Stm] -> m ()
- addFinalStm :: MonadC m => Stm -> m ()
- inBlock :: MonadC m => m a -> m a
- inNewBlock :: MonadC m => m a -> m (a, [BlockItem])
- inNewBlock_ :: MonadC m => m a -> m [BlockItem]
- inNewFunction :: MonadC m => m a -> m (a, Set Id, [Param], [BlockItem])
- inFunction :: MonadC m => String -> m a -> m a
- inFunctionTy :: MonadC m => Type -> String -> m a -> m a
- collectDefinitions :: MonadC m => m a -> m (a, [Definition])
- collectArgs :: MonadC m => m [Exp]
- inModule :: MonadC m => String -> m a -> m a
- wrapMain :: MonadC m => m a -> m ()
- liftSharedLocals :: MonadC m => m a -> m ()
- extractDecls :: (Id -> Bool) -> Definition -> (Definition, Set InitGroup)
Documentation
Code generator state.
CEnv | |
|
prototypes :: Lens' CEnv [Definition] Source #
defaultCEnv :: Flags -> CEnv Source #
Default code generator state
type MonadC m = (Functor m, Applicative m, Monad m, MonadState CEnv m, MonadException m, MonadFix m) Source #
Code generation type constraints
The C code generation monad transformer
CGenT | |
|
Instances
cenvToCUnit :: CEnv -> [Definition] Source #
Extract a compilation unit from the CEnv
state
prettyCGenT :: Monad m => CGenT m a -> m [(String, Doc)] Source #
Generate C documents for each module
gensym :: MonadC m => String -> m String Source #
Generate a fresh symbol by appending a fresh id to a base name
setUsedVars :: MonadC m => String -> Set Id -> m () Source #
Set the Set
of identifers used in the body of the given function.
addInclude :: MonadC m => String -> m () Source #
Add an include pre-processor directive. Specify <>
or '""' around
the file name.
addLocalInclude :: MonadC m => String -> m () Source #
Add a local include directive. The argument will be surrounded by '""'
addSystemInclude :: MonadC m => String -> m () Source #
Add a system include directive. The argument will be surrounded by <>
addTypedef :: MonadC m => Definition -> m () Source #
Add a type definition
addPrototype :: MonadC m => Definition -> m () Source #
Add a function prototype
addGlobal :: MonadC m => Definition -> m () Source #
Add a global definition
addGlobals :: MonadC m => [Definition] -> m () Source #
Add multiple global definitions
withAlias :: MonadC m => Integer -> String -> m a -> m a Source #
Let a variable be known by another name
addParam :: MonadC m => Param -> m () Source #
Add a function parameter when building a function definition
addLocal :: MonadC m => InitGroup -> m () Source #
Add a local declaration (including initializations)
addItem :: MonadC m => BlockItem -> m () Source #
Add an item (a declaration or a statement) to the current block This functionality is necessary to declare C99 variable-length arrays in the middle of a block, as other local delcarations are lifted to the beginning of the block, and that makes the evaluation of the length expression impossible.
addFinalStm :: MonadC m => Stm -> m () Source #
Add a statement to the end of the current block
inNewBlock :: MonadC m => m a -> m (a, [BlockItem]) Source #
Run an action as a block and capture the items. Does not place the items in an actual C block.
inNewBlock_ :: MonadC m => m a -> m [BlockItem] Source #
Run an action as a block and capture the items. Does not place the items in an actual C block.
inNewFunction :: MonadC m => m a -> m (a, Set Id, [Param], [BlockItem]) Source #
Run an action as a function declaration. Does not create a new function.
inFunction :: MonadC m => String -> m a -> m a Source #
Declare a function
inFunctionTy :: MonadC m => Type -> String -> m a -> m a Source #
Declare a function with the given return type.
collectDefinitions :: MonadC m => m a -> m (a, [Definition]) Source #
Collect all global definitions in the current state
collectArgs :: MonadC m => m [Exp] Source #
Collect all function arguments in the current state
liftSharedLocals :: MonadC m => m a -> m () Source #
Lift the declarations of all variables that are shared between functions to the top level. This relies on variable IDs being unique across programs, not just across the functions in which they are declared.
Only affects locally declared vars, not function arguments.
extractDecls :: (Id -> Bool) -> Definition -> (Definition, Set InitGroup) Source #
Remove all declarations matching a predicate from the given function and return them in a separate list.