Copyright | (c) 2008 Benedikt Huber |
---|---|
License | BSD-style |
Maintainer | benedikt.huber@gmail.com |
Stability | alpha |
Portability | ghc |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
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
- class Monad m => MonadName m where
- class Monad m => MonadSymtab m where
- getDefTable :: m DefTable
- withDefTable :: (DefTable -> (a, DefTable)) -> m a
- class Monad m => MonadCError m where
- throwTravError :: Error e => e -> m a
- catchTravError :: m a -> (CError -> m a) -> m a
- recordError :: Error e => e -> m ()
- getErrors :: m [CError]
- class (MonadName m, MonadSymtab m, MonadCError m) => MonadTrav m where
- handleDecl :: DeclEvent -> m ()
- handleTagDecl :: (MonadCError m, MonadSymtab m) => TagFwdDecl -> m ()
- handleTagDef :: MonadTrav m => TagDef -> m ()
- handleEnumeratorDef :: (MonadCError m, MonadSymtab m) => Enumerator -> m ()
- handleTypeDef :: MonadTrav m => TypeDef -> m ()
- handleObjectDef :: MonadTrav m => Bool -> Ident -> ObjDef -> m ()
- handleFunDef :: MonadTrav m => Ident -> FunDef -> m ()
- handleVarDecl :: MonadTrav m => Bool -> Decl -> m ()
- handleParamDecl :: MonadTrav m => ParamDecl -> m ()
- handleAsmBlock :: MonadTrav m => AsmBlock -> m ()
- enterPrototypeScope :: MonadSymtab m => m ()
- leavePrototypeScope :: MonadSymtab m => m ()
- enterFunctionScope :: MonadSymtab m => m ()
- leaveFunctionScope :: MonadSymtab m => m ()
- enterBlockScope :: MonadSymtab m => m ()
- leaveBlockScope :: MonadSymtab m => m ()
- lookupTypeDef :: (MonadCError m, MonadSymtab m) => Ident -> m Type
- lookupObject :: (MonadCError m, MonadSymtab m) => Ident -> m (Maybe IdentDecl)
- createSUERef :: (MonadCError m, MonadSymtab m) => NodeInfo -> Maybe Ident -> m SUERef
- hadHardErrors :: [CError] -> Bool
- handleTravError :: MonadCError m => m a -> m (Maybe a)
- throwOnLeft :: (MonadCError m, Error e) => Either e a -> m a
- astError :: MonadCError m => NodeInfo -> String -> m a
- warn :: (Error e, MonadCError m) => e -> m ()
- type Trav s a = TravT s Identity a
- data TravT s m a
- runTravT :: forall m s a. Monad m => s -> TravT s m a -> m (Either [CError] (a, TravState m s))
- runTravTWithTravState :: forall s m a. Monad m => TravState m s -> TravT s m a -> m (Either [CError] (a, TravState m s))
- runTrav :: forall s a. s -> Trav s a -> Either [CError] (a, TravState Identity s)
- runTrav_ :: Trav () a -> Either [CError] (a, [CError])
- data TravState m s
- initTravState :: Monad m => s -> TravState m s
- withExtDeclHandler :: Monad m => TravT s m a -> (DeclEvent -> TravT s m ()) -> TravT s m a
- modifyUserState :: (s -> s) -> Trav s ()
- userState :: TravState m s -> s
- getUserState :: Trav s s
- data TravOptions = TravOptions {}
- modifyOptions :: (TravOptions -> TravOptions) -> Trav s ()
- travErrors :: TravState m s -> [CError]
- data CLanguage
- mapMaybeM :: Monad m => Maybe a -> (a -> m b) -> m (Maybe b)
- maybeM :: Monad m => Maybe a -> (a -> m ()) -> m ()
- mapSndM :: Monad m => (b -> m c) -> (a, b) -> m (a, c)
- concatMapM :: Monad m => (a -> m [b]) -> [a] -> m [b]
Name generation monad
Symbol table monad
class Monad m => MonadSymtab m where Source #
getDefTable :: m DefTable Source #
return the definition table
withDefTable :: (DefTable -> (a, DefTable)) -> m a Source #
perform an action modifying the definition table
Instances
Monad m => MonadSymtab (TravT s m) Source # | |
Defined in Language.C.Analysis.TravMonad |
Specialized C error-handling monad
class Monad m => MonadCError m where Source #
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
Monad m => MonadCError (TravT s m) Source # | |
AST traversal monad
class (MonadName m, MonadSymtab m, MonadCError m) => MonadTrav m where Source #
Traversal monad
handleDecl :: DeclEvent -> m () Source #
handling declarations and definitions
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).
handleEnumeratorDef :: (MonadCError m, MonadSymtab m) => Enumerator -> m () Source #
handleTypeDef :: MonadTrav m => TypeDef -> m () Source #
handleObjectDef :: MonadTrav m => Bool -> Ident -> ObjDef -> m () Source #
handle object defintions (maybe tentative)
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
handleAsmBlock :: MonadTrav m => AsmBlock -> m () Source #
Symbol table scope modification
enterPrototypeScope :: MonadSymtab m => m () Source #
leavePrototypeScope :: MonadSymtab m => m () Source #
enterFunctionScope :: MonadSymtab m => m () Source #
leaveFunctionScope :: MonadSymtab m => m () Source #
enterBlockScope :: MonadSymtab m => m () Source #
leaveBlockScope :: MonadSymtab m => m () Source #
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
handleTravError :: MonadCError m => m a -> m (Maybe a) Source #
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
simple traversal monad, providing user state and callbacks
Instances
MonadTrans (TravT s) Source # | |
Defined in Language.C.Analysis.TravMonad | |
MonadIO m => MonadIO (TravT s m) Source # | |
Defined in Language.C.Analysis.TravMonad | |
Monad f => Applicative (TravT s f) Source # | |
Monad f => Functor (TravT s f) Source # | |
Monad m => Monad (TravT s m) Source # | |
Monad m => MonadCError (TravT s m) Source # | |
Monad m => MonadName (TravT s m) Source # | |
Monad m => MonadSymtab (TravT s m) Source # | |
Defined in Language.C.Analysis.TravMonad | |
Monad m => MonadTrav (TravT s m) Source # | |
Defined in Language.C.Analysis.TravMonad handleDecl :: DeclEvent -> TravT s m () Source # | |
Monad m => MonadState (TravState m s) (TravT s m) Source # | |
runTravT :: forall m s a. Monad m => s -> TravT s m a -> m (Either [CError] (a, TravState m s)) Source #
runTravTWithTravState :: forall s m a. Monad m => TravState m s -> TravT s m a -> m (Either [CError] (a, TravState m s)) Source #
initTravState :: Monad m => s -> TravState m s Source #
modifyUserState :: (s -> s) -> Trav s () Source #
getUserState :: Trav s s Source #
data TravOptions Source #
modifyOptions :: (TravOptions -> TravOptions) -> Trav s () Source #
travErrors :: TravState m s -> [CError] Source #
Language options
The variety of the C language to accept. Note: this is not yet enforced.
Helpers
concatMapM :: Monad m => (a -> m [b]) -> [a] -> m [b] Source #