Safe Haskell | None |
---|---|
Language | Haskell2010 |
Documentation
traverseAst :: (TraverseAst itext otext a, Applicative f) => AstActions f itext otext -> a -> f (Mapped itext otext a) Source #
doFiles :: AstActions f itext otext -> [(FilePath, [Node (Lexeme itext)])] -> f [(FilePath, [Node (Lexeme otext)])] -> f [(FilePath, [Node (Lexeme otext)])] Source #
doFile :: AstActions f itext otext -> (FilePath, [Node (Lexeme itext)]) -> f (FilePath, [Node (Lexeme otext)]) -> f (FilePath, [Node (Lexeme otext)]) Source #
doNodes :: AstActions f itext otext -> FilePath -> [Node (Lexeme itext)] -> f [Node (Lexeme otext)] -> f [Node (Lexeme otext)] Source #
doNode :: AstActions f itext otext -> FilePath -> Node (Lexeme itext) -> f (Node (Lexeme otext)) -> f (Node (Lexeme otext)) Source #
doLexemes :: AstActions f itext otext -> FilePath -> [Lexeme itext] -> f [Lexeme otext] -> f [Lexeme otext] Source #
doLexeme :: AstActions f itext otext -> FilePath -> Lexeme itext -> f (Lexeme otext) -> f (Lexeme otext) Source #
astActions :: Applicative f => (itext -> f otext) -> AstActions f itext otext Source #
type TextActions f itext otext = AstActions f itext otext Source #
textActions :: Applicative f => (itext -> f otext) -> TextActions f itext otext Source #
type IdentityActions f text = AstActions f text text Source #
identityActions :: Applicative f => AstActions f text text Source #
data LexemeClass Source #
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.7-inplace" '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)))) |
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
BopNe | |
BopEq | |
BopOr | |
BopBitXor | |
BopBitOr | |
BopAnd | |
BopBitAnd | |
BopDiv | |
BopMul | |
BopMod | |
BopPlus | |
BopMinus | |
BopLt | |
BopLe | |
BopLsh | |
BopGt | |
BopGe | |
BopRsh |
Instances
Instances
Eq UnaryOp Source # | |
Read 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.7-inplace" '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
Instances
data CommentStyle Source #
Instances
Instances
removeAnnot :: AnnotNode lexeme -> Node lexeme Source #
type AstActions a = IdentityActions (State a) Text Source #
defaultActions :: AstActions state Source #