Safe Haskell | Safe-Inferred |
---|---|
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 Ident = Ident String
- data Name = Name [Ident]
- data PrimType
- data RefType
- data ClassType = ClassType [(Ident, [TypeArgument])]
- data TypeArgument
- data WildcardBound
- data TypeDeclSpecifier
- data Diamond = Diamond
- data TypeParam = TypeParam Ident [RefType]
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 PackageDecl Source # | |||||
Defined in Language.Java.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PackageDecl -> c PackageDecl # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PackageDecl # toConstr :: PackageDecl -> Constr # dataTypeOf :: PackageDecl -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c PackageDecl) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PackageDecl) # gmapT :: (forall b. Data b => b -> b) -> PackageDecl -> PackageDecl # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PackageDecl -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PackageDecl -> r # gmapQ :: (forall d. Data d => d -> u) -> PackageDecl -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> PackageDecl -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> PackageDecl -> m PackageDecl # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PackageDecl -> m PackageDecl # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PackageDecl -> m PackageDecl # | |||||
Generic PackageDecl Source # | |||||
Defined in Language.Java.Syntax Associated Types
| |||||
Read PackageDecl Source # | |||||
Defined in Language.Java.Syntax Methods readsPrec :: Int -> ReadS PackageDecl # readList :: ReadS [PackageDecl] # readPrec :: ReadPrec PackageDecl # readListPrec :: ReadPrec [PackageDecl] # | |||||
Show PackageDecl Source # | |||||
Defined in Language.Java.Syntax Methods showsPrec :: Int -> PackageDecl -> ShowS # show :: PackageDecl -> String # showList :: [PackageDecl] -> ShowS # | |||||
Eq PackageDecl Source # | |||||
Defined in Language.Java.Syntax | |||||
Pretty PackageDecl Source # | |||||
Defined in Language.Java.Pretty | |||||
type Rep PackageDecl Source # | |||||
Defined in Language.Java.Syntax type Rep PackageDecl = D1 ('MetaData "PackageDecl" "Language.Java.Syntax" "language-java-0.2.9-6oreAEG1ght3zZkJEpyPXU" 'True) (C1 ('MetaCons "PackageDecl" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name))) |
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
Data ImportDecl Source # | |||||
Defined in Language.Java.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ImportDecl -> c ImportDecl # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ImportDecl # toConstr :: ImportDecl -> Constr # dataTypeOf :: ImportDecl -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ImportDecl) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ImportDecl) # gmapT :: (forall b. Data b => b -> b) -> ImportDecl -> ImportDecl # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ImportDecl -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ImportDecl -> r # gmapQ :: (forall d. Data d => d -> u) -> ImportDecl -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ImportDecl -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ImportDecl -> m ImportDecl # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ImportDecl -> m ImportDecl # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ImportDecl -> m ImportDecl # | |||||
Generic ImportDecl Source # | |||||
Defined in Language.Java.Syntax Associated Types
| |||||
Read ImportDecl Source # | |||||
Defined in Language.Java.Syntax Methods readsPrec :: Int -> ReadS ImportDecl # readList :: ReadS [ImportDecl] # readPrec :: ReadPrec ImportDecl # readListPrec :: ReadPrec [ImportDecl] # | |||||
Show ImportDecl Source # | |||||
Defined in Language.Java.Syntax Methods showsPrec :: Int -> ImportDecl -> ShowS # show :: ImportDecl -> String # showList :: [ImportDecl] -> ShowS # | |||||
Eq ImportDecl Source # | |||||
Defined in Language.Java.Syntax | |||||
Pretty ImportDecl Source # | |||||
Defined in Language.Java.Pretty | |||||
type Rep ImportDecl Source # | |||||
Defined in Language.Java.Syntax type Rep ImportDecl = D1 ('MetaData "ImportDecl" "Language.Java.Syntax" "language-java-0.2.9-6oreAEG1ght3zZkJEpyPXU" 'False) (C1 ('MetaCons "ImportDecl" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))) |
A type declaration declares a class type or an interface type.
Constructors
ClassTypeDecl ClassDecl | |
InterfaceTypeDecl InterfaceDecl |
Instances
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 :: forall r r'. (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 # | |||||
Generic TypeDecl Source # | |||||
Defined in Language.Java.Syntax Associated Types
| |||||
Read TypeDecl Source # | |||||
Show TypeDecl Source # | |||||
Eq 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-6oreAEG1ght3zZkJEpyPXU" '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
Data ClassDecl Source # | |||||
Defined in Language.Java.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ClassDecl -> c ClassDecl # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ClassDecl # toConstr :: ClassDecl -> Constr # dataTypeOf :: ClassDecl -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ClassDecl) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ClassDecl) # gmapT :: (forall b. Data b => b -> b) -> ClassDecl -> ClassDecl # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ClassDecl -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ClassDecl -> r # gmapQ :: (forall d. Data d => d -> u) -> ClassDecl -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ClassDecl -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ClassDecl -> m ClassDecl # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ClassDecl -> m ClassDecl # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ClassDecl -> m ClassDecl # | |||||
Generic ClassDecl Source # | |||||
Defined in Language.Java.Syntax Associated Types
| |||||
Read ClassDecl Source # | |||||
Show ClassDecl Source # | |||||
Eq ClassDecl Source # | |||||
Pretty ClassDecl Source # | |||||
type Rep ClassDecl Source # | |||||
Defined in Language.Java.Syntax type Rep ClassDecl = D1 ('MetaData "ClassDecl" "Language.Java.Syntax" "language-java-0.2.9-6oreAEG1ght3zZkJEpyPXU" 'False) (C1 ('MetaCons "ClassDecl" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Modifier]) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Ident) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TypeParam]))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe RefType)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [RefType]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ClassBody)))) :+: C1 ('MetaCons "EnumDecl" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Modifier]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Ident)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [RefType]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 EnumBody)))) |
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
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 :: forall r r'. (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 # | |||||
Generic ClassBody Source # | |||||
Defined in Language.Java.Syntax Associated Types
| |||||
Read ClassBody Source # | |||||
Show ClassBody Source # | |||||
Eq 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
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 :: forall r r'. (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 # | |||||
Generic EnumBody Source # | |||||
Defined in Language.Java.Syntax Associated Types
| |||||
Read EnumBody Source # | |||||
Show EnumBody Source # | |||||
Eq 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-6oreAEG1ght3zZkJEpyPXU" '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 EnumConstant Source # | |||||
Defined in Language.Java.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> EnumConstant -> c EnumConstant # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c EnumConstant # toConstr :: EnumConstant -> Constr # dataTypeOf :: EnumConstant -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c EnumConstant) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c EnumConstant) # gmapT :: (forall b. Data b => b -> b) -> EnumConstant -> EnumConstant # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EnumConstant -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EnumConstant -> r # gmapQ :: (forall d. Data d => d -> u) -> EnumConstant -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> EnumConstant -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> EnumConstant -> m EnumConstant # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EnumConstant -> m EnumConstant # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EnumConstant -> m EnumConstant # | |||||
Generic EnumConstant Source # | |||||
Defined in Language.Java.Syntax Associated Types
| |||||
Read EnumConstant Source # | |||||
Defined in Language.Java.Syntax Methods readsPrec :: Int -> ReadS EnumConstant # readList :: ReadS [EnumConstant] # | |||||
Show EnumConstant Source # | |||||
Defined in Language.Java.Syntax Methods showsPrec :: Int -> EnumConstant -> ShowS # show :: EnumConstant -> String # showList :: [EnumConstant] -> ShowS # | |||||
Eq EnumConstant Source # | |||||
Defined in Language.Java.Syntax | |||||
Pretty EnumConstant Source # | |||||
Defined in Language.Java.Pretty | |||||
type Rep EnumConstant Source # | |||||
Defined in Language.Java.Syntax type Rep EnumConstant = D1 ('MetaData "EnumConstant" "Language.Java.Syntax" "language-java-0.2.9-6oreAEG1ght3zZkJEpyPXU" 'False) (C1 ('MetaCons "EnumConstant" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Ident) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Argument]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ClassBody))))) |
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
Data InterfaceDecl Source # | |||||
Defined in Language.Java.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> InterfaceDecl -> c InterfaceDecl # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c InterfaceDecl # toConstr :: InterfaceDecl -> Constr # dataTypeOf :: InterfaceDecl -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c InterfaceDecl) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c InterfaceDecl) # gmapT :: (forall b. Data b => b -> b) -> InterfaceDecl -> InterfaceDecl # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InterfaceDecl -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InterfaceDecl -> r # gmapQ :: (forall d. Data d => d -> u) -> InterfaceDecl -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> InterfaceDecl -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> InterfaceDecl -> m InterfaceDecl # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InterfaceDecl -> m InterfaceDecl # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InterfaceDecl -> m InterfaceDecl # | |||||
Generic InterfaceDecl Source # | |||||
Defined in Language.Java.Syntax Associated Types
| |||||
Read InterfaceDecl Source # | |||||
Defined in Language.Java.Syntax Methods readsPrec :: Int -> ReadS InterfaceDecl # readList :: ReadS [InterfaceDecl] # | |||||
Show InterfaceDecl Source # | |||||
Defined in Language.Java.Syntax Methods showsPrec :: Int -> InterfaceDecl -> ShowS # show :: InterfaceDecl -> String # showList :: [InterfaceDecl] -> ShowS # | |||||
Eq InterfaceDecl Source # | |||||
Defined in Language.Java.Syntax Methods (==) :: InterfaceDecl -> InterfaceDecl -> Bool # (/=) :: InterfaceDecl -> InterfaceDecl -> Bool # | |||||
Pretty InterfaceDecl Source # | |||||
Defined in Language.Java.Pretty | |||||
type Rep InterfaceDecl Source # | |||||
Defined in Language.Java.Syntax type Rep InterfaceDecl = D1 ('MetaData "InterfaceDecl" "Language.Java.Syntax" "language-java-0.2.9-6oreAEG1ght3zZkJEpyPXU" 'False) (C1 ('MetaCons "InterfaceDecl" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 InterfaceKind) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Modifier]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Ident))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TypeParam]) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [RefType]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 InterfaceBody))))) |
newtype InterfaceBody Source #
The body of an interface may declare members of the interface.
Constructors
InterfaceBody [MemberDecl] |
Instances
Data InterfaceBody Source # | |||||
Defined in Language.Java.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> InterfaceBody -> c InterfaceBody # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c InterfaceBody # toConstr :: InterfaceBody -> Constr # dataTypeOf :: InterfaceBody -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c InterfaceBody) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c InterfaceBody) # gmapT :: (forall b. Data b => b -> b) -> InterfaceBody -> InterfaceBody # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InterfaceBody -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InterfaceBody -> r # gmapQ :: (forall d. Data d => d -> u) -> InterfaceBody -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> InterfaceBody -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> InterfaceBody -> m InterfaceBody # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InterfaceBody -> m InterfaceBody # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InterfaceBody -> m InterfaceBody # | |||||
Generic InterfaceBody Source # | |||||
Defined in Language.Java.Syntax Associated Types
| |||||
Read InterfaceBody Source # | |||||
Defined in Language.Java.Syntax Methods readsPrec :: Int -> ReadS InterfaceBody # readList :: ReadS [InterfaceBody] # | |||||
Show InterfaceBody Source # | |||||
Defined in Language.Java.Syntax Methods showsPrec :: Int -> InterfaceBody -> ShowS # show :: InterfaceBody -> String # showList :: [InterfaceBody] -> ShowS # | |||||
Eq InterfaceBody Source # | |||||
Defined in Language.Java.Syntax Methods (==) :: InterfaceBody -> InterfaceBody -> Bool # (/=) :: InterfaceBody -> InterfaceBody -> Bool # | |||||
Pretty InterfaceBody Source # | |||||
Defined in Language.Java.Pretty | |||||
type Rep InterfaceBody Source # | |||||
Defined in Language.Java.Syntax type Rep InterfaceBody = D1 ('MetaData "InterfaceBody" "Language.Java.Syntax" "language-java-0.2.9-6oreAEG1ght3zZkJEpyPXU" 'True) (C1 ('MetaCons "InterfaceBody" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [MemberDecl]))) |
data InterfaceKind Source #
Interface can declare either a normal interface or an annotation
Constructors
InterfaceNormal | |
InterfaceAnnotation |
Instances
Data InterfaceKind Source # | |||||
Defined in Language.Java.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> InterfaceKind -> c InterfaceKind # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c InterfaceKind # toConstr :: InterfaceKind -> Constr # dataTypeOf :: InterfaceKind -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c InterfaceKind) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c InterfaceKind) # gmapT :: (forall b. Data b => b -> b) -> InterfaceKind -> InterfaceKind # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InterfaceKind -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InterfaceKind -> r # gmapQ :: (forall d. Data d => d -> u) -> InterfaceKind -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> InterfaceKind -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> InterfaceKind -> m InterfaceKind # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InterfaceKind -> m InterfaceKind # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InterfaceKind -> m InterfaceKind # | |||||
Generic InterfaceKind Source # | |||||
Defined in Language.Java.Syntax Associated Types
| |||||
Read InterfaceKind Source # | |||||
Defined in Language.Java.Syntax Methods readsPrec :: Int -> ReadS InterfaceKind # readList :: ReadS [InterfaceKind] # | |||||
Show InterfaceKind Source # | |||||
Defined in Language.Java.Syntax Methods showsPrec :: Int -> InterfaceKind -> ShowS # show :: InterfaceKind -> String # showList :: [InterfaceKind] -> ShowS # | |||||
Eq InterfaceKind Source # | |||||
Defined in Language.Java.Syntax Methods (==) :: InterfaceKind -> InterfaceKind -> Bool # (/=) :: InterfaceKind -> InterfaceKind -> Bool # | |||||
type Rep InterfaceKind Source # | |||||
Defined in Language.Java.Syntax |
A declaration is either a member declaration, or a declaration of an initializer, which may be static.
Constructors
MemberDecl MemberDecl | |
InitDecl Bool Block |
Instances
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 :: forall r r'. (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 # | |||||
Generic Decl Source # | |||||
Defined in Language.Java.Syntax Associated Types
| |||||
Read Decl Source # | |||||
Show Decl Source # | |||||
Eq 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-6oreAEG1ght3zZkJEpyPXU" '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
Data MemberDecl Source # | |||||
Defined in Language.Java.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MemberDecl -> c MemberDecl # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MemberDecl # toConstr :: MemberDecl -> Constr # dataTypeOf :: MemberDecl -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c MemberDecl) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MemberDecl) # gmapT :: (forall b. Data b => b -> b) -> MemberDecl -> MemberDecl # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MemberDecl -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MemberDecl -> r # gmapQ :: (forall d. Data d => d -> u) -> MemberDecl -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> MemberDecl -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> MemberDecl -> m MemberDecl # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MemberDecl -> m MemberDecl # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MemberDecl -> m MemberDecl # | |||||
Generic MemberDecl Source # | |||||
Defined in Language.Java.Syntax Associated Types
| |||||
Read MemberDecl Source # | |||||
Defined in Language.Java.Syntax Methods readsPrec :: Int -> ReadS MemberDecl # readList :: ReadS [MemberDecl] # readPrec :: ReadPrec MemberDecl # readListPrec :: ReadPrec [MemberDecl] # | |||||
Show MemberDecl Source # | |||||
Defined in Language.Java.Syntax Methods showsPrec :: Int -> MemberDecl -> ShowS # show :: MemberDecl -> String # showList :: [MemberDecl] -> ShowS # | |||||
Eq MemberDecl Source # | |||||
Defined in Language.Java.Syntax | |||||
Pretty MemberDecl Source # | |||||
Defined in Language.Java.Pretty | |||||
type Rep MemberDecl Source # | |||||
Defined in Language.Java.Syntax type Rep MemberDecl = D1 ('MetaData "MemberDecl" "Language.Java.Syntax" "language-java-0.2.9-6oreAEG1ght3zZkJEpyPXU" 'False) ((C1 ('MetaCons "FieldDecl" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Modifier]) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [VarDecl]))) :+: C1 ('MetaCons "MethodDecl" 'PrefixI 'False) (((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Modifier]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TypeParam])) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Type)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Ident))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FormalParam]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ExceptionType])) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Exp)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 MethodBody))))) :+: (C1 ('MetaCons "ConstructorDecl" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Modifier]) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TypeParam]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Ident))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FormalParam]) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ExceptionType]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ConstructorBody)))) :+: (C1 ('MetaCons "MemberClassDecl" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ClassDecl)) :+: C1 ('MetaCons "MemberInterfaceDecl" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 InterfaceDecl))))) |
A declaration of a variable, which may be explicitly initialized.
Instances
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 :: forall r r'. (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 # | |||||
Generic VarDecl Source # | |||||
Defined in Language.Java.Syntax Associated Types
| |||||
Read VarDecl Source # | |||||
Show VarDecl Source # | |||||
Eq 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-6oreAEG1ght3zZkJEpyPXU" '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
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 :: forall r r'. (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 # | |||||
Generic VarDeclId Source # | |||||
Defined in Language.Java.Syntax Associated Types
| |||||
Read VarDeclId Source # | |||||
Show VarDeclId Source # | |||||
Eq 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-6oreAEG1ght3zZkJEpyPXU" '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
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 :: forall r r'. (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 # | |||||
Generic VarInit Source # | |||||
Defined in Language.Java.Syntax Associated Types
| |||||
Read VarInit Source # | |||||
Show VarInit Source # | |||||
Eq 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-6oreAEG1ght3zZkJEpyPXU" '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
Data FormalParam Source # | |||||
Defined in Language.Java.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FormalParam -> c FormalParam # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FormalParam # toConstr :: FormalParam -> Constr # dataTypeOf :: FormalParam -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c FormalParam) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FormalParam) # gmapT :: (forall b. Data b => b -> b) -> FormalParam -> FormalParam # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FormalParam -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FormalParam -> r # gmapQ :: (forall d. Data d => d -> u) -> FormalParam -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> FormalParam -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> FormalParam -> m FormalParam # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FormalParam -> m FormalParam # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FormalParam -> m FormalParam # | |||||
Generic FormalParam Source # | |||||
Defined in Language.Java.Syntax Associated Types
| |||||
Read FormalParam Source # | |||||
Defined in Language.Java.Syntax Methods readsPrec :: Int -> ReadS FormalParam # readList :: ReadS [FormalParam] # readPrec :: ReadPrec FormalParam # readListPrec :: ReadPrec [FormalParam] # | |||||
Show FormalParam Source # | |||||
Defined in Language.Java.Syntax Methods showsPrec :: Int -> FormalParam -> ShowS # show :: FormalParam -> String # showList :: [FormalParam] -> ShowS # | |||||
Eq FormalParam Source # | |||||
Defined in Language.Java.Syntax | |||||
Pretty FormalParam Source # | |||||
Defined in Language.Java.Pretty | |||||
type Rep FormalParam Source # | |||||
Defined in Language.Java.Syntax type Rep FormalParam = D1 ('MetaData "FormalParam" "Language.Java.Syntax" "language-java-0.2.9-6oreAEG1ght3zZkJEpyPXU" 'False) (C1 ('MetaCons "FormalParam" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Modifier]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 VarDeclId)))) |
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 MethodBody Source # | |||||
Defined in Language.Java.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MethodBody -> c MethodBody # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MethodBody # toConstr :: MethodBody -> Constr # dataTypeOf :: MethodBody -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c MethodBody) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MethodBody) # gmapT :: (forall b. Data b => b -> b) -> MethodBody -> MethodBody # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MethodBody -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MethodBody -> r # gmapQ :: (forall d. Data d => d -> u) -> MethodBody -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> MethodBody -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> MethodBody -> m MethodBody # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MethodBody -> m MethodBody # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MethodBody -> m MethodBody # | |||||
Generic MethodBody Source # | |||||
Defined in Language.Java.Syntax Associated Types
| |||||
Read MethodBody Source # | |||||
Defined in Language.Java.Syntax Methods readsPrec :: Int -> ReadS MethodBody # readList :: ReadS [MethodBody] # readPrec :: ReadPrec MethodBody # readListPrec :: ReadPrec [MethodBody] # | |||||
Show MethodBody Source # | |||||
Defined in Language.Java.Syntax Methods showsPrec :: Int -> MethodBody -> ShowS # show :: MethodBody -> String # showList :: [MethodBody] -> ShowS # | |||||
Eq MethodBody Source # | |||||
Defined in Language.Java.Syntax | |||||
Pretty MethodBody Source # | |||||
Defined in Language.Java.Pretty | |||||
type Rep MethodBody Source # | |||||
Defined in Language.Java.Syntax type Rep MethodBody = D1 ('MetaData "MethodBody" "Language.Java.Syntax" "language-java-0.2.9-6oreAEG1ght3zZkJEpyPXU" 'True) (C1 ('MetaCons "MethodBody" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Block)))) |
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 ConstructorBody Source # | |||||
Defined in Language.Java.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ConstructorBody -> c ConstructorBody # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ConstructorBody # toConstr :: ConstructorBody -> Constr # dataTypeOf :: ConstructorBody -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ConstructorBody) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ConstructorBody) # gmapT :: (forall b. Data b => b -> b) -> ConstructorBody -> ConstructorBody # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ConstructorBody -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ConstructorBody -> r # gmapQ :: (forall d. Data d => d -> u) -> ConstructorBody -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ConstructorBody -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ConstructorBody -> m ConstructorBody # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ConstructorBody -> m ConstructorBody # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ConstructorBody -> m ConstructorBody # | |||||
Generic ConstructorBody Source # | |||||
Defined in Language.Java.Syntax Associated Types
Methods from :: ConstructorBody -> Rep ConstructorBody x # to :: Rep ConstructorBody x -> ConstructorBody # | |||||
Read ConstructorBody Source # | |||||
Defined in Language.Java.Syntax Methods readsPrec :: Int -> ReadS ConstructorBody # readList :: ReadS [ConstructorBody] # | |||||
Show ConstructorBody Source # | |||||
Defined in Language.Java.Syntax Methods showsPrec :: Int -> ConstructorBody -> ShowS # show :: ConstructorBody -> String # showList :: [ConstructorBody] -> ShowS # | |||||
Eq ConstructorBody Source # | |||||
Defined in Language.Java.Syntax Methods (==) :: ConstructorBody -> ConstructorBody -> Bool # (/=) :: ConstructorBody -> ConstructorBody -> Bool # | |||||
Pretty ConstructorBody Source # | |||||
Defined in Language.Java.Pretty Methods pretty :: ConstructorBody -> Doc Source # prettyPrec :: Int -> ConstructorBody -> Doc Source # | |||||
type Rep ConstructorBody Source # | |||||
Defined in Language.Java.Syntax type Rep ConstructorBody = D1 ('MetaData "ConstructorBody" "Language.Java.Syntax" "language-java-0.2.9-6oreAEG1ght3zZkJEpyPXU" 'False) (C1 ('MetaCons "ConstructorBody" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ExplConstrInv)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [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] |
Instances
Data ExplConstrInv Source # | |||||
Defined in Language.Java.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ExplConstrInv -> c ExplConstrInv # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ExplConstrInv # toConstr :: ExplConstrInv -> Constr # dataTypeOf :: ExplConstrInv -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ExplConstrInv) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ExplConstrInv) # gmapT :: (forall b. Data b => b -> b) -> ExplConstrInv -> ExplConstrInv # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ExplConstrInv -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ExplConstrInv -> r # gmapQ :: (forall d. Data d => d -> u) -> ExplConstrInv -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ExplConstrInv -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ExplConstrInv -> m ExplConstrInv # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ExplConstrInv -> m ExplConstrInv # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ExplConstrInv -> m ExplConstrInv # | |||||
Generic ExplConstrInv Source # | |||||
Defined in Language.Java.Syntax Associated Types
| |||||
Read ExplConstrInv Source # | |||||
Defined in Language.Java.Syntax Methods readsPrec :: Int -> ReadS ExplConstrInv # readList :: ReadS [ExplConstrInv] # | |||||
Show ExplConstrInv Source # | |||||
Defined in Language.Java.Syntax Methods showsPrec :: Int -> ExplConstrInv -> ShowS # show :: ExplConstrInv -> String # showList :: [ExplConstrInv] -> ShowS # | |||||
Eq ExplConstrInv Source # | |||||
Defined in Language.Java.Syntax Methods (==) :: ExplConstrInv -> ExplConstrInv -> Bool # (/=) :: ExplConstrInv -> ExplConstrInv -> Bool # | |||||
Pretty ExplConstrInv Source # | |||||
Defined in Language.Java.Pretty | |||||
type Rep ExplConstrInv Source # | |||||
Defined in Language.Java.Syntax type Rep ExplConstrInv = D1 ('MetaData "ExplConstrInv" "Language.Java.Syntax" "language-java-0.2.9-6oreAEG1ght3zZkJEpyPXU" 'False) (C1 ('MetaCons "ThisInvoke" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [RefType]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Argument])) :+: (C1 ('MetaCons "SuperInvoke" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [RefType]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Argument])) :+: C1 ('MetaCons "PrimarySuperInvoke" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [RefType]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [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.
Constructors
Public | |
Private | |
Protected | |
Abstract | |
Final | |
Static | |
StrictFP | |
Transient | |
Volatile | |
Native | |
Annotation Annotation | |
Synchronized_ |
Instances
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 :: forall r r'. (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 # | |||||
Generic Modifier Source # | |||||
Defined in Language.Java.Syntax Associated Types
| |||||
Read Modifier Source # | |||||
Show Modifier Source # | |||||
Eq 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-6oreAEG1ght3zZkJEpyPXU" 'False) (((C1 ('MetaCons "Public" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Private" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Protected" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "Abstract" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Final" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Static" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "StrictFP" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Transient" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Volatile" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "Native" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Annotation" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Annotation)) :+: C1 ('MetaCons "Synchronized_" 'PrefixI 'False) (U1 :: Type -> Type))))) |
data Annotation Source #
Annotations have three different forms: no-parameter, single-parameter or key-value pairs
Constructors
NormalAnnotation | |
Fields
| |
SingleElementAnnotation | |
Fields
| |
MarkerAnnotation | |
Instances
Data Annotation Source # | |||||
Defined in Language.Java.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Annotation -> c Annotation # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Annotation # toConstr :: Annotation -> Constr # dataTypeOf :: Annotation -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Annotation) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Annotation) # gmapT :: (forall b. Data b => b -> b) -> Annotation -> Annotation # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Annotation -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Annotation -> r # gmapQ :: (forall d. Data d => d -> u) -> Annotation -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Annotation -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Annotation -> m Annotation # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Annotation -> m Annotation # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Annotation -> m Annotation # | |||||
Generic Annotation Source # | |||||
Defined in Language.Java.Syntax Associated Types
| |||||
Read Annotation Source # | |||||
Defined in Language.Java.Syntax Methods readsPrec :: Int -> ReadS Annotation # readList :: ReadS [Annotation] # readPrec :: ReadPrec Annotation # readListPrec :: ReadPrec [Annotation] # | |||||
Show Annotation Source # | |||||
Defined in Language.Java.Syntax Methods showsPrec :: Int -> Annotation -> ShowS # show :: Annotation -> String # showList :: [Annotation] -> ShowS # | |||||
Eq Annotation Source # | |||||
Defined in Language.Java.Syntax | |||||
Pretty Annotation Source # | |||||
Defined in Language.Java.Pretty | |||||
type Rep Annotation Source # | |||||
Defined in Language.Java.Syntax type Rep Annotation = D1 ('MetaData "Annotation" "Language.Java.Syntax" "language-java-0.2.9-6oreAEG1ght3zZkJEpyPXU" 'False) (C1 ('MetaCons "NormalAnnotation" 'PrefixI 'True) (S1 ('MetaSel ('Just "annName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Just "annKV") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(Ident, ElementValue)])) :+: (C1 ('MetaCons "SingleElementAnnotation" 'PrefixI 'True) (S1 ('MetaSel ('Just "annName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Just "annValue") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ElementValue)) :+: C1 ('MetaCons "MarkerAnnotation" 'PrefixI 'True) (S1 ('MetaSel ('Just "annName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name)))) |
desugarAnnotation :: Annotation -> (Name, [(Ident, ElementValue)]) Source #
data ElementValue Source #
Annotations may contain annotations or (loosely) expressions
Constructors
EVVal VarInit | |
EVAnn Annotation |
Instances
Data ElementValue Source # | |||||
Defined in Language.Java.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ElementValue -> c ElementValue # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ElementValue # toConstr :: ElementValue -> Constr # dataTypeOf :: ElementValue -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ElementValue) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ElementValue) # gmapT :: (forall b. Data b => b -> b) -> ElementValue -> ElementValue # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ElementValue -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ElementValue -> r # gmapQ :: (forall d. Data d => d -> u) -> ElementValue -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ElementValue -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ElementValue -> m ElementValue # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ElementValue -> m ElementValue # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ElementValue -> m ElementValue # | |||||
Generic ElementValue Source # | |||||
Defined in Language.Java.Syntax Associated Types
| |||||
Read ElementValue Source # | |||||
Defined in Language.Java.Syntax Methods readsPrec :: Int -> ReadS ElementValue # readList :: ReadS [ElementValue] # | |||||
Show ElementValue Source # | |||||
Defined in Language.Java.Syntax Methods showsPrec :: Int -> ElementValue -> ShowS # show :: ElementValue -> String # showList :: [ElementValue] -> ShowS # | |||||
Eq ElementValue Source # | |||||
Defined in Language.Java.Syntax | |||||
Pretty ElementValue Source # | |||||
Defined in Language.Java.Pretty | |||||
type Rep ElementValue Source # | |||||
Defined in Language.Java.Syntax type Rep ElementValue = D1 ('MetaData "ElementValue" "Language.Java.Syntax" "language-java-0.2.9-6oreAEG1ght3zZkJEpyPXU" 'False) (C1 ('MetaCons "EVVal" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 VarInit)) :+: C1 ('MetaCons "EVAnn" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Annotation))) |
A block is a sequence of statements, local class declarations and local variable declaration statements within braces.
Instances
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 :: forall r r'. (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 # | |||||
Generic Block Source # | |||||
Defined in Language.Java.Syntax Associated Types
| |||||
Read Block Source # | |||||
Show Block Source # | |||||
Eq 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
Data BlockStmt Source # | |||||
Defined in Language.Java.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BlockStmt -> c BlockStmt # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BlockStmt # toConstr :: BlockStmt -> Constr # dataTypeOf :: BlockStmt -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c BlockStmt) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BlockStmt) # gmapT :: (forall b. Data b => b -> b) -> BlockStmt -> BlockStmt # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BlockStmt -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BlockStmt -> r # gmapQ :: (forall d. Data d => d -> u) -> BlockStmt -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> BlockStmt -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> BlockStmt -> m BlockStmt # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BlockStmt -> m BlockStmt # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BlockStmt -> m BlockStmt # | |||||
Generic BlockStmt Source # | |||||
Defined in Language.Java.Syntax Associated Types
| |||||
Read BlockStmt Source # | |||||
Show BlockStmt Source # | |||||
Eq BlockStmt Source # | |||||
Pretty BlockStmt Source # | |||||
type Rep BlockStmt Source # | |||||
Defined in Language.Java.Syntax type Rep BlockStmt = D1 ('MetaData "BlockStmt" "Language.Java.Syntax" "language-java-0.2.9-6oreAEG1ght3zZkJEpyPXU" 'False) (C1 ('MetaCons "BlockStmt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Stmt)) :+: (C1 ('MetaCons "LocalClass" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ClassDecl)) :+: C1 ('MetaCons "LocalVars" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Modifier]) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [VarDecl]))))) |
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
Data Stmt Source # | |||||
Defined in Language.Java.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Stmt -> c Stmt # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Stmt # dataTypeOf :: Stmt -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Stmt) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Stmt) # gmapT :: (forall b. Data b => b -> b) -> Stmt -> Stmt # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Stmt -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Stmt -> r # gmapQ :: (forall d. Data d => d -> u) -> Stmt -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Stmt -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Stmt -> m Stmt # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Stmt -> m Stmt # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Stmt -> m Stmt # | |||||
Generic Stmt Source # | |||||
Defined in Language.Java.Syntax Associated Types
| |||||
Read Stmt Source # | |||||
Show Stmt Source # | |||||
Eq Stmt Source # | |||||
Pretty Stmt Source # | |||||
type Rep Stmt Source # | |||||
Defined in Language.Java.Syntax type Rep Stmt = D1 ('MetaData "Stmt" "Language.Java.Syntax" "language-java-0.2.9-6oreAEG1ght3zZkJEpyPXU" 'False) ((((C1 ('MetaCons "StmtBlock" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Block)) :+: C1 ('MetaCons "IfThen" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Stmt))) :+: (C1 ('MetaCons "IfThenElse" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Stmt) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Stmt))) :+: C1 ('MetaCons "While" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Stmt)))) :+: ((C1 ('MetaCons "BasicFor" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ForInit)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Exp))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [Exp])) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Stmt))) :+: C1 ('MetaCons "EnhancedFor" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Modifier]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Ident) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Stmt))))) :+: (C1 ('MetaCons "Empty" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ExpStmt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp)) :+: C1 ('MetaCons "Assert" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Exp))))))) :+: (((C1 ('MetaCons "Switch" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [SwitchBlock])) :+: C1 ('MetaCons "Do" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Stmt) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp))) :+: (C1 ('MetaCons "Break" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Ident))) :+: C1 ('MetaCons "Continue" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Ident))))) :+: ((C1 ('MetaCons "Return" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Exp))) :+: C1 ('MetaCons "Synchronized" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Block))) :+: (C1 ('MetaCons "Throw" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp)) :+: (C1 ('MetaCons "Try" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Block) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Catch]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Block)))) :+: C1 ('MetaCons "Labeled" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Ident) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Stmt))))))) |
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
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 :: forall r r'. (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 # | |||||
Generic Catch Source # | |||||
Defined in Language.Java.Syntax Associated Types
| |||||
Read Catch Source # | |||||
Show Catch Source # | |||||
Eq 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-6oreAEG1ght3zZkJEpyPXU" '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 SwitchBlock Source # | |||||
Defined in Language.Java.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SwitchBlock -> c SwitchBlock # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SwitchBlock # toConstr :: SwitchBlock -> Constr # dataTypeOf :: SwitchBlock -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SwitchBlock) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SwitchBlock) # gmapT :: (forall b. Data b => b -> b) -> SwitchBlock -> SwitchBlock # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SwitchBlock -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SwitchBlock -> r # gmapQ :: (forall d. Data d => d -> u) -> SwitchBlock -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> SwitchBlock -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SwitchBlock -> m SwitchBlock # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SwitchBlock -> m SwitchBlock # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SwitchBlock -> m SwitchBlock # | |||||
Generic SwitchBlock Source # | |||||
Defined in Language.Java.Syntax Associated Types
| |||||
Read SwitchBlock Source # | |||||
Defined in Language.Java.Syntax Methods readsPrec :: Int -> ReadS SwitchBlock # readList :: ReadS [SwitchBlock] # readPrec :: ReadPrec SwitchBlock # readListPrec :: ReadPrec [SwitchBlock] # | |||||
Show SwitchBlock Source # | |||||
Defined in Language.Java.Syntax Methods showsPrec :: Int -> SwitchBlock -> ShowS # show :: SwitchBlock -> String # showList :: [SwitchBlock] -> ShowS # | |||||
Eq SwitchBlock Source # | |||||
Defined in Language.Java.Syntax | |||||
Pretty SwitchBlock Source # | |||||
Defined in Language.Java.Pretty | |||||
type Rep SwitchBlock Source # | |||||
Defined in Language.Java.Syntax type Rep SwitchBlock = D1 ('MetaData "SwitchBlock" "Language.Java.Syntax" "language-java-0.2.9-6oreAEG1ght3zZkJEpyPXU" 'False) (C1 ('MetaCons "SwitchBlock" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SwitchLabel) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BlockStmt]))) |
data SwitchLabel Source #
A label within a switch
statement.
Constructors
SwitchCase Exp | The expression contained in the |
Default |
Instances
Data SwitchLabel Source # | |||||
Defined in Language.Java.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SwitchLabel -> c SwitchLabel # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SwitchLabel # toConstr :: SwitchLabel -> Constr # dataTypeOf :: SwitchLabel -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SwitchLabel) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SwitchLabel) # gmapT :: (forall b. Data b => b -> b) -> SwitchLabel -> SwitchLabel # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SwitchLabel -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SwitchLabel -> r # gmapQ :: (forall d. Data d => d -> u) -> SwitchLabel -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> SwitchLabel -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SwitchLabel -> m SwitchLabel # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SwitchLabel -> m SwitchLabel # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SwitchLabel -> m SwitchLabel # | |||||
Generic SwitchLabel Source # | |||||
Defined in Language.Java.Syntax Associated Types
| |||||
Read SwitchLabel Source # | |||||
Defined in Language.Java.Syntax Methods readsPrec :: Int -> ReadS SwitchLabel # readList :: ReadS [SwitchLabel] # readPrec :: ReadPrec SwitchLabel # readListPrec :: ReadPrec [SwitchLabel] # | |||||
Show SwitchLabel Source # | |||||
Defined in Language.Java.Syntax Methods showsPrec :: Int -> SwitchLabel -> ShowS # show :: SwitchLabel -> String # showList :: [SwitchLabel] -> ShowS # | |||||
Eq SwitchLabel Source # | |||||
Defined in Language.Java.Syntax | |||||
Pretty SwitchLabel Source # | |||||
Defined in Language.Java.Pretty | |||||
type Rep SwitchLabel Source # | |||||
Defined in Language.Java.Syntax type Rep SwitchLabel = D1 ('MetaData "SwitchLabel" "Language.Java.Syntax" "language-java-0.2.9-6oreAEG1ght3zZkJEpyPXU" 'False) (C1 ('MetaCons "SwitchCase" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp)) :+: C1 ('MetaCons "Default" 'PrefixI 'False) (U1 :: Type -> Type)) |
Initialization code for a basic for
statement.
Constructors
ForLocalVars [Modifier] Type [VarDecl] | |
ForInitExps [Exp] |
Instances
Data ForInit Source # | |||||
Defined in Language.Java.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ForInit -> c ForInit # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ForInit # toConstr :: ForInit -> Constr # dataTypeOf :: ForInit -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ForInit) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ForInit) # gmapT :: (forall b. Data b => b -> b) -> ForInit -> ForInit # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ForInit -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ForInit -> r # gmapQ :: (forall d. Data d => d -> u) -> ForInit -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ForInit -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ForInit -> m ForInit # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ForInit -> m ForInit # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ForInit -> m ForInit # | |||||
Generic ForInit Source # | |||||
Defined in Language.Java.Syntax Associated Types
| |||||
Read ForInit Source # | |||||
Show ForInit Source # | |||||
Eq ForInit Source # | |||||
Pretty ForInit Source # | |||||
type Rep ForInit Source # | |||||
Defined in Language.Java.Syntax type Rep ForInit = D1 ('MetaData "ForInit" "Language.Java.Syntax" "language-java-0.2.9-6oreAEG1ght3zZkJEpyPXU" 'False) (C1 ('MetaCons "ForLocalVars" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Modifier]) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [VarDecl]))) :+: C1 ('MetaCons "ForInitExps" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [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 |
Instances
Data Exp Source # | |||||
Defined in Language.Java.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Exp -> c Exp # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Exp # dataTypeOf :: Exp -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Exp) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Exp) # gmapT :: (forall b. Data b => b -> b) -> Exp -> Exp # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Exp -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Exp -> r # gmapQ :: (forall d. Data d => d -> u) -> Exp -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Exp -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Exp -> m Exp # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Exp -> m Exp # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Exp -> m Exp # | |||||
Generic Exp Source # | |||||
Defined in Language.Java.Syntax Associated Types
| |||||
Read Exp Source # | |||||
Show Exp Source # | |||||
Eq Exp Source # | |||||
Pretty Exp Source # | |||||
type Rep Exp Source # | |||||
Defined in Language.Java.Syntax type Rep Exp = D1 ('MetaData "Exp" "Language.Java.Syntax" "language-java-0.2.9-6oreAEG1ght3zZkJEpyPXU" 'False) ((((C1 ('MetaCons "Lit" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Literal)) :+: (C1 ('MetaCons "ClassLit" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Type))) :+: C1 ('MetaCons "This" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "ThisClass" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name)) :+: (C1 ('MetaCons "InstanceCreation" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TypeArgument]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TypeDeclSpecifier)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Argument]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ClassBody)))) :+: C1 ('MetaCons "QualInstanceCreation" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TypeArgument])) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Ident) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Argument]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ClassBody)))))))) :+: ((C1 ('MetaCons "ArrayCreate" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Exp]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int))) :+: (C1 ('MetaCons "ArrayCreateInit" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ArrayInit))) :+: C1 ('MetaCons "FieldAccess" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FieldAccess)))) :+: ((C1 ('MetaCons "MethodInv" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 MethodInvocation)) :+: C1 ('MetaCons "ArrayAccess" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ArrayIndex))) :+: (C1 ('MetaCons "ExpName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name)) :+: C1 ('MetaCons "PostIncrement" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp)))))) :+: (((C1 ('MetaCons "PostDecrement" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp)) :+: (C1 ('MetaCons "PreIncrement" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp)) :+: C1 ('MetaCons "PreDecrement" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp)))) :+: ((C1 ('MetaCons "PrePlus" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp)) :+: C1 ('MetaCons "PreMinus" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp))) :+: (C1 ('MetaCons "PreBitCompl" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp)) :+: C1 ('MetaCons "PreNot" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp))))) :+: ((C1 ('MetaCons "Cast" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp)) :+: (C1 ('MetaCons "BinOp" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Op) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp))) :+: C1 ('MetaCons "InstanceOf" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 RefType)))) :+: ((C1 ('MetaCons "Cond" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp))) :+: C1 ('MetaCons "Assign" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Lhs) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AssignOp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp)))) :+: (C1 ('MetaCons "Lambda" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 LambdaParams) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 LambdaExpression)) :+: C1 ('MetaCons "MethodRef" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Ident))))))) |
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
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 :: forall r r'. (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 # | |||||
Generic Lhs Source # | |||||
Defined in Language.Java.Syntax Associated Types
| |||||
Read Lhs Source # | |||||
Show Lhs Source # | |||||
Eq 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-6oreAEG1ght3zZkJEpyPXU" '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 ArrayIndex Source # | |||||
Defined in Language.Java.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ArrayIndex -> c ArrayIndex # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ArrayIndex # toConstr :: ArrayIndex -> Constr # dataTypeOf :: ArrayIndex -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ArrayIndex) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ArrayIndex) # gmapT :: (forall b. Data b => b -> b) -> ArrayIndex -> ArrayIndex # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ArrayIndex -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ArrayIndex -> r # gmapQ :: (forall d. Data d => d -> u) -> ArrayIndex -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ArrayIndex -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ArrayIndex -> m ArrayIndex # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ArrayIndex -> m ArrayIndex # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ArrayIndex -> m ArrayIndex # | |||||
Generic ArrayIndex Source # | |||||
Defined in Language.Java.Syntax Associated Types
| |||||
Read ArrayIndex Source # | |||||
Defined in Language.Java.Syntax Methods readsPrec :: Int -> ReadS ArrayIndex # readList :: ReadS [ArrayIndex] # readPrec :: ReadPrec ArrayIndex # readListPrec :: ReadPrec [ArrayIndex] # | |||||
Show ArrayIndex Source # | |||||
Defined in Language.Java.Syntax Methods showsPrec :: Int -> ArrayIndex -> ShowS # show :: ArrayIndex -> String # showList :: [ArrayIndex] -> ShowS # | |||||
Eq ArrayIndex Source # | |||||
Defined in Language.Java.Syntax | |||||
Pretty ArrayIndex Source # | |||||
Defined in Language.Java.Pretty | |||||
type Rep ArrayIndex Source # | |||||
Defined in Language.Java.Syntax type Rep ArrayIndex = D1 ('MetaData "ArrayIndex" "Language.Java.Syntax" "language-java-0.2.9-6oreAEG1ght3zZkJEpyPXU" 'False) (C1 ('MetaCons "ArrayIndex" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Exp]))) |
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 FieldAccess Source # | |||||
Defined in Language.Java.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FieldAccess -> c FieldAccess # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FieldAccess # toConstr :: FieldAccess -> Constr # dataTypeOf :: FieldAccess -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c FieldAccess) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FieldAccess) # gmapT :: (forall b. Data b => b -> b) -> FieldAccess -> FieldAccess # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FieldAccess -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FieldAccess -> r # gmapQ :: (forall d. Data d => d -> u) -> FieldAccess -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> FieldAccess -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> FieldAccess -> m FieldAccess # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FieldAccess -> m FieldAccess # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FieldAccess -> m FieldAccess # | |||||
Generic FieldAccess Source # | |||||
Defined in Language.Java.Syntax Associated Types
| |||||
Read FieldAccess Source # | |||||
Defined in Language.Java.Syntax Methods readsPrec :: Int -> ReadS FieldAccess # readList :: ReadS [FieldAccess] # readPrec :: ReadPrec FieldAccess # readListPrec :: ReadPrec [FieldAccess] # | |||||
Show FieldAccess Source # | |||||
Defined in Language.Java.Syntax Methods showsPrec :: Int -> FieldAccess -> ShowS # show :: FieldAccess -> String # showList :: [FieldAccess] -> ShowS # | |||||
Eq FieldAccess Source # | |||||
Defined in Language.Java.Syntax | |||||
Pretty FieldAccess Source # | |||||
Defined in Language.Java.Pretty | |||||
type Rep FieldAccess Source # | |||||
Defined in Language.Java.Syntax type Rep FieldAccess = D1 ('MetaData "FieldAccess" "Language.Java.Syntax" "language-java-0.2.9-6oreAEG1ght3zZkJEpyPXU" 'False) (C1 ('MetaCons "PrimaryFieldAccess" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Ident)) :+: (C1 ('MetaCons "SuperFieldAccess" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Ident)) :+: C1 ('MetaCons "ClassFieldAccess" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Ident)))) |
data LambdaParams Source #
Constructors
LambdaSingleParam Ident | |
LambdaFormalParams [FormalParam] | |
LambdaInferredParams [Ident] |
Instances
Data LambdaParams Source # | |||||
Defined in Language.Java.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LambdaParams -> c LambdaParams # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LambdaParams # toConstr :: LambdaParams -> Constr # dataTypeOf :: LambdaParams -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c LambdaParams) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LambdaParams) # gmapT :: (forall b. Data b => b -> b) -> LambdaParams -> LambdaParams # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LambdaParams -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LambdaParams -> r # gmapQ :: (forall d. Data d => d -> u) -> LambdaParams -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> LambdaParams -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> LambdaParams -> m LambdaParams # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LambdaParams -> m LambdaParams # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LambdaParams -> m LambdaParams # | |||||
Generic LambdaParams Source # | |||||
Defined in Language.Java.Syntax Associated Types
| |||||
Read LambdaParams Source # | |||||
Defined in Language.Java.Syntax Methods readsPrec :: Int -> ReadS LambdaParams # readList :: ReadS [LambdaParams] # | |||||
Show LambdaParams Source # | |||||
Defined in Language.Java.Syntax Methods showsPrec :: Int -> LambdaParams -> ShowS # show :: LambdaParams -> String # showList :: [LambdaParams] -> ShowS # | |||||
Eq LambdaParams Source # | |||||
Defined in Language.Java.Syntax | |||||
Pretty LambdaParams Source # | |||||
Defined in Language.Java.Pretty | |||||
type Rep LambdaParams Source # | |||||
Defined in Language.Java.Syntax type Rep LambdaParams = D1 ('MetaData "LambdaParams" "Language.Java.Syntax" "language-java-0.2.9-6oreAEG1ght3zZkJEpyPXU" 'False) (C1 ('MetaCons "LambdaSingleParam" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Ident)) :+: (C1 ('MetaCons "LambdaFormalParams" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FormalParam])) :+: C1 ('MetaCons "LambdaInferredParams" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Ident])))) |
data LambdaExpression Source #
Lambda expression, starting from java 8
Constructors
LambdaExpression Exp | |
LambdaBlock Block |
Instances
Data LambdaExpression Source # | |||||
Defined in Language.Java.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LambdaExpression -> c LambdaExpression # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LambdaExpression # toConstr :: LambdaExpression -> Constr # dataTypeOf :: LambdaExpression -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c LambdaExpression) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LambdaExpression) # gmapT :: (forall b. Data b => b -> b) -> LambdaExpression -> LambdaExpression # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LambdaExpression -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LambdaExpression -> r # gmapQ :: (forall d. Data d => d -> u) -> LambdaExpression -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> LambdaExpression -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> LambdaExpression -> m LambdaExpression # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LambdaExpression -> m LambdaExpression # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LambdaExpression -> m LambdaExpression # | |||||
Generic LambdaExpression Source # | |||||
Defined in Language.Java.Syntax Associated Types
Methods from :: LambdaExpression -> Rep LambdaExpression x # to :: Rep LambdaExpression x -> LambdaExpression # | |||||
Read LambdaExpression Source # | |||||
Defined in Language.Java.Syntax Methods readsPrec :: Int -> ReadS LambdaExpression # readList :: ReadS [LambdaExpression] # | |||||
Show LambdaExpression Source # | |||||
Defined in Language.Java.Syntax Methods showsPrec :: Int -> LambdaExpression -> ShowS # show :: LambdaExpression -> String # showList :: [LambdaExpression] -> ShowS # | |||||
Eq LambdaExpression Source # | |||||
Defined in Language.Java.Syntax Methods (==) :: LambdaExpression -> LambdaExpression -> Bool # (/=) :: LambdaExpression -> LambdaExpression -> Bool # | |||||
Pretty LambdaExpression Source # | |||||
Defined in Language.Java.Pretty Methods pretty :: LambdaExpression -> Doc Source # prettyPrec :: Int -> LambdaExpression -> Doc Source # | |||||
type Rep LambdaExpression Source # | |||||
Defined in Language.Java.Syntax type Rep LambdaExpression = D1 ('MetaData "LambdaExpression" "Language.Java.Syntax" "language-java-0.2.9-6oreAEG1ght3zZkJEpyPXU" 'False) (C1 ('MetaCons "LambdaExpression" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp)) :+: C1 ('MetaCons "LambdaBlock" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 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
Instances
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 :: forall r r'. (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 # | |||||
Generic ArrayInit Source # | |||||
Defined in Language.Java.Syntax Associated Types
| |||||
Read ArrayInit Source # | |||||
Show ArrayInit Source # | |||||
Eq 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
Data MethodInvocation Source # | |||||
Defined in Language.Java.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MethodInvocation -> c MethodInvocation # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MethodInvocation # toConstr :: MethodInvocation -> Constr # dataTypeOf :: MethodInvocation -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c MethodInvocation) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MethodInvocation) # gmapT :: (forall b. Data b => b -> b) -> MethodInvocation -> MethodInvocation # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MethodInvocation -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MethodInvocation -> r # gmapQ :: (forall d. Data d => d -> u) -> MethodInvocation -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> MethodInvocation -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> MethodInvocation -> m MethodInvocation # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MethodInvocation -> m MethodInvocation # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MethodInvocation -> m MethodInvocation # | |||||
Generic MethodInvocation Source # | |||||
Defined in Language.Java.Syntax Associated Types
Methods from :: MethodInvocation -> Rep MethodInvocation x # to :: Rep MethodInvocation x -> MethodInvocation # | |||||
Read MethodInvocation Source # | |||||
Defined in Language.Java.Syntax Methods readsPrec :: Int -> ReadS MethodInvocation # readList :: ReadS [MethodInvocation] # | |||||
Show MethodInvocation Source # | |||||
Defined in Language.Java.Syntax Methods showsPrec :: Int -> MethodInvocation -> ShowS # show :: MethodInvocation -> String # showList :: [MethodInvocation] -> ShowS # | |||||
Eq MethodInvocation Source # | |||||
Defined in Language.Java.Syntax Methods (==) :: MethodInvocation -> MethodInvocation -> Bool # (/=) :: MethodInvocation -> MethodInvocation -> Bool # | |||||
Pretty MethodInvocation Source # | |||||
Defined in Language.Java.Pretty Methods pretty :: MethodInvocation -> Doc Source # prettyPrec :: Int -> MethodInvocation -> Doc Source # | |||||
type Rep MethodInvocation Source # | |||||
Defined in Language.Java.Syntax type Rep MethodInvocation = D1 ('MetaData "MethodInvocation" "Language.Java.Syntax" "language-java-0.2.9-6oreAEG1ght3zZkJEpyPXU" 'False) ((C1 ('MetaCons "MethodCall" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Argument])) :+: C1 ('MetaCons "PrimaryMethodCall" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [RefType])) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Ident) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Argument])))) :+: (C1 ('MetaCons "SuperMethodCall" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [RefType]) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Ident) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Argument]))) :+: (C1 ('MetaCons "ClassMethodCall" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [RefType])) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Ident) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Argument]))) :+: C1 ('MetaCons "TypeMethodCall" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [RefType])) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Ident) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Argument])))))) |
A literal denotes a fixed, unchanging value.
Constructors
Int Integer | |
Word Integer | |
Float Double | |
Double Double | |
Boolean Bool | |
Char Char | |
String String | |
Null |
Instances
Data Literal 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) -> Literal -> c Literal # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Literal # toConstr :: Literal -> Constr # dataTypeOf :: Literal -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Literal) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Literal) # gmapT :: (forall b. Data b => b -> b) -> Literal -> Literal # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Literal -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Literal -> r # gmapQ :: (forall d. Data d => d -> u) -> Literal -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Literal -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Literal -> m Literal # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Literal -> m Literal # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Literal -> m Literal # | |||||
Generic Literal Source # | |||||
Defined in Language.Java.Syntax.Exp Associated Types
| |||||
Read Literal Source # | |||||
Show Literal Source # | |||||
Eq Literal Source # | |||||
Pretty Literal Source # | |||||
type Rep Literal Source # | |||||
Defined in Language.Java.Syntax.Exp type Rep Literal = D1 ('MetaData "Literal" "Language.Java.Syntax.Exp" "language-java-0.2.9-6oreAEG1ght3zZkJEpyPXU" 'False) (((C1 ('MetaCons "Int" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer)) :+: C1 ('MetaCons "Word" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer))) :+: (C1 ('MetaCons "Float" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double)) :+: C1 ('MetaCons "Double" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double)))) :+: ((C1 ('MetaCons "Boolean" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)) :+: C1 ('MetaCons "Char" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Char))) :+: (C1 ('MetaCons "String" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: C1 ('MetaCons "Null" 'PrefixI 'False) (U1 :: Type -> Type)))) |
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
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 :: forall r r'. (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 # | |||||
Generic Op Source # | |||||
Defined in Language.Java.Syntax.Exp Associated Types
| |||||
Read Op Source # | |||||
Show Op Source # | |||||
Eq 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-6oreAEG1ght3zZkJEpyPXU" 'False) ((((C1 ('MetaCons "Mult" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Div" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Rem" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Add" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Sub" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LShift" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "RShift" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "RRShift" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LThan" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "GThan" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LThanE" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "GThanE" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Equal" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NotEq" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "And" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Or" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Xor" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "CAnd" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "COr" 'PrefixI 'False) (U1 :: Type -> Type)))))) |
An assignment operator.
Instances
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 :: forall r r'. (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 # | |||||
Generic AssignOp Source # | |||||
Defined in Language.Java.Syntax.Exp Associated Types
| |||||
Read AssignOp Source # | |||||
Show AssignOp Source # | |||||
Eq 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-6oreAEG1ght3zZkJEpyPXU" 'False) (((C1 ('MetaCons "EqualA" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "MultA" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DivA" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "RemA" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "AddA" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SubA" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "LShiftA" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "RShiftA" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RRShiftA" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "AndA" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "XorA" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OrA" 'PrefixI 'False) (U1 :: Type -> Type))))) |
There are two kinds of types in the Java programming language: primitive types and reference types.
Instances
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 :: forall r r'. (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 # | |||||
Generic Type Source # | |||||
Defined in Language.Java.Syntax.Types Associated Types
| |||||
Read Type Source # | |||||
Show Type Source # | |||||
Eq 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-6oreAEG1ght3zZkJEpyPXU" '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))) |
A single identifier.
Instances
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 :: forall r r'. (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 # | |||||
Generic Ident Source # | |||||
Defined in Language.Java.Syntax.Types Associated Types
| |||||
Read Ident Source # | |||||
Show Ident Source # | |||||
Eq Ident Source # | |||||
Ord 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
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 :: forall r r'. (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 # | |||||
Generic Name Source # | |||||
Defined in Language.Java.Syntax.Types Associated Types
| |||||
Read Name Source # | |||||
Show Name Source # | |||||
Eq Name Source # | |||||
Ord Name Source # | |||||
Pretty Name Source # | |||||
type Rep Name Source # | |||||
Defined in Language.Java.Syntax.Types |
A primitive type is predefined by the Java programming language and named by its reserved keyword.
Instances
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 :: forall r r'. (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 # | |||||
Generic PrimType Source # | |||||
Defined in Language.Java.Syntax.Types Associated Types
| |||||
Read PrimType Source # | |||||
Show PrimType Source # | |||||
Eq 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-6oreAEG1ght3zZkJEpyPXU" 'False) (((C1 ('MetaCons "BooleanT" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ByteT" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ShortT" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "IntT" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "LongT" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CharT" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "FloatT" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DoubleT" 'PrefixI 'False) (U1 :: Type -> Type)))) |
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
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 :: forall r r'. (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 # | |||||
Generic RefType Source # | |||||
Defined in Language.Java.Syntax.Types Associated Types
| |||||
Read RefType Source # | |||||
Show RefType Source # | |||||
Eq 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-6oreAEG1ght3zZkJEpyPXU" '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
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 :: forall r r'. (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 # | |||||
Generic ClassType Source # | |||||
Defined in Language.Java.Syntax.Types Associated Types
| |||||
Read ClassType Source # | |||||
Show ClassType Source # | |||||
Eq 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-6oreAEG1ght3zZkJEpyPXU" '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 TypeArgument 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) -> TypeArgument -> c TypeArgument # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TypeArgument # toConstr :: TypeArgument -> Constr # dataTypeOf :: TypeArgument -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TypeArgument) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TypeArgument) # gmapT :: (forall b. Data b => b -> b) -> TypeArgument -> TypeArgument # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TypeArgument -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TypeArgument -> r # gmapQ :: (forall d. Data d => d -> u) -> TypeArgument -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> TypeArgument -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TypeArgument -> m TypeArgument # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TypeArgument -> m TypeArgument # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TypeArgument -> m TypeArgument # | |||||
Generic TypeArgument Source # | |||||
Defined in Language.Java.Syntax.Types Associated Types
| |||||
Read TypeArgument Source # | |||||
Defined in Language.Java.Syntax.Types Methods readsPrec :: Int -> ReadS TypeArgument # readList :: ReadS [TypeArgument] # | |||||
Show TypeArgument Source # | |||||
Defined in Language.Java.Syntax.Types Methods showsPrec :: Int -> TypeArgument -> ShowS # show :: TypeArgument -> String # showList :: [TypeArgument] -> ShowS # | |||||
Eq TypeArgument Source # | |||||
Defined in Language.Java.Syntax.Types | |||||
Pretty TypeArgument Source # | |||||
Defined in Language.Java.Pretty | |||||
type Rep TypeArgument Source # | |||||
Defined in Language.Java.Syntax.Types type Rep TypeArgument = D1 ('MetaData "TypeArgument" "Language.Java.Syntax.Types" "language-java-0.2.9-6oreAEG1ght3zZkJEpyPXU" 'False) (C1 ('MetaCons "Wildcard" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe WildcardBound))) :+: C1 ('MetaCons "ActualType" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 RefType))) |
data WildcardBound Source #
Wildcards may be given explicit bounds, either upper (extends
) or lower (super
) bounds.
Constructors
ExtendsBound RefType | |
SuperBound RefType |
Instances
Data WildcardBound 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) -> WildcardBound -> c WildcardBound # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c WildcardBound # toConstr :: WildcardBound -> Constr # dataTypeOf :: WildcardBound -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c WildcardBound) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c WildcardBound) # gmapT :: (forall b. Data b => b -> b) -> WildcardBound -> WildcardBound # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> WildcardBound -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> WildcardBound -> r # gmapQ :: (forall d. Data d => d -> u) -> WildcardBound -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> WildcardBound -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> WildcardBound -> m WildcardBound # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> WildcardBound -> m WildcardBound # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> WildcardBound -> m WildcardBound # | |||||
Generic WildcardBound Source # | |||||
Defined in Language.Java.Syntax.Types Associated Types
| |||||
Read WildcardBound Source # | |||||
Defined in Language.Java.Syntax.Types Methods readsPrec :: Int -> ReadS WildcardBound # readList :: ReadS [WildcardBound] # | |||||
Show WildcardBound Source # | |||||
Defined in Language.Java.Syntax.Types Methods showsPrec :: Int -> WildcardBound -> ShowS # show :: WildcardBound -> String # showList :: [WildcardBound] -> ShowS # | |||||
Eq WildcardBound Source # | |||||
Defined in Language.Java.Syntax.Types Methods (==) :: WildcardBound -> WildcardBound -> Bool # (/=) :: WildcardBound -> WildcardBound -> Bool # | |||||
Pretty WildcardBound Source # | |||||
Defined in Language.Java.Pretty | |||||
type Rep WildcardBound Source # | |||||
Defined in Language.Java.Syntax.Types type Rep WildcardBound = D1 ('MetaData "WildcardBound" "Language.Java.Syntax.Types" "language-java-0.2.9-6oreAEG1ght3zZkJEpyPXU" 'False) (C1 ('MetaCons "ExtendsBound" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 RefType)) :+: C1 ('MetaCons "SuperBound" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 RefType))) |
data TypeDeclSpecifier Source #
Constructors
TypeDeclSpecifier ClassType | |
TypeDeclSpecifierWithDiamond ClassType Ident Diamond | |
TypeDeclSpecifierUnqualifiedWithDiamond Ident Diamond |
Instances
Data TypeDeclSpecifier 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) -> TypeDeclSpecifier -> c TypeDeclSpecifier # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TypeDeclSpecifier # toConstr :: TypeDeclSpecifier -> Constr # dataTypeOf :: TypeDeclSpecifier -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TypeDeclSpecifier) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TypeDeclSpecifier) # gmapT :: (forall b. Data b => b -> b) -> TypeDeclSpecifier -> TypeDeclSpecifier # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TypeDeclSpecifier -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TypeDeclSpecifier -> r # gmapQ :: (forall d. Data d => d -> u) -> TypeDeclSpecifier -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> TypeDeclSpecifier -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TypeDeclSpecifier -> m TypeDeclSpecifier # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TypeDeclSpecifier -> m TypeDeclSpecifier # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TypeDeclSpecifier -> m TypeDeclSpecifier # | |||||
Generic TypeDeclSpecifier Source # | |||||
Defined in Language.Java.Syntax.Types Associated Types
Methods from :: TypeDeclSpecifier -> Rep TypeDeclSpecifier x # to :: Rep TypeDeclSpecifier x -> TypeDeclSpecifier # | |||||
Read TypeDeclSpecifier Source # | |||||
Defined in Language.Java.Syntax.Types Methods readsPrec :: Int -> ReadS TypeDeclSpecifier # readList :: ReadS [TypeDeclSpecifier] # | |||||
Show TypeDeclSpecifier Source # | |||||
Defined in Language.Java.Syntax.Types Methods showsPrec :: Int -> TypeDeclSpecifier -> ShowS # show :: TypeDeclSpecifier -> String # showList :: [TypeDeclSpecifier] -> ShowS # | |||||
Eq TypeDeclSpecifier Source # | |||||
Defined in Language.Java.Syntax.Types Methods (==) :: TypeDeclSpecifier -> TypeDeclSpecifier -> Bool # (/=) :: TypeDeclSpecifier -> TypeDeclSpecifier -> Bool # | |||||
Pretty TypeDeclSpecifier Source # | |||||
Defined in Language.Java.Pretty Methods pretty :: TypeDeclSpecifier -> Doc Source # prettyPrec :: Int -> TypeDeclSpecifier -> Doc Source # | |||||
type Rep TypeDeclSpecifier Source # | |||||
Defined in Language.Java.Syntax.Types type Rep TypeDeclSpecifier = D1 ('MetaData "TypeDeclSpecifier" "Language.Java.Syntax.Types" "language-java-0.2.9-6oreAEG1ght3zZkJEpyPXU" 'False) (C1 ('MetaCons "TypeDeclSpecifier" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ClassType)) :+: (C1 ('MetaCons "TypeDeclSpecifierWithDiamond" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ClassType) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Ident) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Diamond))) :+: C1 ('MetaCons "TypeDeclSpecifierUnqualifiedWithDiamond" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Ident) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Diamond)))) |
Constructors
Diamond |
Instances
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 :: forall r r'. (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 # | |
Generic Diamond Source # | |
Defined in Language.Java.Syntax.Types | |
Read Diamond Source # | |
Show Diamond Source # | |
Eq Diamond Source # | |
Pretty Diamond Source # | |
type Rep Diamond Source # | |
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
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 :: forall r r'. (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 # | |||||
Generic TypeParam Source # | |||||
Defined in Language.Java.Syntax.Types Associated Types
| |||||
Read TypeParam Source # | |||||
Show TypeParam Source # | |||||
Eq 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-6oreAEG1ght3zZkJEpyPXU" '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]))) |