Safe Haskell | Safe |
---|---|
Language | Haskell98 |
Language.Java.Syntax
Synopsis
- 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] |
Instances
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 |
Instances
Eq TypeDecl Source # | |
Data TypeDecl Source # | |
Defined in Language.Java.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TypeDecl -> c TypeDecl # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TypeDecl # toConstr :: TypeDecl -> Constr # dataTypeOf :: TypeDecl -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TypeDecl) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TypeDecl) # gmapT :: (forall b. Data b => b -> b) -> TypeDecl -> TypeDecl # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TypeDecl -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TypeDecl -> r # gmapQ :: (forall d. Data d => d -> u) -> TypeDecl -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> TypeDecl -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TypeDecl -> m TypeDecl # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TypeDecl -> m TypeDecl # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TypeDecl -> m TypeDecl # | |
Read TypeDecl Source # | |
Show TypeDecl Source # | |
Generic TypeDecl Source # | |
Pretty TypeDecl Source # | |
type Rep TypeDecl Source # | |
Defined in Language.Java.Syntax type Rep TypeDecl = D1 (MetaData "TypeDecl" "Language.Java.Syntax" "language-java-0.2.9-Bljb1EtMqjmG2khI9V9uGm" False) (C1 (MetaCons "ClassTypeDecl" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ClassDecl)) :+: C1 (MetaCons "InterfaceTypeDecl" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 InterfaceDecl))) |
A class declaration specifies a new named reference type.
Constructors
ClassDecl [Modifier] Ident [TypeParam] (Maybe RefType) [RefType] ClassBody | |
EnumDecl [Modifier] Ident [RefType] EnumBody |
Instances
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.
Instances
Eq ClassBody Source # | |
Data ClassBody Source # | |
Defined in Language.Java.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ClassBody -> c ClassBody # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ClassBody # toConstr :: ClassBody -> Constr # dataTypeOf :: ClassBody -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ClassBody) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ClassBody) # gmapT :: (forall b. Data b => b -> b) -> ClassBody -> ClassBody # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ClassBody -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ClassBody -> r # gmapQ :: (forall d. Data d => d -> u) -> ClassBody -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ClassBody -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ClassBody -> m ClassBody # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ClassBody -> m ClassBody # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ClassBody -> m ClassBody # | |
Read ClassBody Source # | |
Show ClassBody Source # | |
Generic ClassBody Source # | |
Pretty ClassBody Source # | |
type Rep ClassBody Source # | |
Defined in Language.Java.Syntax |
The body of an enum type may contain enum constants.
Constructors
EnumBody [EnumConstant] [Decl] |
Instances
Eq EnumBody Source # | |
Data EnumBody Source # | |
Defined in Language.Java.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> EnumBody -> c EnumBody # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c EnumBody # toConstr :: EnumBody -> Constr # dataTypeOf :: EnumBody -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c EnumBody) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c EnumBody) # gmapT :: (forall b. Data b => b -> b) -> EnumBody -> EnumBody # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EnumBody -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EnumBody -> r # gmapQ :: (forall d. Data d => d -> u) -> EnumBody -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> EnumBody -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> EnumBody -> m EnumBody # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EnumBody -> m EnumBody # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EnumBody -> m EnumBody # | |
Read EnumBody Source # | |
Show EnumBody Source # | |
Generic EnumBody Source # | |
Pretty EnumBody Source # | |
type Rep EnumBody Source # | |
Defined in Language.Java.Syntax type Rep EnumBody = D1 (MetaData "EnumBody" "Language.Java.Syntax" "language-java-0.2.9-Bljb1EtMqjmG2khI9V9uGm" False) (C1 (MetaCons "EnumBody" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [EnumConstant]) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [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 |
Instances
newtype InterfaceBody Source #
The body of an interface may declare members of the interface.
Constructors
InterfaceBody [MemberDecl] |
Instances
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 |
Instances
Eq Decl Source # | |
Data Decl Source # | |
Defined in Language.Java.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Decl -> c Decl # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Decl # dataTypeOf :: Decl -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Decl) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Decl) # gmapT :: (forall b. Data b => b -> b) -> Decl -> Decl # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Decl -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Decl -> r # gmapQ :: (forall d. Data d => d -> u) -> Decl -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Decl -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Decl -> m Decl # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Decl -> m Decl # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Decl -> m Decl # | |
Read Decl Source # | |
Show Decl Source # | |
Generic Decl Source # | |
Pretty Decl Source # | |
type Rep Decl Source # | |
Defined in Language.Java.Syntax type Rep Decl = D1 (MetaData "Decl" "Language.Java.Syntax" "language-java-0.2.9-Bljb1EtMqjmG2khI9V9uGm" False) (C1 (MetaCons "MemberDecl" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 MemberDecl)) :+: C1 (MetaCons "InitDecl" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 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.
Instances
Eq VarDecl Source # | |
Data VarDecl Source # | |
Defined in Language.Java.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VarDecl -> c VarDecl # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VarDecl # toConstr :: VarDecl -> Constr # dataTypeOf :: VarDecl -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c VarDecl) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VarDecl) # gmapT :: (forall b. Data b => b -> b) -> VarDecl -> VarDecl # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VarDecl -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VarDecl -> r # gmapQ :: (forall d. Data d => d -> u) -> VarDecl -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> VarDecl -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> VarDecl -> m VarDecl # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VarDecl -> m VarDecl # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VarDecl -> m VarDecl # | |
Read VarDecl Source # | |
Show VarDecl Source # | |
Generic VarDecl Source # | |
Pretty VarDecl Source # | |
type Rep VarDecl Source # | |
Defined in Language.Java.Syntax type Rep VarDecl = D1 (MetaData "VarDecl" "Language.Java.Syntax" "language-java-0.2.9-Bljb1EtMqjmG2khI9V9uGm" False) (C1 (MetaCons "VarDecl" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VarDeclId) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe VarInit)))) |
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 |
Instances
Eq VarDeclId Source # | |
Data VarDeclId Source # | |
Defined in Language.Java.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VarDeclId -> c VarDeclId # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VarDeclId # toConstr :: VarDeclId -> Constr # dataTypeOf :: VarDeclId -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c VarDeclId) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VarDeclId) # gmapT :: (forall b. Data b => b -> b) -> VarDeclId -> VarDeclId # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VarDeclId -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VarDeclId -> r # gmapQ :: (forall d. Data d => d -> u) -> VarDeclId -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> VarDeclId -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> VarDeclId -> m VarDeclId # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VarDeclId -> m VarDeclId # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VarDeclId -> m VarDeclId # | |
Read VarDeclId Source # | |
Show VarDeclId Source # | |
Generic VarDeclId Source # | |
Pretty VarDeclId Source # | |
type Rep VarDeclId Source # | |
Defined in Language.Java.Syntax type Rep VarDeclId = D1 (MetaData "VarDeclId" "Language.Java.Syntax" "language-java-0.2.9-Bljb1EtMqjmG2khI9V9uGm" False) (C1 (MetaCons "VarId" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Ident)) :+: C1 (MetaCons "VarDeclArray" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VarDeclId))) |
Explicit initializer for a variable declaration.
Instances
Eq VarInit Source # | |
Data VarInit Source # | |
Defined in Language.Java.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VarInit -> c VarInit # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VarInit # toConstr :: VarInit -> Constr # dataTypeOf :: VarInit -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c VarInit) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VarInit) # gmapT :: (forall b. Data b => b -> b) -> VarInit -> VarInit # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VarInit -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VarInit -> r # gmapQ :: (forall d. Data d => d -> u) -> VarInit -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> VarInit -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> VarInit -> m VarInit # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VarInit -> m VarInit # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VarInit -> m VarInit # | |
Read VarInit Source # | |
Show VarInit Source # | |
Generic VarInit Source # | |
Pretty VarInit Source # | |
type Rep VarInit Source # | |
Defined in Language.Java.Syntax type Rep VarInit = D1 (MetaData "VarInit" "Language.Java.Syntax" "language-java-0.2.9-Bljb1EtMqjmG2khI9V9uGm" False) (C1 (MetaCons "InitExp" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp)) :+: C1 (MetaCons "InitArray" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ArrayInit))) |
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] |
Instances
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] |
Instances
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 | |
Private | |
Protected | |
Abstract | |
Final | |
Static | |
StrictFP | |
Transient | |
Volatile | |
Native | |
Annotation Annotation | |
Synchronized_ |
Instances
Eq Modifier Source # | |
Data Modifier Source # | |
Defined in Language.Java.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Modifier -> c Modifier # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Modifier # toConstr :: Modifier -> Constr # dataTypeOf :: Modifier -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Modifier) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Modifier) # gmapT :: (forall b. Data b => b -> b) -> Modifier -> Modifier # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Modifier -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Modifier -> r # gmapQ :: (forall d. Data d => d -> u) -> Modifier -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Modifier -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Modifier -> m Modifier # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Modifier -> m Modifier # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Modifier -> m Modifier # | |
Read Modifier Source # | |
Show Modifier Source # | |
Generic Modifier Source # | |
Pretty Modifier Source # | |
type Rep Modifier Source # | |
Defined in Language.Java.Syntax type Rep Modifier = D1 (MetaData "Modifier" "Language.Java.Syntax" "language-java-0.2.9-Bljb1EtMqjmG2khI9V9uGm" False) (((C1 (MetaCons "Public" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "Private" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Protected" PrefixI False) (U1 :: * -> *))) :+: (C1 (MetaCons "Abstract" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "Final" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Static" PrefixI False) (U1 :: * -> *)))) :+: ((C1 (MetaCons "StrictFP" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "Transient" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Volatile" PrefixI False) (U1 :: * -> *))) :+: (C1 (MetaCons "Native" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "Annotation" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Annotation)) :+: C1 (MetaCons "Synchronized_" PrefixI False) (U1 :: * -> *))))) |
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.
Instances
Eq Block Source # | |
Data Block Source # | |
Defined in Language.Java.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Block -> c Block # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Block # dataTypeOf :: Block -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Block) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Block) # gmapT :: (forall b. Data b => b -> b) -> Block -> Block # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Block -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Block -> r # gmapQ :: (forall d. Data d => d -> u) -> Block -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Block -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Block -> m Block # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Block -> m Block # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Block -> m Block # | |
Read Block Source # | |
Show Block Source # | |
Generic Block Source # | |
Pretty Block Source # | |
type Rep Block Source # | |
Defined in Language.Java.Syntax |
A block statement is either a normal statement, a local class declaration or a local variable declaration.
Instances
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. |
Instances
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 |
Instances
Eq Catch Source # | |
Data Catch Source # | |
Defined in Language.Java.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Catch -> c Catch # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Catch # dataTypeOf :: Catch -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Catch) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Catch) # gmapT :: (forall b. Data b => b -> b) -> Catch -> Catch # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Catch -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Catch -> r # gmapQ :: (forall d. Data d => d -> u) -> Catch -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Catch -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Catch -> m Catch # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Catch -> m Catch # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Catch -> m Catch # | |
Read Catch Source # | |
Show Catch Source # | |
Generic Catch Source # | |
Pretty Catch Source # | |
type Rep Catch Source # | |
Defined in Language.Java.Syntax type Rep Catch = D1 (MetaData "Catch" "Language.Java.Syntax" "language-java-0.2.9-Bljb1EtMqjmG2khI9V9uGm" False) (C1 (MetaCons "Catch" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FormalParam) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 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] |
Instances
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 |
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
NameLhs Name | Assign to a variable |
FieldLhs FieldAccess | Assign through a field access |
ArrayLhs ArrayIndex | Assign to an array |
Instances
Eq Lhs Source # | |
Data Lhs Source # | |
Defined in Language.Java.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Lhs -> c Lhs # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Lhs # dataTypeOf :: Lhs -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Lhs) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Lhs) # gmapT :: (forall b. Data b => b -> b) -> Lhs -> Lhs # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Lhs -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Lhs -> r # gmapQ :: (forall d. Data d => d -> u) -> Lhs -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Lhs -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Lhs -> m Lhs # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Lhs -> m Lhs # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Lhs -> m Lhs # | |
Read Lhs Source # | |
Show Lhs Source # | |
Generic Lhs Source # | |
Pretty Lhs Source # | |
type Rep Lhs Source # | |
Defined in Language.Java.Syntax type Rep Lhs = D1 (MetaData "Lhs" "Language.Java.Syntax" "language-java-0.2.9-Bljb1EtMqjmG2khI9V9uGm" False) (C1 (MetaCons "NameLhs" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Name)) :+: (C1 (MetaCons "FieldLhs" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FieldAccess)) :+: C1 (MetaCons "ArrayLhs" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ArrayIndex)))) |
data ArrayIndex Source #
Array access
Constructors
ArrayIndex Exp [Exp] | Index into an array |
Instances
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 |
Instances
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
Instances
Eq ArrayInit Source # | |
Data ArrayInit Source # | |
Defined in Language.Java.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ArrayInit -> c ArrayInit # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ArrayInit # toConstr :: ArrayInit -> Constr # dataTypeOf :: ArrayInit -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ArrayInit) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ArrayInit) # gmapT :: (forall b. Data b => b -> b) -> ArrayInit -> ArrayInit # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ArrayInit -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ArrayInit -> r # gmapQ :: (forall d. Data d => d -> u) -> ArrayInit -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ArrayInit -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ArrayInit -> m ArrayInit # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ArrayInit -> m ArrayInit # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ArrayInit -> m ArrayInit # | |
Read ArrayInit Source # | |
Show ArrayInit Source # | |
Generic ArrayInit Source # | |
Pretty ArrayInit Source # | |
type Rep ArrayInit Source # | |
Defined in Language.Java.Syntax |
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. |
Instances
A literal denotes a fixed, unchanging value.
Constructors
Int Integer | |
Word Integer | |
Float Double | |
Double Double | |
Boolean Bool | |
Char Char | |
String String | |
Null |
Instances
A binary infix operator.
Constructors
Mult | |
Div | |
Rem | |
Add | |
Sub | |
LShift | |
RShift | |
RRShift | |
LThan | |
GThan | |
LThanE | |
GThanE | |
Equal | |
NotEq | |
And | |
Or | |
Xor | |
CAnd | |
COr |
Instances
Eq Op Source # | |
Data Op Source # | |
Defined in Language.Java.Syntax.Exp Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Op -> c Op # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Op # dataTypeOf :: Op -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Op) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Op) # gmapT :: (forall b. Data b => b -> b) -> Op -> Op # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Op -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Op -> r # gmapQ :: (forall d. Data d => d -> u) -> Op -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Op -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Op -> m Op # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Op -> m Op # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Op -> m Op # | |
Read Op Source # | |
Show Op Source # | |
Generic Op Source # | |
Pretty Op Source # | |
type Rep Op Source # | |
Defined in Language.Java.Syntax.Exp type Rep Op = D1 (MetaData "Op" "Language.Java.Syntax.Exp" "language-java-0.2.9-Bljb1EtMqjmG2khI9V9uGm" False) ((((C1 (MetaCons "Mult" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Div" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "Rem" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Add" PrefixI False) (U1 :: * -> *))) :+: ((C1 (MetaCons "Sub" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "LShift" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "RShift" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "RRShift" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "LThan" PrefixI False) (U1 :: * -> *))))) :+: (((C1 (MetaCons "GThan" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "LThanE" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "GThanE" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "Equal" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "NotEq" PrefixI False) (U1 :: * -> *)))) :+: ((C1 (MetaCons "And" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Or" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "Xor" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "CAnd" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "COr" PrefixI False) (U1 :: * -> *)))))) |
An assignment operator.
Instances
Eq AssignOp Source # | |
Data AssignOp Source # | |
Defined in Language.Java.Syntax.Exp Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AssignOp -> c AssignOp # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AssignOp # toConstr :: AssignOp -> Constr # dataTypeOf :: AssignOp -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c AssignOp) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AssignOp) # gmapT :: (forall b. Data b => b -> b) -> AssignOp -> AssignOp # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AssignOp -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AssignOp -> r # gmapQ :: (forall d. Data d => d -> u) -> AssignOp -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> AssignOp -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> AssignOp -> m AssignOp # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AssignOp -> m AssignOp # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AssignOp -> m AssignOp # | |
Read AssignOp Source # | |
Show AssignOp Source # | |
Generic AssignOp Source # | |
Pretty AssignOp Source # | |
type Rep AssignOp Source # | |
Defined in Language.Java.Syntax.Exp type Rep AssignOp = D1 (MetaData "AssignOp" "Language.Java.Syntax.Exp" "language-java-0.2.9-Bljb1EtMqjmG2khI9V9uGm" False) (((C1 (MetaCons "EqualA" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "MultA" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "DivA" PrefixI False) (U1 :: * -> *))) :+: (C1 (MetaCons "RemA" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "AddA" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "SubA" PrefixI False) (U1 :: * -> *)))) :+: ((C1 (MetaCons "LShiftA" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "RShiftA" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "RRShiftA" PrefixI False) (U1 :: * -> *))) :+: (C1 (MetaCons "AndA" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "XorA" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "OrA" PrefixI False) (U1 :: * -> *))))) |
There are two kinds of types in the Java programming language: primitive types and reference types.
Instances
Eq Type Source # | |
Data Type Source # | |
Defined in Language.Java.Syntax.Types Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Type -> c Type # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Type # dataTypeOf :: Type -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Type) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Type) # gmapT :: (forall b. Data b => b -> b) -> Type -> Type # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Type -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Type -> r # gmapQ :: (forall d. Data d => d -> u) -> Type -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Type -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Type -> m Type # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Type -> m Type # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Type -> m Type # | |
Read Type Source # | |
Show Type Source # | |
Generic Type Source # | |
Pretty Type Source # | |
type Rep Type Source # | |
Defined in Language.Java.Syntax.Types type Rep Type = D1 (MetaData "Type" "Language.Java.Syntax.Types" "language-java-0.2.9-Bljb1EtMqjmG2khI9V9uGm" False) (C1 (MetaCons "PrimType" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PrimType)) :+: C1 (MetaCons "RefType" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 RefType))) |
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 |
Instances
Eq RefType Source # | |
Data RefType Source # | |
Defined in Language.Java.Syntax.Types Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RefType -> c RefType # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RefType # toConstr :: RefType -> Constr # dataTypeOf :: RefType -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c RefType) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RefType) # gmapT :: (forall b. Data b => b -> b) -> RefType -> RefType # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RefType -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RefType -> r # gmapQ :: (forall d. Data d => d -> u) -> RefType -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> RefType -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> RefType -> m RefType # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RefType -> m RefType # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RefType -> m RefType # | |
Read RefType Source # | |
Show RefType Source # | |
Generic RefType Source # | |
Pretty RefType Source # | |
type Rep RefType Source # | |
Defined in Language.Java.Syntax.Types type Rep RefType = D1 (MetaData "RefType" "Language.Java.Syntax.Types" "language-java-0.2.9-Bljb1EtMqjmG2khI9V9uGm" False) (C1 (MetaCons "ClassRefType" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ClassType)) :+: C1 (MetaCons "ArrayType" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Type))) |
A class or interface type consists of a type declaration specifier, optionally followed by type arguments (in which case it is a parameterized type).
Constructors
ClassType [(Ident, [TypeArgument])] |
Instances
Eq ClassType Source # | |
Data ClassType Source # | |
Defined in Language.Java.Syntax.Types Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ClassType -> c ClassType # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ClassType # toConstr :: ClassType -> Constr # dataTypeOf :: ClassType -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ClassType) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ClassType) # gmapT :: (forall b. Data b => b -> b) -> ClassType -> ClassType # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ClassType -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ClassType -> r # gmapQ :: (forall d. Data d => d -> u) -> ClassType -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ClassType -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ClassType -> m ClassType # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ClassType -> m ClassType # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ClassType -> m ClassType # | |
Read ClassType Source # | |
Show ClassType Source # | |
Generic ClassType Source # | |
Pretty ClassType Source # | |
type Rep ClassType Source # | |
Defined in Language.Java.Syntax.Types type Rep ClassType = D1 (MetaData "ClassType" "Language.Java.Syntax.Types" "language-java-0.2.9-Bljb1EtMqjmG2khI9V9uGm" False) (C1 (MetaCons "ClassType" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [(Ident, [TypeArgument])]))) |
data TypeArgument Source #
Type arguments may be either reference types or wildcards.
Constructors
Wildcard (Maybe WildcardBound) | |
ActualType RefType |
Instances
data TypeDeclSpecifier Source #
Constructors
TypeDeclSpecifier ClassType | |
TypeDeclSpecifierWithDiamond ClassType Ident Diamond | |
TypeDeclSpecifierUnqualifiedWithDiamond Ident Diamond |
Instances
Constructors
Diamond |
Instances
Eq Diamond Source # | |
Data Diamond Source # | |
Defined in Language.Java.Syntax.Types Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Diamond -> c Diamond # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Diamond # toConstr :: Diamond -> Constr # dataTypeOf :: Diamond -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Diamond) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Diamond) # gmapT :: (forall b. Data b => b -> b) -> Diamond -> Diamond # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Diamond -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Diamond -> r # gmapQ :: (forall d. Data d => d -> u) -> Diamond -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Diamond -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Diamond -> m Diamond # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Diamond -> m Diamond # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Diamond -> m Diamond # | |
Read Diamond Source # | |
Show Diamond Source # | |
Generic Diamond Source # | |
Pretty Diamond Source # | |
type Rep Diamond Source # | |
data WildcardBound Source #
Wildcards may be given explicit bounds, either upper (extends
) or lower (super
) bounds.
Constructors
ExtendsBound RefType | |
SuperBound RefType |
Instances
A primitive type is predefined by the Java programming language and named by its reserved keyword.
Instances
Eq PrimType Source # | |
Data PrimType Source # | |
Defined in Language.Java.Syntax.Types Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PrimType -> c PrimType # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PrimType # toConstr :: PrimType -> Constr # dataTypeOf :: PrimType -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c PrimType) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PrimType) # gmapT :: (forall b. Data b => b -> b) -> PrimType -> PrimType # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PrimType -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PrimType -> r # gmapQ :: (forall d. Data d => d -> u) -> PrimType -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> PrimType -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> PrimType -> m PrimType # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PrimType -> m PrimType # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PrimType -> m PrimType # | |
Read PrimType Source # | |
Show PrimType Source # | |
Generic PrimType Source # | |
Pretty PrimType Source # | |
type Rep PrimType Source # | |
Defined in Language.Java.Syntax.Types type Rep PrimType = D1 (MetaData "PrimType" "Language.Java.Syntax.Types" "language-java-0.2.9-Bljb1EtMqjmG2khI9V9uGm" False) (((C1 (MetaCons "BooleanT" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "ByteT" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "ShortT" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "IntT" PrefixI False) (U1 :: * -> *))) :+: ((C1 (MetaCons "LongT" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "CharT" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "FloatT" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "DoubleT" PrefixI False) (U1 :: * -> *)))) |
A class is generic if it declares one or more type variables. These type variables are known as the type parameters of the class.
Instances
Eq TypeParam Source # | |
Data TypeParam Source # | |
Defined in Language.Java.Syntax.Types Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TypeParam -> c TypeParam # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TypeParam # toConstr :: TypeParam -> Constr # dataTypeOf :: TypeParam -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TypeParam) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TypeParam) # gmapT :: (forall b. Data b => b -> b) -> TypeParam -> TypeParam # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TypeParam -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TypeParam -> r # gmapQ :: (forall d. Data d => d -> u) -> TypeParam -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> TypeParam -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TypeParam -> m TypeParam # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TypeParam -> m TypeParam # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TypeParam -> m TypeParam # | |
Read TypeParam Source # | |
Show TypeParam Source # | |
Generic TypeParam Source # | |
Pretty TypeParam Source # | |
type Rep TypeParam Source # | |
Defined in Language.Java.Syntax.Types type Rep TypeParam = D1 (MetaData "TypeParam" "Language.Java.Syntax.Types" "language-java-0.2.9-Bljb1EtMqjmG2khI9V9uGm" False) (C1 (MetaCons "TypeParam" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Ident) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [RefType]))) |
A single identifier.
Instances
Eq Ident Source # | |
Data Ident Source # | |
Defined in Language.Java.Syntax.Types Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Ident -> c Ident # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Ident # dataTypeOf :: Ident -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Ident) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Ident) # gmapT :: (forall b. Data b => b -> b) -> Ident -> Ident # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Ident -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Ident -> r # gmapQ :: (forall d. Data d => d -> u) -> Ident -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Ident -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Ident -> m Ident # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Ident -> m Ident # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Ident -> m Ident # | |
Ord Ident Source # | |
Read Ident Source # | |
Show Ident Source # | |
Generic Ident Source # | |
Pretty Ident Source # | |
type Rep Ident Source # | |
Defined in Language.Java.Syntax.Types |
A name, i.e. a period-separated list of identifiers.
Instances
Eq Name Source # | |
Data Name Source # | |
Defined in Language.Java.Syntax.Types Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Name -> c Name # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Name # dataTypeOf :: Name -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Name) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Name) # gmapT :: (forall b. Data b => b -> b) -> Name -> Name # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Name -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Name -> r # gmapQ :: (forall d. Data d => d -> u) -> Name -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Name -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Name -> m Name # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Name -> m Name # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Name -> m Name # | |
Ord Name Source # | |
Read Name Source # | |
Show Name Source # | |
Generic Name Source # | |
Pretty Name Source # | |
type Rep Name Source # | |
Defined in Language.Java.Syntax.Types |