Safe Haskell | Safe |
---|---|
Language | Haskell98 |
Language.Java.Syntax
- data CompilationUnitNode l
- data ModuleSpecNode l
- data TypeDeclNode l
- data ClassDeclNode l
- = ClassDeclNode (ClassDecl l)
- | EnumDeclNode (EnumDecl l)
- data DeclNode l
- = MemberDeclNode (MemberDeclNode l)
- | InitDeclNode (InitDecl l)
- data MemberDeclNode l
- data VarDeclIdNode l
- = VarIdNode (VarId l)
- | VarDeclArrayNode (VarDeclIdNode l)
- data VarInitNode l
- = InitExpNode (ExpNode l)
- | InitArrayNode (ArrayInit l)
- data ExplConstrInvNode l
- data BlockStmtNode l
- = BlockStmtNode (StmtNode l)
- | LocalClassNode (ClassDeclNode l)
- | LocalVarsNode (LocalVars l)
- data StmtNode l
- = StmtBlockNode (Block l)
- | IfThenElseNode (IfThenElse l)
- | WhileNode (While l)
- | BasicForNode (BasicFor l)
- | EnhancedForNode (EnhancedFor l)
- | EmptyNode (Empty l)
- | ExpStmtNode (ExpNode l)
- | AssertNode (Assert l)
- | SwitchNode (Switch l)
- | DoNode (Do l)
- | BreakNode (Break l)
- | ContinueNode (Continue l)
- | ReturnNode (Return l)
- | SynchronizedNode (Synchronized l)
- | ThrowNode (Throw l)
- | TryNode (Try l)
- | LabeledNode (Labeled l)
- data TryResourceNode l
- data SwitchLabelNode l
- = SwitchCaseNode (ExpNode l)
- | DefaultNode l
- data ForInitNode l
- = ForLocalVarsNode (ForLocalVars l)
- | ForInitExpsNode (ForInitExps l)
- data ExpNode l
- = LitNode (Lit l)
- | ClassLitNode (ClassLit l)
- | ThisNode (This l)
- | QualifiedThisNode (QualifiedThis l)
- | InstanceCreationNode (InstanceCreation l)
- | QualInstanceCreationNode (QualInstanceCreation l)
- | ArrayCreateNode (ArrayCreate l)
- | ArrayCreateInitNode (ArrayCreateInit l)
- | FieldAccessNode (FieldAccessNode l)
- | MethodInvNode (MethodInvocationNode l)
- | ArrayAccessNode (ArrayIndex l)
- | ExpNameNode (ExpName l)
- | PostIncrementNode (ExpNode l)
- | PostDecrementNode (ExpNode l)
- | PreIncrementNode (ExpNode l)
- | PreDecrementNode (ExpNode l)
- | PrePlusNode (ExpNode l)
- | PreMinusNode (ExpNode l)
- | PreBitComplNode (ExpNode l)
- | PreNotNode (ExpNode l)
- | CastNode (Cast l)
- | BinOpNode (BinOp l)
- | InstanceOfNode (InstanceOf l)
- | CondNode (Cond l)
- | AssignNode (Assign l)
- | LambdaNode (Lambda l)
- | MethodRefNode (MethodRef l)
- data LhsNode l
- = NameLhsNode (NameLhs l)
- | FieldLhsNode (FieldAccessNode l)
- | ArrayLhsNode (ArrayIndex l)
- data FieldAccessNode l
- data LambdaParamsNode l
- data LambdaExpressionNode l
- = LambdaExpressionNode (ExpNode l)
- | LambdaBlockNode (Block l)
- data MethodInvocationNode l
- data CompilationUnit l = CompilationUnit {
- infoCompUnit :: l
- packageLocation :: Maybe (PackageDecl l)
- imports :: [ImportDecl l]
- typeDecls :: [TypeDeclNode l]
- data ModuleDeclaration l = ModuleDeclaration {
- infoModuleDecl :: l
- modulePackage :: Package
- moduleSpecs :: [ModuleSpecNode l]
- data PackageDecl l = PackageDecl {
- infoPackDec :: l
- packageDecl :: Package
- data ModuleRequires l = ModuleRequires {}
- data ModuleExports l = ModuleExports {}
- data ImportDecl l = ImportDecl {
- infoImportDecl :: l
- staticImport :: Bool
- importPackage :: Package
- data ClassDecl l = ClassDecl {
- infoClassDecl :: l
- classDeclModifiers :: [Modifier l]
- classDeclName :: Ident
- classTypeParams :: [TypeParam]
- extends :: Maybe (Extends l)
- classImplements :: [Implements l]
- classBody :: ClassBody l
- data EnumDecl l = EnumDecl {
- infoEnumDecl :: l
- enumDeclModifiers :: [Modifier l]
- enumeDeclName :: Ident
- enumImplements :: [Implements l]
- enumBody :: EnumBody l
- data Extends l = Extends {
- infoExtends :: l
- extendsClass :: RefType
- data Implements l = Implements {}
- data ClassBody l = ClassBody {
- infoClassBody :: l
- classDecls :: [DeclNode l]
- data EnumBody l = EnumBody {
- infoEnumBody :: l
- enumConstants :: [EnumConstant l]
- enumDecls :: [DeclNode l]
- data EnumConstant l = EnumConstant {
- infoEnumConstant :: l
- enumConstantName :: Ident
- enumArguments :: [Argument l]
- enumConstantBody :: Maybe (ClassBody l)
- data InterfaceDecl l = InterfaceDecl {}
- data InterfaceKind
- data InterfaceBody l = InterfaceBody {
- infoInterfaceBody :: l
- members :: [MemberDeclNode l]
- data InitDecl l = InitDecl {
- infoInitDecl :: l
- staticDecl :: Bool
- statements :: Block l
- data FieldDecl l = FieldDecl {
- infoFieldDecl :: l
- memberDeclModifiers :: [Modifier l]
- fieldType :: Type
- fieldVarDecls :: [VarDecl l]
- data MethodDecl l = MethodDecl {
- infoMethodDecl :: l
- methodDeclModifiers :: [Modifier l]
- methodTypeParams :: [TypeParam]
- returnType :: Maybe Type
- methodDeclName :: Ident
- params :: [FormalParam l]
- exceptions :: [ExceptionType l]
- defaultInterfaceAnnotation :: Maybe (ExpNode l)
- methodBody :: MethodBody l
- data ConstructorDecl l = ConstructorDecl {}
- data VarDecl l = VarDecl {
- infoVarDecl :: l
- varDeclName :: VarDeclIdNode l
- varInit :: Maybe (VarInitNode l)
- data VarId l = VarId {}
- data FormalParam l = FormalParam {
- infoFormalParam :: l
- formalParamModifiers :: [Modifier l]
- paramType :: Type
- variableArity :: Bool
- paramName :: VarDeclIdNode l
- data MethodBody l = MethodBody {
- infoMethodBody :: l
- impl :: Maybe (Block l)
- data ConstructorBody l = ConstructorBody {
- infoConstructorBody :: l
- constructorInvoc :: Maybe (ExplConstrInvNode l)
- constrBody :: [BlockStmtNode l]
- data ThisInvoke l = ThisInvoke {
- infoThisInvoke :: l
- thisTypeArguments :: [RefType]
- thisConstrArguments :: [Argument l]
- data SuperInvoke l = SuperInvoke {
- infoSuperInvoke :: l
- superTypeArguments :: [RefType]
- superConstrArguments :: [Argument l]
- data PrimarySuperInvoke l = PrimarySuperInvoke {
- infoPrimarySuperInvoke :: l
- primary :: ExpNode l
- primaryTypeArguments :: [RefType]
- primaryConstrArguments :: [Argument l]
- data Modifier l
- = Public l
- | Private l
- | Protected l
- | Abstract l
- | Final l
- | Static l
- | StrictFP l
- | Transient l
- | Volatile l
- | Native l
- | Annotation (Annotation l)
- | Synchronized_ l
- | DefaultModifier l
- data Annotation l
- = NormalAnnotation {
- annName :: Name
- annKV :: [(Ident, ElementValue l)]
- | SingleElementAnnotation {
- annName :: Name
- annValue :: ElementValue l
- | MarkerAnnotation { }
- = NormalAnnotation {
- data ElementValue l
- = EVVal {
- infoEVVal :: l
- elementVarInit :: VarInitNode l
- | EVAnn {
- infoEVAnn :: l
- annotation :: Annotation l
- = EVVal {
- data Block l = Block {
- infoBlock :: l
- blockStatements :: [BlockStmtNode l]
- data LocalVars l = LocalVars {
- infoLocalVars :: l
- locaVarModifiers :: [Modifier l]
- blockVarType :: Type
- localVarDecls :: [VarDecl l]
- data IfThenElse l = IfThenElse {}
- data While l = While {
- infoWhile :: l
- whileVondition :: ExpNode l
- whileBody :: StmtNode l
- data BasicFor l = BasicFor {
- infoBasicFor :: l
- forInit :: Maybe (ForInitNode l)
- forCond :: Maybe (ExpNode l)
- forUpdate :: Maybe [ExpNode l]
- basicForBody :: StmtNode l
- data EnhancedFor l = EnhancedFor {
- infoEnhancedFor :: l
- loopVarModifiers :: [Modifier l]
- loopVarType :: Type
- loopVarName :: Ident
- iterable :: ExpNode l
- enhancedForBody :: StmtNode l
- newtype Empty l = Empty {
- infoEmpty :: l
- data Assert l = Assert {
- infoAssert :: l
- booleanExp :: ExpNode l
- valueExp :: Maybe (ExpNode l)
- data Switch l = Switch {
- infoSwitch :: l
- switchValue :: ExpNode l
- switchBlocks :: [SwitchBlock l]
- data Do l = Do {
- infoDo :: l
- doBody :: StmtNode l
- doCondition :: ExpNode l
- data Break l = Break {
- infoBreak :: l
- breakLabel :: Maybe Ident
- data Continue l = Continue {
- infoContinue :: l
- continueLabel :: Maybe Ident
- data Return l = Return {
- infoReturn :: l
- returnExp :: Maybe (ExpNode l)
- data Synchronized l = Synchronized {
- infoSynchronized :: l
- synchronizeOn :: ExpNode l
- synchronizeBloc :: Block l
- data Throw l = Throw {}
- data Try l = Try {
- infoTry :: l
- tryResource :: [TryResourceNode l]
- tryBlock :: Block l
- catches :: [Catch l]
- finally :: Maybe (Block l)
- data Labeled l = Labeled {
- infoLabeled :: l
- label :: Ident
- labeledStmt :: StmtNode l
- data Catch l = Catch {
- infoCatch :: l
- catchParam :: FormalParam l
- catchBlock :: Block l
- data TryResourceVar l = TryResourceVar {
- infoTryResourceVar :: l
- resourceModifiers :: [Modifier l]
- resourceVarType :: RefType
- resourceVarDecl :: [VarDecl l]
- data TryResourceFinalVar l = TryResourceFinalVar {}
- data SwitchBlock l = SwitchBlock {
- infoSwitchBlock :: l
- switchLabel :: SwitchLabelNode l
- switchStmts :: [BlockStmtNode l]
- data ForLocalVars l = ForLocalVars {
- infoForLocalVars :: l
- forVarModifiers :: [Modifier l]
- forVarType :: Type
- forVarDecls :: [VarDecl l]
- data ForInitExps l = ForInitExps {
- infoForInitExps :: l
- initExpr :: [ExpNode l]
- data ExceptionType l = ExceptionType {}
- data Lit l = Lit {}
- data ClassLit l = ClassLit {
- infoClassLit :: l
- classLit :: Maybe Type
- newtype This l = This {
- infoThis :: l
- data QualifiedThis l = QualifiedThis {
- infoQualifiedThis :: l
- qualiType :: Type
- data InstanceCreation l = InstanceCreation {}
- data QualInstanceCreation l = QualInstanceCreation {}
- data ArrayCreate l = ArrayCreate {
- infoArrayCreate :: l
- arrayType :: Type
- arrayDimExprs :: [ExpNode l]
- dimensions :: Int
- data ArrayCreateInit l = ArrayCreateInit {}
- data ExpName l = ExpName {
- infoExpName :: l
- expName :: Name
- data Cast l = Cast {
- infoCast :: l
- castTarget :: Type
- castArg :: ExpNode l
- data BinOp l = BinOp {
- infoBinOp :: l
- binArgLeft :: ExpNode l
- binOp :: Op
- binOpRight :: ExpNode l
- data InstanceOf l = InstanceOf {
- infoInstanceOf :: l
- instanceOfArg :: ExpNode l
- instanceOfTarget :: RefType
- data Cond l = Cond {
- infoCond :: l
- condition :: ExpNode l
- conditionTrueExp :: ExpNode l
- conditionFalseExp :: ExpNode l
- data Assign l = Assign {
- infoAssign :: l
- assignTarget :: LhsNode l
- assignOp :: AssignOp
- assignSource :: ExpNode l
- data Lambda l = Lambda {}
- data MethodRef l = MethodRef {
- infoMethodRef :: l
- methodClass :: Name
- methodName :: Ident
- data NameLhs l = NameLhs {
- infoNameLhs :: l
- varLhsName :: Name
- data ArrayIndex l = ArrayIndex {
- infoArrayIndex :: l
- arrayName :: ExpNode l
- arrayIndices :: [ExpNode l]
- data PrimaryFieldAccess l = PrimaryFieldAccess {
- infoPrimaryFieldAccess :: l
- targetObject :: ExpNode l
- targetField :: Ident
- data SuperFieldAccess l = SuperFieldAccess {
- infoSuperFieldAccess :: l
- superField :: Ident
- data ClassFieldAccess l = ClassFieldAccess {
- infoClassFieldAccess :: l
- targetClass :: Name
- staticField :: Ident
- data LambdaSingleParam l = LambdaSingleParam {}
- data LambdaFormalParams l = LambdaFormalParams {
- infoLambdaFormalParams :: l
- lambdaFormalParams :: [FormalParam l]
- data LambdaInferredParams l = LambdaInferredParams {}
- data MethodCall l = MethodCall {
- infoMethodCall :: l
- methodCallName :: Name
- methodCallArgs :: [Argument l]
- data PrimaryMethodCall l = PrimaryMethodCall {}
- data SuperMethodCall l = SuperMethodCall {
- infoSuperMethodCall :: l
- superMethodTypeArgs :: [RefType]
- superMethodName :: Ident
- superMethodArgs :: [Argument l]
- data ClassMethodCall l = ClassMethodCall {}
- data TypeMethodCall l = TypeMethodCall {}
- data ArrayInit l = ArrayInit {
- infoArrayInit :: l
- arrayInits :: [VarInitNode l]
- type Argument = ExpNode
Documentation
data CompilationUnitNode l Source #
A compilation unit is the top level syntactic goal symbol of a Java program.
Constructors
CompilationUnitNode (CompilationUnit l) | |
ModuleDeclarationNode (ModuleDeclaration l) |
Instances
HasNode ModuleDeclaration CompilationUnitNode Source # | |
HasNode CompilationUnit CompilationUnitNode Source # | |
Eq l => Eq (CompilationUnitNode l) Source # | |
Data l => Data (CompilationUnitNode l) Source # | |
Read l => Read (CompilationUnitNode l) Source # | |
Show l => Show (CompilationUnitNode l) Source # | |
Generic (CompilationUnitNode l) Source # | |
Show l => Pretty (CompilationUnitNode l) Source # | |
type Rep (CompilationUnitNode l) Source # | |
data ModuleSpecNode l Source #
specifies the module declarations
Constructors
ModuleRequiresNode (ModuleRequires l) | requires the module to work |
ModuleExportsNode (ModuleExports l) | exports the package |
Instances
HasNode ModuleExports ModuleSpecNode Source # | |
HasNode ModuleRequires ModuleSpecNode Source # | |
Eq l => Eq (ModuleSpecNode l) Source # | |
Data l => Data (ModuleSpecNode l) Source # | |
Read l => Read (ModuleSpecNode l) Source # | |
Show l => Show (ModuleSpecNode l) Source # | |
Generic (ModuleSpecNode l) Source # | |
Show l => Pretty (ModuleSpecNode l) Source # | |
type Rep (ModuleSpecNode l) Source # | |
data TypeDeclNode l Source #
A type declaration declares a class type or an interface type.
Constructors
ClassTypeDeclNode (ClassDeclNode l) | |
InterfaceTypeDeclNode (InterfaceDecl l) |
Instances
HasNode InterfaceDecl TypeDeclNode Source # | |
HasNode ClassDeclNode TypeDeclNode Source # | |
Eq l => Eq (TypeDeclNode l) Source # | |
Data l => Data (TypeDeclNode l) Source # | |
Read l => Read (TypeDeclNode l) Source # | |
Show l => Show (TypeDeclNode l) Source # | |
Generic (TypeDeclNode l) Source # | |
CollectTypes (TypeDeclNode l) Source # | |
HasType (TypeDeclNode l) Source # | Get type of TypeDeclNode |
Show l => Pretty (TypeDeclNode l) Source # | |
HasBody (TypeDeclNode l) l Source # | Get the body of TypeDecl |
type Rep (TypeDeclNode l) Source # | |
data ClassDeclNode l Source #
A class declaration specifies a new named reference type.
Constructors
ClassDeclNode (ClassDecl l) | |
EnumDeclNode (EnumDecl l) |
Instances
HasNode EnumDecl ClassDeclNode Source # | |
HasNode ClassDecl ClassDeclNode Source # | |
HasNode ClassDeclNode BlockStmtNode Source # | |
HasNode ClassDeclNode MemberDeclNode Source # | |
HasNode ClassDeclNode TypeDeclNode Source # | |
Eq l => Eq (ClassDeclNode l) Source # | |
Data l => Data (ClassDeclNode l) Source # | |
Read l => Read (ClassDeclNode l) Source # | |
Show l => Show (ClassDeclNode l) Source # | |
Generic (ClassDeclNode l) Source # | |
CollectTypes (ClassDeclNode l) Source # | |
HasType (ClassDeclNode l) Source # | Get type of ClassDecl |
Show l => Pretty (ClassDeclNode l) Source # | |
HasBody (ClassDeclNode l) l Source # | Get the body of ClassDecl |
type Rep (ClassDeclNode l) Source # | |
A declaration is either a member declaration, or a declaration of an initializer, which may be static.
Constructors
MemberDeclNode (MemberDeclNode l) | |
InitDeclNode (InitDecl l) |
Instances
HasNode InitDecl DeclNode Source # | |
HasNode MemberDeclNode DeclNode Source # | |
Eq l => Eq (DeclNode l) Source # | |
Data l => Data (DeclNode l) Source # | |
Read l => Read (DeclNode l) Source # | |
Show l => Show (DeclNode l) Source # | |
Generic (DeclNode l) Source # | |
Show l => Pretty (DeclNode l) Source # | |
type Rep (DeclNode l) Source # | |
data MemberDeclNode l Source #
A class or interface member can be an inner class or interface, a field or constant, or a method or constructor. An interface may only have as members constants (not fields), abstract methods, and no constructors.
Constructors
FieldDeclNode (FieldDecl l) | The variables of a class type are introduced by field declarations. |
MethodDeclNode (MethodDecl l) | A method declares executable code that can be invoked, passing a fixed number of values as arguments. |
ConstructorDeclNode (ConstructorDecl l) | A constructor is used in the creation of an object that is an instance of a class. |
MemberClassDeclNode (ClassDeclNode l) | A member class is a class whose declaration is directly enclosed in another class or interface declaration. |
MemberInterfaceDeclNode (InterfaceDecl l) | A member interface is an interface whose declaration is directly enclosed in another class or interface declaration. |
Instances
HasNode ConstructorDecl MemberDeclNode Source # | |
HasNode MethodDecl MemberDeclNode Source # | |
HasNode FieldDecl MemberDeclNode Source # | |
HasNode InterfaceDecl MemberDeclNode Source # | |
HasNode MemberDeclNode DeclNode Source # | |
HasNode ClassDeclNode MemberDeclNode Source # | |
Eq l => Eq (MemberDeclNode l) Source # | |
Data l => Data (MemberDeclNode l) Source # | |
Read l => Read (MemberDeclNode l) Source # | |
Show l => Show (MemberDeclNode l) Source # | |
Generic (MemberDeclNode l) Source # | |
CollectTypes (MemberDeclNode l) Source # | Get type of MemberDecl if it is a MethodDecl (our solution to handeling the Maybe) |
Show l => Pretty (MemberDeclNode l) Source # | |
type Rep (MemberDeclNode l) Source # | |
data VarDeclIdNode l Source #
The name of a variable in a declaration, which may be an array.
Constructors
VarIdNode (VarId l) | |
VarDeclArrayNode (VarDeclIdNode l) | Multi-dimensional arrays are represented by nested applications of |
Instances
HasNode VarId VarDeclIdNode Source # | |
HasNode VarDeclIdNode VarDeclIdNode Source # | |
Eq l => Eq (VarDeclIdNode l) Source # | |
Data l => Data (VarDeclIdNode l) Source # | |
Read l => Read (VarDeclIdNode l) Source # | |
Show l => Show (VarDeclIdNode l) Source # | |
Generic (VarDeclIdNode l) Source # | |
Show l => Pretty (VarDeclIdNode l) Source # | |
type Rep (VarDeclIdNode l) Source # | |
data VarInitNode l Source #
Explicit initializer for a variable declaration.
Constructors
InitExpNode (ExpNode l) | |
InitArrayNode (ArrayInit l) |
Instances
HasNode ArrayInit VarInitNode Source # | |
HasNode ExpNode VarInitNode Source # | |
Eq l => Eq (VarInitNode l) Source # | |
Data l => Data (VarInitNode l) Source # | |
Read l => Read (VarInitNode l) Source # | |
Show l => Show (VarInitNode l) Source # | |
Generic (VarInitNode l) Source # | |
Show l => Pretty (VarInitNode l) Source # | |
type Rep (VarInitNode l) Source # | |
data ExplConstrInvNode l Source #
An explicit constructor invocation invokes another constructor of the same class, or a constructor of the direct superclass, which may be qualified to explicitly specify the newly created object's immediately enclosing instance.
Constructors
ThisInvokeNode (ThisInvoke l) | |
SuperInvokeNode (SuperInvoke l) | |
PrimarySuperInvokeNode (PrimarySuperInvoke l) |
Instances
HasNode PrimarySuperInvoke ExplConstrInvNode Source # | |
HasNode SuperInvoke ExplConstrInvNode Source # | |
HasNode ThisInvoke ExplConstrInvNode Source # | |
Eq l => Eq (ExplConstrInvNode l) Source # | |
Data l => Data (ExplConstrInvNode l) Source # | |
Read l => Read (ExplConstrInvNode l) Source # | |
Show l => Show (ExplConstrInvNode l) Source # | |
Generic (ExplConstrInvNode l) Source # | |
Show l => Pretty (ExplConstrInvNode l) Source # | |
type Rep (ExplConstrInvNode l) Source # | |
data BlockStmtNode l Source #
A block statement is either a normal statement, a local class declaration or a local variable declaration.
Constructors
BlockStmtNode (StmtNode l) | |
LocalClassNode (ClassDeclNode l) | |
LocalVarsNode (LocalVars l) |
Instances
HasNode LocalVars BlockStmtNode Source # | |
HasNode StmtNode BlockStmtNode Source # | |
HasNode ClassDeclNode BlockStmtNode Source # | |
Eq l => Eq (BlockStmtNode l) Source # | |
Data l => Data (BlockStmtNode l) Source # | |
Read l => Read (BlockStmtNode l) Source # | |
Show l => Show (BlockStmtNode l) Source # | |
Generic (BlockStmtNode l) Source # | |
Show l => Pretty (BlockStmtNode l) Source # | |
type Rep (BlockStmtNode l) Source # | |
A Java statement.
Constructors
StmtBlockNode (Block l) | A statement can be a nested block. |
IfThenElseNode (IfThenElse l) | The |
WhileNode (While l) | The |
BasicForNode (BasicFor l) | The basic |
EnhancedForNode (EnhancedFor l) | The enhanced |
EmptyNode (Empty l) | An empty statement does nothing. |
ExpStmtNode (ExpNode l) | Certain kinds of expressions may be used as statements by following them with semicolons: assignments, pre- or post-inc- or decrementation, method invocation or class instance creation expressions. |
AssertNode (Assert l) | An assertion is a statement containing a boolean expression, where an error is reported if the expression evaluates to false. |
SwitchNode (Switch l) | The switch statement transfers control to one of several statements depending on the value of an expression. |
DoNode (Do l) | The |
BreakNode (Break l) | A |
ContinueNode (Continue l) | A |
ReturnNode (Return l) | |
SynchronizedNode (Synchronized l) | A |
ThrowNode (Throw l) | A |
TryNode (Try l) | A try statement executes a block and may catch a thrown exception |
LabeledNode (Labeled l) | Statements may have label prefixes. |
Instances
HasNode Labeled StmtNode Source # | |
HasNode Try StmtNode Source # | |
HasNode Throw StmtNode Source # | |
HasNode Synchronized StmtNode Source # | |
HasNode Return StmtNode Source # | |
HasNode Continue StmtNode Source # | |
HasNode Break StmtNode Source # | |
HasNode Do StmtNode Source # | |
HasNode Switch StmtNode Source # | |
HasNode Assert StmtNode Source # | |
HasNode Empty StmtNode Source # | |
HasNode EnhancedFor StmtNode Source # | |
HasNode BasicFor StmtNode Source # | |
HasNode While StmtNode Source # | |
HasNode IfThenElse StmtNode Source # | |
HasNode Block StmtNode Source # | |
HasNode ExpNode StmtNode Source # | |
HasNode StmtNode BlockStmtNode Source # | |
Eq l => Eq (StmtNode l) Source # | |
Data l => Data (StmtNode l) Source # | |
Read l => Read (StmtNode l) Source # | |
Show l => Show (StmtNode l) Source # | |
Generic (StmtNode l) Source # | |
Show l => Pretty (StmtNode l) Source # | |
type Rep (StmtNode l) Source # | |
data TryResourceNode l Source #
Resource in a try-with-resources statement
Constructors
TryResourceVarNode (TryResourceVar l) | Newly declared variables |
TryResourceFinalVarNode (TryResourceFinalVar l) | Effectively final variable |
Instances
HasNode TryResourceFinalVar TryResourceNode Source # | |
HasNode TryResourceVar TryResourceNode Source # | |
Eq l => Eq (TryResourceNode l) Source # | |
Data l => Data (TryResourceNode l) Source # | |
Read l => Read (TryResourceNode l) Source # | |
Show l => Show (TryResourceNode l) Source # | |
Generic (TryResourceNode l) Source # | |
Show l => Pretty (TryResourceNode l) Source # | |
type Rep (TryResourceNode l) Source # | |
data SwitchLabelNode l Source #
A label within a switch
statement.
Constructors
SwitchCaseNode (ExpNode l) | The expression contained in the |
DefaultNode l |
Instances
HasNode ExpNode SwitchLabelNode Source # | |
Eq l => Eq (SwitchLabelNode l) Source # | |
Data l => Data (SwitchLabelNode l) Source # | |
Read l => Read (SwitchLabelNode l) Source # | |
Show l => Show (SwitchLabelNode l) Source # | |
Generic (SwitchLabelNode l) Source # | |
Show l => Pretty (SwitchLabelNode l) Source # | |
type Rep (SwitchLabelNode l) Source # | |
data ForInitNode l Source #
Initialization code for a basic for
statement.
Constructors
ForLocalVarsNode (ForLocalVars l) | |
ForInitExpsNode (ForInitExps l) |
Instances
HasNode ForInitExps ForInitNode Source # | |
HasNode ForLocalVars ForInitNode Source # | |
Eq l => Eq (ForInitNode l) Source # | |
Data l => Data (ForInitNode l) Source # | |
Read l => Read (ForInitNode l) Source # | |
Show l => Show (ForInitNode l) Source # | |
Generic (ForInitNode l) Source # | |
Show l => Pretty (ForInitNode l) Source # | |
type Rep (ForInitNode l) Source # | |
A Java expression.
Constructors
LitNode (Lit l) | A literal denotes a fixed, unchanging value. |
ClassLitNode (ClassLit l) | A class literal, which is an expression consisting of the name of a class, interface, array,
or primitive type, or the pseudo-type void (modelled by |
ThisNode (This l) | The keyword |
QualifiedThisNode (QualifiedThis l) | Any lexically enclosing instance can be referred to by explicitly qualifying the keyword this. TODO: Fix Parser here |
InstanceCreationNode (InstanceCreation l) | A class instance creation expression is used to create new objects that are instances of classes. | The first argument is a list of non-wildcard type arguments to a generic constructor. What follows is the type to be instantiated, the list of arguments passed to the constructor, and optionally a class body that makes the constructor result in an object of an anonymous class. |
QualInstanceCreationNode (QualInstanceCreation l) | A qualified class instance creation expression enables the creation of instances of inner member classes and their anonymous subclasses. |
ArrayCreateNode (ArrayCreate l) | An array instance creation expression is used to create new arrays. The last argument denotes the number of dimensions that have no explicit length given. These dimensions must be given last. |
ArrayCreateInitNode (ArrayCreateInit l) | An array instance creation expression may come with an explicit initializer. Such expressions may not be given explicit lengths for any of its dimensions. |
FieldAccessNode (FieldAccessNode l) | A field access expression. |
MethodInvNode (MethodInvocationNode l) | A method invocation expression. |
ArrayAccessNode (ArrayIndex l) | An array access expression refers to a variable that is a component of an array. |
ExpNameNode (ExpName l) | An expression name, e.g. a variable. |
PostIncrementNode (ExpNode l) | Post-incrementation expression, i.e. an expression followed by |
PostDecrementNode (ExpNode l) | Post-decrementation expression, i.e. an expression followed by |
PreIncrementNode (ExpNode l) | Pre-incrementation expression, i.e. an expression preceded by |
PreDecrementNode (ExpNode l) | Pre-decrementation expression, i.e. an expression preceded by |
PrePlusNode (ExpNode l) | Unary plus, the promotion of the value of the expression to a primitive numeric type. |
PreMinusNode (ExpNode l) | Unary minus, the promotion of the negation of the value of the expression to a primitive numeric type. |
PreBitComplNode (ExpNode l) | Unary bitwise complementation: note that, in all cases, |
PreNotNode (ExpNode l) | Logical complementation of boolean values. |
CastNode (Cast l) | A cast expression converts, at run time, a value of one numeric type to a similar value of another numeric type; or confirms, at compile time, that the type of an expression is boolean; or checks, at run time, that a reference value refers to an object whose class is compatible with a specified reference type. |
BinOpNode (BinOp l) | The application of a binary operator to two operand expressions. |
InstanceOfNode (InstanceOf l) | Testing whether the result of an expression is an instance of some reference type. |
CondNode (Cond l) | The conditional operator |
AssignNode (Assign l) | Assignment of the result of an expression to a variable. |
LambdaNode (Lambda l) | Lambda expression |
MethodRefNode (MethodRef l) | Method reference |
Instances
The left-hand side of an assignment expression. This operand may be a named variable, such as a local variable or a field of the current object or class, or it may be a computed variable, as can result from a field access or an array access.
Constructors
NameLhsNode (NameLhs l) | Assign to a variable |
FieldLhsNode (FieldAccessNode l) | Assign through a field access |
ArrayLhsNode (ArrayIndex l) | Assign to an array |
Instances
HasNode ArrayIndex LhsNode Source # | |
HasNode NameLhs LhsNode Source # | |
HasNode FieldAccessNode LhsNode Source # | |
Eq l => Eq (LhsNode l) Source # | |
Data l => Data (LhsNode l) Source # | |
Read l => Read (LhsNode l) Source # | |
Show l => Show (LhsNode l) Source # | |
Generic (LhsNode l) Source # | |
Show l => Pretty (LhsNode l) Source # | |
type Rep (LhsNode l) Source # | |
data FieldAccessNode l Source #
A field access expression may access a field of an object or array, a reference to which is the value of either an expression or the special keyword super.
Constructors
PrimaryFieldAccessNode (PrimaryFieldAccess l) | Accessing a field of an object or array computed from an expression. |
SuperFieldAccessNode (SuperFieldAccess l) | Accessing a field of the superclass. |
ClassFieldAccessNode (ClassFieldAccess l) | Accessing a (static) field of a named class. |
Instances
HasNode ClassFieldAccess FieldAccessNode Source # | |
HasNode SuperFieldAccess FieldAccessNode Source # | |
HasNode PrimaryFieldAccess FieldAccessNode Source # | |
HasNode FieldAccessNode LhsNode Source # | |
HasNode FieldAccessNode ExpNode Source # | |
Eq l => Eq (FieldAccessNode l) Source # | |
Data l => Data (FieldAccessNode l) Source # | |
Read l => Read (FieldAccessNode l) Source # | |
Show l => Show (FieldAccessNode l) Source # | |
Generic (FieldAccessNode l) Source # | |
Show l => Pretty (FieldAccessNode l) Source # | |
type Rep (FieldAccessNode l) Source # | |
data LambdaParamsNode l Source #
Constructors
LambdaSingleParamNode (LambdaSingleParam l) | |
LambdaFormalParamsNode (LambdaFormalParams l) | |
LambdaInferredParamsNode (LambdaInferredParams l) |
Instances
HasNode LambdaInferredParams LambdaParamsNode Source # | |
HasNode LambdaFormalParams LambdaParamsNode Source # | |
HasNode LambdaSingleParam LambdaParamsNode Source # | |
Eq l => Eq (LambdaParamsNode l) Source # | |
Data l => Data (LambdaParamsNode l) Source # | |
Read l => Read (LambdaParamsNode l) Source # | |
Show l => Show (LambdaParamsNode l) Source # | |
Generic (LambdaParamsNode l) Source # | |
Show l => Pretty (LambdaParamsNode l) Source # | |
type Rep (LambdaParamsNode l) Source # | |
data LambdaExpressionNode l Source #
Lambda expression, starting from java 8
Constructors
LambdaExpressionNode (ExpNode l) | |
LambdaBlockNode (Block l) |
Instances
HasNode Block LambdaExpressionNode Source # | |
HasNode ExpNode LambdaExpressionNode Source # | |
Eq l => Eq (LambdaExpressionNode l) Source # | |
Data l => Data (LambdaExpressionNode l) Source # | |
Read l => Read (LambdaExpressionNode l) Source # | |
Show l => Show (LambdaExpressionNode l) Source # | |
Generic (LambdaExpressionNode l) Source # | |
Show l => Pretty (LambdaExpressionNode l) Source # | |
type Rep (LambdaExpressionNode l) Source # | |
data MethodInvocationNode l Source #
A method invocation expression is used to invoke a class or instance method.
Constructors
MethodCallNode (MethodCall l) | Invoking a specific named method. |
PrimaryMethodCallNode (PrimaryMethodCall l) | Invoking a method of a class computed from a primary expression, giving arguments for any generic type parameters. |
SuperMethodCallNode (SuperMethodCall l) | Invoking a method of the super class, giving arguments for any generic type parameters. |
ClassMethodCallNode (ClassMethodCall l) | Invoking a method of the superclass of a named class, giving arguments for any generic type parameters. |
TypeMethodCallNode (TypeMethodCall l) | Invoking a method of a named type, giving arguments for any generic type parameters. |
Instances
data CompilationUnit l Source #
A compilation unit is the top level syntactic goal symbol of a Java program.
Constructors
CompilationUnit | |
Fields
|
Instances
HasNode CompilationUnit CompilationUnitNode Source # | |
Eq l => Eq (CompilationUnit l) Source # | |
Data l => Data (CompilationUnit l) Source # | |
Read l => Read (CompilationUnit l) Source # | |
Show l => Show (CompilationUnit l) Source # | |
Generic (CompilationUnit l) Source # | |
Show l => Pretty (CompilationUnit l) Source # | |
type Rep (CompilationUnit l) Source # | |
data ModuleDeclaration l Source #
Constructors
ModuleDeclaration | |
Fields
|
Instances
HasNode ModuleDeclaration CompilationUnitNode Source # | |
Eq l => Eq (ModuleDeclaration l) Source # | |
Data l => Data (ModuleDeclaration l) Source # | |
Read l => Read (ModuleDeclaration l) Source # | |
Show l => Show (ModuleDeclaration l) Source # | |
Generic (ModuleDeclaration l) Source # | |
Show l => Pretty (ModuleDeclaration l) Source # | |
type Rep (ModuleDeclaration l) Source # | |
data PackageDecl l Source #
A package declaration appears within a compilation unit to indicate the package to which the compilation unit belongs.
Constructors
PackageDecl | |
Fields
|
Instances
Eq l => Eq (PackageDecl l) Source # | |
Data l => Data (PackageDecl l) Source # | |
Read l => Read (PackageDecl l) Source # | |
Show l => Show (PackageDecl l) Source # | |
Generic (PackageDecl l) Source # | |
Pretty (PackageDecl l) Source # | |
type Rep (PackageDecl l) Source # | |
data ModuleRequires l Source #
requires the module to work
Constructors
ModuleRequires | |
Fields
|
Instances
HasNode ModuleRequires ModuleSpecNode Source # | |
Eq l => Eq (ModuleRequires l) Source # | |
Data l => Data (ModuleRequires l) Source # | |
Read l => Read (ModuleRequires l) Source # | |
Show l => Show (ModuleRequires l) Source # | |
Generic (ModuleRequires l) Source # | |
Pretty (ModuleRequires l) Source # | |
type Rep (ModuleRequires l) Source # | |
data ModuleExports l Source #
Exports the package
Constructors
ModuleExports | |
Fields
|
Instances
HasNode ModuleExports ModuleSpecNode Source # | |
Eq l => Eq (ModuleExports l) Source # | |
Data l => Data (ModuleExports l) Source # | |
Read l => Read (ModuleExports l) Source # | |
Show l => Show (ModuleExports l) Source # | |
Generic (ModuleExports l) Source # | |
Pretty (ModuleExports l) Source # | |
type Rep (ModuleExports l) Source # | |
data ImportDecl l Source #
An import declaration allows a static member or a named type to be referred to by a single unqualified identifier. The first argument signals whether the declaration only imports static members. The last argument signals whether the declaration brings all names in the named type or package, or only brings a single name into scope.
Constructors
ImportDecl | |
Fields
|
Instances
Eq l => Eq (ImportDecl l) Source # | |
Data l => Data (ImportDecl l) Source # | |
Read l => Read (ImportDecl l) Source # | |
Show l => Show (ImportDecl l) Source # | |
Generic (ImportDecl l) Source # | |
HasType (ImportDecl l) Source # | |
Pretty (ImportDecl l) Source # | |
type Rep (ImportDecl l) Source # | |
A class declaration specifies a new named reference type.
Constructors
ClassDecl | |
Fields
|
Instances
HasNode ClassDecl ClassDeclNode Source # | |
Eq l => Eq (ClassDecl l) Source # | |
Data l => Data (ClassDecl l) Source # | |
Read l => Read (ClassDecl l) Source # | |
Show l => Show (ClassDecl l) Source # | |
Generic (ClassDecl l) Source # | |
CollectTypes (ClassDecl l) Source # | |
HasType (ClassDecl l) Source # | |
Show l => Pretty (ClassDecl l) Source # | |
HasBody (ClassDecl l) l Source # | Get the body of ClassDecl |
type Rep (ClassDecl l) Source # | |
Constructors
EnumDecl | |
Fields
|
Instances
HasNode EnumDecl ClassDeclNode Source # | |
Eq l => Eq (EnumDecl l) Source # | |
Data l => Data (EnumDecl l) Source # | |
Read l => Read (EnumDecl l) Source # | |
Show l => Show (EnumDecl l) Source # | |
Generic (EnumDecl l) Source # | |
CollectTypes (EnumDecl l) Source # | |
HasType (EnumDecl l) Source # | |
Show l => Pretty (EnumDecl l) Source # | |
HasBody (EnumDecl l) l Source # | |
type Rep (EnumDecl l) Source # | |
An extends clause
Constructors
Extends | |
Fields
|
data Implements l Source #
An implements clause
Constructors
Implements | |
Fields
|
Instances
Eq l => Eq (Implements l) Source # | |
Data l => Data (Implements l) Source # | |
Read l => Read (Implements l) Source # | |
Show l => Show (Implements l) Source # | |
Generic (Implements l) Source # | |
HasType (Implements l) Source # | |
Show l => Pretty (Implements l) Source # | |
type Rep (Implements l) Source # | |
A class body may contain declarations of members of the class, that is, fields, classes, interfaces and methods. A class body may also contain instance initializers, static initializers, and declarations of constructors for the class.
Constructors
ClassBody | |
Fields
|
Instances
Eq l => Eq (ClassBody l) Source # | |
Data l => Data (ClassBody l) Source # | |
Read l => Read (ClassBody l) Source # | |
Show l => Show (ClassBody l) Source # | |
Generic (ClassBody l) Source # | |
Show l => Pretty (ClassBody l) Source # | |
HasBody (ClassBody l) l Source # | Get the body of ClassBody |
type Rep (ClassBody l) Source # | |
The body of an enum type may contain enum constants.
Constructors
EnumBody | |
Fields
|
Instances
data EnumConstant l Source #
An enum constant defines an instance of the enum type.
Constructors
EnumConstant | |
Fields
|
Instances
Eq l => Eq (EnumConstant l) Source # | |
Data l => Data (EnumConstant l) Source # | |
Read l => Read (EnumConstant l) Source # | |
Show l => Show (EnumConstant l) Source # | |
Generic (EnumConstant l) Source # | |
HasType (EnumConstant l) Source # | Get type of EnumConstant |
Show l => Pretty (EnumConstant l) Source # | |
type Rep (EnumConstant l) Source # | |
data InterfaceDecl l Source #
An interface declaration introduces a new reference type whose members are classes, interfaces, constants and abstract methods. This type has no implementation, but otherwise unrelated classes can implement it by providing implementations for its abstract methods.
Constructors
InterfaceDecl | |
Fields
|
Instances
HasNode InterfaceDecl MemberDeclNode Source # | |
HasNode InterfaceDecl TypeDeclNode Source # | |
Eq l => Eq (InterfaceDecl l) Source # | |
Data l => Data (InterfaceDecl l) Source # | |
Read l => Read (InterfaceDecl l) Source # | |
Show l => Show (InterfaceDecl l) Source # | |
Generic (InterfaceDecl l) Source # | |
CollectTypes (InterfaceDecl l) Source # | |
HasType (InterfaceDecl l) Source # | Get type of InterfaceDecl |
Show l => Pretty (InterfaceDecl l) Source # | |
HasBody (InterfaceDecl l) l Source # | Get the body of InterfaceDecl |
type Rep (InterfaceDecl l) Source # | |
data InterfaceKind Source #
Interface can declare either a normal interface or an annotation
Constructors
InterfaceNormal | |
InterfaceAnnotation |
Instances
data InterfaceBody l Source #
The body of an interface may declare members of the interface.
Constructors
InterfaceBody | |
Fields
|
Instances
Eq l => Eq (InterfaceBody l) Source # | |
Data l => Data (InterfaceBody l) Source # | |
Read l => Read (InterfaceBody l) Source # | |
Show l => Show (InterfaceBody l) Source # | |
Generic (InterfaceBody l) Source # | |
Show l => Pretty (InterfaceBody l) Source # | |
HasBody (InterfaceBody l) l Source # | Get the body of ClassDecl |
type Rep (InterfaceBody l) Source # | |
A declaration is either a member declaration, or a declaration of an initializer, which may be static.
Constructors
InitDecl | |
Fields
|
The variables of a class type are introduced by field declarations.
Example:
>>>
parseCompilationUnit "public class MyClass {private String foo = \"Hello World\"; }"
... __FieldDecl__ {__infoFieldDecl__ = Segment (Position 1 31) (Position 1 31), __memberDeclModifiers__ = [private], __fieldType__ = RefType (ClassRefType (WithoutPackage (ClassName [(Ident "String",[])]))), __fieldVarDecls__ = [VarDecl {infoVarDecl = Segment (Position 1 38) (Position 1 38), varDeclName = VarId {infoVarId = Segment (Position 1 38) (Position 1 38), varIdName = Ident "foo"}, varInit = Just (InitExp {infoInitExp= Segment (Position 1 44) (Position 1 44), init = Lit {infoLit = Segment (Position 1 44) (Position 1 44), literal = String "Hello World"}})}]}}]}}}]})
Constructors
FieldDecl | |
Fields
|
Instances
HasNode FieldDecl MemberDeclNode Source # | |
Eq l => Eq (FieldDecl l) Source # | |
Data l => Data (FieldDecl l) Source # | |
Read l => Read (FieldDecl l) Source # | |
Show l => Show (FieldDecl l) Source # | |
Generic (FieldDecl l) Source # | |
CollectTypes (FieldDecl l) Source # | Get type of MemberDecl if it is a MethodDecl (our solution to handeling the Maybe) |
Show l => Pretty (FieldDecl l) Source # | |
type Rep (FieldDecl l) Source # | |
data MethodDecl l Source #
A method declares executable code that can be invoked, passing a fixed number of values as arguments. Example:
>>>
parseCompilationUnit "public class MyClass {private String foo() {}}"
... [MemberDecl {infoMemberDecl = Segment (Position 1 23) (Position 1 23), member = MethodDecl {infoMethodDecl = Segment (Position 1 31) (Position 1 31), methodDeclModifiers = [private], methodTypeParams = [], returnType = Just (RefType (ClassRefType (WithoutPackage (ClassName [(Ident "String",[])])))), methodDeclName = Ident "foo", params = [], exceptions = [], defaultInterfaceAnnotation = Nothing, methodBody = MethodBody {infoMethodBody = Segment (Position 1 44) (Position 1 44), impl= Just (Block {infoBlock = Segment (Position 1 45) (Position 1 45), blockStatements = []})}}}]}}}]})
Constructors
MethodDecl | |
Fields
|
Instances
HasNode MethodDecl MemberDeclNode Source # | |
Eq l => Eq (MethodDecl l) Source # | |
Data l => Data (MethodDecl l) Source # | |
Read l => Read (MethodDecl l) Source # | |
Show l => Show (MethodDecl l) Source # | |
Generic (MethodDecl l) Source # | |
CollectTypes (MethodDecl l) Source # | |
Show l => Pretty (MethodDecl l) Source # | |
type Rep (MethodDecl l) Source # | |
data ConstructorDecl l Source #
A constructor is used in the creation of an object that is an instance of a class.
Constructors
ConstructorDecl | |
Fields
|
Instances
HasNode ConstructorDecl MemberDeclNode Source # | |
Eq l => Eq (ConstructorDecl l) Source # | |
Data l => Data (ConstructorDecl l) Source # | |
Read l => Read (ConstructorDecl l) Source # | |
Show l => Show (ConstructorDecl l) Source # | |
Generic (ConstructorDecl l) Source # | |
Show l => Pretty (ConstructorDecl l) Source # | |
type Rep (ConstructorDecl l) Source # | |
A declaration of a variable, which may be explicitly initialized.
Constructors
VarDecl | |
Fields
|
The name of a variable in a declaration, which may be an array.
data FormalParam l Source #
A formal parameter in method declaration. The last parameter for a given declaration may be marked as variable arity, indicated by the boolean argument.
Constructors
FormalParam | |
Fields
|
Instances
Eq l => Eq (FormalParam l) Source # | |
Data l => Data (FormalParam l) Source # | |
Read l => Read (FormalParam l) Source # | |
Show l => Show (FormalParam l) Source # | |
Generic (FormalParam l) Source # | |
HasType (FormalParam l) Source # | Gets type of FormalParam |
Show l => Pretty (FormalParam l) Source # | |
type Rep (FormalParam l) Source # | |
data MethodBody l Source #
A method body is either a block of code that implements the method or simply a
semicolon, indicating the lack of an implementation (modelled by Nothing
).
Constructors
MethodBody | |
Fields
|
Instances
Eq l => Eq (MethodBody l) Source # | |
Data l => Data (MethodBody l) Source # | |
Read l => Read (MethodBody l) Source # | |
Show l => Show (MethodBody l) Source # | |
Generic (MethodBody l) Source # | |
Show l => Pretty (MethodBody l) Source # | |
type Rep (MethodBody l) Source # | |
data ConstructorBody l Source #
The first statement of a constructor body may be an explicit invocation of another constructor of the same class or of the direct superclass.
Constructors
ConstructorBody | |
Fields
|
Instances
Eq l => Eq (ConstructorBody l) Source # | |
Data l => Data (ConstructorBody l) Source # | |
Read l => Read (ConstructorBody l) Source # | |
Show l => Show (ConstructorBody l) Source # | |
Generic (ConstructorBody l) Source # | |
Show l => Pretty (ConstructorBody l) Source # | |
type Rep (ConstructorBody l) Source # | |
data ThisInvoke l Source #
An explicit constructor invocation invokes another constructor of the same class, or a constructor of the direct superclass, which may be qualified to explicitly specify the newly created object's immediately enclosing instance.
Constructors
ThisInvoke | |
Fields
|
Instances
HasNode ThisInvoke ExplConstrInvNode Source # | |
Eq l => Eq (ThisInvoke l) Source # | |
Data l => Data (ThisInvoke l) Source # | |
Read l => Read (ThisInvoke l) Source # | |
Show l => Show (ThisInvoke l) Source # | |
Generic (ThisInvoke l) Source # | |
Show l => Pretty (ThisInvoke l) Source # | |
type Rep (ThisInvoke l) Source # | |
data SuperInvoke l Source #
Constructors
SuperInvoke | |
Fields
|
Instances
HasNode SuperInvoke ExplConstrInvNode Source # | |
Eq l => Eq (SuperInvoke l) Source # | |
Data l => Data (SuperInvoke l) Source # | |
Read l => Read (SuperInvoke l) Source # | |
Show l => Show (SuperInvoke l) Source # | |
Generic (SuperInvoke l) Source # | |
Show l => Pretty (SuperInvoke l) Source # | |
type Rep (SuperInvoke l) Source # | |
data PrimarySuperInvoke l Source #
Constructors
PrimarySuperInvoke | |
Fields
|
Instances
HasNode PrimarySuperInvoke ExplConstrInvNode Source # | |
Eq l => Eq (PrimarySuperInvoke l) Source # | |
Data l => Data (PrimarySuperInvoke l) Source # | |
Read l => Read (PrimarySuperInvoke l) Source # | |
Show l => Show (PrimarySuperInvoke l) Source # | |
Generic (PrimarySuperInvoke l) Source # | |
Show l => Pretty (PrimarySuperInvoke l) Source # | |
type Rep (PrimarySuperInvoke l) Source # | |
A modifier specifying properties of a given declaration. In general only a few of these modifiers are allowed for each declaration type, for instance a member type declaration may only specify one of public, private or protected.
Constructors
Public l | |
Private l | |
Protected l | |
Abstract l | |
Final l | |
Static l | |
StrictFP l | |
Transient l | |
Volatile l | |
Native l | |
Annotation (Annotation l) | |
Synchronized_ l | |
DefaultModifier l |
data Annotation l Source #
Annotations have three different forms: no-parameter, single-parameter or key-value pairs
Constructors
NormalAnnotation | |
Fields
| |
SingleElementAnnotation | |
Fields
| |
MarkerAnnotation | |
Instances
HasNode Annotation Modifier Source # | |
Eq l => Eq (Annotation l) Source # | |
Data l => Data (Annotation l) Source # | |
Read l => Read (Annotation l) Source # | |
Show l => Show (Annotation l) Source # | |
Generic (Annotation l) Source # | |
Show l => Pretty (Annotation l) Source # | |
type Rep (Annotation l) Source # | |
data ElementValue l Source #
Annotations may contain annotations or (loosely) expressions
Constructors
EVVal | |
Fields
| |
EVAnn | |
Fields
|
Instances
Eq l => Eq (ElementValue l) Source # | |
Data l => Data (ElementValue l) Source # | |
Read l => Read (ElementValue l) Source # | |
Show l => Show (ElementValue l) Source # | |
Generic (ElementValue l) Source # | |
Show l => Pretty (ElementValue l) Source # | |
type Rep (ElementValue l) Source # | |
A block is a sequence of statements, local class declarations and local variable declaration statements within braces.
Constructors
Block | |
Fields
|
Instances
A block statement is either a normal statement, a local class declaration or a local variable declaration.
Constructors
LocalVars | |
Fields
|
Instances
data IfThenElse l Source #
The if-then
statement allows conditional execution of a statement.
Constructors
IfThenElse | |
Instances
HasNode IfThenElse StmtNode Source # | |
Eq l => Eq (IfThenElse l) Source # | |
Data l => Data (IfThenElse l) Source # | |
Read l => Read (IfThenElse l) Source # | |
Show l => Show (IfThenElse l) Source # | |
Generic (IfThenElse l) Source # | |
Show l => Pretty (IfThenElse l) Source # | |
type Rep (IfThenElse l) Source # | |
The while
statement executes an expression and a statement repeatedly until the value of the expression is false.
The basic for
statement executes some initialization code, then executes an expression, a statement, and some
update code repeatedly until the value of the expression is false.
Constructors
BasicFor | |
Fields
|
data EnhancedFor l Source #
The enhanced for
statement iterates over an array or a value of a class that implements the iterator
interface.
Constructors
EnhancedFor | |
Fields
|
Instances
HasNode EnhancedFor StmtNode Source # | |
Eq l => Eq (EnhancedFor l) Source # | |
Data l => Data (EnhancedFor l) Source # | |
Read l => Read (EnhancedFor l) Source # | |
Show l => Show (EnhancedFor l) Source # | |
Generic (EnhancedFor l) Source # | |
Show l => Pretty (EnhancedFor l) Source # | |
type Rep (EnhancedFor l) Source # | |
An empty statement does nothing.
An assertion is a statement containing a boolean expression, where an error is reported if the expression evaluates to false.
Constructors
Assert | |
Fields
|
The switch statement transfers control to one of several statements depending on the value of an expression.
Constructors
Switch | |
Fields
|
The do
statement executes a statement and an expression repeatedly until the value of the expression is false.
A break
statement transfers control out of an enclosing statement.
Constructors
Break | |
Fields
|
A continue
statement may occur only in a while, do, or for statement. Control passes to the loop-continuation
point of that statement.
Constructors
Continue | |
Fields
|
A return
statement returns control to the invoker of a method or constructor.
Constructors
Return | |
Fields
|
data Synchronized l Source #
A synchronized
statement acquires a mutual-exclusion lock on behalf of the executing thread, executes a block,
then releases the lock. While the executing thread owns the lock, no other thread may acquire the lock.
Constructors
Synchronized | |
Fields
|
Instances
HasNode Synchronized StmtNode Source # | |
Eq l => Eq (Synchronized l) Source # | |
Data l => Data (Synchronized l) Source # | |
Read l => Read (Synchronized l) Source # | |
Show l => Show (Synchronized l) Source # | |
Generic (Synchronized l) Source # | |
Show l => Pretty (Synchronized l) Source # | |
type Rep (Synchronized l) Source # | |
A throw
statement causes an exception to be thrown.
A try statement executes a block. If a value is thrown and the try statement has one or more catch clauses that can catch it, then control will be transferred to the first such catch clause. If the try statement has a finally clause, then another block of code is executed, no matter whether the try block completes normally or abruptly, and no matter whether a catch clause is first given control.
Statements may have label prefixes.
Constructors
Labeled | |
Fields
|
If a value is thrown and the try statement has one or more catch clauses that can catch it, then control will be transferred to the first such catch clause.
Constructors
Catch | |
Fields
|
data TryResourceVar l Source #
Newly declared variables
Constructors
TryResourceVar | |
Fields
|
Instances
HasNode TryResourceVar TryResourceNode Source # | |
Eq l => Eq (TryResourceVar l) Source # | |
Data l => Data (TryResourceVar l) Source # | |
Read l => Read (TryResourceVar l) Source # | |
Show l => Show (TryResourceVar l) Source # | |
Generic (TryResourceVar l) Source # | |
Show l => Pretty (TryResourceVar l) Source # | |
type Rep (TryResourceVar l) Source # | |
data TryResourceFinalVar l Source #
Effectively final variable
Constructors
TryResourceFinalVar | |
Fields |
Instances
HasNode TryResourceFinalVar TryResourceNode Source # | |
Eq l => Eq (TryResourceFinalVar l) Source # | |
Data l => Data (TryResourceFinalVar l) Source # | |
Read l => Read (TryResourceFinalVar l) Source # | |
Show l => Show (TryResourceFinalVar l) Source # | |
Generic (TryResourceFinalVar l) Source # | |
Show l => Pretty (TryResourceFinalVar l) Source # | |
type Rep (TryResourceFinalVar l) Source # | |
data SwitchBlock l Source #
A block of code labelled with a case
or default
within a switch
statement.
Constructors
SwitchBlock | |
Fields
|
Instances
Eq l => Eq (SwitchBlock l) Source # | |
Data l => Data (SwitchBlock l) Source # | |
Read l => Read (SwitchBlock l) Source # | |
Show l => Show (SwitchBlock l) Source # | |
Generic (SwitchBlock l) Source # | |
Show l => Pretty (SwitchBlock l) Source # | |
type Rep (SwitchBlock l) Source # | |
data ForLocalVars l Source #
Initialization code for a basic for
statement.
Constructors
ForLocalVars | |
Fields
|
Instances
HasNode ForLocalVars ForInitNode Source # | |
Eq l => Eq (ForLocalVars l) Source # | |
Data l => Data (ForLocalVars l) Source # | |
Read l => Read (ForLocalVars l) Source # | |
Show l => Show (ForLocalVars l) Source # | |
Generic (ForLocalVars l) Source # | |
Show l => Pretty (ForLocalVars l) Source # | |
type Rep (ForLocalVars l) Source # | |
data ForInitExps l Source #
Constructors
ForInitExps | |
Fields
|
Instances
HasNode ForInitExps ForInitNode Source # | |
Eq l => Eq (ForInitExps l) Source # | |
Data l => Data (ForInitExps l) Source # | |
Read l => Read (ForInitExps l) Source # | |
Show l => Show (ForInitExps l) Source # | |
Generic (ForInitExps l) Source # | |
Show l => Pretty (ForInitExps l) Source # | |
type Rep (ForInitExps l) Source # | |
data ExceptionType l Source #
An exception type has to be a class type or a type variable.
Constructors
ExceptionType | |
Fields
|
Instances
Eq l => Eq (ExceptionType l) Source # | |
Data l => Data (ExceptionType l) Source # | |
Read l => Read (ExceptionType l) Source # | |
Show l => Show (ExceptionType l) Source # | |
Generic (ExceptionType l) Source # | |
HasType (ExceptionType l) Source # | |
Pretty (ExceptionType l) Source # | |
type Rep (ExceptionType l) Source # | |
A literal denotes a fixed, unchanging value.
A class literal, which is an expression consisting of the name of a class, interface, array,
or primitive type, or the pseudo-type void (modelled by Nothing
), followed by a .
and the token class.
Constructors
ClassLit | |
Fields
|
The keyword this
denotes a value that is a reference to the object for which the instance method
was invoked, or to the object being constructed.
data QualifiedThis l Source #
Any lexically enclosing instance can be referred to by explicitly qualifying the keyword this. TODO: Fix Parser here
Constructors
QualifiedThis | |
Fields
|
Instances
HasNode QualifiedThis ExpNode Source # | |
Eq l => Eq (QualifiedThis l) Source # | |
Data l => Data (QualifiedThis l) Source # | |
Read l => Read (QualifiedThis l) Source # | |
Show l => Show (QualifiedThis l) Source # | |
Generic (QualifiedThis l) Source # | |
Show l => Pretty (QualifiedThis l) Source # | |
type Rep (QualifiedThis l) Source # | |
data InstanceCreation l Source #
A class instance creation expression is used to create new objects that are instances of classes. | The first argument is a list of non-wildcard type arguments to a generic constructor. What follows is the type to be instantiated, the list of arguments passed to the constructor, and optionally a class body that makes the constructor result in an object of an anonymous class.
Constructors
InstanceCreation | |
Fields
|
Instances
HasNode InstanceCreation ExpNode Source # | |
Eq l => Eq (InstanceCreation l) Source # | |
Data l => Data (InstanceCreation l) Source # | |
Read l => Read (InstanceCreation l) Source # | |
Show l => Show (InstanceCreation l) Source # | |
Generic (InstanceCreation l) Source # | |
Show l => Pretty (InstanceCreation l) Source # | |
type Rep (InstanceCreation l) Source # | |
data QualInstanceCreation l Source #
A qualified class instance creation expression enables the creation of instances of inner member classes and their anonymous subclasses.
Constructors
QualInstanceCreation | |
Fields
|
Instances
HasNode QualInstanceCreation ExpNode Source # | |
Eq l => Eq (QualInstanceCreation l) Source # | |
Data l => Data (QualInstanceCreation l) Source # | |
Read l => Read (QualInstanceCreation l) Source # | |
Show l => Show (QualInstanceCreation l) Source # | |
Generic (QualInstanceCreation l) Source # | |
Show l => Pretty (QualInstanceCreation l) Source # | |
type Rep (QualInstanceCreation l) Source # | |
data ArrayCreate l Source #
An array instance creation expression is used to create new arrays. The last argument denotes the number of dimensions that have no explicit length given. These dimensions must be given last.
Constructors
ArrayCreate | |
Fields
|
Instances
HasNode ArrayCreate ExpNode Source # | |
Eq l => Eq (ArrayCreate l) Source # | |
Data l => Data (ArrayCreate l) Source # | |
Read l => Read (ArrayCreate l) Source # | |
Show l => Show (ArrayCreate l) Source # | |
Generic (ArrayCreate l) Source # | |
Show l => Pretty (ArrayCreate l) Source # | |
type Rep (ArrayCreate l) Source # | |
data ArrayCreateInit l Source #
An array instance creation expression may come with an explicit initializer. Such expressions may not be given explicit lengths for any of its dimensions.
Constructors
ArrayCreateInit | |
Fields
|
Instances
HasNode ArrayCreateInit ExpNode Source # | |
Eq l => Eq (ArrayCreateInit l) Source # | |
Data l => Data (ArrayCreateInit l) Source # | |
Read l => Read (ArrayCreateInit l) Source # | |
Show l => Show (ArrayCreateInit l) Source # | |
Generic (ArrayCreateInit l) Source # | |
Show l => Pretty (ArrayCreateInit l) Source # | |
type Rep (ArrayCreateInit l) Source # | |
An expression name, e.g. a variable.
Constructors
ExpName | |
Fields
|
A cast expression converts, at run time, a value of one numeric type to a similar value of another numeric type; or confirms, at compile time, that the type of an expression is boolean; or checks, at run time, that a reference value refers to an object whose class is compatible with a specified reference type.
The application of a binary operator to two operand expressions.
Constructors
BinOp | |
Fields
|
data InstanceOf l Source #
Testing whether the result of an expression is an instance of some reference type.
Constructors
InstanceOf | |
Fields
|
Instances
HasNode InstanceOf ExpNode Source # | |
Eq l => Eq (InstanceOf l) Source # | |
Data l => Data (InstanceOf l) Source # | |
Read l => Read (InstanceOf l) Source # | |
Show l => Show (InstanceOf l) Source # | |
Generic (InstanceOf l) Source # | |
Show l => Pretty (InstanceOf l) Source # | |
type Rep (InstanceOf l) Source # | |
The conditional operator ? :
uses the boolean value of one expression to decide which of two other
expressions should be evaluated.
Constructors
Cond | |
Fields
|
Assignment of the result of an expression to a variable.
Constructors
Assign | |
Fields
|
Lambda expression
Constructors
Lambda | |
Fields
|
Method reference
Constructors
MethodRef | |
Fields
|
Assign to a variable
Constructors
NameLhs | |
Fields
|
data ArrayIndex l Source #
Array access
Constructors
ArrayIndex | |
Fields
|
Instances
HasNode ArrayIndex LhsNode Source # | |
HasNode ArrayIndex ExpNode Source # | |
Eq l => Eq (ArrayIndex l) Source # | |
Data l => Data (ArrayIndex l) Source # | |
Read l => Read (ArrayIndex l) Source # | |
Show l => Show (ArrayIndex l) Source # | |
Generic (ArrayIndex l) Source # | |
Show l => Pretty (ArrayIndex l) Source # | |
type Rep (ArrayIndex l) Source # | |
data PrimaryFieldAccess l Source #
Accessing a field of an object or array computed from an expression.
Constructors
PrimaryFieldAccess | |
Fields
|
Instances
HasNode PrimaryFieldAccess FieldAccessNode Source # | |
Eq l => Eq (PrimaryFieldAccess l) Source # | |
Data l => Data (PrimaryFieldAccess l) Source # | |
Read l => Read (PrimaryFieldAccess l) Source # | |
Show l => Show (PrimaryFieldAccess l) Source # | |
Generic (PrimaryFieldAccess l) Source # | |
Show l => Pretty (PrimaryFieldAccess l) Source # | |
type Rep (PrimaryFieldAccess l) Source # | |
data SuperFieldAccess l Source #
Accessing a field of the superclass.
Constructors
SuperFieldAccess | |
Fields
|
Instances
HasNode SuperFieldAccess FieldAccessNode Source # | |
Eq l => Eq (SuperFieldAccess l) Source # | |
Data l => Data (SuperFieldAccess l) Source # | |
Read l => Read (SuperFieldAccess l) Source # | |
Show l => Show (SuperFieldAccess l) Source # | |
Generic (SuperFieldAccess l) Source # | |
Show l => Pretty (SuperFieldAccess l) Source # | |
type Rep (SuperFieldAccess l) Source # | |
data ClassFieldAccess l Source #
Accessing a (static) field of a named class.
Constructors
ClassFieldAccess | |
Fields
|
Instances
HasNode ClassFieldAccess FieldAccessNode Source # | |
Eq l => Eq (ClassFieldAccess l) Source # | |
Data l => Data (ClassFieldAccess l) Source # | |
Read l => Read (ClassFieldAccess l) Source # | |
Show l => Show (ClassFieldAccess l) Source # | |
Generic (ClassFieldAccess l) Source # | |
Show l => Pretty (ClassFieldAccess l) Source # | |
type Rep (ClassFieldAccess l) Source # | |
data LambdaSingleParam l Source #
Constructors
LambdaSingleParam | |
Fields |
Instances
HasNode LambdaSingleParam LambdaParamsNode Source # | |
Eq l => Eq (LambdaSingleParam l) Source # | |
Data l => Data (LambdaSingleParam l) Source # | |
Read l => Read (LambdaSingleParam l) Source # | |
Show l => Show (LambdaSingleParam l) Source # | |
Generic (LambdaSingleParam l) Source # | |
Show l => Pretty (LambdaSingleParam l) Source # | |
type Rep (LambdaSingleParam l) Source # | |
data LambdaFormalParams l Source #
Constructors
LambdaFormalParams | |
Fields
|
Instances
HasNode LambdaFormalParams LambdaParamsNode Source # | |
Eq l => Eq (LambdaFormalParams l) Source # | |
Data l => Data (LambdaFormalParams l) Source # | |
Read l => Read (LambdaFormalParams l) Source # | |
Show l => Show (LambdaFormalParams l) Source # | |
Generic (LambdaFormalParams l) Source # | |
Show l => Pretty (LambdaFormalParams l) Source # | |
type Rep (LambdaFormalParams l) Source # | |
data LambdaInferredParams l Source #
Constructors
LambdaInferredParams | |
Fields
|
Instances
HasNode LambdaInferredParams LambdaParamsNode Source # | |
Eq l => Eq (LambdaInferredParams l) Source # | |
Data l => Data (LambdaInferredParams l) Source # | |
Read l => Read (LambdaInferredParams l) Source # | |
Show l => Show (LambdaInferredParams l) Source # | |
Generic (LambdaInferredParams l) Source # | |
Show l => Pretty (LambdaInferredParams l) Source # | |
type Rep (LambdaInferredParams l) Source # | |
data MethodCall l Source #
Invoking a specific named method.
Constructors
MethodCall | |
Fields
|
Instances
HasNode MethodCall MethodInvocationNode Source # | |
Eq l => Eq (MethodCall l) Source # | |
Data l => Data (MethodCall l) Source # | |
Read l => Read (MethodCall l) Source # | |
Show l => Show (MethodCall l) Source # | |
Generic (MethodCall l) Source # | |
Show l => Pretty (MethodCall l) Source # | |
type Rep (MethodCall l) Source # | |
data PrimaryMethodCall l Source #
Invoking a method of a class computed from a primary expression, giving arguments for any generic type parameters.
Constructors
PrimaryMethodCall | |
Fields
|
Instances
HasNode PrimaryMethodCall MethodInvocationNode Source # | |
Eq l => Eq (PrimaryMethodCall l) Source # | |
Data l => Data (PrimaryMethodCall l) Source # | |
Read l => Read (PrimaryMethodCall l) Source # | |
Show l => Show (PrimaryMethodCall l) Source # | |
Generic (PrimaryMethodCall l) Source # | |
Show l => Pretty (PrimaryMethodCall l) Source # | |
type Rep (PrimaryMethodCall l) Source # | |
data SuperMethodCall l Source #
Invoking a method of the super class, giving arguments for any generic type parameters.
Constructors
SuperMethodCall | |
Fields
|
Instances
HasNode SuperMethodCall MethodInvocationNode Source # | |
Eq l => Eq (SuperMethodCall l) Source # | |
Data l => Data (SuperMethodCall l) Source # | |
Read l => Read (SuperMethodCall l) Source # | |
Show l => Show (SuperMethodCall l) Source # | |
Generic (SuperMethodCall l) Source # | |
Show l => Pretty (SuperMethodCall l) Source # | |
type Rep (SuperMethodCall l) Source # | |
data ClassMethodCall l Source #
Invoking a method of the superclass of a named class, giving arguments for any generic type parameters.
Constructors
ClassMethodCall | |
Fields
|
Instances
HasNode ClassMethodCall MethodInvocationNode Source # | |
Eq l => Eq (ClassMethodCall l) Source # | |
Data l => Data (ClassMethodCall l) Source # | |
Read l => Read (ClassMethodCall l) Source # | |
Show l => Show (ClassMethodCall l) Source # | |
Generic (ClassMethodCall l) Source # | |
Show l => Pretty (ClassMethodCall l) Source # | |
type Rep (ClassMethodCall l) Source # | |
data TypeMethodCall l Source #
Invoking a method of a named type, giving arguments for any generic type parameters.
Constructors
TypeMethodCall | |
Fields
|
Instances
HasNode TypeMethodCall MethodInvocationNode Source # | |
Eq l => Eq (TypeMethodCall l) Source # | |
Data l => Data (TypeMethodCall l) Source # | |
Read l => Read (TypeMethodCall l) Source # | |
Show l => Show (TypeMethodCall l) Source # | |
Generic (TypeMethodCall l) Source # | |
Show l => Pretty (TypeMethodCall l) Source # | |
type Rep (TypeMethodCall l) Source # | |
An array initializer may be specified in a declaration, or as part of an array creation expression, creating an array and providing some initial values
Constructors
ArrayInit | |
Fields
|