language-c-0.7.0: Analysis and generation of C code

Copyright(c) 2008 Benedikt Huber
LicenseBSD-style
Maintainerbenedikt.huber@gmail.com
Stabilityalpha
Portabilityghc
Safe HaskellNone
LanguageHaskell98

Language.C.Analysis.TravMonad

Contents

Description

Monad for Traversals of the C AST.

For the traversal, we maintain a symboltable and need MonadError and unique name generation facilities. Furthermore, the user may provide callbacks to handle declarations and definitions.

Synopsis

Name generation monad

class Monad m => MonadName m where Source #

Minimal complete definition

genName

Methods

genName :: m Name Source #

unique name generation

Instances

Symbol table monad

class Monad m => MonadSymtab m where Source #

Minimal complete definition

getDefTable, withDefTable

Methods

getDefTable :: m DefTable Source #

return the definition table

withDefTable :: (DefTable -> (a, DefTable)) -> m a Source #

perform an action modifying the definition table

Specialized C error-handling monad

class Monad m => MonadCError m where Source #

Minimal complete definition

throwTravError, catchTravError, recordError, getErrors

Methods

throwTravError :: Error e => e -> m a Source #

throw an Error

catchTravError :: m a -> (CError -> m a) -> m a Source #

catch an Error (we could implement dynamically-typed catch here)

recordError :: Error e => e -> m () Source #

remember that an Error occurred (without throwing it)

getErrors :: m [CError] Source #

return the list of recorded errors

Instances

MonadCError (Trav s) Source # 

Methods

throwTravError :: Error e => e -> Trav s a Source #

catchTravError :: Trav s a -> (CError -> Trav s a) -> Trav s a Source #

recordError :: Error e => e -> Trav s () Source #

getErrors :: Trav s [CError] Source #

AST traversal monad

class (MonadName m, MonadSymtab m, MonadCError m) => MonadTrav m where Source #

Traversal monad

Minimal complete definition

handleDecl

Methods

handleDecl :: DeclEvent -> m () Source #

handling declarations and definitions

Instances

Handling declarations

handleTagDecl :: (MonadCError m, MonadSymtab m) => TagFwdDecl -> m () Source #

forward declaration of a tag. Only necessary for name analysis, but otherwise no semantic consequences.

handleTagDef :: MonadTrav m => TagDef -> m () Source #

define the given composite type or enumeration If there is a declaration visible, overwrite it with the definition. Otherwise, enter a new definition in the current namespace. If there is already a definition present, yield an error (redeclaration).

handleObjectDef :: MonadTrav m => Bool -> Ident -> ObjDef -> m () Source #

handle object defintions (maybe tentative)

handleFunDef :: MonadTrav m => Ident -> FunDef -> m () Source #

handle function definitions

handleVarDecl :: MonadTrav m => Bool -> Decl -> m () Source #

handle variable declarations (external object declarations and function prototypes) variable declarations are either function prototypes, or external declarations, and not very interesting on their own. we only put them in the symbol table and call the handle. declarations never override definitions

handleParamDecl :: MonadTrav m => ParamDecl -> m () Source #

handle parameter declaration. The interesting part is that parameters can be abstract (if they are part of a type). If they have a name, we enter the name (usually in function prototype or function scope), checking if there are duplicate definitions. FIXME: I think it would be more transparent to handle parameter declarations in a special way

Symbol table scope modification

Symbol table lookup (delegate)

lookupTypeDef :: (MonadCError m, MonadSymtab m) => Ident -> m Type Source #

lookup a type definition the 'wrong kind of object' is an internal error here, because the parser should distinguish typeDefs and other objects

lookupObject :: (MonadCError m, MonadSymtab m) => Ident -> m (Maybe IdentDecl) Source #

lookup an object, function or enumerator

Symbol table modification

createSUERef :: (MonadCError m, MonadSymtab m) => NodeInfo -> Maybe Ident -> m SUERef Source #

create a reference to a struct/union/enum

This currently depends on the fact the structs are tagged with unique names. We could use the name generation of TravMonad as well, which might be the better choice when dealing with autogenerated code.

Additional error handling facilities

hadHardErrors :: [CError] -> Bool Source #

check wheter non-recoverable errors occurred

throwOnLeft :: (MonadCError m, Error e) => Either e a -> m a Source #

raise an error based on an Either argument

astError :: MonadCError m => NodeInfo -> String -> m a Source #

raise an error caused by a malformed AST

warn :: (Error e, MonadCError m) => e -> m () Source #

Trav - default MonadTrav implementation

data Trav s a Source #

simple traversal monad, providing user state and callbacks

Instances

Monad (Trav s) Source # 

Methods

(>>=) :: Trav s a -> (a -> Trav s b) -> Trav s b #

(>>) :: Trav s a -> Trav s b -> Trav s b #

return :: a -> Trav s a #

fail :: String -> Trav s a #

Functor (Trav s) Source # 

Methods

fmap :: (a -> b) -> Trav s a -> Trav s b #

(<$) :: a -> Trav s b -> Trav s a #

Applicative (Trav s) Source # 

Methods

pure :: a -> Trav s a #

(<*>) :: Trav s (a -> b) -> Trav s a -> Trav s b #

(*>) :: Trav s a -> Trav s b -> Trav s b #

(<*) :: Trav s a -> Trav s b -> Trav s a #

MonadTrav (Trav s) Source # 

Methods

handleDecl :: DeclEvent -> Trav s () Source #

MonadCError (Trav s) Source # 

Methods

throwTravError :: Error e => e -> Trav s a Source #

catchTravError :: Trav s a -> (CError -> Trav s a) -> Trav s a Source #

recordError :: Error e => e -> Trav s () Source #

getErrors :: Trav s [CError] Source #

MonadSymtab (Trav s) Source # 
MonadName (Trav s) Source # 

Methods

genName :: Trav s Name Source #

runTrav :: forall s a. s -> Trav s a -> Either [CError] (a, TravState s) Source #

runTrav_ :: Trav () a -> Either [CError] (a, [CError]) Source #

withExtDeclHandler :: Trav s a -> (DeclEvent -> Trav s ()) -> Trav s a Source #

modifyUserState :: (s -> s) -> Trav s () Source #

data TravOptions Source #

Constructors

TravOptions 

Fields

Language options

data CLanguage Source #

The variety of the C language to accept. Note: this is not yet enforced.

Constructors

C89 
C99 
GNU89 
GNU99 

Helpers

mapMaybeM :: Monad m => Maybe a -> (a -> m b) -> m (Maybe b) Source #

maybeM :: Monad m => Maybe a -> (a -> m ()) -> m () Source #

mapSndM :: Monad m => (b -> m c) -> (a, b) -> m (a, c) Source #

concatMapM :: Monad m => (a -> m [b]) -> [a] -> m [b] Source #