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

Language.Cimple

Documentation

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.15-inplace" '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 "IdVar" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KwBreak" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "KwCase" '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 "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 "KwNonNull" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "KwNullable" '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 "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 "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 "CmtCommand" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "CmtEndDocSection" '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 "CmtStartDocSection" '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

Read 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.15-inplace" '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

Read 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.15-inplace" '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 #

Read UnaryOp Source # 
Instance details

Defined in Language.Cimple.Ast

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.15-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 #

Constructors

Char 
Int 
Bool 
String 
ConstId 

Instances

Instances details
Eq LiteralType Source # 
Instance details

Defined in Language.Cimple.Ast

Read 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.15-inplace" '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))))

type Node lexeme = Fix (NodeF lexeme) Source #

data NodeF lexeme a Source #

Constructors

PreprocInclude lexeme 
PreprocDefine lexeme 
PreprocDefineConst lexeme a 
PreprocDefineMacro lexeme [a] a 
PreprocIf a [a] a 
PreprocIfdef lexeme [a] a 
PreprocIfndef lexeme [a] a 
PreprocElse [a] 
PreprocElif a [a] a 
PreprocUndef lexeme 
PreprocDefined lexeme 
PreprocScopedDefine a [a] a 
MacroBodyStmt a 
MacroBodyFunCall a 
MacroParam lexeme 
StaticAssert a lexeme 
LicenseDecl lexeme [a] 
CopyrightDecl lexeme (Maybe lexeme) [lexeme] 
Comment CommentStyle lexeme [lexeme] lexeme 
CommentSectionEnd lexeme 
Commented a a 
ExternC [a] 
CompoundStmt [a] 
Break 
Goto lexeme 
Continue 
Return (Maybe a) 
SwitchStmt a [a] 
IfStmt a a (Maybe a) 
ForStmt a a a a 
WhileStmt a a 
DoWhileStmt a a 
Case a a 
Default a 
Label lexeme a 
ExprStmt a 
VLA a lexeme a 
VarDeclStmt a (Maybe a) 
VarDecl a lexeme [a] 
DeclSpecArray (Maybe a) 
InitialiserList [a] 
UnaryExpr UnaryOp a 
BinaryExpr a BinaryOp a 
TernaryExpr a a a 
AssignExpr a AssignOp a 
ParenExpr a 
CastExpr a a 
CompoundExpr a a 
CompoundLiteral a a 
SizeofExpr a 
SizeofType a 
LiteralExpr LiteralType lexeme 
VarExpr lexeme 
MemberAccess a lexeme 
PointerAccess a lexeme 
ArrayAccess a a 
FunctionCall a [a] 
CommentExpr a a 
EnumConsts (Maybe lexeme) [a] 
EnumDecl lexeme [a] lexeme 
Enumerator lexeme (Maybe a) 
AggregateDecl a 
Typedef a lexeme 
TypedefFunction a 
Struct lexeme [a] 
Union lexeme [a] 
MemberDecl a (Maybe lexeme) 
TyConst a 
TyPointer a 
TyStruct lexeme 
TyFunc lexeme 
TyStd lexeme 
TyUserDefined lexeme 
FunctionDecl Scope a 
FunctionDefn Scope a a 
FunctionPrototype a lexeme [a] 
CallbackDecl lexeme lexeme 
Ellipsis 
NonNull [lexeme] [lexeme] a 
ConstDecl a lexeme 
ConstDefn Scope a lexeme a 

Instances

Instances details
Functor (NodeF lexeme) Source # 
Instance details

Defined in Language.Cimple.Ast

Methods

fmap :: (a -> b) -> NodeF lexeme a -> NodeF lexeme b #

(<$) :: a -> NodeF lexeme b -> NodeF lexeme a #

Foldable (NodeF lexeme) Source # 
Instance details

Defined in Language.Cimple.Ast

Methods

fold :: Monoid m => NodeF lexeme m -> m #

foldMap :: Monoid m => (a -> m) -> NodeF lexeme a -> m #

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

foldr :: (a -> b -> b) -> b -> NodeF lexeme a -> b #

foldr' :: (a -> b -> b) -> b -> NodeF lexeme a -> b #

foldl :: (b -> a -> b) -> b -> NodeF lexeme a -> b #

foldl' :: (b -> a -> b) -> b -> NodeF lexeme a -> b #

foldr1 :: (a -> a -> a) -> NodeF lexeme a -> a #

foldl1 :: (a -> a -> a) -> NodeF lexeme a -> a #

toList :: NodeF lexeme a -> [a] #

null :: NodeF lexeme a -> Bool #

length :: NodeF lexeme a -> Int #

elem :: Eq a => a -> NodeF lexeme a -> Bool #

maximum :: Ord a => NodeF lexeme a -> a #

minimum :: Ord a => NodeF lexeme a -> a #

sum :: Num a => NodeF lexeme a -> a #

product :: Num a => NodeF lexeme a -> a #

Traversable (NodeF lexeme) Source # 
Instance details

Defined in Language.Cimple.Ast

Methods

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

sequenceA :: Applicative f => NodeF lexeme (f a) -> f (NodeF lexeme a) #

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

sequence :: Monad m => NodeF lexeme (m a) -> m (NodeF lexeme a) #

ToJSON lexeme => ToJSON1 (NodeF lexeme) Source # 
Instance details

Defined in Language.Cimple.Ast

Methods

liftToJSON :: (a -> Value) -> ([a] -> Value) -> NodeF lexeme a -> Value #

liftToJSONList :: (a -> Value) -> ([a] -> Value) -> [NodeF lexeme a] -> Value #

liftToEncoding :: (a -> Encoding) -> ([a] -> Encoding) -> NodeF lexeme a -> Encoding #

liftToEncodingList :: (a -> Encoding) -> ([a] -> Encoding) -> [NodeF lexeme a] -> Encoding #

FromJSON lexeme => FromJSON1 (NodeF lexeme) Source # 
Instance details

Defined in Language.Cimple.Ast

Methods

liftParseJSON :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser (NodeF lexeme a) #

liftParseJSONList :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser [NodeF lexeme a] #

Eq lexeme => Eq1 (NodeF lexeme) Source # 
Instance details

Defined in Language.Cimple.Ast

Methods

liftEq :: (a -> b -> Bool) -> NodeF lexeme a -> NodeF lexeme b -> Bool #

Read lexeme => Read1 (NodeF lexeme) Source # 
Instance details

Defined in Language.Cimple.Ast

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (NodeF lexeme a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [NodeF lexeme a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (NodeF lexeme a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [NodeF lexeme a] #

Show lexeme => Show1 (NodeF lexeme) Source # 
Instance details

Defined in Language.Cimple.Ast

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> NodeF lexeme a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [NodeF lexeme a] -> ShowS #

Generic1 (NodeF lexeme :: Type -> Type) Source # 
Instance details

Defined in Language.Cimple.Ast

Associated Types

type Rep1 (NodeF lexeme) :: k -> Type #

Methods

from1 :: forall (a :: k). NodeF lexeme a -> Rep1 (NodeF lexeme) a #

to1 :: forall (a :: k). Rep1 (NodeF lexeme) a -> NodeF lexeme a #

(Eq lexeme, Eq a) => Eq (NodeF lexeme a) Source # 
Instance details

Defined in Language.Cimple.Ast

Methods

(==) :: NodeF lexeme a -> NodeF lexeme a -> Bool #

(/=) :: NodeF lexeme a -> NodeF lexeme a -> Bool #

(Read lexeme, Read a) => Read (NodeF lexeme a) Source # 
Instance details

Defined in Language.Cimple.Ast

Methods

readsPrec :: Int -> ReadS (NodeF lexeme a) #

readList :: ReadS [NodeF lexeme a] #

readPrec :: ReadPrec (NodeF lexeme a) #

readListPrec :: ReadPrec [NodeF lexeme a] #

(Show lexeme, Show a) => Show (NodeF lexeme a) Source # 
Instance details

Defined in Language.Cimple.Ast

Methods

showsPrec :: Int -> NodeF lexeme a -> ShowS #

show :: NodeF lexeme a -> String #

showList :: [NodeF lexeme a] -> ShowS #

Generic (NodeF lexeme a) Source # 
Instance details

Defined in Language.Cimple.Ast

Associated Types

type Rep (NodeF lexeme a) :: Type -> Type #

Methods

from :: NodeF lexeme a -> Rep (NodeF lexeme a) x #

to :: Rep (NodeF lexeme a) x -> NodeF lexeme a #

type Rep1 (NodeF lexeme :: Type -> Type) Source # 
Instance details

Defined in Language.Cimple.Ast

type Rep1 (NodeF lexeme :: Type -> Type) = D1 ('MetaData "NodeF" "Language.Cimple.Ast" "cimple-0.0.15-inplace" 'False) ((((((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) Par1) :+: (C1 ('MetaCons "PreprocDefineMacro" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 lexeme) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec1 []) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) Par1)) :+: C1 ('MetaCons "PreprocIf" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) Par1 :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec1 []) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) Par1))))) :+: ((C1 ('MetaCons "PreprocIfdef" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 lexeme) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec1 []) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) Par1)) :+: C1 ('MetaCons "PreprocIfndef" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 lexeme) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec1 []) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) Par1))) :+: (C1 ('MetaCons "PreprocElse" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec1 [])) :+: (C1 ('MetaCons "PreprocElif" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) Par1 :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec1 []) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) Par1)) :+: 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) Par1 :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec1 []) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) Par1))) :+: (C1 ('MetaCons "MacroBodyStmt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) Par1) :+: (C1 ('MetaCons "MacroBodyFunCall" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) Par1) :+: 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) Par1 :*: 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) (Rec1 []))) :+: (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 [lexeme]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 lexeme))) :+: C1 ('MetaCons "CommentSectionEnd" '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) Par1 :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) Par1) :+: C1 ('MetaCons "ExternC" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec1 []))) :+: (C1 ('MetaCons "CompoundStmt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec1 [])) :+: (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) (Rec1 Maybe))) :+: (C1 ('MetaCons "SwitchStmt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) Par1 :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec1 [])) :+: (C1 ('MetaCons "IfStmt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) Par1 :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) Par1 :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec1 Maybe))) :+: C1 ('MetaCons "ForStmt" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) Par1 :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) Par1) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) Par1 :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) Par1)))))) :+: (((C1 ('MetaCons "WhileStmt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) Par1 :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) Par1) :+: C1 ('MetaCons "DoWhileStmt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) Par1 :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) Par1)) :+: (C1 ('MetaCons "Case" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) Par1 :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) Par1) :+: (C1 ('MetaCons "Default" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) Par1) :+: C1 ('MetaCons "Label" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 lexeme) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) Par1)))) :+: ((C1 ('MetaCons "ExprStmt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) Par1) :+: C1 ('MetaCons "VLA" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) Par1 :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 lexeme) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) Par1))) :+: (C1 ('MetaCons "VarDeclStmt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) Par1 :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec1 Maybe)) :+: (C1 ('MetaCons "VarDecl" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) Par1 :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 lexeme) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec1 []))) :+: C1 ('MetaCons "DeclSpecArray" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec1 Maybe)))))))) :+: (((((C1 ('MetaCons "InitialiserList" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec1 [])) :+: C1 ('MetaCons "UnaryExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 UnaryOp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) Par1)) :+: (C1 ('MetaCons "BinaryExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) Par1 :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 BinaryOp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) Par1)) :+: (C1 ('MetaCons "TernaryExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) Par1 :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) Par1 :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) Par1)) :+: C1 ('MetaCons "AssignExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) Par1 :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 AssignOp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) Par1))))) :+: ((C1 ('MetaCons "ParenExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) Par1) :+: C1 ('MetaCons "CastExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) Par1 :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) Par1)) :+: (C1 ('MetaCons "CompoundExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) Par1 :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) Par1) :+: (C1 ('MetaCons "CompoundLiteral" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) Par1 :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) Par1) :+: C1 ('MetaCons "SizeofExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) Par1))))) :+: (((C1 ('MetaCons "SizeofType" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) Par1) :+: 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) Par1 :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 lexeme)) :+: C1 ('MetaCons "PointerAccess" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) Par1 :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 lexeme))))) :+: ((C1 ('MetaCons "ArrayAccess" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) Par1 :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) Par1) :+: C1 ('MetaCons "FunctionCall" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) Par1 :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec1 []))) :+: (C1 ('MetaCons "CommentExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) Par1 :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) Par1) :+: (C1 ('MetaCons "EnumConsts" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe lexeme)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec1 [])) :+: C1 ('MetaCons "EnumDecl" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 lexeme) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec1 []) :*: 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) (Rec1 Maybe)) :+: C1 ('MetaCons "AggregateDecl" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) Par1)) :+: (C1 ('MetaCons "Typedef" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) Par1 :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 lexeme)) :+: (C1 ('MetaCons "TypedefFunction" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) Par1) :+: C1 ('MetaCons "Struct" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 lexeme) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec1 []))))) :+: ((C1 ('MetaCons "Union" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 lexeme) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec1 [])) :+: C1 ('MetaCons "MemberDecl" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) Par1 :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe lexeme)))) :+: (C1 ('MetaCons "TyConst" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) Par1) :+: (C1 ('MetaCons "TyPointer" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) Par1) :+: 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 "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) Par1) :+: C1 ('MetaCons "FunctionDefn" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Scope) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) Par1 :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) Par1))))) :+: ((C1 ('MetaCons "FunctionPrototype" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) Par1 :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 lexeme) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec1 []))) :+: (C1 ('MetaCons "CallbackDecl" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 lexeme) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 lexeme)) :+: C1 ('MetaCons "Ellipsis" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "NonNull" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [lexeme]) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [lexeme]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) Par1)) :+: (C1 ('MetaCons "ConstDecl" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) Par1 :*: 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) Par1) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 lexeme) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) Par1)))))))))
type Rep (NodeF lexeme a) Source # 
Instance details

Defined in Language.Cimple.Ast

type Rep (NodeF lexeme a) = D1 ('MetaData "NodeF" "Language.Cimple.Ast" "cimple-0.0.15-inplace" 'False) ((((((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 a)) :+: (C1 ('MetaCons "PreprocDefineMacro" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 lexeme) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [a]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 a))) :+: C1 ('MetaCons "PreprocIf" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [a]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 a)))))) :+: ((C1 ('MetaCons "PreprocIfdef" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 lexeme) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [a]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 a))) :+: C1 ('MetaCons "PreprocIfndef" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 lexeme) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [a]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 a)))) :+: (C1 ('MetaCons "PreprocElse" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [a])) :+: (C1 ('MetaCons "PreprocElif" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [a]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 a))) :+: 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 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [a]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 a)))) :+: (C1 ('MetaCons "MacroBodyStmt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 a)) :+: (C1 ('MetaCons "MacroBodyFunCall" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 a)) :+: 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 a) :*: 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 [a]))) :+: (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 [lexeme]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 lexeme))) :+: C1 ('MetaCons "CommentSectionEnd" '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 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 a)) :+: C1 ('MetaCons "ExternC" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [a]))) :+: (C1 ('MetaCons "CompoundStmt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [a])) :+: (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 a)))) :+: (C1 ('MetaCons "SwitchStmt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [a])) :+: (C1 ('MetaCons "IfStmt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe a)))) :+: C1 ('MetaCons "ForStmt" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 a)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 a))))))) :+: (((C1 ('MetaCons "WhileStmt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 a)) :+: C1 ('MetaCons "DoWhileStmt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 a))) :+: (C1 ('MetaCons "Case" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 a)) :+: (C1 ('MetaCons "Default" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 a)) :+: C1 ('MetaCons "Label" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 lexeme) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 a))))) :+: ((C1 ('MetaCons "ExprStmt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 a)) :+: C1 ('MetaCons "VLA" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 lexeme) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 a)))) :+: (C1 ('MetaCons "VarDeclStmt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe a))) :+: (C1 ('MetaCons "VarDecl" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 lexeme) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [a]))) :+: C1 ('MetaCons "DeclSpecArray" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe a))))))))) :+: (((((C1 ('MetaCons "InitialiserList" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [a])) :+: C1 ('MetaCons "UnaryExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 UnaryOp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 a))) :+: (C1 ('MetaCons "BinaryExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 BinaryOp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 a))) :+: (C1 ('MetaCons "TernaryExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 a))) :+: C1 ('MetaCons "AssignExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 AssignOp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 a)))))) :+: ((C1 ('MetaCons "ParenExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 a)) :+: C1 ('MetaCons "CastExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 a))) :+: (C1 ('MetaCons "CompoundExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 a)) :+: (C1 ('MetaCons "CompoundLiteral" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 a)) :+: C1 ('MetaCons "SizeofExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 a)))))) :+: (((C1 ('MetaCons "SizeofType" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 a)) :+: 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 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 lexeme)) :+: C1 ('MetaCons "PointerAccess" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 lexeme))))) :+: ((C1 ('MetaCons "ArrayAccess" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 a)) :+: C1 ('MetaCons "FunctionCall" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [a]))) :+: (C1 ('MetaCons "CommentExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 a)) :+: (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 [a])) :+: C1 ('MetaCons "EnumDecl" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 lexeme) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [a]) :*: 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 a))) :+: C1 ('MetaCons "AggregateDecl" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 a))) :+: (C1 ('MetaCons "Typedef" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 lexeme)) :+: (C1 ('MetaCons "TypedefFunction" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 a)) :+: C1 ('MetaCons "Struct" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 lexeme) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [a]))))) :+: ((C1 ('MetaCons "Union" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 lexeme) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [a])) :+: C1 ('MetaCons "MemberDecl" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 a) :*: 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 a)) :+: (C1 ('MetaCons "TyPointer" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 a)) :+: 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 "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 a)) :+: C1 ('MetaCons "FunctionDefn" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Scope) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 a)))))) :+: ((C1 ('MetaCons "FunctionPrototype" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 lexeme) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [a]))) :+: (C1 ('MetaCons "CallbackDecl" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 lexeme) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 lexeme)) :+: C1 ('MetaCons "Ellipsis" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "NonNull" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [lexeme]) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [lexeme]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 a))) :+: (C1 ('MetaCons "ConstDecl" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 a) :*: 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 a)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 lexeme) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 a))))))))))

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 #

Read Scope Source # 
Instance details

Defined in Language.Cimple.Ast

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.15-inplace" '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

Read 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.15-inplace" '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)))

data AnnotF attr a Source #

Constructors

Annot 

Fields

Instances

Instances details
Functor (AnnotF attr) Source # 
Instance details

Defined in Language.Cimple.Annot

Methods

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

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

Eq attr => Eq1 (AnnotF attr) Source # 
Instance details

Defined in Language.Cimple.Annot

Methods

liftEq :: (a -> b -> Bool) -> AnnotF attr a -> AnnotF attr b -> Bool #

Read attr => Read1 (AnnotF attr) Source # 
Instance details

Defined in Language.Cimple.Annot

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (AnnotF attr a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [AnnotF attr a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (AnnotF attr a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [AnnotF attr a] #

Show attr => Show1 (AnnotF attr) Source # 
Instance details

Defined in Language.Cimple.Annot

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> AnnotF attr a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [AnnotF attr a] -> ShowS #

Generic1 (AnnotF attr :: Type -> Type) Source # 
Instance details

Defined in Language.Cimple.Annot

Associated Types

type Rep1 (AnnotF attr) :: k -> Type #

Methods

from1 :: forall (a :: k). AnnotF attr a -> Rep1 (AnnotF attr) a #

to1 :: forall (a :: k). Rep1 (AnnotF attr) a -> AnnotF attr a #

Generic (AnnotF attr a) Source # 
Instance details

Defined in Language.Cimple.Annot

Associated Types

type Rep (AnnotF attr a) :: Type -> Type #

Methods

from :: AnnotF attr a -> Rep (AnnotF attr a) x #

to :: Rep (AnnotF attr a) x -> AnnotF attr a #

type Rep1 (AnnotF attr :: Type -> Type) Source # 
Instance details

Defined in Language.Cimple.Annot

type Rep1 (AnnotF attr :: Type -> Type) = D1 ('MetaData "AnnotF" "Language.Cimple.Annot" "cimple-0.0.15-inplace" 'False) (C1 ('MetaCons "Annot" 'PrefixI 'True) (S1 ('MetaSel ('Just "attr") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 attr) :*: S1 ('MetaSel ('Just "unAnnot") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) Par1))
type Rep (AnnotF attr a) Source # 
Instance details

Defined in Language.Cimple.Annot

type Rep (AnnotF attr a) = D1 ('MetaData "AnnotF" "Language.Cimple.Annot" "cimple-0.0.15-inplace" 'False) (C1 ('MetaCons "Annot" 'PrefixI 'True) (S1 ('MetaSel ('Just "attr") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 attr) :*: S1 ('MetaSel ('Just "unAnnot") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 a)))

type AnnotNode lexeme = Fix (AnnotF () `Compose` NodeF lexeme) Source #

addAnnot :: Node lexeme -> AnnotNode lexeme Source #

removeAnnot :: AnnotNode lexeme -> Node lexeme Source #