tokstyle-0.0.5: TokTok C code style checker

Safe HaskellNone
LanguageHaskell2010

Tokstyle.Cimple.AST

Documentation

data AssignOp Source #

Instances
Eq AssignOp Source # 
Instance details

Defined in Tokstyle.Cimple.AST

Show AssignOp Source # 
Instance details

Defined in Tokstyle.Cimple.AST

Generic AssignOp Source # 
Instance details

Defined in Tokstyle.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 Tokstyle.Cimple.AST

FromJSON AssignOp Source # 
Instance details

Defined in Tokstyle.Cimple.AST

type Rep AssignOp Source # 
Instance details

Defined in Tokstyle.Cimple.AST

type Rep AssignOp = D1 (MetaData "AssignOp" "Tokstyle.Cimple.AST" "tokstyle-0.0.5-3t4QCZhHJCmBeRl7IcprH4" 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
Eq BinaryOp Source # 
Instance details

Defined in Tokstyle.Cimple.AST

Show BinaryOp Source # 
Instance details

Defined in Tokstyle.Cimple.AST

Generic BinaryOp Source # 
Instance details

Defined in Tokstyle.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 Tokstyle.Cimple.AST

FromJSON BinaryOp Source # 
Instance details

Defined in Tokstyle.Cimple.AST

type Rep BinaryOp Source # 
Instance details

Defined in Tokstyle.Cimple.AST

type Rep BinaryOp = D1 (MetaData "BinaryOp" "Tokstyle.Cimple.AST" "tokstyle-0.0.5-3t4QCZhHJCmBeRl7IcprH4" 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
Eq UnaryOp Source # 
Instance details

Defined in Tokstyle.Cimple.AST

Methods

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

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

Show UnaryOp Source # 
Instance details

Defined in Tokstyle.Cimple.AST

Generic UnaryOp Source # 
Instance details

Defined in Tokstyle.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 Tokstyle.Cimple.AST

FromJSON UnaryOp Source # 
Instance details

Defined in Tokstyle.Cimple.AST

type Rep UnaryOp Source # 
Instance details

Defined in Tokstyle.Cimple.AST

type Rep UnaryOp = D1 (MetaData "UnaryOp" "Tokstyle.Cimple.AST" "tokstyle-0.0.5-3t4QCZhHJCmBeRl7IcprH4" 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
Eq LiteralType Source # 
Instance details

Defined in Tokstyle.Cimple.AST

Show LiteralType Source # 
Instance details

Defined in Tokstyle.Cimple.AST

Generic LiteralType Source # 
Instance details

Defined in Tokstyle.Cimple.AST

Associated Types

type Rep LiteralType :: Type -> Type #

ToJSON LiteralType Source # 
Instance details

Defined in Tokstyle.Cimple.AST

FromJSON LiteralType Source # 
Instance details

Defined in Tokstyle.Cimple.AST

type Rep LiteralType Source # 
Instance details

Defined in Tokstyle.Cimple.AST

type Rep LiteralType = D1 (MetaData "LiteralType" "Tokstyle.Cimple.AST" "tokstyle-0.0.5-3t4QCZhHJCmBeRl7IcprH4" 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 lexeme Source #

Constructors

PreprocInclude lexeme 
PreprocDefine lexeme 
PreprocDefineConst lexeme (Node lexeme) 
PreprocDefineMacro lexeme [Node lexeme] (Node lexeme) 
PreprocIf (Node lexeme) [Node lexeme] (Node lexeme) 
PreprocIfdef lexeme [Node lexeme] (Node lexeme) 
PreprocIfndef lexeme [Node lexeme] (Node lexeme) 
PreprocElse [Node lexeme] 
PreprocElif (Node lexeme) [Node lexeme] (Node lexeme) 
PreprocError lexeme 
PreprocUndef lexeme 
PreprocDefined lexeme 
PreprocScopedDefine (Node lexeme) [Node lexeme] (Node lexeme) 
MacroBodyStmt [Node lexeme] 
MacroBodyFunCall (Node lexeme) 
MacroParam lexeme 
Comment [Node lexeme] 
CommentBlock lexeme 
CommentWord lexeme 
ExternC [Node lexeme] 
CompoundStmt [Node lexeme] 
Break 
Goto lexeme 
Continue 
Return (Maybe (Node lexeme)) 
Switch (Node lexeme) [Node lexeme] 
IfStmt (Node lexeme) [Node lexeme] (Maybe (Node lexeme)) 
ForStmt (Maybe (Node lexeme)) (Maybe (Node lexeme)) (Maybe (Node lexeme)) [Node lexeme] 
WhileStmt (Node lexeme) [Node lexeme] 
DoWhileStmt [Node lexeme] (Node lexeme) 
Case (Node lexeme) (Node lexeme) 
Default (Node lexeme) 
Label lexeme (Node lexeme) 
VLA (Node lexeme) lexeme (Node lexeme) 
VarDecl (Node lexeme) [Node lexeme] 
Declarator (Node lexeme) (Maybe (Node lexeme)) 
DeclSpecVar lexeme 
DeclSpecArray (Node lexeme) (Maybe (Node lexeme)) 
InitialiserList [Node lexeme] 
UnaryExpr UnaryOp (Node lexeme) 
BinaryExpr (Node lexeme) BinaryOp (Node lexeme) 
TernaryExpr (Node lexeme) (Node lexeme) (Node lexeme) 
AssignExpr (Node lexeme) AssignOp (Node lexeme) 
ParenExpr (Node lexeme) 
CastExpr (Node lexeme) (Node lexeme) 
SizeofExpr (Node lexeme) 
LiteralExpr LiteralType lexeme 
VarExpr lexeme 
MemberAccess (Node lexeme) lexeme 
PointerAccess (Node lexeme) lexeme 
ArrayAccess (Node lexeme) (Node lexeme) 
FunctionCall (Node lexeme) [Node lexeme] 
CommentExpr (Node lexeme) (Node lexeme) 
EnumDecl lexeme [Node lexeme] lexeme 
Enumerator lexeme (Maybe (Node lexeme)) 
Typedef (Node lexeme) lexeme 
TypedefFunction (Node lexeme) 
Struct lexeme [Node lexeme] 
Union lexeme [Node lexeme] 
MemberDecl (Node lexeme) (Node lexeme) (Maybe lexeme) 
TyConst (Node lexeme) 
TyPointer (Node lexeme) 
TyStruct lexeme 
TyFunc lexeme 
TyStd lexeme 
TyUserDefined lexeme 
FunctionDecl Scope (Node lexeme) 
FunctionDefn Scope (Node lexeme) [Node lexeme] 
FunctionPrototype (Node lexeme) lexeme [Node lexeme] 
FunctionParam (Node lexeme) (Node lexeme) 
Ellipsis 
ConstDecl (Node lexeme) lexeme 
ConstDefn Scope (Node lexeme) lexeme (Node lexeme) 
Instances
Functor Node Source # 
Instance details

Defined in Tokstyle.Cimple.AST

Methods

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

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

Foldable Node Source # 
Instance details

Defined in Tokstyle.Cimple.AST

Methods

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

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

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

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

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

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

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

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

toList :: Node a -> [a] #

null :: Node a -> Bool #

length :: Node a -> Int #

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

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

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

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

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

Traversable Node Source # 
Instance details

Defined in Tokstyle.Cimple.AST

Methods

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

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

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

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

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

Defined in Tokstyle.Cimple.AST

Methods

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

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

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

Defined in Tokstyle.Cimple.AST

Methods

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

show :: Node lexeme -> String #

showList :: [Node lexeme] -> ShowS #

Generic (Node lexeme) Source # 
Instance details

Defined in Tokstyle.Cimple.AST

Associated Types

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

Methods

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

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

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

Defined in Tokstyle.Cimple.AST

Methods

toJSON :: Node lexeme -> Value #

toEncoding :: Node lexeme -> Encoding #

toJSONList :: [Node lexeme] -> Value #

toEncodingList :: [Node lexeme] -> Encoding #

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

Defined in Tokstyle.Cimple.AST

Methods

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

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

TraverseAst [Node (Lexeme Text)] Source # 
Instance details

Defined in Tokstyle.Cimple.TraverseAst

TraverseAst (Node (Lexeme Text)) Source # 
Instance details

Defined in Tokstyle.Cimple.TraverseAst

type Rep (Node lexeme) Source # 
Instance details

Defined in Tokstyle.Cimple.AST

type Rep (Node lexeme) = D1 (MetaData "Node" "Tokstyle.Cimple.AST" "tokstyle-0.0.5-3t4QCZhHJCmBeRl7IcprH4" False) ((((((C1 (MetaCons "PreprocInclude" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 lexeme)) :+: C1 (MetaCons "PreprocDefine" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 lexeme))) :+: (C1 (MetaCons "PreprocDefineConst" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 lexeme) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Node lexeme))) :+: C1 (MetaCons "PreprocDefineMacro" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 lexeme) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Node lexeme]) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Node lexeme)))))) :+: ((C1 (MetaCons "PreprocIf" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Node lexeme)) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Node lexeme]) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Node lexeme)))) :+: C1 (MetaCons "PreprocIfdef" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 lexeme) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Node lexeme]) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Node lexeme))))) :+: (C1 (MetaCons "PreprocIfndef" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 lexeme) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Node lexeme]) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Node lexeme)))) :+: (C1 (MetaCons "PreprocElse" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Node lexeme])) :+: C1 (MetaCons "PreprocElif" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Node lexeme)) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Node lexeme]) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Node lexeme)))))))) :+: (((C1 (MetaCons "PreprocError" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 lexeme)) :+: C1 (MetaCons "PreprocUndef" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 lexeme))) :+: (C1 (MetaCons "PreprocDefined" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 lexeme)) :+: C1 (MetaCons "PreprocScopedDefine" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Node lexeme)) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Node lexeme]) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Node lexeme)))))) :+: ((C1 (MetaCons "MacroBodyStmt" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Node lexeme])) :+: C1 (MetaCons "MacroBodyFunCall" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Node lexeme)))) :+: (C1 (MetaCons "MacroParam" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 lexeme)) :+: (C1 (MetaCons "Comment" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Node lexeme])) :+: C1 (MetaCons "CommentBlock" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 lexeme))))))) :+: ((((C1 (MetaCons "CommentWord" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 lexeme)) :+: C1 (MetaCons "ExternC" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Node lexeme]))) :+: (C1 (MetaCons "CompoundStmt" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Node lexeme])) :+: C1 (MetaCons "Break" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "Goto" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 lexeme)) :+: C1 (MetaCons "Continue" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Return" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (Node lexeme)))) :+: (C1 (MetaCons "Switch" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Node lexeme)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Node lexeme])) :+: C1 (MetaCons "IfStmt" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Node lexeme)) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Node lexeme]) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (Node lexeme))))))))) :+: (((C1 (MetaCons "ForStmt" PrefixI False) ((S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (Node lexeme))) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (Node lexeme)))) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (Node lexeme))) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Node lexeme]))) :+: C1 (MetaCons "WhileStmt" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Node lexeme)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Node lexeme]))) :+: (C1 (MetaCons "DoWhileStmt" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Node lexeme]) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Node lexeme))) :+: C1 (MetaCons "Case" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Node lexeme)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Node lexeme))))) :+: ((C1 (MetaCons "Default" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Node lexeme))) :+: C1 (MetaCons "Label" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 lexeme) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Node lexeme)))) :+: (C1 (MetaCons "VLA" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Node lexeme)) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 lexeme) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Node lexeme)))) :+: (C1 (MetaCons "VarDecl" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Node lexeme)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Node lexeme])) :+: C1 (MetaCons "Declarator" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Node lexeme)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (Node lexeme)))))))))) :+: (((((C1 (MetaCons "DeclSpecVar" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 lexeme)) :+: C1 (MetaCons "DeclSpecArray" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Node lexeme)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (Node lexeme))))) :+: (C1 (MetaCons "InitialiserList" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Node lexeme])) :+: C1 (MetaCons "UnaryExpr" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 UnaryOp) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Node lexeme))))) :+: ((C1 (MetaCons "BinaryExpr" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Node lexeme)) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 BinaryOp) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Node lexeme)))) :+: C1 (MetaCons "TernaryExpr" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Node lexeme)) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Node lexeme)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Node lexeme))))) :+: (C1 (MetaCons "AssignExpr" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Node lexeme)) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 AssignOp) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Node lexeme)))) :+: (C1 (MetaCons "ParenExpr" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Node lexeme))) :+: C1 (MetaCons "CastExpr" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Node lexeme)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Node lexeme))))))) :+: (((C1 (MetaCons "SizeofExpr" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Node lexeme))) :+: C1 (MetaCons "LiteralExpr" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 LiteralType) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 lexeme))) :+: (C1 (MetaCons "VarExpr" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 lexeme)) :+: C1 (MetaCons "MemberAccess" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Node lexeme)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 lexeme)))) :+: ((C1 (MetaCons "PointerAccess" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Node lexeme)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 lexeme)) :+: C1 (MetaCons "ArrayAccess" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Node lexeme)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Node lexeme)))) :+: (C1 (MetaCons "FunctionCall" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Node lexeme)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Node lexeme])) :+: (C1 (MetaCons "CommentExpr" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Node lexeme)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Node lexeme))) :+: C1 (MetaCons "EnumDecl" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 lexeme) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Node lexeme]) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 lexeme)))))))) :+: ((((C1 (MetaCons "Enumerator" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 lexeme) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (Node lexeme)))) :+: C1 (MetaCons "Typedef" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Node lexeme)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 lexeme))) :+: (C1 (MetaCons "TypedefFunction" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Node lexeme))) :+: C1 (MetaCons "Struct" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 lexeme) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Node lexeme])))) :+: ((C1 (MetaCons "Union" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 lexeme) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Node lexeme])) :+: C1 (MetaCons "MemberDecl" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Node lexeme)) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Node lexeme)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe lexeme))))) :+: (C1 (MetaCons "TyConst" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Node lexeme))) :+: (C1 (MetaCons "TyPointer" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Node lexeme))) :+: C1 (MetaCons "TyStruct" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 lexeme)))))) :+: (((C1 (MetaCons "TyFunc" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 lexeme)) :+: C1 (MetaCons "TyStd" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 lexeme))) :+: (C1 (MetaCons "TyUserDefined" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 lexeme)) :+: (C1 (MetaCons "FunctionDecl" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Scope) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Node lexeme))) :+: C1 (MetaCons "FunctionDefn" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Scope) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Node lexeme)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Node lexeme])))))) :+: ((C1 (MetaCons "FunctionPrototype" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Node lexeme)) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 lexeme) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Node lexeme]))) :+: C1 (MetaCons "FunctionParam" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Node lexeme)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Node lexeme)))) :+: (C1 (MetaCons "Ellipsis" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "ConstDecl" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Node lexeme)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 lexeme)) :+: C1 (MetaCons "ConstDefn" PrefixI False) ((S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Scope) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Node lexeme))) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 lexeme) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Node lexeme)))))))))))

data Scope Source #

Constructors

Global 
Static 
Instances
Eq Scope Source # 
Instance details

Defined in Tokstyle.Cimple.AST

Methods

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

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

Show Scope Source # 
Instance details

Defined in Tokstyle.Cimple.AST

Methods

showsPrec :: Int -> Scope -> ShowS #

show :: Scope -> String #

showList :: [Scope] -> ShowS #

Generic Scope Source # 
Instance details

Defined in Tokstyle.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 Tokstyle.Cimple.AST

FromJSON Scope Source # 
Instance details

Defined in Tokstyle.Cimple.AST

type Rep Scope Source # 
Instance details

Defined in Tokstyle.Cimple.AST

type Rep Scope = D1 (MetaData "Scope" "Tokstyle.Cimple.AST" "tokstyle-0.0.5-3t4QCZhHJCmBeRl7IcprH4" False) (C1 (MetaCons "Global" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Static" PrefixI False) (U1 :: Type -> Type))