imperative-edsl-0.5: Deep embedding of imperative programs with code generation

Safe HaskellNone
LanguageHaskell2010

Language.C.Monad

Description

A monad for C code generation

Synopsis

Documentation

data Flags Source

Code generation flags

Constructors

Flags 

(<<%=) :: MonadState s m => (forall f. Functor f => LensLike' f s a) -> (a -> a) -> m a Source

Reimplementation of <<%= from the lens package

(<<.=) :: MonadState s m => (forall f. Functor f => LensLike' f s a) -> a -> m a Source

Reimplementation of <<.= from the lens package

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

newtype CGenT t a Source

The C code generation monad transformer

Constructors

CGenT 

Fields

unCGenT :: StateT CEnv (ExceptionT t) a
 

runCGenT :: Monad m => CGenT m a -> CEnv -> m (a, CEnv) Source

Run the C code generation monad

runCGen :: CGen a -> CEnv -> (a, CEnv) Source

Run the C code generation monad

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

freshId :: MonadC m => m Integer Source

Retrieve a fresh identifier

gensym :: MonadC m => String -> m String Source

Generate a fresh symbol by appending a fresh id to a base name

touchVar :: (MonadC m, ToIdent v) => v -> m () Source

Mark an identifier as used in this context.

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

addParams :: MonadC m => [Param] -> m () Source

addArg :: MonadC m => Exp -> m () Source

Add a function argument when building a function call

addLocal :: MonadC m => InitGroup -> m () Source

Add a local declaration (including initializations)

addLocals :: MonadC m => [InitGroup] -> m () Source

Add multiple local declarations

addStm :: MonadC m => Stm -> m () Source

Add a statement to the current block

addStms :: MonadC m => [Stm] -> m () Source

Add a sequence of statements to the current block

addFinalStm :: MonadC m => Stm -> m () Source

Add a statement to the end of the current block

inBlock :: MonadC m => m a -> m a Source

Run an action in a new 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

inModule :: MonadC m => String -> m a -> m a Source

Declare a C translation unit

wrapMain :: MonadC m => m a -> m () Source

Wrap a program in a main function

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.