Safe Haskell | Safe |
---|---|
Language | Haskell98 |
Language.Java.Syntax
- data CompilationUnit = CompilationUnit (Maybe PackageDecl) [ImportDecl] [TypeDecl]
- newtype PackageDecl = PackageDecl Name
- data ImportDecl = ImportDecl Bool Name Bool
- data TypeDecl
- data ClassDecl
- newtype ClassBody = ClassBody [Decl]
- data EnumBody = EnumBody [EnumConstant] [Decl]
- data EnumConstant = EnumConstant Ident [Argument] (Maybe ClassBody)
- data InterfaceDecl = InterfaceDecl InterfaceKind [Modifier] Ident [TypeParam] [RefType] InterfaceBody
- newtype InterfaceBody = InterfaceBody [MemberDecl]
- data InterfaceKind
- data Decl
- data MemberDecl
- data VarDecl = VarDecl VarDeclId (Maybe VarInit)
- data VarDeclId
- data VarInit
- data FormalParam = FormalParam [Modifier] Type Bool VarDeclId
- newtype MethodBody = MethodBody (Maybe Block)
- data ConstructorBody = ConstructorBody (Maybe ExplConstrInv) [BlockStmt]
- data ExplConstrInv
- = ThisInvoke [RefType] [Argument]
- | SuperInvoke [RefType] [Argument]
- | PrimarySuperInvoke Exp [RefType] [Argument]
- data Modifier
- data Annotation
- = NormalAnnotation {
- annName :: Name
- annKV :: [(Ident, ElementValue)]
- | SingleElementAnnotation {
- annName :: Name
- annValue :: ElementValue
- | MarkerAnnotation { }
- = NormalAnnotation {
- desugarAnnotation :: Annotation -> (Name, [(Ident, ElementValue)])
- desugarAnnotation' :: Annotation -> Annotation
- data ElementValue
- data Block = Block [BlockStmt]
- data BlockStmt
- data Stmt
- = StmtBlock Block
- | IfThen Exp Stmt
- | IfThenElse Exp Stmt Stmt
- | While Exp Stmt
- | BasicFor (Maybe ForInit) (Maybe Exp) (Maybe [Exp]) Stmt
- | EnhancedFor [Modifier] Type Ident Exp Stmt
- | Empty
- | ExpStmt Exp
- | Assert Exp (Maybe Exp)
- | Switch Exp [SwitchBlock]
- | Do Stmt Exp
- | Break (Maybe Ident)
- | Continue (Maybe Ident)
- | Return (Maybe Exp)
- | Synchronized Exp Block
- | Throw Exp
- | Try Block [Catch] (Maybe Block)
- | Labeled Ident Stmt
- data Catch = Catch FormalParam Block
- data SwitchBlock = SwitchBlock SwitchLabel [BlockStmt]
- data SwitchLabel
- = SwitchCase Exp
- | Default
- data ForInit
- = ForLocalVars [Modifier] Type [VarDecl]
- | ForInitExps [Exp]
- type ExceptionType = RefType
- type Argument = Exp
- data Exp
- = Lit Literal
- | ClassLit (Maybe Type)
- | This
- | ThisClass Name
- | InstanceCreation [TypeArgument] TypeDeclSpecifier [Argument] (Maybe ClassBody)
- | QualInstanceCreation Exp [TypeArgument] Ident [Argument] (Maybe ClassBody)
- | ArrayCreate Type [Exp] Int
- | ArrayCreateInit Type Int ArrayInit
- | FieldAccess FieldAccess
- | MethodInv MethodInvocation
- | ArrayAccess ArrayIndex
- | ExpName Name
- | PostIncrement Exp
- | PostDecrement Exp
- | PreIncrement Exp
- | PreDecrement Exp
- | PrePlus Exp
- | PreMinus Exp
- | PreBitCompl Exp
- | PreNot Exp
- | Cast Type Exp
- | BinOp Exp Op Exp
- | InstanceOf Exp RefType
- | Cond Exp Exp Exp
- | Assign Lhs AssignOp Exp
- | Lambda LambdaParams LambdaExpression
- | MethodRef Name Ident
- data Lhs
- data ArrayIndex = ArrayIndex Exp [Exp]
- data FieldAccess
- data LambdaParams
- data LambdaExpression
- data ArrayInit = ArrayInit [VarInit]
- data MethodInvocation
- = MethodCall Name [Argument]
- | PrimaryMethodCall Exp [RefType] Ident [Argument]
- | SuperMethodCall [RefType] Ident [Argument]
- | ClassMethodCall Name [RefType] Ident [Argument]
- | TypeMethodCall Name [RefType] Ident [Argument]
- data Literal
- data Op
- data AssignOp
- data Type
- data RefType
- data ClassType = ClassType [(Ident, [TypeArgument])]
- data TypeArgument
- data TypeDeclSpecifier
- data Diamond = Diamond
- data WildcardBound
- data PrimType
- data TypeParam = TypeParam Ident [RefType]
- data Ident = Ident String
- data Name = Name [Ident]
Documentation
data CompilationUnit Source #
A compilation unit is the top level syntactic goal symbol of a Java program.
Constructors
CompilationUnit (Maybe PackageDecl) [ImportDecl] [TypeDecl] |
newtype PackageDecl Source #
A package declaration appears within a compilation unit to indicate the package to which the compilation unit belongs.
Constructors
PackageDecl Name |
Instances
data ImportDecl 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 Bool Name Bool |
Instances
A type declaration declares a class type or an interface type.
Constructors
ClassTypeDecl ClassDecl | |
InterfaceTypeDecl InterfaceDecl |
A class declaration specifies a new named reference type.
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.
The body of an enum type may contain enum constants.
Constructors
EnumBody [EnumConstant] [Decl] |
data EnumConstant Source #
An enum constant defines an instance of the enum type.
Constructors
EnumConstant Ident [Argument] (Maybe ClassBody) |
Instances
data InterfaceDecl 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 InterfaceKind [Modifier] Ident [TypeParam] [RefType] InterfaceBody |
newtype InterfaceBody Source #
The body of an interface may declare members of the interface.
Constructors
InterfaceBody [MemberDecl] |
data InterfaceKind Source #
Interface can declare either a normal interface or an annotation
Constructors
InterfaceNormal | |
InterfaceAnnotation |
Instances
A declaration is either a member declaration, or a declaration of an initializer, which may be static.
Constructors
MemberDecl MemberDecl | |
InitDecl Bool Block |
data MemberDecl 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
FieldDecl [Modifier] Type [VarDecl] | The variables of a class type are introduced by field declarations. |
MethodDecl [Modifier] [TypeParam] (Maybe Type) Ident [FormalParam] [ExceptionType] (Maybe Exp) MethodBody | A method declares executable code that can be invoked, passing a fixed number of values as arguments. |
ConstructorDecl [Modifier] [TypeParam] Ident [FormalParam] [ExceptionType] ConstructorBody | A constructor is used in the creation of an object that is an instance of a class. |
MemberClassDecl ClassDecl | A member class is a class whose declaration is directly enclosed in another class or interface declaration. |
MemberInterfaceDecl InterfaceDecl | A member interface is an interface whose declaration is directly enclosed in another class or interface declaration. |
Instances
A declaration of a variable, which may be explicitly initialized.
The name of a variable in a declaration, which may be an array.
Constructors
VarId Ident | |
VarDeclArray VarDeclId | Multi-dimensional arrays are represented by nested applications of |
Explicit initializer for a variable declaration.
data FormalParam 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 [Modifier] Type Bool VarDeclId |
Instances
newtype MethodBody 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 (Maybe Block) |
Instances
data ConstructorBody 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 (Maybe ExplConstrInv) [BlockStmt] |
data ExplConstrInv 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 [RefType] [Argument] | |
SuperInvoke [RefType] [Argument] | |
PrimarySuperInvoke Exp [RefType] [Argument] |
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.
data Annotation Source #
Annotations have three different forms: no-parameter, single-parameter or key-value pairs
Constructors
NormalAnnotation | |
Fields
| |
SingleElementAnnotation | |
Fields
| |
MarkerAnnotation | |
Instances
desugarAnnotation :: Annotation -> (Name, [(Ident, ElementValue)]) Source #
data ElementValue Source #
Annotations may contain annotations or (loosely) expressions
Constructors
EVVal VarInit | |
EVAnn Annotation |
Instances
A block is a sequence of statements, local class declarations and local variable declaration statements within braces.
A block statement is either a normal statement, a local class declaration or a local variable declaration.
A Java statement.
Constructors
StmtBlock Block | A statement can be a nested block. |
IfThen Exp Stmt | The |
IfThenElse Exp Stmt Stmt | The |
While Exp Stmt | The |
BasicFor (Maybe ForInit) (Maybe Exp) (Maybe [Exp]) Stmt | The basic |
EnhancedFor [Modifier] Type Ident Exp Stmt | The enhanced |
Empty | An empty statement does nothing. |
ExpStmt Exp | 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. |
Assert Exp (Maybe Exp) | An assertion is a statement containing a boolean expression, where an error is reported if the expression evaluates to false. |
Switch Exp [SwitchBlock] | The switch statement transfers control to one of several statements depending on the value of an expression. |
Do Stmt Exp | The |
Break (Maybe Ident) | A |
Continue (Maybe Ident) | A |
Return (Maybe Exp) | |
Synchronized Exp Block | A |
Throw Exp | A |
Try Block [Catch] (Maybe Block) | 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. |
Labeled Ident Stmt | Statements may have label prefixes. |
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 FormalParam Block |
data SwitchBlock Source #
A block of code labelled with a case
or default
within a switch
statement.
Constructors
SwitchBlock SwitchLabel [BlockStmt] |
Instances
data SwitchLabel Source #
A label within a switch
statement.
Constructors
SwitchCase Exp | The expression contained in the |
Default |
Instances
Initialization code for a basic for
statement.
Constructors
ForLocalVars [Modifier] Type [VarDecl] | |
ForInitExps [Exp] |
type ExceptionType = RefType Source #
An exception type has to be a class type or a type variable.
A Java expression.
Constructors
Lit Literal | A literal denotes a fixed, unchanging value. |
ClassLit (Maybe Type) | 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 |
This | The keyword |
ThisClass Name | Any lexically enclosing instance can be referred to by explicitly qualifying the keyword this. |
InstanceCreation [TypeArgument] TypeDeclSpecifier [Argument] (Maybe ClassBody) | 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. |
QualInstanceCreation Exp [TypeArgument] Ident [Argument] (Maybe ClassBody) | A qualified class instance creation expression enables the creation of instances of inner member classes and their anonymous subclasses. |
ArrayCreate Type [Exp] Int | 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. |
ArrayCreateInit Type Int ArrayInit | An array instance creation expression may come with an explicit initializer. Such expressions may not be given explicit lengths for any of its dimensions. |
FieldAccess FieldAccess | A field access expression. |
MethodInv MethodInvocation | A method invocation expression. |
ArrayAccess ArrayIndex | An array access expression refers to a variable that is a component of an array. |
ExpName Name | An expression name, e.g. a variable. |
PostIncrement Exp | Post-incrementation expression, i.e. an expression followed by |
PostDecrement Exp | Post-decrementation expression, i.e. an expression followed by |
PreIncrement Exp | Pre-incrementation expression, i.e. an expression preceded by |
PreDecrement Exp | Pre-decrementation expression, i.e. an expression preceded by |
PrePlus Exp | Unary plus, the promotion of the value of the expression to a primitive numeric type. |
PreMinus Exp | Unary minus, the promotion of the negation of the value of the expression to a primitive numeric type. |
PreBitCompl Exp | Unary bitwise complementation: note that, in all cases, |
PreNot Exp | Logical complementation of boolean values. |
Cast Type Exp | 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. |
BinOp Exp Op Exp | The application of a binary operator to two operand expressions. |
InstanceOf Exp RefType | Testing whether the result of an expression is an instance of some reference type. |
Cond Exp Exp Exp | The conditional operator |
Assign Lhs AssignOp Exp | Assignment of the result of an expression to a variable. |
Lambda LambdaParams LambdaExpression | Lambda expression |
MethodRef Name Ident | Method reference |
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
NameLhs Name | Assign to a variable |
FieldLhs FieldAccess | Assign through a field access |
ArrayLhs ArrayIndex | Assign to an array |
data FieldAccess 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
PrimaryFieldAccess Exp Ident | Accessing a field of an object or array computed from an expression. |
SuperFieldAccess Ident | Accessing a field of the superclass. |
ClassFieldAccess Name Ident | Accessing a (static) field of a named class. |
Instances
data LambdaParams Source #
Constructors
LambdaSingleParam Ident | |
LambdaFormalParams [FormalParam] | |
LambdaInferredParams [Ident] |
Instances
data LambdaExpression Source #
Lambda expression, starting from java 8
Constructors
LambdaExpression Exp | |
LambdaBlock Block |
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
data MethodInvocation Source #
A method invocation expression is used to invoke a class or instance method.
Constructors
MethodCall Name [Argument] | Invoking a specific named method. |
PrimaryMethodCall Exp [RefType] Ident [Argument] | Invoking a method of a class computed from a primary expression, giving arguments for any generic type parameters. |
SuperMethodCall [RefType] Ident [Argument] | Invoking a method of the super class, giving arguments for any generic type parameters. |
ClassMethodCall Name [RefType] Ident [Argument] | Invoking a method of the superclass of a named class, giving arguments for any generic type parameters. |
TypeMethodCall Name [RefType] Ident [Argument] | Invoking a method of a named type, giving arguments for any generic type parameters. |
A literal denotes a fixed, unchanging value.
A binary infix operator.
An assignment operator.
There are two kinds of types in the Java programming language: primitive types and reference types.
There are three kinds of reference types: class types, interface types, and array types. Reference types may be parameterized with type arguments. Type variables cannot be syntactically distinguished from class type identifiers, and are thus represented uniformly as single ident class types.
Constructors
ClassRefType ClassType | |
ArrayType Type | TypeVariable Ident |