cimple-0.0.5: Simple C-like programming language
Safe HaskellNone
LanguageHaskell2010

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 #

doText :: AstActions f iattr oattr itext otext -> FilePath -> itext -> f otext Source #

doAttr :: AstActions f iattr oattr itext otext -> FilePath -> iattr -> f oattr 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 #

Instances

Instances details
Eq LexemeClass Source # 
Instance details

Defined in Language.Cimple.Tokens

Ord LexemeClass Source # 
Instance details

Defined in Language.Cimple.Tokens

Show LexemeClass Source # 
Instance details

Defined in Language.Cimple.Tokens

Generic LexemeClass Source # 
Instance details

Defined in Language.Cimple.Tokens

Associated Types

type Rep LexemeClass :: Type -> Type #

ToJSON LexemeClass Source # 
Instance details

Defined in Language.Cimple.Tokens

FromJSON LexemeClass Source # 
Instance details

Defined in Language.Cimple.Tokens

type Rep LexemeClass Source # 
Instance details

Defined in Language.Cimple.Tokens

type Rep LexemeClass = D1 ('MetaData "LexemeClass" "Language.Cimple.Tokens" "cimple-0.0.5-LjWpKNCBm32813iMrbr1Ed" 'False) ((((((C1 ('MetaCons "IdConst" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "IdFuncType" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "IdStdType" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "IdSueType" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "IdTyVar" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "IdVar" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KwBitmask" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "KwBreak" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "KwCase" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KwClass" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "KwConst" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KwContinue" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "KwDefault" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KwDo" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "KwElse" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "KwEnum" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KwError" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "KwEvent" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KwExtern" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "KwFor" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KwGoto" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "KwIf" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "KwNamespace" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KwReturn" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "KwSizeof" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KwStatic" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "KwStaticAssert" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KwStruct" 'PrefixI 'False) (U1 :: Type -> Type)))))) :+: ((((C1 ('MetaCons "KwSwitch" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "KwThis" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KwTypedef" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "KwUnion" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KwVla" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "KwVoid" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KwWhile" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "KwWith" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "LitFalse" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LitTrue" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "LitChar" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LitInteger" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "LitString" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LitSysInclude" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "PctAmpersand" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PctAmpersandAmpersand" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PctAmpersandEq" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "PctArrow" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PctAsterisk" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "PctAsteriskEq" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PctCaret" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "PctCaretEq" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PctColon" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PctComma" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "PctEllipsis" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PctEMark" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "PctEMarkEq" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PctEq" 'PrefixI 'False) (U1 :: Type -> Type))))))) :+: (((((C1 ('MetaCons "PctEqEq" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PctGreater" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PctGreaterEq" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "PctGreaterGreater" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PctGreaterGreaterEq" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "PctLBrace" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PctLBrack" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "PctLess" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PctLessEq" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PctLessLess" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "PctLessLessEq" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PctLParen" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "PctMinus" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PctMinusEq" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "PctMinusMinus" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PctPeriod" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PctPercent" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "PctPercentEq" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PctPipe" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "PctPipeEq" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PctPipePipe" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "PctPlus" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PctPlusEq" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PctPlusPlus" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "PctQMark" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PctRBrace" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "PctRBrack" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PctRParen" 'PrefixI 'False) (U1 :: Type -> Type)))))) :+: ((((C1 ('MetaCons "PctSemicolon" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PctSlash" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PctSlashEq" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "PctTilde" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PpDefine" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "PpDefined" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PpElif" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "PpElse" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PpEndif" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PpIf" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "PpIfdef" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PpIfndef" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "PpInclude" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PpNewline" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "PpUndef" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "CmtBlock" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CmtIndent" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "CmtStart" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CmtStartBlock" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "CmtStartDoc" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CmtSpdxCopyright" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "CmtSpdxLicense" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "CmtCode" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CmtWord" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "CmtRef" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CmtEnd" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Error" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Eof" 'PrefixI 'False) (U1 :: Type -> Type))))))))

data Alex a Source #

Instances

Instances details
Monad Alex Source # 
Instance details

Defined in Language.Cimple.Lexer

Methods

(>>=) :: Alex a -> (a -> Alex b) -> Alex b #

(>>) :: Alex a -> Alex b -> Alex b #

return :: a -> Alex a #

Functor Alex Source # 
Instance details

Defined in Language.Cimple.Lexer

Methods

fmap :: (a -> b) -> Alex a -> Alex b #

(<$) :: a -> Alex b -> Alex a #

Applicative Alex Source # 
Instance details

Defined in Language.Cimple.Lexer

Methods

pure :: a -> Alex a #

(<*>) :: Alex (a -> b) -> Alex a -> Alex b #

liftA2 :: (a -> b -> c) -> Alex a -> Alex b -> Alex c #

(*>) :: Alex a -> Alex b -> Alex b #

(<*) :: Alex a -> Alex b -> Alex a #

data AlexPosn Source #

Constructors

AlexPn !Int !Int !Int 

Instances

Instances details
Eq AlexPosn Source # 
Instance details

Defined in Language.Cimple.Lexer

Show AlexPosn Source # 
Instance details

Defined in Language.Cimple.Lexer

Generic AlexPosn Source # 
Instance details

Defined in Language.Cimple.Lexer

Associated Types

type Rep AlexPosn :: Type -> Type #

Methods

from :: AlexPosn -> Rep AlexPosn x #

to :: Rep AlexPosn x -> AlexPosn #

ToJSON AlexPosn Source # 
Instance details

Defined in Language.Cimple.Lexer

FromJSON AlexPosn Source # 
Instance details

Defined in Language.Cimple.Lexer

type Rep AlexPosn Source # 
Instance details

Defined in Language.Cimple.Lexer

data Lexeme text Source #

Constructors

L AlexPosn LexemeClass text 

Instances

Instances details
Functor Lexeme Source # 
Instance details

Defined in Language.Cimple.Lexer

Methods

fmap :: (a -> b) -> Lexeme a -> Lexeme b #

(<$) :: a -> Lexeme b -> Lexeme a #

Foldable Lexeme Source # 
Instance details

Defined in Language.Cimple.Lexer

Methods

fold :: Monoid m => Lexeme m -> m #

foldMap :: Monoid m => (a -> m) -> Lexeme a -> m #

foldMap' :: Monoid m => (a -> m) -> Lexeme a -> m #

foldr :: (a -> b -> b) -> b -> Lexeme a -> b #

foldr' :: (a -> b -> b) -> b -> Lexeme a -> b #

foldl :: (b -> a -> b) -> b -> Lexeme a -> b #

foldl' :: (b -> a -> b) -> b -> Lexeme a -> b #

foldr1 :: (a -> a -> a) -> Lexeme a -> a #

foldl1 :: (a -> a -> a) -> Lexeme a -> a #

toList :: Lexeme a -> [a] #

null :: Lexeme a -> Bool #

length :: Lexeme a -> Int #

elem :: Eq a => a -> Lexeme a -> Bool #

maximum :: Ord a => Lexeme a -> a #

minimum :: Ord a => Lexeme a -> a #

sum :: Num a => Lexeme a -> a #

product :: Num a => Lexeme a -> a #

Traversable Lexeme Source # 
Instance details

Defined in Language.Cimple.Lexer

Methods

traverse :: Applicative f => (a -> f b) -> Lexeme a -> f (Lexeme b) #

sequenceA :: Applicative f => Lexeme (f a) -> f (Lexeme a) #

mapM :: Monad m => (a -> m b) -> Lexeme a -> m (Lexeme b) #

sequence :: Monad m => Lexeme (m a) -> m (Lexeme a) #

Eq text => Eq (Lexeme text) Source # 
Instance details

Defined in Language.Cimple.Lexer

Methods

(==) :: Lexeme text -> Lexeme text -> Bool #

(/=) :: Lexeme text -> Lexeme text -> Bool #

Show text => Show (Lexeme text) Source # 
Instance details

Defined in Language.Cimple.Lexer

Methods

showsPrec :: Int -> Lexeme text -> ShowS #

show :: Lexeme text -> String #

showList :: [Lexeme text] -> ShowS #

Generic (Lexeme text) Source # 
Instance details

Defined in Language.Cimple.Lexer

Associated Types

type Rep (Lexeme text) :: Type -> Type #

Methods

from :: Lexeme text -> Rep (Lexeme text) x #

to :: Rep (Lexeme text) x -> Lexeme text #

ToJSON text => ToJSON (Lexeme text) Source # 
Instance details

Defined in Language.Cimple.Lexer

Methods

toJSON :: Lexeme text -> Value #

toEncoding :: Lexeme text -> Encoding #

toJSONList :: [Lexeme text] -> Value #

toEncodingList :: [Lexeme text] -> Encoding #

FromJSON text => FromJSON (Lexeme text) Source # 
Instance details

Defined in Language.Cimple.Lexer

Methods

parseJSON :: Value -> Parser (Lexeme text) #

parseJSONList :: Value -> Parser [Lexeme text] #

type Rep (Lexeme text) Source # 
Instance details

Defined in Language.Cimple.Lexer

lexemeText :: Lexeme text -> text Source #

mkL :: Applicative m => LexemeClass -> AlexInput -> Int -> m (Lexeme String) Source #

data AssignOp Source #

Instances

Instances details
Eq AssignOp Source # 
Instance details

Defined in Language.Cimple.AST

Show AssignOp Source # 
Instance details

Defined in Language.Cimple.AST

Generic AssignOp Source # 
Instance details

Defined in Language.Cimple.AST

Associated Types

type Rep AssignOp :: Type -> Type #

Methods

from :: AssignOp -> Rep AssignOp x #

to :: Rep AssignOp x -> AssignOp #

ToJSON AssignOp Source # 
Instance details

Defined in Language.Cimple.AST

FromJSON AssignOp Source # 
Instance details

Defined in Language.Cimple.AST

type Rep AssignOp Source # 
Instance details

Defined in Language.Cimple.AST

type Rep AssignOp = D1 ('MetaData "AssignOp" "Language.Cimple.AST" "cimple-0.0.5-LjWpKNCBm32813iMrbr1Ed" 'False) (((C1 ('MetaCons "AopEq" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AopMul" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "AopDiv" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "AopPlus" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AopMinus" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "AopBitAnd" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "AopBitOr" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AopBitXor" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "AopMod" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "AopLsh" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AopRsh" 'PrefixI 'False) (U1 :: Type -> Type)))))

data BinaryOp Source #

Instances

Instances details
Eq BinaryOp Source # 
Instance details

Defined in Language.Cimple.AST

Show BinaryOp Source # 
Instance details

Defined in Language.Cimple.AST

Generic BinaryOp Source # 
Instance details

Defined in Language.Cimple.AST

Associated Types

type Rep BinaryOp :: Type -> Type #

Methods

from :: BinaryOp -> Rep BinaryOp x #

to :: Rep BinaryOp x -> BinaryOp #

ToJSON BinaryOp Source # 
Instance details

Defined in Language.Cimple.AST

FromJSON BinaryOp Source # 
Instance details

Defined in Language.Cimple.AST

type Rep BinaryOp Source # 
Instance details

Defined in Language.Cimple.AST

type Rep BinaryOp = D1 ('MetaData "BinaryOp" "Language.Cimple.AST" "cimple-0.0.5-LjWpKNCBm32813iMrbr1Ed" 'False) ((((C1 ('MetaCons "BopNe" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BopEq" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "BopOr" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BopBitXor" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "BopBitOr" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BopAnd" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "BopBitAnd" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "BopDiv" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BopMul" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "BopMod" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BopPlus" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "BopMinus" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BopLt" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "BopLe" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BopLsh" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "BopGt" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "BopGe" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BopRsh" 'PrefixI 'False) (U1 :: Type -> Type))))))

data UnaryOp Source #

Instances

Instances details
Eq UnaryOp Source # 
Instance details

Defined in Language.Cimple.AST

Methods

(==) :: UnaryOp -> UnaryOp -> Bool #

(/=) :: UnaryOp -> UnaryOp -> Bool #

Show UnaryOp Source # 
Instance details

Defined in Language.Cimple.AST

Generic UnaryOp Source # 
Instance details

Defined in Language.Cimple.AST

Associated Types

type Rep UnaryOp :: Type -> Type #

Methods

from :: UnaryOp -> Rep UnaryOp x #

to :: Rep UnaryOp x -> UnaryOp #

ToJSON UnaryOp Source # 
Instance details

Defined in Language.Cimple.AST

FromJSON UnaryOp Source # 
Instance details

Defined in Language.Cimple.AST

type Rep UnaryOp Source # 
Instance details

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 #

Constructors

Char 
Int 
Bool 
String 
ConstId 

Instances

Instances details
Eq LiteralType Source # 
Instance details

Defined in Language.Cimple.AST

Show LiteralType Source # 
Instance details

Defined in Language.Cimple.AST

Generic LiteralType Source # 
Instance details

Defined in Language.Cimple.AST

Associated Types

type Rep LiteralType :: Type -> Type #

ToJSON LiteralType Source # 
Instance details

Defined in Language.Cimple.AST

FromJSON LiteralType Source # 
Instance details

Defined in Language.Cimple.AST

type Rep LiteralType Source # 
Instance details

Defined in Language.Cimple.AST

type Rep LiteralType = D1 ('MetaData "LiteralType" "Language.Cimple.AST" "cimple-0.0.5-LjWpKNCBm32813iMrbr1Ed" 'False) ((C1 ('MetaCons "Char" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Int" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Bool" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "String" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ConstId" 'PrefixI 'False) (U1 :: Type -> Type))))

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

Instances details
Functor (Node attr) Source # 
Instance details

Defined in Language.Cimple.AST

Methods

fmap :: (a -> b) -> Node attr a -> Node attr b #

(<$) :: a -> Node attr b -> Node attr a #

Foldable (Node attr) Source # 
Instance details

Defined in Language.Cimple.AST

Methods

fold :: Monoid m => Node attr m -> m #

foldMap :: Monoid m => (a -> m) -> Node attr a -> m #

foldMap' :: Monoid m => (a -> m) -> Node attr a -> m #

foldr :: (a -> b -> b) -> b -> Node attr a -> b #

foldr' :: (a -> b -> b) -> b -> Node attr a -> b #

foldl :: (b -> a -> b) -> b -> Node attr a -> b #

foldl' :: (b -> a -> b) -> b -> Node attr a -> b #

foldr1 :: (a -> a -> a) -> Node attr a -> a #

foldl1 :: (a -> a -> a) -> Node attr a -> a #

toList :: Node attr a -> [a] #

null :: Node attr a -> Bool #

length :: Node attr a -> Int #

elem :: Eq a => a -> Node attr a -> Bool #

maximum :: Ord a => Node attr a -> a #

minimum :: Ord a => Node attr a -> a #

sum :: Num a => Node attr a -> a #

product :: Num a => Node attr a -> a #

Traversable (Node attr) Source # 
Instance details

Defined in Language.Cimple.AST

Methods

traverse :: Applicative f => (a -> f b) -> Node attr a -> f (Node attr b) #

sequenceA :: Applicative f => Node attr (f a) -> f (Node attr a) #

mapM :: Monad m => (a -> m b) -> Node attr a -> m (Node attr b) #

sequence :: Monad m => Node attr (m a) -> m (Node attr a) #

(Eq attr, Eq lexeme) => Eq (Node attr lexeme) Source # 
Instance details

Defined in Language.Cimple.AST

Methods

(==) :: Node attr lexeme -> Node attr lexeme -> Bool #

(/=) :: Node attr lexeme -> Node attr lexeme -> Bool #

(Show attr, Show lexeme) => Show (Node attr lexeme) Source # 
Instance details

Defined in Language.Cimple.AST

Methods

showsPrec :: Int -> Node attr lexeme -> ShowS #

show :: Node attr lexeme -> String #

showList :: [Node attr lexeme] -> ShowS #

Generic (Node attr lexeme) Source # 
Instance details

Defined in Language.Cimple.AST

Associated Types

type Rep (Node attr lexeme) :: Type -> Type #

Methods

from :: Node attr lexeme -> Rep (Node attr lexeme) x #

to :: Rep (Node attr lexeme) x -> Node attr lexeme #

(ToJSON attr, ToJSON lexeme) => ToJSON (Node attr lexeme) Source # 
Instance details

Defined in Language.Cimple.AST

Methods

toJSON :: Node attr lexeme -> Value #

toEncoding :: Node attr lexeme -> Encoding #

toJSONList :: [Node attr lexeme] -> Value #

toEncodingList :: [Node attr lexeme] -> Encoding #

(FromJSON attr, FromJSON lexeme) => FromJSON (Node attr lexeme) Source # 
Instance details

Defined in Language.Cimple.AST

Methods

parseJSON :: Value -> Parser (Node attr lexeme) #

parseJSONList :: Value -> Parser [Node attr lexeme] #

type Rep (Node attr lexeme) Source # 
Instance details

Defined in Language.Cimple.AST

type Rep (Node attr lexeme) = D1 ('MetaData "Node" "Language.Cimple.AST" "cimple-0.0.5-LjWpKNCBm32813iMrbr1Ed" 'False) ((((((C1 ('MetaCons "Attr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 attr) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Node attr lexeme))) :+: C1 ('MetaCons "PreprocInclude" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 lexeme))) :+: (C1 ('MetaCons "PreprocDefine" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 lexeme)) :+: (C1 ('MetaCons "PreprocDefineConst" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 lexeme) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Node attr lexeme))) :+: C1 ('MetaCons "PreprocDefineMacro" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 lexeme) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Node attr lexeme]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Node attr lexeme))))))) :+: ((C1 ('MetaCons "PreprocIf" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Node attr lexeme)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Node attr lexeme]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Node attr lexeme)))) :+: (C1 ('MetaCons "PreprocIfdef" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 lexeme) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Node attr lexeme]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Node attr lexeme)))) :+: C1 ('MetaCons "PreprocIfndef" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 lexeme) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Node attr lexeme]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Node attr lexeme)))))) :+: (C1 ('MetaCons "PreprocElse" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Node attr lexeme])) :+: (C1 ('MetaCons "PreprocElif" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Node attr lexeme)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Node attr lexeme]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Node attr lexeme)))) :+: C1 ('MetaCons "PreprocUndef" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 lexeme)))))) :+: (((C1 ('MetaCons "PreprocDefined" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 lexeme)) :+: (C1 ('MetaCons "PreprocScopedDefine" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Node attr lexeme)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Node attr lexeme]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Node attr lexeme)))) :+: C1 ('MetaCons "MacroBodyStmt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Node attr lexeme])))) :+: (C1 ('MetaCons "MacroBodyFunCall" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Node attr lexeme))) :+: (C1 ('MetaCons "MacroParam" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 lexeme)) :+: C1 ('MetaCons "StaticAssert" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Node attr lexeme)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 lexeme))))) :+: ((C1 ('MetaCons "LicenseDecl" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 lexeme) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Node attr lexeme])) :+: (C1 ('MetaCons "CopyrightDecl" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 lexeme) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe lexeme)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [lexeme]))) :+: C1 ('MetaCons "Comment" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 CommentStyle) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 lexeme)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Node attr lexeme]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 lexeme))))) :+: (C1 ('MetaCons "CommentBlock" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 lexeme)) :+: (C1 ('MetaCons "CommentWord" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 lexeme)) :+: C1 ('MetaCons "Commented" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Node attr lexeme)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Node attr lexeme)))))))) :+: ((((C1 ('MetaCons "ExternC" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Node attr lexeme])) :+: C1 ('MetaCons "Class" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Scope) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 lexeme)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Node attr lexeme]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Node attr lexeme])))) :+: (C1 ('MetaCons "Namespace" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Scope) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 lexeme) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Node attr lexeme]))) :+: (C1 ('MetaCons "CompoundStmt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Node attr lexeme])) :+: C1 ('MetaCons "Break" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "Goto" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 lexeme)) :+: (C1 ('MetaCons "Continue" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Return" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe (Node attr lexeme)))))) :+: (C1 ('MetaCons "SwitchStmt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Node attr lexeme)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Node attr lexeme])) :+: (C1 ('MetaCons "IfStmt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Node attr lexeme)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Node attr lexeme]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe (Node attr lexeme))))) :+: C1 ('MetaCons "ForStmt" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Node attr lexeme)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Node attr lexeme))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Node attr lexeme)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Node attr lexeme]))))))) :+: (((C1 ('MetaCons "WhileStmt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Node attr lexeme)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Node attr lexeme])) :+: (C1 ('MetaCons "DoWhileStmt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Node attr lexeme]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Node attr lexeme))) :+: C1 ('MetaCons "Case" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Node attr lexeme)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Node attr lexeme))))) :+: (C1 ('MetaCons "Default" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Node attr lexeme))) :+: (C1 ('MetaCons "Label" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 lexeme) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Node attr lexeme))) :+: C1 ('MetaCons "VLA" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Node attr lexeme)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 lexeme) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Node attr lexeme))))))) :+: ((C1 ('MetaCons "VarDecl" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Node attr lexeme)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Node attr lexeme))) :+: (C1 ('MetaCons "Declarator" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Node attr lexeme)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe (Node attr lexeme)))) :+: C1 ('MetaCons "DeclSpecVar" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 lexeme)))) :+: (C1 ('MetaCons "DeclSpecArray" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Node attr lexeme)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe (Node attr lexeme)))) :+: (C1 ('MetaCons "InitialiserList" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Node attr lexeme])) :+: C1 ('MetaCons "UnaryExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 UnaryOp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Node attr lexeme))))))))) :+: (((((C1 ('MetaCons "BinaryExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Node attr lexeme)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 BinaryOp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Node attr lexeme)))) :+: C1 ('MetaCons "TernaryExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Node attr lexeme)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Node attr lexeme)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Node attr lexeme))))) :+: (C1 ('MetaCons "AssignExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Node attr lexeme)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 AssignOp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Node attr lexeme)))) :+: (C1 ('MetaCons "ParenExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Node attr lexeme))) :+: C1 ('MetaCons "CastExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Node attr lexeme)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Node attr lexeme)))))) :+: ((C1 ('MetaCons "CompoundExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Node attr lexeme)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Node attr lexeme))) :+: (C1 ('MetaCons "SizeofExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Node attr lexeme))) :+: C1 ('MetaCons "SizeofType" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Node attr lexeme))))) :+: (C1 ('MetaCons "LiteralExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 LiteralType) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 lexeme)) :+: (C1 ('MetaCons "VarExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 lexeme)) :+: C1 ('MetaCons "MemberAccess" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Node attr lexeme)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 lexeme)))))) :+: (((C1 ('MetaCons "PointerAccess" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Node attr lexeme)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 lexeme)) :+: (C1 ('MetaCons "ArrayAccess" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Node attr lexeme)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Node attr lexeme))) :+: C1 ('MetaCons "FunctionCall" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Node attr lexeme)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Node attr lexeme])))) :+: (C1 ('MetaCons "CommentExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Node attr lexeme)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Node attr lexeme))) :+: (C1 ('MetaCons "EnumClass" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 lexeme) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Node attr lexeme])) :+: C1 ('MetaCons "EnumConsts" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe lexeme)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Node attr lexeme]))))) :+: ((C1 ('MetaCons "EnumDecl" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 lexeme) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Node attr lexeme]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 lexeme))) :+: (C1 ('MetaCons "Enumerator" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 lexeme) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe (Node attr lexeme)))) :+: C1 ('MetaCons "ClassForward" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 lexeme) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Node attr lexeme])))) :+: (C1 ('MetaCons "Typedef" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Node attr lexeme)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 lexeme)) :+: (C1 ('MetaCons "TypedefFunction" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Node attr lexeme))) :+: C1 ('MetaCons "Struct" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 lexeme) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Node attr lexeme]))))))) :+: ((((C1 ('MetaCons "Union" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 lexeme) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Node attr lexeme])) :+: C1 ('MetaCons "MemberDecl" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Node attr lexeme)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Node attr lexeme)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe lexeme))))) :+: (C1 ('MetaCons "TyConst" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Node attr lexeme))) :+: (C1 ('MetaCons "TyPointer" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Node attr lexeme))) :+: C1 ('MetaCons "TyStruct" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 lexeme))))) :+: ((C1 ('MetaCons "TyFunc" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 lexeme)) :+: (C1 ('MetaCons "TyStd" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 lexeme)) :+: C1 ('MetaCons "TyVar" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 lexeme)))) :+: (C1 ('MetaCons "TyUserDefined" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 lexeme)) :+: (C1 ('MetaCons "FunctionDecl" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Scope) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Node attr lexeme)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe (Node attr lexeme))))) :+: C1 ('MetaCons "FunctionDefn" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Scope) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Node attr lexeme)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Node attr lexeme]))))))) :+: (((C1 ('MetaCons "FunctionPrototype" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Node attr lexeme)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 lexeme) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Node attr lexeme]))) :+: (C1 ('MetaCons "FunctionParam" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Node attr lexeme)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Node attr lexeme))) :+: C1 ('MetaCons "Event" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 lexeme) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Node attr lexeme))))) :+: (C1 ('MetaCons "EventParams" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Node attr lexeme])) :+: (C1 ('MetaCons "Property" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Node attr lexeme)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Node attr lexeme)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Node attr lexeme]))) :+: C1 ('MetaCons "Accessor" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 lexeme) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Node attr lexeme]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe (Node attr lexeme)))))))) :+: ((C1 ('MetaCons "ErrorDecl" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 lexeme) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Node attr lexeme])) :+: (C1 ('MetaCons "ErrorList" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Node attr lexeme])) :+: C1 ('MetaCons "ErrorFor" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 lexeme)))) :+: (C1 ('MetaCons "Ellipsis" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ConstDecl" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Node attr lexeme)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 lexeme)) :+: C1 ('MetaCons "ConstDefn" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Scope) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Node attr lexeme))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 lexeme) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Node attr lexeme)))))))))))

data Scope Source #

Constructors

Global 
Static 

Instances

Instances details
Eq Scope Source # 
Instance details

Defined in Language.Cimple.AST

Methods

(==) :: Scope -> Scope -> Bool #

(/=) :: Scope -> Scope -> Bool #

Show Scope Source # 
Instance details

Defined in Language.Cimple.AST

Methods

showsPrec :: Int -> Scope -> ShowS #

show :: Scope -> String #

showList :: [Scope] -> ShowS #

Generic Scope Source # 
Instance details

Defined in Language.Cimple.AST

Associated Types

type Rep Scope :: Type -> Type #

Methods

from :: Scope -> Rep Scope x #

to :: Rep Scope x -> Scope #

ToJSON Scope Source # 
Instance details

Defined in Language.Cimple.AST

FromJSON Scope Source # 
Instance details

Defined in Language.Cimple.AST

type Rep Scope Source # 
Instance details

Defined in Language.Cimple.AST

type Rep Scope = D1 ('MetaData "Scope" "Language.Cimple.AST" "cimple-0.0.5-LjWpKNCBm32813iMrbr1Ed" 'False) (C1 ('MetaCons "Global" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Static" 'PrefixI 'False) (U1 :: Type -> Type))

data CommentStyle Source #

Constructors

Regular 
Doxygen 
Block 

Instances

Instances details
Eq CommentStyle Source # 
Instance details

Defined in Language.Cimple.AST

Show CommentStyle Source # 
Instance details

Defined in Language.Cimple.AST

Generic CommentStyle Source # 
Instance details

Defined in Language.Cimple.AST

Associated Types

type Rep CommentStyle :: Type -> Type #

ToJSON CommentStyle Source # 
Instance details

Defined in Language.Cimple.AST

FromJSON CommentStyle Source # 
Instance details

Defined in Language.Cimple.AST

type Rep CommentStyle Source # 
Instance details

Defined in Language.Cimple.AST

type Rep CommentStyle = D1 ('MetaData "CommentStyle" "Language.Cimple.AST" "cimple-0.0.5-LjWpKNCBm32813iMrbr1Ed" 'False) (C1 ('MetaCons "Regular" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Doxygen" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Block" 'PrefixI 'False) (U1 :: Type -> Type)))