| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Language.Cimple
Documentation
mapAst :: (TraverseAst iattr oattr itext otext a b, Applicative f) => AstActions f iattr oattr itext otext -> a -> f b Source #
traverseAst :: (TraverseAst iattr oattr itext otext a a, Applicative f) => AstActions f iattr oattr itext otext -> a -> f a Source #
doFiles :: AstActions f iattr oattr itext otext -> [(FilePath, [Node iattr (Lexeme itext)])] -> f [(FilePath, [Node oattr (Lexeme otext)])] -> f [(FilePath, [Node oattr (Lexeme otext)])] Source #
doFile :: AstActions f iattr oattr itext otext -> (FilePath, [Node iattr (Lexeme itext)]) -> f (FilePath, [Node oattr (Lexeme otext)]) -> f (FilePath, [Node oattr (Lexeme otext)]) Source #
doNodes :: AstActions f iattr oattr itext otext -> FilePath -> [Node iattr (Lexeme itext)] -> f [Node oattr (Lexeme otext)] -> f [Node oattr (Lexeme otext)] Source #
doNode :: AstActions f iattr oattr itext otext -> FilePath -> Node iattr (Lexeme itext) -> f (Node oattr (Lexeme otext)) -> f (Node oattr (Lexeme otext)) Source #
doLexemes :: AstActions f iattr oattr itext otext -> FilePath -> [Lexeme itext] -> f [Lexeme otext] -> f [Lexeme otext] Source #
doLexeme :: AstActions f iattr oattr itext otext -> FilePath -> Lexeme itext -> f (Lexeme otext) -> f (Lexeme otext) Source #
astActions :: Applicative f => (iattr -> f oattr) -> (itext -> f otext) -> AstActions f iattr oattr itext otext Source #
type AttrActions f iattr oattr text = AstActions f iattr oattr text text Source #
attrActions :: Applicative f => (iattr -> f oattr) -> AttrActions f iattr oattr text Source #
type TextActions f attr itext otext = AstActions f attr attr itext otext Source #
textActions :: Applicative f => (itext -> f otext) -> TextActions f attr itext otext Source #
type IdentityActions f attr text = AstActions f attr attr text text Source #
identityActions :: Applicative f => AstActions f attr attr text text Source #
data LexemeClass Source #
Constructors
Instances
parseTranslationUnit :: Alex [StringNode] Source #
Instances
| Eq AlexPosn Source # | |
| Show AlexPosn Source # | |
| Generic AlexPosn Source # | |
| ToJSON AlexPosn Source # | |
Defined in Language.Cimple.Lexer | |
| FromJSON AlexPosn Source # | |
| type Rep AlexPosn Source # | |
Defined in Language.Cimple.Lexer type Rep AlexPosn = D1 ('MetaData "AlexPosn" "Language.Cimple.Lexer" "cimple-0.0.5-LjWpKNCBm32813iMrbr1Ed" 'False) (C1 ('MetaCons "AlexPn" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int)))) | |
Constructors
| L AlexPosn LexemeClass text |
Instances
lexemeClass :: Lexeme text -> LexemeClass Source #
lexemePosn :: Lexeme text -> AlexPosn Source #
lexemeText :: Lexeme text -> text Source #
lexemeLine :: Lexeme text -> Int Source #
mkL :: Applicative m => LexemeClass -> AlexInput -> Int -> m (Lexeme String) Source #
Instances
Constructors
| BopNe | |
| BopEq | |
| BopOr | |
| BopBitXor | |
| BopBitOr | |
| BopAnd | |
| BopBitAnd | |
| BopDiv | |
| BopMul | |
| BopMod | |
| BopPlus | |
| BopMinus | |
| BopLt | |
| BopLe | |
| BopLsh | |
| BopGt | |
| BopGe | |
| BopRsh |
Instances
Instances
| Eq UnaryOp Source # | |
| Show UnaryOp Source # | |
| Generic UnaryOp Source # | |
| ToJSON UnaryOp Source # | |
Defined in Language.Cimple.AST | |
| FromJSON UnaryOp Source # | |
| type Rep UnaryOp Source # | |
Defined in Language.Cimple.AST type Rep UnaryOp = D1 ('MetaData "UnaryOp" "Language.Cimple.AST" "cimple-0.0.5-LjWpKNCBm32813iMrbr1Ed" 'False) ((C1 ('MetaCons "UopNot" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "UopNeg" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "UopMinus" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "UopAddress" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "UopDeref" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "UopIncr" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "UopDecr" 'PrefixI 'False) (U1 :: Type -> Type)))) | |
data LiteralType Source #
Instances
data Node attr lexeme Source #
Constructors
| Attr attr (Node attr lexeme) | |
| PreprocInclude lexeme | |
| PreprocDefine lexeme | |
| PreprocDefineConst lexeme (Node attr lexeme) | |
| PreprocDefineMacro lexeme [Node attr lexeme] (Node attr lexeme) | |
| PreprocIf (Node attr lexeme) [Node attr lexeme] (Node attr lexeme) | |
| PreprocIfdef lexeme [Node attr lexeme] (Node attr lexeme) | |
| PreprocIfndef lexeme [Node attr lexeme] (Node attr lexeme) | |
| PreprocElse [Node attr lexeme] | |
| PreprocElif (Node attr lexeme) [Node attr lexeme] (Node attr lexeme) | |
| PreprocUndef lexeme | |
| PreprocDefined lexeme | |
| PreprocScopedDefine (Node attr lexeme) [Node attr lexeme] (Node attr lexeme) | |
| MacroBodyStmt [Node attr lexeme] | |
| MacroBodyFunCall (Node attr lexeme) | |
| MacroParam lexeme | |
| StaticAssert (Node attr lexeme) lexeme | |
| LicenseDecl lexeme [Node attr lexeme] | |
| CopyrightDecl lexeme (Maybe lexeme) [lexeme] | |
| Comment CommentStyle lexeme [Node attr lexeme] lexeme | |
| CommentBlock lexeme | |
| CommentWord lexeme | |
| Commented (Node attr lexeme) (Node attr lexeme) | |
| ExternC [Node attr lexeme] | |
| Class Scope lexeme [Node attr lexeme] [Node attr lexeme] | |
| Namespace Scope lexeme [Node attr lexeme] | |
| CompoundStmt [Node attr lexeme] | |
| Break | |
| Goto lexeme | |
| Continue | |
| Return (Maybe (Node attr lexeme)) | |
| SwitchStmt (Node attr lexeme) [Node attr lexeme] | |
| IfStmt (Node attr lexeme) [Node attr lexeme] (Maybe (Node attr lexeme)) | |
| ForStmt (Node attr lexeme) (Node attr lexeme) (Node attr lexeme) [Node attr lexeme] | |
| WhileStmt (Node attr lexeme) [Node attr lexeme] | |
| DoWhileStmt [Node attr lexeme] (Node attr lexeme) | |
| Case (Node attr lexeme) (Node attr lexeme) | |
| Default (Node attr lexeme) | |
| Label lexeme (Node attr lexeme) | |
| VLA (Node attr lexeme) lexeme (Node attr lexeme) | |
| VarDecl (Node attr lexeme) (Node attr lexeme) | |
| Declarator (Node attr lexeme) (Maybe (Node attr lexeme)) | |
| DeclSpecVar lexeme | |
| DeclSpecArray (Node attr lexeme) (Maybe (Node attr lexeme)) | |
| InitialiserList [Node attr lexeme] | |
| UnaryExpr UnaryOp (Node attr lexeme) | |
| BinaryExpr (Node attr lexeme) BinaryOp (Node attr lexeme) | |
| TernaryExpr (Node attr lexeme) (Node attr lexeme) (Node attr lexeme) | |
| AssignExpr (Node attr lexeme) AssignOp (Node attr lexeme) | |
| ParenExpr (Node attr lexeme) | |
| CastExpr (Node attr lexeme) (Node attr lexeme) | |
| CompoundExpr (Node attr lexeme) (Node attr lexeme) | |
| SizeofExpr (Node attr lexeme) | |
| SizeofType (Node attr lexeme) | |
| LiteralExpr LiteralType lexeme | |
| VarExpr lexeme | |
| MemberAccess (Node attr lexeme) lexeme | |
| PointerAccess (Node attr lexeme) lexeme | |
| ArrayAccess (Node attr lexeme) (Node attr lexeme) | |
| FunctionCall (Node attr lexeme) [Node attr lexeme] | |
| CommentExpr (Node attr lexeme) (Node attr lexeme) | |
| EnumClass lexeme [Node attr lexeme] | |
| EnumConsts (Maybe lexeme) [Node attr lexeme] | |
| EnumDecl lexeme [Node attr lexeme] lexeme | |
| Enumerator lexeme (Maybe (Node attr lexeme)) | |
| ClassForward lexeme [Node attr lexeme] | |
| Typedef (Node attr lexeme) lexeme | |
| TypedefFunction (Node attr lexeme) | |
| Struct lexeme [Node attr lexeme] | |
| Union lexeme [Node attr lexeme] | |
| MemberDecl (Node attr lexeme) (Node attr lexeme) (Maybe lexeme) | |
| TyConst (Node attr lexeme) | |
| TyPointer (Node attr lexeme) | |
| TyStruct lexeme | |
| TyFunc lexeme | |
| TyStd lexeme | |
| TyVar lexeme | |
| TyUserDefined lexeme | |
| FunctionDecl Scope (Node attr lexeme) (Maybe (Node attr lexeme)) | |
| FunctionDefn Scope (Node attr lexeme) [Node attr lexeme] | |
| FunctionPrototype (Node attr lexeme) lexeme [Node attr lexeme] | |
| FunctionParam (Node attr lexeme) (Node attr lexeme) | |
| Event lexeme (Node attr lexeme) | |
| EventParams [Node attr lexeme] | |
| Property (Node attr lexeme) (Node attr lexeme) [Node attr lexeme] | |
| Accessor lexeme [Node attr lexeme] (Maybe (Node attr lexeme)) | |
| ErrorDecl lexeme [Node attr lexeme] | |
| ErrorList [Node attr lexeme] | |
| ErrorFor lexeme | |
| Ellipsis | |
| ConstDecl (Node attr lexeme) lexeme | |
| ConstDefn Scope (Node attr lexeme) lexeme (Node attr lexeme) |
Instances
data CommentStyle Source #
Instances
type AstActions a = IdentityActions (State a) () Text Source #
defaultActions :: IdentityActions (State a) () Text Source #