Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Hydra.Ext.Java.Syntax
Description
A Java syntax module. Based on the Oracle Java SE 12 BNF: | https://docs.oracle.com/javase/specs/jls/se12/html/jls-19.html | Note: all *WithComments types were added manually, rather than derived from the BNF, which does not allow for comments.
Synopsis
- newtype Identifier = Identifier {}
- _Identifier :: Name
- newtype TypeIdentifier = TypeIdentifier {}
- _TypeIdentifier :: Name
- data Literal
- _Literal :: Name
- _Literal_null :: FieldName
- _Literal_integer :: FieldName
- _Literal_floatingPoint :: FieldName
- _Literal_boolean :: FieldName
- _Literal_character :: FieldName
- _Literal_string :: FieldName
- newtype IntegerLiteral = IntegerLiteral {}
- _IntegerLiteral :: Name
- newtype FloatingPointLiteral = FloatingPointLiteral {}
- _FloatingPointLiteral :: Name
- newtype StringLiteral = StringLiteral {}
- _StringLiteral :: Name
- data Type
- _Type :: Name
- _Type_primitive :: FieldName
- _Type_reference :: FieldName
- data PrimitiveTypeWithAnnotations = PrimitiveTypeWithAnnotations {}
- _PrimitiveTypeWithAnnotations :: Name
- _PrimitiveTypeWithAnnotations_type :: FieldName
- _PrimitiveTypeWithAnnotations_annotations :: FieldName
- data PrimitiveType
- _PrimitiveType :: Name
- _PrimitiveType_numeric :: FieldName
- _PrimitiveType_boolean :: FieldName
- data NumericType
- _NumericType :: Name
- _NumericType_integral :: FieldName
- _NumericType_floatingPoint :: FieldName
- data IntegralType
- _IntegralType :: Name
- _IntegralType_byte :: FieldName
- _IntegralType_short :: FieldName
- _IntegralType_int :: FieldName
- _IntegralType_long :: FieldName
- _IntegralType_char :: FieldName
- data FloatingPointType
- _FloatingPointType :: Name
- _FloatingPointType_float :: FieldName
- _FloatingPointType_double :: FieldName
- data ReferenceType
- _ReferenceType :: Name
- _ReferenceType_classOrInterface :: FieldName
- _ReferenceType_variable :: FieldName
- _ReferenceType_array :: FieldName
- data ClassOrInterfaceType
- _ClassOrInterfaceType :: Name
- _ClassOrInterfaceType_class :: FieldName
- _ClassOrInterfaceType_interface :: FieldName
- data ClassType = ClassType {}
- _ClassType :: Name
- _ClassType_annotations :: FieldName
- _ClassType_qualifier :: FieldName
- _ClassType_identifier :: FieldName
- _ClassType_arguments :: FieldName
- data ClassTypeQualifier
- _ClassTypeQualifier :: Name
- _ClassTypeQualifier_none :: FieldName
- _ClassTypeQualifier_package :: FieldName
- _ClassTypeQualifier_parent :: FieldName
- newtype InterfaceType = InterfaceType {}
- _InterfaceType :: Name
- data TypeVariable = TypeVariable {}
- _TypeVariable :: Name
- _TypeVariable_annotations :: FieldName
- _TypeVariable_identifier :: FieldName
- data ArrayType = ArrayType {}
- _ArrayType :: Name
- _ArrayType_dims :: FieldName
- _ArrayType_variant :: FieldName
- data ArrayType_Variant
- _ArrayType_Variant :: Name
- _ArrayType_Variant_primitive :: FieldName
- _ArrayType_Variant_classOrInterface :: FieldName
- _ArrayType_Variant_variable :: FieldName
- newtype Dims = Dims {
- unDims :: [[Annotation]]
- _Dims :: Name
- data TypeParameter = TypeParameter {}
- _TypeParameter :: Name
- _TypeParameter_modifiers :: FieldName
- _TypeParameter_identifier :: FieldName
- _TypeParameter_bound :: FieldName
- newtype TypeParameterModifier = TypeParameterModifier {}
- _TypeParameterModifier :: Name
- data TypeBound
- _TypeBound :: Name
- _TypeBound_variable :: FieldName
- _TypeBound_classOrInterface :: FieldName
- data TypeBound_ClassOrInterface = TypeBound_ClassOrInterface {}
- _TypeBound_ClassOrInterface :: Name
- _TypeBound_ClassOrInterface_type :: FieldName
- _TypeBound_ClassOrInterface_additional :: FieldName
- newtype AdditionalBound = AdditionalBound {}
- _AdditionalBound :: Name
- data TypeArgument
- _TypeArgument :: Name
- _TypeArgument_reference :: FieldName
- _TypeArgument_wildcard :: FieldName
- data Wildcard = Wildcard {}
- _Wildcard :: Name
- _Wildcard_annotations :: FieldName
- _Wildcard_wildcard :: FieldName
- data WildcardBounds
- _WildcardBounds :: Name
- _WildcardBounds_extends :: FieldName
- _WildcardBounds_super :: FieldName
- data ModuleName = ModuleName {}
- _ModuleName :: Name
- _ModuleName_identifier :: FieldName
- _ModuleName_name :: FieldName
- newtype PackageName = PackageName {
- unPackageName :: [Identifier]
- _PackageName :: Name
- data TypeName = TypeName {}
- _TypeName :: Name
- _TypeName_identifier :: FieldName
- _TypeName_qualifier :: FieldName
- data ExpressionName = ExpressionName {}
- _ExpressionName :: Name
- _ExpressionName_qualifier :: FieldName
- _ExpressionName_identifier :: FieldName
- newtype MethodName = MethodName {}
- _MethodName :: Name
- newtype PackageOrTypeName = PackageOrTypeName {}
- _PackageOrTypeName :: Name
- newtype AmbiguousName = AmbiguousName {}
- _AmbiguousName :: Name
- data CompilationUnit
- _CompilationUnit :: Name
- _CompilationUnit_ordinary :: FieldName
- _CompilationUnit_modular :: FieldName
- data OrdinaryCompilationUnit = OrdinaryCompilationUnit {}
- _OrdinaryCompilationUnit :: Name
- _OrdinaryCompilationUnit_package :: FieldName
- _OrdinaryCompilationUnit_imports :: FieldName
- _OrdinaryCompilationUnit_types :: FieldName
- data ModularCompilationUnit = ModularCompilationUnit {}
- _ModularCompilationUnit :: Name
- _ModularCompilationUnit_imports :: FieldName
- _ModularCompilationUnit_module :: FieldName
- data PackageDeclaration = PackageDeclaration {}
- _PackageDeclaration :: Name
- _PackageDeclaration_modifiers :: FieldName
- _PackageDeclaration_identifiers :: FieldName
- newtype PackageModifier = PackageModifier {}
- _PackageModifier :: Name
- data ImportDeclaration
- _ImportDeclaration :: Name
- _ImportDeclaration_singleType :: FieldName
- _ImportDeclaration_typeImportOnDemand :: FieldName
- _ImportDeclaration_singleStaticImport :: FieldName
- _ImportDeclaration_staticImportOnDemand :: FieldName
- newtype SingleTypeImportDeclaration = SingleTypeImportDeclaration {}
- _SingleTypeImportDeclaration :: Name
- newtype TypeImportOnDemandDeclaration = TypeImportOnDemandDeclaration {}
- _TypeImportOnDemandDeclaration :: Name
- data SingleStaticImportDeclaration = SingleStaticImportDeclaration {}
- _SingleStaticImportDeclaration :: Name
- _SingleStaticImportDeclaration_typeName :: FieldName
- _SingleStaticImportDeclaration_identifier :: FieldName
- newtype StaticImportOnDemandDeclaration = StaticImportOnDemandDeclaration {}
- _StaticImportOnDemandDeclaration :: Name
- data TypeDeclaration
- _TypeDeclaration :: Name
- _TypeDeclaration_class :: FieldName
- _TypeDeclaration_interface :: FieldName
- _TypeDeclaration_none :: FieldName
- data TypeDeclarationWithComments = TypeDeclarationWithComments {}
- _TypeDeclarationWithComments :: Name
- _TypeDeclarationWithComments_value :: FieldName
- _TypeDeclarationWithComments_comments :: FieldName
- data ModuleDeclaration = ModuleDeclaration {}
- _ModuleDeclaration :: Name
- _ModuleDeclaration_annotations :: FieldName
- _ModuleDeclaration_open :: FieldName
- _ModuleDeclaration_identifiers :: FieldName
- _ModuleDeclaration_directives :: FieldName
- data ModuleDirective
- _ModuleDirective :: Name
- _ModuleDirective_requires :: FieldName
- _ModuleDirective_exports :: FieldName
- _ModuleDirective_opens :: FieldName
- _ModuleDirective_uses :: FieldName
- _ModuleDirective_provides :: FieldName
- data ModuleDirective_Requires = ModuleDirective_Requires {}
- _ModuleDirective_Requires :: Name
- _ModuleDirective_Requires_modifiers :: FieldName
- _ModuleDirective_Requires_module :: FieldName
- data ModuleDirective_ExportsOrOpens = ModuleDirective_ExportsOrOpens {}
- _ModuleDirective_ExportsOrOpens :: Name
- _ModuleDirective_ExportsOrOpens_package :: FieldName
- _ModuleDirective_ExportsOrOpens_modules :: FieldName
- data ModuleDirective_Provides = ModuleDirective_Provides {}
- _ModuleDirective_Provides :: Name
- _ModuleDirective_Provides_to :: FieldName
- _ModuleDirective_Provides_with :: FieldName
- data RequiresModifier
- _RequiresModifier :: Name
- _RequiresModifier_transitive :: FieldName
- _RequiresModifier_static :: FieldName
- data ClassDeclaration
- _ClassDeclaration :: Name
- _ClassDeclaration_normal :: FieldName
- _ClassDeclaration_enum :: FieldName
- data NormalClassDeclaration = NormalClassDeclaration {}
- _NormalClassDeclaration :: Name
- _NormalClassDeclaration_modifiers :: FieldName
- _NormalClassDeclaration_identifier :: FieldName
- _NormalClassDeclaration_parameters :: FieldName
- _NormalClassDeclaration_extends :: FieldName
- _NormalClassDeclaration_implements :: FieldName
- _NormalClassDeclaration_body :: FieldName
- data ClassModifier
- _ClassModifier :: Name
- _ClassModifier_annotation :: FieldName
- _ClassModifier_public :: FieldName
- _ClassModifier_protected :: FieldName
- _ClassModifier_private :: FieldName
- _ClassModifier_abstract :: FieldName
- _ClassModifier_static :: FieldName
- _ClassModifier_final :: FieldName
- _ClassModifier_strictfp :: FieldName
- newtype ClassBody = ClassBody {}
- _ClassBody :: Name
- data ClassBodyDeclaration
- _ClassBodyDeclaration :: Name
- _ClassBodyDeclaration_classMember :: FieldName
- _ClassBodyDeclaration_instanceInitializer :: FieldName
- _ClassBodyDeclaration_staticInitializer :: FieldName
- _ClassBodyDeclaration_constructorDeclaration :: FieldName
- data ClassBodyDeclarationWithComments = ClassBodyDeclarationWithComments {}
- _ClassBodyDeclarationWithComments :: Name
- _ClassBodyDeclarationWithComments_value :: FieldName
- _ClassBodyDeclarationWithComments_comments :: FieldName
- data ClassMemberDeclaration
- _ClassMemberDeclaration :: Name
- _ClassMemberDeclaration_field :: FieldName
- _ClassMemberDeclaration_method :: FieldName
- _ClassMemberDeclaration_class :: FieldName
- _ClassMemberDeclaration_interface :: FieldName
- _ClassMemberDeclaration_none :: FieldName
- data FieldDeclaration = FieldDeclaration {}
- _FieldDeclaration :: Name
- _FieldDeclaration_modifiers :: FieldName
- _FieldDeclaration_unannType :: FieldName
- _FieldDeclaration_variableDeclarators :: FieldName
- data FieldModifier
- _FieldModifier :: Name
- _FieldModifier_annotation :: FieldName
- _FieldModifier_public :: FieldName
- _FieldModifier_protected :: FieldName
- _FieldModifier_private :: FieldName
- _FieldModifier_static :: FieldName
- _FieldModifier_final :: FieldName
- _FieldModifier_transient :: FieldName
- _FieldModifier_volatile :: FieldName
- data VariableDeclarator = VariableDeclarator {}
- _VariableDeclarator :: Name
- _VariableDeclarator_id :: FieldName
- _VariableDeclarator_initializer :: FieldName
- data VariableDeclaratorId = VariableDeclaratorId {}
- _VariableDeclaratorId :: Name
- _VariableDeclaratorId_identifier :: FieldName
- _VariableDeclaratorId_dims :: FieldName
- data VariableInitializer
- _VariableInitializer :: Name
- _VariableInitializer_expression :: FieldName
- _VariableInitializer_arrayInitializer :: FieldName
- newtype UnannType = UnannType {
- unUnannType :: Type
- _UnannType :: Name
- newtype UnannClassType = UnannClassType {}
- _UnannClassType :: Name
- data MethodDeclaration = MethodDeclaration {}
- _MethodDeclaration :: Name
- _MethodDeclaration_annotations :: FieldName
- _MethodDeclaration_modifiers :: FieldName
- _MethodDeclaration_header :: FieldName
- _MethodDeclaration_body :: FieldName
- data MethodModifier
- _MethodModifier :: Name
- _MethodModifier_annotation :: FieldName
- _MethodModifier_public :: FieldName
- _MethodModifier_protected :: FieldName
- _MethodModifier_private :: FieldName
- _MethodModifier_abstract :: FieldName
- _MethodModifier_static :: FieldName
- _MethodModifier_final :: FieldName
- _MethodModifier_synchronized :: FieldName
- _MethodModifier_native :: FieldName
- _MethodModifier_strictfb :: FieldName
- data MethodHeader = MethodHeader {}
- _MethodHeader :: Name
- _MethodHeader_parameters :: FieldName
- _MethodHeader_result :: FieldName
- _MethodHeader_declarator :: FieldName
- _MethodHeader_throws :: FieldName
- data Result
- _Result :: Name
- _Result_type :: FieldName
- _Result_void :: FieldName
- data MethodDeclarator = MethodDeclarator {}
- _MethodDeclarator :: Name
- _MethodDeclarator_identifier :: FieldName
- _MethodDeclarator_receiverParameter :: FieldName
- _MethodDeclarator_formalParameters :: FieldName
- data ReceiverParameter = ReceiverParameter {}
- _ReceiverParameter :: Name
- _ReceiverParameter_annotations :: FieldName
- _ReceiverParameter_unannType :: FieldName
- _ReceiverParameter_identifier :: FieldName
- data FormalParameter
- _FormalParameter :: Name
- _FormalParameter_simple :: FieldName
- _FormalParameter_variableArity :: FieldName
- data FormalParameter_Simple = FormalParameter_Simple {}
- _FormalParameter_Simple :: Name
- _FormalParameter_Simple_modifiers :: FieldName
- _FormalParameter_Simple_type :: FieldName
- _FormalParameter_Simple_id :: FieldName
- data VariableArityParameter = VariableArityParameter {}
- _VariableArityParameter :: Name
- _VariableArityParameter_modifiers :: FieldName
- _VariableArityParameter_type :: FieldName
- _VariableArityParameter_annotations :: FieldName
- _VariableArityParameter_identifier :: FieldName
- data VariableModifier
- _VariableModifier :: Name
- _VariableModifier_annotation :: FieldName
- _VariableModifier_final :: FieldName
- newtype Throws = Throws {
- unThrows :: [ExceptionType]
- _Throws :: Name
- data ExceptionType
- _ExceptionType :: Name
- _ExceptionType_class :: FieldName
- _ExceptionType_variable :: FieldName
- data MethodBody
- _MethodBody :: Name
- _MethodBody_block :: FieldName
- _MethodBody_none :: FieldName
- newtype InstanceInitializer = InstanceInitializer {}
- _InstanceInitializer :: Name
- newtype StaticInitializer = StaticInitializer {}
- _StaticInitializer :: Name
- data ConstructorDeclaration = ConstructorDeclaration {}
- _ConstructorDeclaration :: Name
- _ConstructorDeclaration_modifiers :: FieldName
- _ConstructorDeclaration_constructor :: FieldName
- _ConstructorDeclaration_throws :: FieldName
- _ConstructorDeclaration_body :: FieldName
- data ConstructorModifier
- _ConstructorModifier :: Name
- _ConstructorModifier_annotation :: FieldName
- _ConstructorModifier_public :: FieldName
- _ConstructorModifier_protected :: FieldName
- _ConstructorModifier_private :: FieldName
- data ConstructorDeclarator = ConstructorDeclarator {}
- _ConstructorDeclarator :: Name
- _ConstructorDeclarator_parameters :: FieldName
- _ConstructorDeclarator_name :: FieldName
- _ConstructorDeclarator_receiverParameter :: FieldName
- _ConstructorDeclarator_formalParameters :: FieldName
- newtype SimpleTypeName = SimpleTypeName {}
- _SimpleTypeName :: Name
- data ConstructorBody = ConstructorBody {}
- _ConstructorBody :: Name
- _ConstructorBody_invocation :: FieldName
- _ConstructorBody_statements :: FieldName
- data ExplicitConstructorInvocation = ExplicitConstructorInvocation {}
- _ExplicitConstructorInvocation :: Name
- _ExplicitConstructorInvocation_typeArguments :: FieldName
- _ExplicitConstructorInvocation_arguments :: FieldName
- _ExplicitConstructorInvocation_variant :: FieldName
- data ExplicitConstructorInvocation_Variant
- _ExplicitConstructorInvocation_Variant :: Name
- _ExplicitConstructorInvocation_Variant_this :: FieldName
- _ExplicitConstructorInvocation_Variant_super :: FieldName
- _ExplicitConstructorInvocation_Variant_primary :: FieldName
- data EnumDeclaration = EnumDeclaration {}
- _EnumDeclaration :: Name
- _EnumDeclaration_modifiers :: FieldName
- _EnumDeclaration_identifier :: FieldName
- _EnumDeclaration_implements :: FieldName
- _EnumDeclaration_body :: FieldName
- newtype EnumBody = EnumBody {}
- _EnumBody :: Name
- data EnumBody_Element = EnumBody_Element {}
- _EnumBody_Element :: Name
- _EnumBody_Element_constants :: FieldName
- _EnumBody_Element_bodyDeclarations :: FieldName
- data EnumConstant = EnumConstant {}
- _EnumConstant :: Name
- _EnumConstant_modifiers :: FieldName
- _EnumConstant_identifier :: FieldName
- _EnumConstant_arguments :: FieldName
- _EnumConstant_body :: FieldName
- newtype EnumConstantModifier = EnumConstantModifier {}
- _EnumConstantModifier :: Name
- data InterfaceDeclaration
- _InterfaceDeclaration :: Name
- _InterfaceDeclaration_normalInterface :: FieldName
- _InterfaceDeclaration_annotationType :: FieldName
- data NormalInterfaceDeclaration = NormalInterfaceDeclaration {}
- _NormalInterfaceDeclaration :: Name
- _NormalInterfaceDeclaration_modifiers :: FieldName
- _NormalInterfaceDeclaration_identifier :: FieldName
- _NormalInterfaceDeclaration_parameters :: FieldName
- _NormalInterfaceDeclaration_extends :: FieldName
- _NormalInterfaceDeclaration_body :: FieldName
- data InterfaceModifier
- _InterfaceModifier :: Name
- _InterfaceModifier_annotation :: FieldName
- _InterfaceModifier_public :: FieldName
- _InterfaceModifier_protected :: FieldName
- _InterfaceModifier_private :: FieldName
- _InterfaceModifier_abstract :: FieldName
- _InterfaceModifier_static :: FieldName
- _InterfaceModifier_strictfb :: FieldName
- newtype InterfaceBody = InterfaceBody {}
- _InterfaceBody :: Name
- data InterfaceMemberDeclaration
- _InterfaceMemberDeclaration :: Name
- _InterfaceMemberDeclaration_constant :: FieldName
- _InterfaceMemberDeclaration_interfaceMethod :: FieldName
- _InterfaceMemberDeclaration_class :: FieldName
- _InterfaceMemberDeclaration_interface :: FieldName
- data ConstantDeclaration = ConstantDeclaration {}
- _ConstantDeclaration :: Name
- _ConstantDeclaration_modifiers :: FieldName
- _ConstantDeclaration_type :: FieldName
- _ConstantDeclaration_variables :: FieldName
- data ConstantModifier
- _ConstantModifier :: Name
- _ConstantModifier_annotation :: FieldName
- _ConstantModifier_public :: FieldName
- _ConstantModifier_static :: FieldName
- _ConstantModifier_final :: FieldName
- data InterfaceMethodDeclaration = InterfaceMethodDeclaration {}
- _InterfaceMethodDeclaration :: Name
- _InterfaceMethodDeclaration_modifiers :: FieldName
- _InterfaceMethodDeclaration_header :: FieldName
- _InterfaceMethodDeclaration_body :: FieldName
- data InterfaceMethodModifier
- _InterfaceMethodModifier :: Name
- _InterfaceMethodModifier_annotation :: FieldName
- _InterfaceMethodModifier_public :: FieldName
- _InterfaceMethodModifier_private :: FieldName
- _InterfaceMethodModifier_abstract :: FieldName
- _InterfaceMethodModifier_default :: FieldName
- _InterfaceMethodModifier_static :: FieldName
- _InterfaceMethodModifier_strictfp :: FieldName
- data AnnotationTypeDeclaration = AnnotationTypeDeclaration {}
- _AnnotationTypeDeclaration :: Name
- _AnnotationTypeDeclaration_modifiers :: FieldName
- _AnnotationTypeDeclaration_identifier :: FieldName
- _AnnotationTypeDeclaration_body :: FieldName
- newtype AnnotationTypeBody = AnnotationTypeBody {}
- _AnnotationTypeBody :: Name
- data AnnotationTypeMemberDeclaration
- _AnnotationTypeMemberDeclaration :: Name
- _AnnotationTypeMemberDeclaration_annotationType :: FieldName
- _AnnotationTypeMemberDeclaration_constant :: FieldName
- _AnnotationTypeMemberDeclaration_class :: FieldName
- _AnnotationTypeMemberDeclaration_interface :: FieldName
- data AnnotationTypeElementDeclaration = AnnotationTypeElementDeclaration {}
- _AnnotationTypeElementDeclaration :: Name
- _AnnotationTypeElementDeclaration_modifiers :: FieldName
- _AnnotationTypeElementDeclaration_type :: FieldName
- _AnnotationTypeElementDeclaration_identifier :: FieldName
- _AnnotationTypeElementDeclaration_dims :: FieldName
- _AnnotationTypeElementDeclaration_default :: FieldName
- data AnnotationTypeElementModifier
- _AnnotationTypeElementModifier :: Name
- _AnnotationTypeElementModifier_public :: FieldName
- _AnnotationTypeElementModifier_abstract :: FieldName
- newtype DefaultValue = DefaultValue {}
- _DefaultValue :: Name
- data Annotation
- _Annotation :: Name
- _Annotation_normal :: FieldName
- _Annotation_marker :: FieldName
- _Annotation_singleElement :: FieldName
- data NormalAnnotation = NormalAnnotation {}
- _NormalAnnotation :: Name
- _NormalAnnotation_typeName :: FieldName
- _NormalAnnotation_pairs :: FieldName
- data ElementValuePair = ElementValuePair {}
- _ElementValuePair :: Name
- _ElementValuePair_key :: FieldName
- _ElementValuePair_value :: FieldName
- data ElementValue
- _ElementValue :: Name
- _ElementValue_conditionalExpression :: FieldName
- _ElementValue_elementValueArrayInitializer :: FieldName
- _ElementValue_annotation :: FieldName
- newtype ElementValueArrayInitializer = ElementValueArrayInitializer {}
- _ElementValueArrayInitializer :: Name
- newtype MarkerAnnotation = MarkerAnnotation {}
- _MarkerAnnotation :: Name
- data SingleElementAnnotation = SingleElementAnnotation {}
- _SingleElementAnnotation :: Name
- _SingleElementAnnotation_name :: FieldName
- _SingleElementAnnotation_value :: FieldName
- newtype ArrayInitializer = ArrayInitializer {}
- _ArrayInitializer :: Name
- newtype Block = Block {
- unBlock :: [BlockStatement]
- _Block :: Name
- data BlockStatement
- _BlockStatement :: Name
- _BlockStatement_localVariableDeclaration :: FieldName
- _BlockStatement_class :: FieldName
- _BlockStatement_statement :: FieldName
- newtype LocalVariableDeclarationStatement = LocalVariableDeclarationStatement {}
- _LocalVariableDeclarationStatement :: Name
- data LocalVariableDeclaration = LocalVariableDeclaration {}
- _LocalVariableDeclaration :: Name
- _LocalVariableDeclaration_modifiers :: FieldName
- _LocalVariableDeclaration_type :: FieldName
- _LocalVariableDeclaration_declarators :: FieldName
- data LocalVariableType
- _LocalVariableType :: Name
- _LocalVariableType_type :: FieldName
- _LocalVariableType_var :: FieldName
- data Statement
- _Statement :: Name
- _Statement_withoutTrailing :: FieldName
- _Statement_labeled :: FieldName
- _Statement_ifThen :: FieldName
- _Statement_ifThenElse :: FieldName
- _Statement_while :: FieldName
- _Statement_for :: FieldName
- data StatementNoShortIf
- _StatementNoShortIf :: Name
- _StatementNoShortIf_withoutTrailing :: FieldName
- _StatementNoShortIf_labeled :: FieldName
- _StatementNoShortIf_ifThenElse :: FieldName
- _StatementNoShortIf_while :: FieldName
- _StatementNoShortIf_for :: FieldName
- data StatementWithoutTrailingSubstatement
- = StatementWithoutTrailingSubstatementBlock Block
- | StatementWithoutTrailingSubstatementEmpty EmptyStatement
- | StatementWithoutTrailingSubstatementExpression ExpressionStatement
- | StatementWithoutTrailingSubstatementAssert AssertStatement
- | StatementWithoutTrailingSubstatementSwitch SwitchStatement
- | StatementWithoutTrailingSubstatementDo DoStatement
- | StatementWithoutTrailingSubstatementBreak BreakStatement
- | StatementWithoutTrailingSubstatementContinue ContinueStatement
- | StatementWithoutTrailingSubstatementReturn ReturnStatement
- | StatementWithoutTrailingSubstatementSynchronized SynchronizedStatement
- | StatementWithoutTrailingSubstatementThrow ThrowStatement
- | StatementWithoutTrailingSubstatementTry TryStatement
- _StatementWithoutTrailingSubstatement :: Name
- _StatementWithoutTrailingSubstatement_block :: FieldName
- _StatementWithoutTrailingSubstatement_empty :: FieldName
- _StatementWithoutTrailingSubstatement_expression :: FieldName
- _StatementWithoutTrailingSubstatement_assert :: FieldName
- _StatementWithoutTrailingSubstatement_switch :: FieldName
- _StatementWithoutTrailingSubstatement_do :: FieldName
- _StatementWithoutTrailingSubstatement_break :: FieldName
- _StatementWithoutTrailingSubstatement_continue :: FieldName
- _StatementWithoutTrailingSubstatement_return :: FieldName
- _StatementWithoutTrailingSubstatement_synchronized :: FieldName
- _StatementWithoutTrailingSubstatement_throw :: FieldName
- _StatementWithoutTrailingSubstatement_try :: FieldName
- data EmptyStatement = EmptyStatement {
- _EmptyStatement :: Name
- data LabeledStatement = LabeledStatement {}
- _LabeledStatement :: Name
- _LabeledStatement_identifier :: FieldName
- _LabeledStatement_statement :: FieldName
- data LabeledStatementNoShortIf = LabeledStatementNoShortIf {}
- _LabeledStatementNoShortIf :: Name
- _LabeledStatementNoShortIf_identifier :: FieldName
- _LabeledStatementNoShortIf_statement :: FieldName
- newtype ExpressionStatement = ExpressionStatement {}
- _ExpressionStatement :: Name
- data StatementExpression
- = StatementExpressionAssignment Assignment
- | StatementExpressionPreIncrement PreIncrementExpression
- | StatementExpressionPreDecrement PreDecrementExpression
- | StatementExpressionPostIncrement PostIncrementExpression
- | StatementExpressionPostDecrement PostDecrementExpression
- | StatementExpressionMethodInvocation MethodInvocation
- | StatementExpressionClassInstanceCreation ClassInstanceCreationExpression
- _StatementExpression :: Name
- _StatementExpression_assignment :: FieldName
- _StatementExpression_preIncrement :: FieldName
- _StatementExpression_preDecrement :: FieldName
- _StatementExpression_postIncrement :: FieldName
- _StatementExpression_postDecrement :: FieldName
- _StatementExpression_methodInvocation :: FieldName
- _StatementExpression_classInstanceCreation :: FieldName
- data IfThenStatement = IfThenStatement {}
- _IfThenStatement :: Name
- _IfThenStatement_expression :: FieldName
- _IfThenStatement_statement :: FieldName
- data IfThenElseStatement = IfThenElseStatement {}
- _IfThenElseStatement :: Name
- _IfThenElseStatement_cond :: FieldName
- _IfThenElseStatement_then :: FieldName
- _IfThenElseStatement_else :: FieldName
- data IfThenElseStatementNoShortIf = IfThenElseStatementNoShortIf {}
- _IfThenElseStatementNoShortIf :: Name
- _IfThenElseStatementNoShortIf_cond :: FieldName
- _IfThenElseStatementNoShortIf_then :: FieldName
- _IfThenElseStatementNoShortIf_else :: FieldName
- data AssertStatement
- _AssertStatement :: Name
- _AssertStatement_single :: FieldName
- _AssertStatement_pair :: FieldName
- data AssertStatement_Pair = AssertStatement_Pair {}
- _AssertStatement_Pair :: Name
- _AssertStatement_Pair_first :: FieldName
- _AssertStatement_Pair_second :: FieldName
- data SwitchStatement = SwitchStatement {}
- _SwitchStatement :: Name
- _SwitchStatement_cond :: FieldName
- _SwitchStatement_block :: FieldName
- newtype SwitchBlock = SwitchBlock {}
- _SwitchBlock :: Name
- data SwitchBlock_Pair = SwitchBlock_Pair {}
- _SwitchBlock_Pair :: Name
- _SwitchBlock_Pair_statements :: FieldName
- _SwitchBlock_Pair_labels :: FieldName
- data SwitchBlockStatementGroup = SwitchBlockStatementGroup {}
- _SwitchBlockStatementGroup :: Name
- _SwitchBlockStatementGroup_labels :: FieldName
- _SwitchBlockStatementGroup_statements :: FieldName
- data SwitchLabel
- _SwitchLabel :: Name
- _SwitchLabel_constant :: FieldName
- _SwitchLabel_enumConstant :: FieldName
- _SwitchLabel_default :: FieldName
- newtype EnumConstantName = EnumConstantName {}
- _EnumConstantName :: Name
- data WhileStatement = WhileStatement {}
- _WhileStatement :: Name
- _WhileStatement_cond :: FieldName
- _WhileStatement_body :: FieldName
- data WhileStatementNoShortIf = WhileStatementNoShortIf {}
- _WhileStatementNoShortIf :: Name
- _WhileStatementNoShortIf_cond :: FieldName
- _WhileStatementNoShortIf_body :: FieldName
- data DoStatement = DoStatement {}
- _DoStatement :: Name
- _DoStatement_body :: FieldName
- _DoStatement_conde :: FieldName
- data ForStatement
- _ForStatement :: Name
- _ForStatement_basic :: FieldName
- _ForStatement_enhanced :: FieldName
- data ForStatementNoShortIf
- _ForStatementNoShortIf :: Name
- _ForStatementNoShortIf_basic :: FieldName
- _ForStatementNoShortIf_enhanced :: FieldName
- data BasicForStatement = BasicForStatement {}
- _BasicForStatement :: Name
- _BasicForStatement_cond :: FieldName
- _BasicForStatement_body :: FieldName
- data ForCond = ForCond {}
- _ForCond :: Name
- _ForCond_init :: FieldName
- _ForCond_cond :: FieldName
- _ForCond_update :: FieldName
- data BasicForStatementNoShortIf = BasicForStatementNoShortIf {}
- _BasicForStatementNoShortIf :: Name
- _BasicForStatementNoShortIf_cond :: FieldName
- _BasicForStatementNoShortIf_body :: FieldName
- data ForInit
- _ForInit :: Name
- _ForInit_statements :: FieldName
- _ForInit_localVariable :: FieldName
- newtype ForUpdate = ForUpdate {}
- _ForUpdate :: Name
- data EnhancedForStatement = EnhancedForStatement {}
- _EnhancedForStatement :: Name
- _EnhancedForStatement_cond :: FieldName
- _EnhancedForStatement_body :: FieldName
- data EnhancedForCond = EnhancedForCond {}
- _EnhancedForCond :: Name
- _EnhancedForCond_modifiers :: FieldName
- _EnhancedForCond_type :: FieldName
- _EnhancedForCond_id :: FieldName
- _EnhancedForCond_expression :: FieldName
- data EnhancedForStatementNoShortIf = EnhancedForStatementNoShortIf {}
- _EnhancedForStatementNoShortIf :: Name
- _EnhancedForStatementNoShortIf_cond :: FieldName
- _EnhancedForStatementNoShortIf_body :: FieldName
- newtype BreakStatement = BreakStatement {}
- _BreakStatement :: Name
- newtype ContinueStatement = ContinueStatement {}
- _ContinueStatement :: Name
- newtype ReturnStatement = ReturnStatement {}
- _ReturnStatement :: Name
- newtype ThrowStatement = ThrowStatement {}
- _ThrowStatement :: Name
- data SynchronizedStatement = SynchronizedStatement {}
- _SynchronizedStatement :: Name
- _SynchronizedStatement_expression :: FieldName
- _SynchronizedStatement_block :: FieldName
- data TryStatement
- _TryStatement :: Name
- _TryStatement_simple :: FieldName
- _TryStatement_withFinally :: FieldName
- _TryStatement_withResources :: FieldName
- data TryStatement_Simple = TryStatement_Simple {}
- _TryStatement_Simple :: Name
- _TryStatement_Simple_block :: FieldName
- _TryStatement_Simple_catches :: FieldName
- data TryStatement_WithFinally = TryStatement_WithFinally {}
- _TryStatement_WithFinally :: Name
- _TryStatement_WithFinally_block :: FieldName
- _TryStatement_WithFinally_catches :: FieldName
- _TryStatement_WithFinally_finally :: FieldName
- newtype Catches = Catches {
- unCatches :: [CatchClause]
- _Catches :: Name
- data CatchClause = CatchClause {}
- _CatchClause :: Name
- _CatchClause_parameter :: FieldName
- _CatchClause_block :: FieldName
- data CatchFormalParameter = CatchFormalParameter {}
- _CatchFormalParameter :: Name
- _CatchFormalParameter_modifiers :: FieldName
- _CatchFormalParameter_type :: FieldName
- _CatchFormalParameter_id :: FieldName
- data CatchType = CatchType {}
- _CatchType :: Name
- _CatchType_type :: FieldName
- _CatchType_types :: FieldName
- newtype Finally = Finally {}
- _Finally :: Name
- data TryWithResourcesStatement = TryWithResourcesStatement {}
- _TryWithResourcesStatement :: Name
- _TryWithResourcesStatement_resourceSpecification :: FieldName
- _TryWithResourcesStatement_block :: FieldName
- _TryWithResourcesStatement_catches :: FieldName
- _TryWithResourcesStatement_finally :: FieldName
- newtype ResourceSpecification = ResourceSpecification {}
- _ResourceSpecification :: Name
- data Resource
- _Resource :: Name
- _Resource_local :: FieldName
- _Resource_variable :: FieldName
- data Resource_Local = Resource_Local {}
- _Resource_Local :: Name
- _Resource_Local_modifiers :: FieldName
- _Resource_Local_type :: FieldName
- _Resource_Local_identifier :: FieldName
- _Resource_Local_expression :: FieldName
- data VariableAccess
- _VariableAccess :: Name
- _VariableAccess_expressionName :: FieldName
- _VariableAccess_fieldAccess :: FieldName
- data Primary
- _Primary :: Name
- _Primary_noNewArray :: FieldName
- _Primary_arrayCreation :: FieldName
- data PrimaryNoNewArray
- = PrimaryNoNewArrayLiteral Literal
- | PrimaryNoNewArrayClassLiteral ClassLiteral
- | PrimaryNoNewArrayThis
- | PrimaryNoNewArrayDotThis TypeName
- | PrimaryNoNewArrayParens Expression
- | PrimaryNoNewArrayClassInstance ClassInstanceCreationExpression
- | PrimaryNoNewArrayFieldAccess FieldAccess
- | PrimaryNoNewArrayArrayAccess ArrayAccess
- | PrimaryNoNewArrayMethodInvocation MethodInvocation
- | PrimaryNoNewArrayMethodReference MethodReference
- _PrimaryNoNewArray :: Name
- _PrimaryNoNewArray_literal :: FieldName
- _PrimaryNoNewArray_classLiteral :: FieldName
- _PrimaryNoNewArray_this :: FieldName
- _PrimaryNoNewArray_dotThis :: FieldName
- _PrimaryNoNewArray_parens :: FieldName
- _PrimaryNoNewArray_classInstance :: FieldName
- _PrimaryNoNewArray_fieldAccess :: FieldName
- _PrimaryNoNewArray_arrayAccess :: FieldName
- _PrimaryNoNewArray_methodInvocation :: FieldName
- _PrimaryNoNewArray_methodReference :: FieldName
- data ClassLiteral
- _ClassLiteral :: Name
- _ClassLiteral_type :: FieldName
- _ClassLiteral_numericType :: FieldName
- _ClassLiteral_boolean :: FieldName
- _ClassLiteral_void :: FieldName
- data TypeNameArray
- _TypeNameArray :: Name
- _TypeNameArray_simple :: FieldName
- _TypeNameArray_array :: FieldName
- data NumericTypeArray
- _NumericTypeArray :: Name
- _NumericTypeArray_simple :: FieldName
- _NumericTypeArray_array :: FieldName
- data BooleanArray
- _BooleanArray :: Name
- _BooleanArray_simple :: FieldName
- _BooleanArray_array :: FieldName
- data ClassInstanceCreationExpression = ClassInstanceCreationExpression {}
- _ClassInstanceCreationExpression :: Name
- _ClassInstanceCreationExpression_qualifier :: FieldName
- _ClassInstanceCreationExpression_expression :: FieldName
- data ClassInstanceCreationExpression_Qualifier
- _ClassInstanceCreationExpression_Qualifier :: Name
- _ClassInstanceCreationExpression_Qualifier_expression :: FieldName
- _ClassInstanceCreationExpression_Qualifier_primary :: FieldName
- data UnqualifiedClassInstanceCreationExpression = UnqualifiedClassInstanceCreationExpression {
- unqualifiedClassInstanceCreationExpressionTypeArguments :: [TypeArgument]
- unqualifiedClassInstanceCreationExpressionClassOrInterface :: ClassOrInterfaceTypeToInstantiate
- unqualifiedClassInstanceCreationExpressionArguments :: [Expression]
- unqualifiedClassInstanceCreationExpressionBody :: Maybe ClassBody
- _UnqualifiedClassInstanceCreationExpression :: Name
- _UnqualifiedClassInstanceCreationExpression_typeArguments :: FieldName
- _UnqualifiedClassInstanceCreationExpression_classOrInterface :: FieldName
- _UnqualifiedClassInstanceCreationExpression_arguments :: FieldName
- _UnqualifiedClassInstanceCreationExpression_body :: FieldName
- data ClassOrInterfaceTypeToInstantiate = ClassOrInterfaceTypeToInstantiate {}
- _ClassOrInterfaceTypeToInstantiate :: Name
- _ClassOrInterfaceTypeToInstantiate_identifiers :: FieldName
- _ClassOrInterfaceTypeToInstantiate_typeArguments :: FieldName
- data AnnotatedIdentifier = AnnotatedIdentifier {}
- _AnnotatedIdentifier :: Name
- _AnnotatedIdentifier_annotations :: FieldName
- _AnnotatedIdentifier_identifier :: FieldName
- data TypeArgumentsOrDiamond
- _TypeArgumentsOrDiamond :: Name
- _TypeArgumentsOrDiamond_arguments :: FieldName
- _TypeArgumentsOrDiamond_diamond :: FieldName
- data FieldAccess = FieldAccess {}
- _FieldAccess :: Name
- _FieldAccess_qualifier :: FieldName
- _FieldAccess_identifier :: FieldName
- data FieldAccess_Qualifier
- _FieldAccess_Qualifier :: Name
- _FieldAccess_Qualifier_primary :: FieldName
- _FieldAccess_Qualifier_super :: FieldName
- _FieldAccess_Qualifier_typed :: FieldName
- data ArrayAccess = ArrayAccess {}
- _ArrayAccess :: Name
- _ArrayAccess_expression :: FieldName
- _ArrayAccess_variant :: FieldName
- data ArrayAccess_Variant
- _ArrayAccess_Variant :: Name
- _ArrayAccess_Variant_name :: FieldName
- _ArrayAccess_Variant_primary :: FieldName
- data MethodInvocation = MethodInvocation {}
- _MethodInvocation :: Name
- _MethodInvocation_header :: FieldName
- _MethodInvocation_arguments :: FieldName
- data MethodInvocation_Header
- _MethodInvocation_Header :: Name
- _MethodInvocation_Header_simple :: FieldName
- _MethodInvocation_Header_complex :: FieldName
- data MethodInvocation_Complex = MethodInvocation_Complex {}
- _MethodInvocation_Complex :: Name
- _MethodInvocation_Complex_variant :: FieldName
- _MethodInvocation_Complex_typeArguments :: FieldName
- _MethodInvocation_Complex_identifier :: FieldName
- data MethodInvocation_Variant
- _MethodInvocation_Variant :: Name
- _MethodInvocation_Variant_type :: FieldName
- _MethodInvocation_Variant_expression :: FieldName
- _MethodInvocation_Variant_primary :: FieldName
- _MethodInvocation_Variant_super :: FieldName
- _MethodInvocation_Variant_typeSuper :: FieldName
- data MethodReference
- _MethodReference :: Name
- _MethodReference_expression :: FieldName
- _MethodReference_primary :: FieldName
- _MethodReference_referenceType :: FieldName
- _MethodReference_super :: FieldName
- _MethodReference_new :: FieldName
- _MethodReference_array :: FieldName
- data MethodReference_Expression = MethodReference_Expression {}
- _MethodReference_Expression :: Name
- _MethodReference_Expression_name :: FieldName
- _MethodReference_Expression_typeArguments :: FieldName
- _MethodReference_Expression_identifier :: FieldName
- data MethodReference_Primary = MethodReference_Primary {}
- _MethodReference_Primary :: Name
- _MethodReference_Primary_primary :: FieldName
- _MethodReference_Primary_typeArguments :: FieldName
- _MethodReference_Primary_identifier :: FieldName
- data MethodReference_ReferenceType = MethodReference_ReferenceType {}
- _MethodReference_ReferenceType :: Name
- _MethodReference_ReferenceType_referenceType :: FieldName
- _MethodReference_ReferenceType_typeArguments :: FieldName
- _MethodReference_ReferenceType_identifier :: FieldName
- data MethodReference_Super = MethodReference_Super {}
- _MethodReference_Super :: Name
- _MethodReference_Super_typeArguments :: FieldName
- _MethodReference_Super_identifier :: FieldName
- _MethodReference_Super_super :: FieldName
- data MethodReference_New = MethodReference_New {}
- _MethodReference_New :: Name
- _MethodReference_New_classType :: FieldName
- _MethodReference_New_typeArguments :: FieldName
- newtype MethodReference_Array = MethodReference_Array {}
- _MethodReference_Array :: Name
- data ArrayCreationExpression
- = ArrayCreationExpressionPrimitive ArrayCreationExpression_Primitive
- | ArrayCreationExpressionClassOrInterface ArrayCreationExpression_ClassOrInterface
- | ArrayCreationExpressionPrimitiveArray ArrayCreationExpression_PrimitiveArray
- | ArrayCreationExpressionClassOrInterfaceArray ArrayCreationExpression_ClassOrInterfaceArray
- _ArrayCreationExpression :: Name
- _ArrayCreationExpression_primitive :: FieldName
- _ArrayCreationExpression_classOrInterface :: FieldName
- _ArrayCreationExpression_primitiveArray :: FieldName
- _ArrayCreationExpression_classOrInterfaceArray :: FieldName
- data ArrayCreationExpression_Primitive = ArrayCreationExpression_Primitive {}
- _ArrayCreationExpression_Primitive :: Name
- _ArrayCreationExpression_Primitive_type :: FieldName
- _ArrayCreationExpression_Primitive_dimExprs :: FieldName
- _ArrayCreationExpression_Primitive_dims :: FieldName
- data ArrayCreationExpression_ClassOrInterface = ArrayCreationExpression_ClassOrInterface {}
- _ArrayCreationExpression_ClassOrInterface :: Name
- _ArrayCreationExpression_ClassOrInterface_type :: FieldName
- _ArrayCreationExpression_ClassOrInterface_dimExprs :: FieldName
- _ArrayCreationExpression_ClassOrInterface_dims :: FieldName
- data ArrayCreationExpression_PrimitiveArray = ArrayCreationExpression_PrimitiveArray {}
- _ArrayCreationExpression_PrimitiveArray :: Name
- _ArrayCreationExpression_PrimitiveArray_type :: FieldName
- _ArrayCreationExpression_PrimitiveArray_dims :: FieldName
- _ArrayCreationExpression_PrimitiveArray_array :: FieldName
- data ArrayCreationExpression_ClassOrInterfaceArray = ArrayCreationExpression_ClassOrInterfaceArray {}
- _ArrayCreationExpression_ClassOrInterfaceArray :: Name
- _ArrayCreationExpression_ClassOrInterfaceArray_type :: FieldName
- _ArrayCreationExpression_ClassOrInterfaceArray_dims :: FieldName
- _ArrayCreationExpression_ClassOrInterfaceArray_array :: FieldName
- data DimExpr = DimExpr {}
- _DimExpr :: Name
- _DimExpr_annotations :: FieldName
- _DimExpr_expression :: FieldName
- data Expression
- _Expression :: Name
- _Expression_lambda :: FieldName
- _Expression_assignment :: FieldName
- data LambdaExpression = LambdaExpression {}
- _LambdaExpression :: Name
- _LambdaExpression_parameters :: FieldName
- _LambdaExpression_body :: FieldName
- data LambdaParameters
- _LambdaParameters :: Name
- _LambdaParameters_tuple :: FieldName
- _LambdaParameters_single :: FieldName
- data LambdaParameter
- _LambdaParameter :: Name
- _LambdaParameter_normal :: FieldName
- _LambdaParameter_variableArity :: FieldName
- data LambdaParameter_Normal = LambdaParameter_Normal {}
- _LambdaParameter_Normal :: Name
- _LambdaParameter_Normal_modifiers :: FieldName
- _LambdaParameter_Normal_type :: FieldName
- _LambdaParameter_Normal_id :: FieldName
- data LambdaParameterType
- _LambdaParameterType :: Name
- _LambdaParameterType_type :: FieldName
- _LambdaParameterType_var :: FieldName
- data LambdaBody
- _LambdaBody :: Name
- _LambdaBody_expression :: FieldName
- _LambdaBody_block :: FieldName
- data AssignmentExpression
- _AssignmentExpression :: Name
- _AssignmentExpression_conditional :: FieldName
- _AssignmentExpression_assignment :: FieldName
- data Assignment = Assignment {}
- _Assignment :: Name
- _Assignment_lhs :: FieldName
- _Assignment_op :: FieldName
- _Assignment_expression :: FieldName
- data LeftHandSide
- _LeftHandSide :: Name
- _LeftHandSide_expressionName :: FieldName
- _LeftHandSide_fieldAccess :: FieldName
- _LeftHandSide_arrayAccess :: FieldName
- data AssignmentOperator
- = AssignmentOperatorSimple
- | AssignmentOperatorTimes
- | AssignmentOperatorDiv
- | AssignmentOperatorMod
- | AssignmentOperatorPlus
- | AssignmentOperatorMinus
- | AssignmentOperatorShiftLeft
- | AssignmentOperatorShiftRight
- | AssignmentOperatorShiftRightZeroFill
- | AssignmentOperatorAnd
- | AssignmentOperatorXor
- | AssignmentOperatorOr
- _AssignmentOperator :: Name
- _AssignmentOperator_simple :: FieldName
- _AssignmentOperator_times :: FieldName
- _AssignmentOperator_div :: FieldName
- _AssignmentOperator_mod :: FieldName
- _AssignmentOperator_plus :: FieldName
- _AssignmentOperator_minus :: FieldName
- _AssignmentOperator_shiftLeft :: FieldName
- _AssignmentOperator_shiftRight :: FieldName
- _AssignmentOperator_shiftRightZeroFill :: FieldName
- _AssignmentOperator_and :: FieldName
- _AssignmentOperator_xor :: FieldName
- _AssignmentOperator_or :: FieldName
- data ConditionalExpression
- _ConditionalExpression :: Name
- _ConditionalExpression_simple :: FieldName
- _ConditionalExpression_ternaryCond :: FieldName
- _ConditionalExpression_ternaryLambda :: FieldName
- data ConditionalExpression_TernaryCond = ConditionalExpression_TernaryCond {}
- _ConditionalExpression_TernaryCond :: Name
- _ConditionalExpression_TernaryCond_cond :: FieldName
- _ConditionalExpression_TernaryCond_ifTrue :: FieldName
- _ConditionalExpression_TernaryCond_ifFalse :: FieldName
- data ConditionalExpression_TernaryLambda = ConditionalExpression_TernaryLambda {}
- _ConditionalExpression_TernaryLambda :: Name
- _ConditionalExpression_TernaryLambda_cond :: FieldName
- _ConditionalExpression_TernaryLambda_ifTrue :: FieldName
- _ConditionalExpression_TernaryLambda_ifFalse :: FieldName
- newtype ConditionalOrExpression = ConditionalOrExpression {}
- _ConditionalOrExpression :: Name
- newtype ConditionalAndExpression = ConditionalAndExpression {}
- _ConditionalAndExpression :: Name
- newtype InclusiveOrExpression = InclusiveOrExpression {}
- _InclusiveOrExpression :: Name
- newtype ExclusiveOrExpression = ExclusiveOrExpression {}
- _ExclusiveOrExpression :: Name
- newtype AndExpression = AndExpression {}
- _AndExpression :: Name
- data EqualityExpression
- _EqualityExpression :: Name
- _EqualityExpression_unary :: FieldName
- _EqualityExpression_equal :: FieldName
- _EqualityExpression_notEqual :: FieldName
- data EqualityExpression_Binary = EqualityExpression_Binary {}
- _EqualityExpression_Binary :: Name
- _EqualityExpression_Binary_lhs :: FieldName
- _EqualityExpression_Binary_rhs :: FieldName
- data RelationalExpression
- = RelationalExpressionSimple ShiftExpression
- | RelationalExpressionLessThan RelationalExpression_LessThan
- | RelationalExpressionGreaterThan RelationalExpression_GreaterThan
- | RelationalExpressionLessThanEqual RelationalExpression_LessThanEqual
- | RelationalExpressionGreaterThanEqual RelationalExpression_GreaterThanEqual
- | RelationalExpressionInstanceof RelationalExpression_InstanceOf
- _RelationalExpression :: Name
- _RelationalExpression_simple :: FieldName
- _RelationalExpression_lessThan :: FieldName
- _RelationalExpression_greaterThan :: FieldName
- _RelationalExpression_lessThanEqual :: FieldName
- _RelationalExpression_greaterThanEqual :: FieldName
- _RelationalExpression_instanceof :: FieldName
- data RelationalExpression_LessThan = RelationalExpression_LessThan {}
- _RelationalExpression_LessThan :: Name
- _RelationalExpression_LessThan_lhs :: FieldName
- _RelationalExpression_LessThan_rhs :: FieldName
- data RelationalExpression_GreaterThan = RelationalExpression_GreaterThan {}
- _RelationalExpression_GreaterThan :: Name
- _RelationalExpression_GreaterThan_lhs :: FieldName
- _RelationalExpression_GreaterThan_rhs :: FieldName
- data RelationalExpression_LessThanEqual = RelationalExpression_LessThanEqual {}
- _RelationalExpression_LessThanEqual :: Name
- _RelationalExpression_LessThanEqual_lhs :: FieldName
- _RelationalExpression_LessThanEqual_rhs :: FieldName
- data RelationalExpression_GreaterThanEqual = RelationalExpression_GreaterThanEqual {}
- _RelationalExpression_GreaterThanEqual :: Name
- _RelationalExpression_GreaterThanEqual_lhs :: FieldName
- _RelationalExpression_GreaterThanEqual_rhs :: FieldName
- data RelationalExpression_InstanceOf = RelationalExpression_InstanceOf {}
- _RelationalExpression_InstanceOf :: Name
- _RelationalExpression_InstanceOf_lhs :: FieldName
- _RelationalExpression_InstanceOf_rhs :: FieldName
- data ShiftExpression
- _ShiftExpression :: Name
- _ShiftExpression_unary :: FieldName
- _ShiftExpression_shiftLeft :: FieldName
- _ShiftExpression_shiftRight :: FieldName
- _ShiftExpression_shiftRightZeroFill :: FieldName
- data ShiftExpression_Binary = ShiftExpression_Binary {}
- _ShiftExpression_Binary :: Name
- _ShiftExpression_Binary_lhs :: FieldName
- _ShiftExpression_Binary_rhs :: FieldName
- data AdditiveExpression
- _AdditiveExpression :: Name
- _AdditiveExpression_unary :: FieldName
- _AdditiveExpression_plus :: FieldName
- _AdditiveExpression_minus :: FieldName
- data AdditiveExpression_Binary = AdditiveExpression_Binary {}
- _AdditiveExpression_Binary :: Name
- _AdditiveExpression_Binary_lhs :: FieldName
- _AdditiveExpression_Binary_rhs :: FieldName
- data MultiplicativeExpression
- _MultiplicativeExpression :: Name
- _MultiplicativeExpression_unary :: FieldName
- _MultiplicativeExpression_times :: FieldName
- _MultiplicativeExpression_divide :: FieldName
- _MultiplicativeExpression_mod :: FieldName
- data MultiplicativeExpression_Binary = MultiplicativeExpression_Binary {}
- _MultiplicativeExpression_Binary :: Name
- _MultiplicativeExpression_Binary_lhs :: FieldName
- _MultiplicativeExpression_Binary_rhs :: FieldName
- data UnaryExpression
- _UnaryExpression :: Name
- _UnaryExpression_preIncrement :: FieldName
- _UnaryExpression_preDecrement :: FieldName
- _UnaryExpression_plus :: FieldName
- _UnaryExpression_minus :: FieldName
- _UnaryExpression_other :: FieldName
- newtype PreIncrementExpression = PreIncrementExpression {}
- _PreIncrementExpression :: Name
- newtype PreDecrementExpression = PreDecrementExpression {}
- _PreDecrementExpression :: Name
- data UnaryExpressionNotPlusMinus
- _UnaryExpressionNotPlusMinus :: Name
- _UnaryExpressionNotPlusMinus_postfix :: FieldName
- _UnaryExpressionNotPlusMinus_tilde :: FieldName
- _UnaryExpressionNotPlusMinus_not :: FieldName
- _UnaryExpressionNotPlusMinus_cast :: FieldName
- data PostfixExpression
- _PostfixExpression :: Name
- _PostfixExpression_primary :: FieldName
- _PostfixExpression_name :: FieldName
- _PostfixExpression_postIncrement :: FieldName
- _PostfixExpression_postDecrement :: FieldName
- newtype PostIncrementExpression = PostIncrementExpression {}
- _PostIncrementExpression :: Name
- newtype PostDecrementExpression = PostDecrementExpression {}
- _PostDecrementExpression :: Name
- data CastExpression
- _CastExpression :: Name
- _CastExpression_primitive :: FieldName
- _CastExpression_notPlusMinus :: FieldName
- _CastExpression_lambda :: FieldName
- data CastExpression_Primitive = CastExpression_Primitive {}
- _CastExpression_Primitive :: Name
- _CastExpression_Primitive_type :: FieldName
- _CastExpression_Primitive_expression :: FieldName
- data CastExpression_NotPlusMinus = CastExpression_NotPlusMinus {}
- _CastExpression_NotPlusMinus :: Name
- _CastExpression_NotPlusMinus_refAndBounds :: FieldName
- _CastExpression_NotPlusMinus_expression :: FieldName
- data CastExpression_Lambda = CastExpression_Lambda {}
- _CastExpression_Lambda :: Name
- _CastExpression_Lambda_refAndBounds :: FieldName
- _CastExpression_Lambda_expression :: FieldName
- data CastExpression_RefAndBounds = CastExpression_RefAndBounds {}
- _CastExpression_RefAndBounds :: Name
- _CastExpression_RefAndBounds_type :: FieldName
- _CastExpression_RefAndBounds_bounds :: FieldName
- newtype ConstantExpression = ConstantExpression {}
- _ConstantExpression :: Name
Documentation
newtype Identifier Source #
Constructors
Identifier | |
Fields |
Instances
Read Identifier Source # | |
Defined in Hydra.Ext.Java.Syntax Methods readsPrec :: Int -> ReadS Identifier # readList :: ReadS [Identifier] # readPrec :: ReadPrec Identifier # readListPrec :: ReadPrec [Identifier] # | |
Show Identifier Source # | |
Defined in Hydra.Ext.Java.Syntax Methods showsPrec :: Int -> Identifier -> ShowS # show :: Identifier -> String # showList :: [Identifier] -> ShowS # | |
Eq Identifier Source # | |
Defined in Hydra.Ext.Java.Syntax | |
Ord Identifier Source # | |
Defined in Hydra.Ext.Java.Syntax Methods compare :: Identifier -> Identifier -> Ordering # (<) :: Identifier -> Identifier -> Bool # (<=) :: Identifier -> Identifier -> Bool # (>) :: Identifier -> Identifier -> Bool # (>=) :: Identifier -> Identifier -> Bool # max :: Identifier -> Identifier -> Identifier # min :: Identifier -> Identifier -> Identifier # |
_Identifier :: Name Source #
newtype TypeIdentifier Source #
Constructors
TypeIdentifier | |
Fields |
Instances
Read TypeIdentifier Source # | |
Defined in Hydra.Ext.Java.Syntax Methods readsPrec :: Int -> ReadS TypeIdentifier # readList :: ReadS [TypeIdentifier] # | |
Show TypeIdentifier Source # | |
Defined in Hydra.Ext.Java.Syntax Methods showsPrec :: Int -> TypeIdentifier -> ShowS # show :: TypeIdentifier -> String # showList :: [TypeIdentifier] -> ShowS # | |
Eq TypeIdentifier Source # | |
Defined in Hydra.Ext.Java.Syntax Methods (==) :: TypeIdentifier -> TypeIdentifier -> Bool # (/=) :: TypeIdentifier -> TypeIdentifier -> Bool # | |
Ord TypeIdentifier Source # | |
Defined in Hydra.Ext.Java.Syntax Methods compare :: TypeIdentifier -> TypeIdentifier -> Ordering # (<) :: TypeIdentifier -> TypeIdentifier -> Bool # (<=) :: TypeIdentifier -> TypeIdentifier -> Bool # (>) :: TypeIdentifier -> TypeIdentifier -> Bool # (>=) :: TypeIdentifier -> TypeIdentifier -> Bool # max :: TypeIdentifier -> TypeIdentifier -> TypeIdentifier # min :: TypeIdentifier -> TypeIdentifier -> TypeIdentifier # |
Constructors
LiteralNull | |
LiteralInteger IntegerLiteral | |
LiteralFloatingPoint FloatingPointLiteral | |
LiteralBoolean Bool | |
LiteralCharacter Int | |
LiteralString StringLiteral |
newtype IntegerLiteral Source #
Note: this is an approximation which ignores encoding
Constructors
IntegerLiteral | |
Fields
|
Instances
Read IntegerLiteral Source # | |
Defined in Hydra.Ext.Java.Syntax Methods readsPrec :: Int -> ReadS IntegerLiteral # readList :: ReadS [IntegerLiteral] # | |
Show IntegerLiteral Source # | |
Defined in Hydra.Ext.Java.Syntax Methods showsPrec :: Int -> IntegerLiteral -> ShowS # show :: IntegerLiteral -> String # showList :: [IntegerLiteral] -> ShowS # | |
Eq IntegerLiteral Source # | |
Defined in Hydra.Ext.Java.Syntax Methods (==) :: IntegerLiteral -> IntegerLiteral -> Bool # (/=) :: IntegerLiteral -> IntegerLiteral -> Bool # | |
Ord IntegerLiteral Source # | |
Defined in Hydra.Ext.Java.Syntax Methods compare :: IntegerLiteral -> IntegerLiteral -> Ordering # (<) :: IntegerLiteral -> IntegerLiteral -> Bool # (<=) :: IntegerLiteral -> IntegerLiteral -> Bool # (>) :: IntegerLiteral -> IntegerLiteral -> Bool # (>=) :: IntegerLiteral -> IntegerLiteral -> Bool # max :: IntegerLiteral -> IntegerLiteral -> IntegerLiteral # min :: IntegerLiteral -> IntegerLiteral -> IntegerLiteral # |
newtype FloatingPointLiteral Source #
Note: this is an approximation which ignores encoding
Constructors
FloatingPointLiteral | |
Fields
|
Instances
newtype StringLiteral Source #
Note: this is an approximation which ignores encoding
Constructors
StringLiteral | |
Fields
|
Instances
Read StringLiteral Source # | |
Defined in Hydra.Ext.Java.Syntax Methods readsPrec :: Int -> ReadS StringLiteral # readList :: ReadS [StringLiteral] # | |
Show StringLiteral Source # | |
Defined in Hydra.Ext.Java.Syntax Methods showsPrec :: Int -> StringLiteral -> ShowS # show :: StringLiteral -> String # showList :: [StringLiteral] -> ShowS # | |
Eq StringLiteral Source # | |
Defined in Hydra.Ext.Java.Syntax Methods (==) :: StringLiteral -> StringLiteral -> Bool # (/=) :: StringLiteral -> StringLiteral -> Bool # | |
Ord StringLiteral Source # | |
Defined in Hydra.Ext.Java.Syntax Methods compare :: StringLiteral -> StringLiteral -> Ordering # (<) :: StringLiteral -> StringLiteral -> Bool # (<=) :: StringLiteral -> StringLiteral -> Bool # (>) :: StringLiteral -> StringLiteral -> Bool # (>=) :: StringLiteral -> StringLiteral -> Bool # max :: StringLiteral -> StringLiteral -> StringLiteral # min :: StringLiteral -> StringLiteral -> StringLiteral # |
data PrimitiveTypeWithAnnotations Source #
Constructors
PrimitiveTypeWithAnnotations | |
Instances
data PrimitiveType Source #
Constructors
PrimitiveTypeNumeric NumericType | |
PrimitiveTypeBoolean |
Instances
Read PrimitiveType Source # | |
Defined in Hydra.Ext.Java.Syntax Methods readsPrec :: Int -> ReadS PrimitiveType # readList :: ReadS [PrimitiveType] # | |
Show PrimitiveType Source # | |
Defined in Hydra.Ext.Java.Syntax Methods showsPrec :: Int -> PrimitiveType -> ShowS # show :: PrimitiveType -> String # showList :: [PrimitiveType] -> ShowS # | |
Eq PrimitiveType Source # | |
Defined in Hydra.Ext.Java.Syntax Methods (==) :: PrimitiveType -> PrimitiveType -> Bool # (/=) :: PrimitiveType -> PrimitiveType -> Bool # | |
Ord PrimitiveType Source # | |
Defined in Hydra.Ext.Java.Syntax Methods compare :: PrimitiveType -> PrimitiveType -> Ordering # (<) :: PrimitiveType -> PrimitiveType -> Bool # (<=) :: PrimitiveType -> PrimitiveType -> Bool # (>) :: PrimitiveType -> PrimitiveType -> Bool # (>=) :: PrimitiveType -> PrimitiveType -> Bool # max :: PrimitiveType -> PrimitiveType -> PrimitiveType # min :: PrimitiveType -> PrimitiveType -> PrimitiveType # |
data NumericType Source #
Instances
Read NumericType Source # | |
Defined in Hydra.Ext.Java.Syntax Methods readsPrec :: Int -> ReadS NumericType # readList :: ReadS [NumericType] # readPrec :: ReadPrec NumericType # readListPrec :: ReadPrec [NumericType] # | |
Show NumericType Source # | |
Defined in Hydra.Ext.Java.Syntax Methods showsPrec :: Int -> NumericType -> ShowS # show :: NumericType -> String # showList :: [NumericType] -> ShowS # | |
Eq NumericType Source # | |
Defined in Hydra.Ext.Java.Syntax | |
Ord NumericType Source # | |
Defined in Hydra.Ext.Java.Syntax Methods compare :: NumericType -> NumericType -> Ordering # (<) :: NumericType -> NumericType -> Bool # (<=) :: NumericType -> NumericType -> Bool # (>) :: NumericType -> NumericType -> Bool # (>=) :: NumericType -> NumericType -> Bool # max :: NumericType -> NumericType -> NumericType # min :: NumericType -> NumericType -> NumericType # |
_NumericType :: Name Source #
data IntegralType Source #
Instances
Read IntegralType Source # | |
Defined in Hydra.Ext.Java.Syntax Methods readsPrec :: Int -> ReadS IntegralType # readList :: ReadS [IntegralType] # | |
Show IntegralType Source # | |
Defined in Hydra.Ext.Java.Syntax Methods showsPrec :: Int -> IntegralType -> ShowS # show :: IntegralType -> String # showList :: [IntegralType] -> ShowS # | |
Eq IntegralType Source # | |
Defined in Hydra.Ext.Java.Syntax | |
Ord IntegralType Source # | |
Defined in Hydra.Ext.Java.Syntax Methods compare :: IntegralType -> IntegralType -> Ordering # (<) :: IntegralType -> IntegralType -> Bool # (<=) :: IntegralType -> IntegralType -> Bool # (>) :: IntegralType -> IntegralType -> Bool # (>=) :: IntegralType -> IntegralType -> Bool # max :: IntegralType -> IntegralType -> IntegralType # min :: IntegralType -> IntegralType -> IntegralType # |
_IntegralType :: Name Source #
data FloatingPointType Source #
Constructors
FloatingPointTypeFloat | |
FloatingPointTypeDouble |
Instances
data ReferenceType Source #
Constructors
ReferenceTypeClassOrInterface ClassOrInterfaceType | |
ReferenceTypeVariable TypeVariable | |
ReferenceTypeArray ArrayType |
Instances
Read ReferenceType Source # | |
Defined in Hydra.Ext.Java.Syntax Methods readsPrec :: Int -> ReadS ReferenceType # readList :: ReadS [ReferenceType] # | |
Show ReferenceType Source # | |
Defined in Hydra.Ext.Java.Syntax Methods showsPrec :: Int -> ReferenceType -> ShowS # show :: ReferenceType -> String # showList :: [ReferenceType] -> ShowS # | |
Eq ReferenceType Source # | |
Defined in Hydra.Ext.Java.Syntax Methods (==) :: ReferenceType -> ReferenceType -> Bool # (/=) :: ReferenceType -> ReferenceType -> Bool # | |
Ord ReferenceType Source # | |
Defined in Hydra.Ext.Java.Syntax Methods compare :: ReferenceType -> ReferenceType -> Ordering # (<) :: ReferenceType -> ReferenceType -> Bool # (<=) :: ReferenceType -> ReferenceType -> Bool # (>) :: ReferenceType -> ReferenceType -> Bool # (>=) :: ReferenceType -> ReferenceType -> Bool # max :: ReferenceType -> ReferenceType -> ReferenceType # min :: ReferenceType -> ReferenceType -> ReferenceType # |
data ClassOrInterfaceType Source #
Instances
Constructors
ClassType | |
Instances
Read ClassType Source # | |
Show ClassType Source # | |
Eq ClassType Source # | |
Ord ClassType Source # | |
_ClassType :: Name Source #
data ClassTypeQualifier Source #
Constructors
ClassTypeQualifierNone | |
ClassTypeQualifierPackage PackageName | |
ClassTypeQualifierParent ClassOrInterfaceType |
Instances
newtype InterfaceType Source #
Constructors
InterfaceType | |
Fields |
Instances
Read InterfaceType Source # | |
Defined in Hydra.Ext.Java.Syntax Methods readsPrec :: Int -> ReadS InterfaceType # readList :: ReadS [InterfaceType] # | |
Show InterfaceType Source # | |
Defined in Hydra.Ext.Java.Syntax Methods showsPrec :: Int -> InterfaceType -> ShowS # show :: InterfaceType -> String # showList :: [InterfaceType] -> ShowS # | |
Eq InterfaceType Source # | |
Defined in Hydra.Ext.Java.Syntax Methods (==) :: InterfaceType -> InterfaceType -> Bool # (/=) :: InterfaceType -> InterfaceType -> Bool # | |
Ord InterfaceType Source # | |
Defined in Hydra.Ext.Java.Syntax Methods compare :: InterfaceType -> InterfaceType -> Ordering # (<) :: InterfaceType -> InterfaceType -> Bool # (<=) :: InterfaceType -> InterfaceType -> Bool # (>) :: InterfaceType -> InterfaceType -> Bool # (>=) :: InterfaceType -> InterfaceType -> Bool # max :: InterfaceType -> InterfaceType -> InterfaceType # min :: InterfaceType -> InterfaceType -> InterfaceType # |
data TypeVariable Source #
Constructors
TypeVariable | |
Instances
Read TypeVariable Source # | |
Defined in Hydra.Ext.Java.Syntax Methods readsPrec :: Int -> ReadS TypeVariable # readList :: ReadS [TypeVariable] # | |
Show TypeVariable Source # | |
Defined in Hydra.Ext.Java.Syntax Methods showsPrec :: Int -> TypeVariable -> ShowS # show :: TypeVariable -> String # showList :: [TypeVariable] -> ShowS # | |
Eq TypeVariable Source # | |
Defined in Hydra.Ext.Java.Syntax | |
Ord TypeVariable Source # | |
Defined in Hydra.Ext.Java.Syntax Methods compare :: TypeVariable -> TypeVariable -> Ordering # (<) :: TypeVariable -> TypeVariable -> Bool # (<=) :: TypeVariable -> TypeVariable -> Bool # (>) :: TypeVariable -> TypeVariable -> Bool # (>=) :: TypeVariable -> TypeVariable -> Bool # max :: TypeVariable -> TypeVariable -> TypeVariable # min :: TypeVariable -> TypeVariable -> TypeVariable # |
_TypeVariable :: Name Source #
Constructors
ArrayType | |
Fields |
Instances
Read ArrayType Source # | |
Show ArrayType Source # | |
Eq ArrayType Source # | |
Ord ArrayType Source # | |
_ArrayType :: Name Source #
data ArrayType_Variant Source #
Constructors
ArrayType_VariantPrimitive PrimitiveTypeWithAnnotations | |
ArrayType_VariantClassOrInterface ClassOrInterfaceType | |
ArrayType_VariantVariable TypeVariable |
Instances
Constructors
Dims | |
Fields
|
data TypeParameter Source #
Constructors
TypeParameter | |
Instances
Read TypeParameter Source # | |
Defined in Hydra.Ext.Java.Syntax Methods readsPrec :: Int -> ReadS TypeParameter # readList :: ReadS [TypeParameter] # | |
Show TypeParameter Source # | |
Defined in Hydra.Ext.Java.Syntax Methods showsPrec :: Int -> TypeParameter -> ShowS # show :: TypeParameter -> String # showList :: [TypeParameter] -> ShowS # | |
Eq TypeParameter Source # | |
Defined in Hydra.Ext.Java.Syntax Methods (==) :: TypeParameter -> TypeParameter -> Bool # (/=) :: TypeParameter -> TypeParameter -> Bool # | |
Ord TypeParameter Source # | |
Defined in Hydra.Ext.Java.Syntax Methods compare :: TypeParameter -> TypeParameter -> Ordering # (<) :: TypeParameter -> TypeParameter -> Bool # (<=) :: TypeParameter -> TypeParameter -> Bool # (>) :: TypeParameter -> TypeParameter -> Bool # (>=) :: TypeParameter -> TypeParameter -> Bool # max :: TypeParameter -> TypeParameter -> TypeParameter # min :: TypeParameter -> TypeParameter -> TypeParameter # |
newtype TypeParameterModifier Source #
Constructors
TypeParameterModifier | |
Fields |
Instances
Instances
Read TypeBound Source # | |
Show TypeBound Source # | |
Eq TypeBound Source # | |
Ord TypeBound Source # | |
_TypeBound :: Name Source #
data TypeBound_ClassOrInterface Source #
Constructors
TypeBound_ClassOrInterface | |
Instances
newtype AdditionalBound Source #
Constructors
AdditionalBound | |
Fields |
Instances
Read AdditionalBound Source # | |
Defined in Hydra.Ext.Java.Syntax Methods readsPrec :: Int -> ReadS AdditionalBound # readList :: ReadS [AdditionalBound] # | |
Show AdditionalBound Source # | |
Defined in Hydra.Ext.Java.Syntax Methods showsPrec :: Int -> AdditionalBound -> ShowS # show :: AdditionalBound -> String # showList :: [AdditionalBound] -> ShowS # | |
Eq AdditionalBound Source # | |
Defined in Hydra.Ext.Java.Syntax Methods (==) :: AdditionalBound -> AdditionalBound -> Bool # (/=) :: AdditionalBound -> AdditionalBound -> Bool # | |
Ord AdditionalBound Source # | |
Defined in Hydra.Ext.Java.Syntax Methods compare :: AdditionalBound -> AdditionalBound -> Ordering # (<) :: AdditionalBound -> AdditionalBound -> Bool # (<=) :: AdditionalBound -> AdditionalBound -> Bool # (>) :: AdditionalBound -> AdditionalBound -> Bool # (>=) :: AdditionalBound -> AdditionalBound -> Bool # max :: AdditionalBound -> AdditionalBound -> AdditionalBound # min :: AdditionalBound -> AdditionalBound -> AdditionalBound # |
data TypeArgument Source #
Instances
Read TypeArgument Source # | |
Defined in Hydra.Ext.Java.Syntax Methods readsPrec :: Int -> ReadS TypeArgument # readList :: ReadS [TypeArgument] # | |
Show TypeArgument Source # | |
Defined in Hydra.Ext.Java.Syntax Methods showsPrec :: Int -> TypeArgument -> ShowS # show :: TypeArgument -> String # showList :: [TypeArgument] -> ShowS # | |
Eq TypeArgument Source # | |
Defined in Hydra.Ext.Java.Syntax | |
Ord TypeArgument Source # | |
Defined in Hydra.Ext.Java.Syntax Methods compare :: TypeArgument -> TypeArgument -> Ordering # (<) :: TypeArgument -> TypeArgument -> Bool # (<=) :: TypeArgument -> TypeArgument -> Bool # (>) :: TypeArgument -> TypeArgument -> Bool # (>=) :: TypeArgument -> TypeArgument -> Bool # max :: TypeArgument -> TypeArgument -> TypeArgument # min :: TypeArgument -> TypeArgument -> TypeArgument # |
_TypeArgument :: Name Source #
Constructors
Wildcard | |
Fields |
data WildcardBounds Source #
Instances
Read WildcardBounds Source # | |
Defined in Hydra.Ext.Java.Syntax Methods readsPrec :: Int -> ReadS WildcardBounds # readList :: ReadS [WildcardBounds] # | |
Show WildcardBounds Source # | |
Defined in Hydra.Ext.Java.Syntax Methods showsPrec :: Int -> WildcardBounds -> ShowS # show :: WildcardBounds -> String # showList :: [WildcardBounds] -> ShowS # | |
Eq WildcardBounds Source # | |
Defined in Hydra.Ext.Java.Syntax Methods (==) :: WildcardBounds -> WildcardBounds -> Bool # (/=) :: WildcardBounds -> WildcardBounds -> Bool # | |
Ord WildcardBounds Source # | |
Defined in Hydra.Ext.Java.Syntax Methods compare :: WildcardBounds -> WildcardBounds -> Ordering # (<) :: WildcardBounds -> WildcardBounds -> Bool # (<=) :: WildcardBounds -> WildcardBounds -> Bool # (>) :: WildcardBounds -> WildcardBounds -> Bool # (>=) :: WildcardBounds -> WildcardBounds -> Bool # max :: WildcardBounds -> WildcardBounds -> WildcardBounds # min :: WildcardBounds -> WildcardBounds -> WildcardBounds # |
data ModuleName Source #
Constructors
ModuleName | |
Fields |
Instances
Read ModuleName Source # | |
Defined in Hydra.Ext.Java.Syntax Methods readsPrec :: Int -> ReadS ModuleName # readList :: ReadS [ModuleName] # readPrec :: ReadPrec ModuleName # readListPrec :: ReadPrec [ModuleName] # | |
Show ModuleName Source # | |
Defined in Hydra.Ext.Java.Syntax Methods showsPrec :: Int -> ModuleName -> ShowS # show :: ModuleName -> String # showList :: [ModuleName] -> ShowS # | |
Eq ModuleName Source # | |
Defined in Hydra.Ext.Java.Syntax | |
Ord ModuleName Source # | |
Defined in Hydra.Ext.Java.Syntax Methods compare :: ModuleName -> ModuleName -> Ordering # (<) :: ModuleName -> ModuleName -> Bool # (<=) :: ModuleName -> ModuleName -> Bool # (>) :: ModuleName -> ModuleName -> Bool # (>=) :: ModuleName -> ModuleName -> Bool # max :: ModuleName -> ModuleName -> ModuleName # min :: ModuleName -> ModuleName -> ModuleName # |
_ModuleName :: Name Source #
newtype PackageName Source #
Constructors
PackageName | |
Fields
|
Instances
Read PackageName Source # | |
Defined in Hydra.Ext.Java.Syntax Methods readsPrec :: Int -> ReadS PackageName # readList :: ReadS [PackageName] # readPrec :: ReadPrec PackageName # readListPrec :: ReadPrec [PackageName] # | |
Show PackageName Source # | |
Defined in Hydra.Ext.Java.Syntax Methods showsPrec :: Int -> PackageName -> ShowS # show :: PackageName -> String # showList :: [PackageName] -> ShowS # | |
Eq PackageName Source # | |
Defined in Hydra.Ext.Java.Syntax | |
Ord PackageName Source # | |
Defined in Hydra.Ext.Java.Syntax Methods compare :: PackageName -> PackageName -> Ordering # (<) :: PackageName -> PackageName -> Bool # (<=) :: PackageName -> PackageName -> Bool # (>) :: PackageName -> PackageName -> Bool # (>=) :: PackageName -> PackageName -> Bool # max :: PackageName -> PackageName -> PackageName # min :: PackageName -> PackageName -> PackageName # |
_PackageName :: Name Source #
Constructors
TypeName | |
data ExpressionName Source #
Constructors
ExpressionName | |
Instances
Read ExpressionName Source # | |
Defined in Hydra.Ext.Java.Syntax Methods readsPrec :: Int -> ReadS ExpressionName # readList :: ReadS [ExpressionName] # | |
Show ExpressionName Source # | |
Defined in Hydra.Ext.Java.Syntax Methods showsPrec :: Int -> ExpressionName -> ShowS # show :: ExpressionName -> String # showList :: [ExpressionName] -> ShowS # | |
Eq ExpressionName Source # | |
Defined in Hydra.Ext.Java.Syntax Methods (==) :: ExpressionName -> ExpressionName -> Bool # (/=) :: ExpressionName -> ExpressionName -> Bool # | |
Ord ExpressionName Source # | |
Defined in Hydra.Ext.Java.Syntax Methods compare :: ExpressionName -> ExpressionName -> Ordering # (<) :: ExpressionName -> ExpressionName -> Bool # (<=) :: ExpressionName -> ExpressionName -> Bool # (>) :: ExpressionName -> ExpressionName -> Bool # (>=) :: ExpressionName -> ExpressionName -> Bool # max :: ExpressionName -> ExpressionName -> ExpressionName # min :: ExpressionName -> ExpressionName -> ExpressionName # |
newtype MethodName Source #
Constructors
MethodName | |
Fields |
Instances
Read MethodName Source # | |
Defined in Hydra.Ext.Java.Syntax Methods readsPrec :: Int -> ReadS MethodName # readList :: ReadS [MethodName] # readPrec :: ReadPrec MethodName # readListPrec :: ReadPrec [MethodName] # | |
Show MethodName Source # | |
Defined in Hydra.Ext.Java.Syntax Methods showsPrec :: Int -> MethodName -> ShowS # show :: MethodName -> String # showList :: [MethodName] -> ShowS # | |
Eq MethodName Source # | |
Defined in Hydra.Ext.Java.Syntax | |
Ord MethodName Source # | |
Defined in Hydra.Ext.Java.Syntax Methods compare :: MethodName -> MethodName -> Ordering # (<) :: MethodName -> MethodName -> Bool # (<=) :: MethodName -> MethodName -> Bool # (>) :: MethodName -> MethodName -> Bool # (>=) :: MethodName -> MethodName -> Bool # max :: MethodName -> MethodName -> MethodName # min :: MethodName -> MethodName -> MethodName # |
_MethodName :: Name Source #
newtype PackageOrTypeName Source #
Constructors
PackageOrTypeName | |
Fields |
Instances
newtype AmbiguousName Source #
Constructors
AmbiguousName | |
Fields |
Instances
Read AmbiguousName Source # | |
Defined in Hydra.Ext.Java.Syntax Methods readsPrec :: Int -> ReadS AmbiguousName # readList :: ReadS [AmbiguousName] # | |
Show AmbiguousName Source # | |
Defined in Hydra.Ext.Java.Syntax Methods showsPrec :: Int -> AmbiguousName -> ShowS # show :: AmbiguousName -> String # showList :: [AmbiguousName] -> ShowS # | |
Eq AmbiguousName Source # | |
Defined in Hydra.Ext.Java.Syntax Methods (==) :: AmbiguousName -> AmbiguousName -> Bool # (/=) :: AmbiguousName -> AmbiguousName -> Bool # | |
Ord AmbiguousName Source # | |
Defined in Hydra.Ext.Java.Syntax Methods compare :: AmbiguousName -> AmbiguousName -> Ordering # (<) :: AmbiguousName -> AmbiguousName -> Bool # (<=) :: AmbiguousName -> AmbiguousName -> Bool # (>) :: AmbiguousName -> AmbiguousName -> Bool # (>=) :: AmbiguousName -> AmbiguousName -> Bool # max :: AmbiguousName -> AmbiguousName -> AmbiguousName # min :: AmbiguousName -> AmbiguousName -> AmbiguousName # |
data CompilationUnit Source #
Constructors
CompilationUnitOrdinary OrdinaryCompilationUnit | |
CompilationUnitModular ModularCompilationUnit |
Instances
Read CompilationUnit Source # | |
Defined in Hydra.Ext.Java.Syntax Methods readsPrec :: Int -> ReadS CompilationUnit # readList :: ReadS [CompilationUnit] # | |
Show CompilationUnit Source # | |
Defined in Hydra.Ext.Java.Syntax Methods showsPrec :: Int -> CompilationUnit -> ShowS # show :: CompilationUnit -> String # showList :: [CompilationUnit] -> ShowS # | |
Eq CompilationUnit Source # | |
Defined in Hydra.Ext.Java.Syntax Methods (==) :: CompilationUnit -> CompilationUnit -> Bool # (/=) :: CompilationUnit -> CompilationUnit -> Bool # | |
Ord CompilationUnit Source # | |
Defined in Hydra.Ext.Java.Syntax Methods compare :: CompilationUnit -> CompilationUnit -> Ordering # (<) :: CompilationUnit -> CompilationUnit -> Bool # (<=) :: CompilationUnit -> CompilationUnit -> Bool # (>) :: CompilationUnit -> CompilationUnit -> Bool # (>=) :: CompilationUnit -> CompilationUnit -> Bool # max :: CompilationUnit -> CompilationUnit -> CompilationUnit # min :: CompilationUnit -> CompilationUnit -> CompilationUnit # |
data OrdinaryCompilationUnit Source #
Constructors
OrdinaryCompilationUnit | |
Instances
data ModularCompilationUnit Source #
Constructors
ModularCompilationUnit | |
Instances
data PackageDeclaration Source #
Constructors
PackageDeclaration | |
Instances
newtype PackageModifier Source #
Constructors
PackageModifier | |
Fields |
Instances
Read PackageModifier Source # | |
Defined in Hydra.Ext.Java.Syntax Methods readsPrec :: Int -> ReadS PackageModifier # readList :: ReadS [PackageModifier] # | |
Show PackageModifier Source # | |
Defined in Hydra.Ext.Java.Syntax Methods showsPrec :: Int -> PackageModifier -> ShowS # show :: PackageModifier -> String # showList :: [PackageModifier] -> ShowS # | |
Eq PackageModifier Source # | |
Defined in Hydra.Ext.Java.Syntax Methods (==) :: PackageModifier -> PackageModifier -> Bool # (/=) :: PackageModifier -> PackageModifier -> Bool # | |
Ord PackageModifier Source # | |
Defined in Hydra.Ext.Java.Syntax Methods compare :: PackageModifier -> PackageModifier -> Ordering # (<) :: PackageModifier -> PackageModifier -> Bool # (<=) :: PackageModifier -> PackageModifier -> Bool # (>) :: PackageModifier -> PackageModifier -> Bool # (>=) :: PackageModifier -> PackageModifier -> Bool # max :: PackageModifier -> PackageModifier -> PackageModifier # min :: PackageModifier -> PackageModifier -> PackageModifier # |
data ImportDeclaration Source #
Constructors
Instances
newtype SingleTypeImportDeclaration Source #
Constructors
SingleTypeImportDeclaration | |
Fields |
Instances
newtype TypeImportOnDemandDeclaration Source #
Constructors
TypeImportOnDemandDeclaration | |
Instances
data SingleStaticImportDeclaration Source #
Constructors
SingleStaticImportDeclaration | |
Instances
newtype StaticImportOnDemandDeclaration Source #
Constructors
StaticImportOnDemandDeclaration | |
Instances
data TypeDeclaration Source #
Constructors
TypeDeclarationClass ClassDeclaration | |
TypeDeclarationInterface InterfaceDeclaration | |
TypeDeclarationNone |
Instances
Read TypeDeclaration Source # | |
Defined in Hydra.Ext.Java.Syntax Methods readsPrec :: Int -> ReadS TypeDeclaration # readList :: ReadS [TypeDeclaration] # | |
Show TypeDeclaration Source # | |
Defined in Hydra.Ext.Java.Syntax Methods showsPrec :: Int -> TypeDeclaration -> ShowS # show :: TypeDeclaration -> String # showList :: [TypeDeclaration] -> ShowS # | |
Eq TypeDeclaration Source # | |
Defined in Hydra.Ext.Java.Syntax Methods (==) :: TypeDeclaration -> TypeDeclaration -> Bool # (/=) :: TypeDeclaration -> TypeDeclaration -> Bool # | |
Ord TypeDeclaration Source # | |
Defined in Hydra.Ext.Java.Syntax Methods compare :: TypeDeclaration -> TypeDeclaration -> Ordering # (<) :: TypeDeclaration -> TypeDeclaration -> Bool # (<=) :: TypeDeclaration -> TypeDeclaration -> Bool # (>) :: TypeDeclaration -> TypeDeclaration -> Bool # (>=) :: TypeDeclaration -> TypeDeclaration -> Bool # max :: TypeDeclaration -> TypeDeclaration -> TypeDeclaration # min :: TypeDeclaration -> TypeDeclaration -> TypeDeclaration # |
data TypeDeclarationWithComments Source #
Constructors
TypeDeclarationWithComments | |
Instances
data ModuleDeclaration Source #
Constructors
ModuleDeclaration | |
Instances
data ModuleDirective Source #
Constructors
Instances
Read ModuleDirective Source # | |
Defined in Hydra.Ext.Java.Syntax Methods readsPrec :: Int -> ReadS ModuleDirective # readList :: ReadS [ModuleDirective] # | |
Show ModuleDirective Source # | |
Defined in Hydra.Ext.Java.Syntax Methods showsPrec :: Int -> ModuleDirective -> ShowS # show :: ModuleDirective -> String # showList :: [ModuleDirective] -> ShowS # | |
Eq ModuleDirective Source # | |
Defined in Hydra.Ext.Java.Syntax Methods (==) :: ModuleDirective -> ModuleDirective -> Bool # (/=) :: ModuleDirective -> ModuleDirective -> Bool # | |
Ord ModuleDirective Source # | |
Defined in Hydra.Ext.Java.Syntax Methods compare :: ModuleDirective -> ModuleDirective -> Ordering # (<) :: ModuleDirective -> ModuleDirective -> Bool # (<=) :: ModuleDirective -> ModuleDirective -> Bool # (>) :: ModuleDirective -> ModuleDirective -> Bool # (>=) :: ModuleDirective -> ModuleDirective -> Bool # max :: ModuleDirective -> ModuleDirective -> ModuleDirective # min :: ModuleDirective -> ModuleDirective -> ModuleDirective # |
data ModuleDirective_Requires Source #
Constructors
ModuleDirective_Requires | |
Instances
data ModuleDirective_ExportsOrOpens Source #
Constructors
ModuleDirective_ExportsOrOpens | |
Fields
|
Instances
data ModuleDirective_Provides Source #
Constructors
ModuleDirective_Provides | |
Fields
|
Instances
data RequiresModifier Source #
Constructors
RequiresModifierTransitive | |
RequiresModifierStatic |
Instances
data ClassDeclaration Source #
Instances
data NormalClassDeclaration Source #
Constructors
NormalClassDeclaration | |
Fields |
Instances
data ClassModifier Source #
Constructors
ClassModifierAnnotation Annotation | |
ClassModifierPublic | |
ClassModifierProtected | |
ClassModifierPrivate | |
ClassModifierAbstract | |
ClassModifierStatic | |
ClassModifierFinal | |
ClassModifierStrictfp |
Instances
Read ClassModifier Source # | |
Defined in Hydra.Ext.Java.Syntax Methods readsPrec :: Int -> ReadS ClassModifier # readList :: ReadS [ClassModifier] # | |
Show ClassModifier Source # | |
Defined in Hydra.Ext.Java.Syntax Methods showsPrec :: Int -> ClassModifier -> ShowS # show :: ClassModifier -> String # showList :: [ClassModifier] -> ShowS # | |
Eq ClassModifier Source # | |
Defined in Hydra.Ext.Java.Syntax Methods (==) :: ClassModifier -> ClassModifier -> Bool # (/=) :: ClassModifier -> ClassModifier -> Bool # | |
Ord ClassModifier Source # | |
Defined in Hydra.Ext.Java.Syntax Methods compare :: ClassModifier -> ClassModifier -> Ordering # (<) :: ClassModifier -> ClassModifier -> Bool # (<=) :: ClassModifier -> ClassModifier -> Bool # (>) :: ClassModifier -> ClassModifier -> Bool # (>=) :: ClassModifier -> ClassModifier -> Bool # max :: ClassModifier -> ClassModifier -> ClassModifier # min :: ClassModifier -> ClassModifier -> ClassModifier # |
Constructors
ClassBody | |
Fields |
Instances
Read ClassBody Source # | |
Show ClassBody Source # | |
Eq ClassBody Source # | |
Ord ClassBody Source # | |
_ClassBody :: Name Source #
data ClassBodyDeclaration Source #
Constructors
Instances
data ClassBodyDeclarationWithComments Source #
Constructors
ClassBodyDeclarationWithComments | |
Instances
data ClassMemberDeclaration Source #
Constructors
Instances
data FieldDeclaration Source #
Constructors
FieldDeclaration | |
Instances
data FieldModifier Source #
Constructors
FieldModifierAnnotation Annotation | |
FieldModifierPublic | |
FieldModifierProtected | |
FieldModifierPrivate | |
FieldModifierStatic | |
FieldModifierFinal | |
FieldModifierTransient | |
FieldModifierVolatile |
Instances
Read FieldModifier Source # | |
Defined in Hydra.Ext.Java.Syntax Methods readsPrec :: Int -> ReadS FieldModifier # readList :: ReadS [FieldModifier] # | |
Show FieldModifier Source # | |
Defined in Hydra.Ext.Java.Syntax Methods showsPrec :: Int -> FieldModifier -> ShowS # show :: FieldModifier -> String # showList :: [FieldModifier] -> ShowS # | |
Eq FieldModifier Source # | |
Defined in Hydra.Ext.Java.Syntax Methods (==) :: FieldModifier -> FieldModifier -> Bool # (/=) :: FieldModifier -> FieldModifier -> Bool # | |
Ord FieldModifier Source # | |
Defined in Hydra.Ext.Java.Syntax Methods compare :: FieldModifier -> FieldModifier -> Ordering # (<) :: FieldModifier -> FieldModifier -> Bool # (<=) :: FieldModifier -> FieldModifier -> Bool # (>) :: FieldModifier -> FieldModifier -> Bool # (>=) :: FieldModifier -> FieldModifier -> Bool # max :: FieldModifier -> FieldModifier -> FieldModifier # min :: FieldModifier -> FieldModifier -> FieldModifier # |
data VariableDeclarator Source #
Constructors
VariableDeclarator | |
Instances
data VariableDeclaratorId Source #
Constructors
VariableDeclaratorId | |
Instances
data VariableInitializer Source #
Constructors
VariableInitializerExpression Expression | |
VariableInitializerArrayInitializer ArrayInitializer |
Instances
A Type which does not allow annotations
Constructors
UnannType | |
Fields
|
Instances
Read UnannType Source # | |
Show UnannType Source # | |
Eq UnannType Source # | |
Ord UnannType Source # | |
_UnannType :: Name Source #
newtype UnannClassType Source #
A ClassType which does not allow annotations
Constructors
UnannClassType | |
Fields
|
Instances
Read UnannClassType Source # | |
Defined in Hydra.Ext.Java.Syntax Methods readsPrec :: Int -> ReadS UnannClassType # readList :: ReadS [UnannClassType] # | |
Show UnannClassType Source # | |
Defined in Hydra.Ext.Java.Syntax Methods showsPrec :: Int -> UnannClassType -> ShowS # show :: UnannClassType -> String # showList :: [UnannClassType] -> ShowS # | |
Eq UnannClassType Source # | |
Defined in Hydra.Ext.Java.Syntax Methods (==) :: UnannClassType -> UnannClassType -> Bool # (/=) :: UnannClassType -> UnannClassType -> Bool # | |
Ord UnannClassType Source # | |
Defined in Hydra.Ext.Java.Syntax Methods compare :: UnannClassType -> UnannClassType -> Ordering # (<) :: UnannClassType -> UnannClassType -> Bool # (<=) :: UnannClassType -> UnannClassType -> Bool # (>) :: UnannClassType -> UnannClassType -> Bool # (>=) :: UnannClassType -> UnannClassType -> Bool # max :: UnannClassType -> UnannClassType -> UnannClassType # min :: UnannClassType -> UnannClassType -> UnannClassType # |
data MethodDeclaration Source #
Constructors
MethodDeclaration | |
Fields
|
Instances
data MethodModifier Source #
Constructors
Instances
Read MethodModifier Source # | |
Defined in Hydra.Ext.Java.Syntax Methods readsPrec :: Int -> ReadS MethodModifier # readList :: ReadS [MethodModifier] # | |
Show MethodModifier Source # | |
Defined in Hydra.Ext.Java.Syntax Methods showsPrec :: Int -> MethodModifier -> ShowS # show :: MethodModifier -> String # showList :: [MethodModifier] -> ShowS # | |
Eq MethodModifier Source # | |
Defined in Hydra.Ext.Java.Syntax Methods (==) :: MethodModifier -> MethodModifier -> Bool # (/=) :: MethodModifier -> MethodModifier -> Bool # | |
Ord MethodModifier Source # | |
Defined in Hydra.Ext.Java.Syntax Methods compare :: MethodModifier -> MethodModifier -> Ordering # (<) :: MethodModifier -> MethodModifier -> Bool # (<=) :: MethodModifier -> MethodModifier -> Bool # (>) :: MethodModifier -> MethodModifier -> Bool # (>=) :: MethodModifier -> MethodModifier -> Bool # max :: MethodModifier -> MethodModifier -> MethodModifier # min :: MethodModifier -> MethodModifier -> MethodModifier # |
data MethodHeader Source #
Constructors
MethodHeader | |
Instances
Read MethodHeader Source # | |
Defined in Hydra.Ext.Java.Syntax Methods readsPrec :: Int -> ReadS MethodHeader # readList :: ReadS [MethodHeader] # | |
Show MethodHeader Source # | |
Defined in Hydra.Ext.Java.Syntax Methods showsPrec :: Int -> MethodHeader -> ShowS # show :: MethodHeader -> String # showList :: [MethodHeader] -> ShowS # | |
Eq MethodHeader Source # | |
Defined in Hydra.Ext.Java.Syntax | |
Ord MethodHeader Source # | |
Defined in Hydra.Ext.Java.Syntax Methods compare :: MethodHeader -> MethodHeader -> Ordering # (<) :: MethodHeader -> MethodHeader -> Bool # (<=) :: MethodHeader -> MethodHeader -> Bool # (>) :: MethodHeader -> MethodHeader -> Bool # (>=) :: MethodHeader -> MethodHeader -> Bool # max :: MethodHeader -> MethodHeader -> MethodHeader # min :: MethodHeader -> MethodHeader -> MethodHeader # |
_MethodHeader :: Name Source #
Constructors
ResultType UnannType | |
ResultVoid |
data MethodDeclarator Source #
Constructors
MethodDeclarator | |
Instances
data ReceiverParameter Source #
Constructors
ReceiverParameter | |
Instances
data FormalParameter Source #
Constructors
FormalParameterSimple FormalParameter_Simple | |
FormalParameterVariableArity VariableArityParameter |
Instances
Read FormalParameter Source # | |
Defined in Hydra.Ext.Java.Syntax Methods readsPrec :: Int -> ReadS FormalParameter # readList :: ReadS [FormalParameter] # | |
Show FormalParameter Source # | |
Defined in Hydra.Ext.Java.Syntax Methods showsPrec :: Int -> FormalParameter -> ShowS # show :: FormalParameter -> String # showList :: [FormalParameter] -> ShowS # | |
Eq FormalParameter Source # | |
Defined in Hydra.Ext.Java.Syntax Methods (==) :: FormalParameter -> FormalParameter -> Bool # (/=) :: FormalParameter -> FormalParameter -> Bool # | |
Ord FormalParameter Source # | |
Defined in Hydra.Ext.Java.Syntax Methods compare :: FormalParameter -> FormalParameter -> Ordering # (<) :: FormalParameter -> FormalParameter -> Bool # (<=) :: FormalParameter -> FormalParameter -> Bool # (>) :: FormalParameter -> FormalParameter -> Bool # (>=) :: FormalParameter -> FormalParameter -> Bool # max :: FormalParameter -> FormalParameter -> FormalParameter # min :: FormalParameter -> FormalParameter -> FormalParameter # |
data FormalParameter_Simple Source #
Constructors
FormalParameter_Simple | |
Instances
data VariableArityParameter Source #
Constructors
VariableArityParameter | |
Instances
data VariableModifier Source #
Instances
Constructors
Throws | |
Fields
|
data ExceptionType Source #
Constructors
ExceptionTypeClass ClassType | |
ExceptionTypeVariable TypeVariable |
Instances
Read ExceptionType Source # | |
Defined in Hydra.Ext.Java.Syntax Methods readsPrec :: Int -> ReadS ExceptionType # readList :: ReadS [ExceptionType] # | |
Show ExceptionType Source # | |
Defined in Hydra.Ext.Java.Syntax Methods showsPrec :: Int -> ExceptionType -> ShowS # show :: ExceptionType -> String # showList :: [ExceptionType] -> ShowS # | |
Eq ExceptionType Source # | |
Defined in Hydra.Ext.Java.Syntax Methods (==) :: ExceptionType -> ExceptionType -> Bool # (/=) :: ExceptionType -> ExceptionType -> Bool # | |
Ord ExceptionType Source # | |
Defined in Hydra.Ext.Java.Syntax Methods compare :: ExceptionType -> ExceptionType -> Ordering # (<) :: ExceptionType -> ExceptionType -> Bool # (<=) :: ExceptionType -> ExceptionType -> Bool # (>) :: ExceptionType -> ExceptionType -> Bool # (>=) :: ExceptionType -> ExceptionType -> Bool # max :: ExceptionType -> ExceptionType -> ExceptionType # min :: ExceptionType -> ExceptionType -> ExceptionType # |
data MethodBody Source #
Constructors
MethodBodyBlock Block | |
MethodBodyNone |
Instances
Read MethodBody Source # | |
Defined in Hydra.Ext.Java.Syntax Methods readsPrec :: Int -> ReadS MethodBody # readList :: ReadS [MethodBody] # readPrec :: ReadPrec MethodBody # readListPrec :: ReadPrec [MethodBody] # | |
Show MethodBody Source # | |
Defined in Hydra.Ext.Java.Syntax Methods showsPrec :: Int -> MethodBody -> ShowS # show :: MethodBody -> String # showList :: [MethodBody] -> ShowS # | |
Eq MethodBody Source # | |
Defined in Hydra.Ext.Java.Syntax | |
Ord MethodBody Source # | |
Defined in Hydra.Ext.Java.Syntax Methods compare :: MethodBody -> MethodBody -> Ordering # (<) :: MethodBody -> MethodBody -> Bool # (<=) :: MethodBody -> MethodBody -> Bool # (>) :: MethodBody -> MethodBody -> Bool # (>=) :: MethodBody -> MethodBody -> Bool # max :: MethodBody -> MethodBody -> MethodBody # min :: MethodBody -> MethodBody -> MethodBody # |
_MethodBody :: Name Source #
newtype InstanceInitializer Source #
Constructors
InstanceInitializer | |
Fields |
Instances
newtype StaticInitializer Source #
Constructors
StaticInitializer | |
Fields |
Instances
data ConstructorDeclaration Source #
Constructors
ConstructorDeclaration | |
Instances
data ConstructorModifier Source #
Constructors
ConstructorModifierAnnotation Annotation | |
ConstructorModifierPublic | |
ConstructorModifierProtected | |
ConstructorModifierPrivate |
Instances
data ConstructorDeclarator Source #
Constructors
ConstructorDeclarator | |
Instances
newtype SimpleTypeName Source #
Constructors
SimpleTypeName | |
Fields |
Instances
Read SimpleTypeName Source # | |
Defined in Hydra.Ext.Java.Syntax Methods readsPrec :: Int -> ReadS SimpleTypeName # readList :: ReadS [SimpleTypeName] # | |
Show SimpleTypeName Source # | |
Defined in Hydra.Ext.Java.Syntax Methods showsPrec :: Int -> SimpleTypeName -> ShowS # show :: SimpleTypeName -> String # showList :: [SimpleTypeName] -> ShowS # | |
Eq SimpleTypeName Source # | |
Defined in Hydra.Ext.Java.Syntax Methods (==) :: SimpleTypeName -> SimpleTypeName -> Bool # (/=) :: SimpleTypeName -> SimpleTypeName -> Bool # | |
Ord SimpleTypeName Source # | |
Defined in Hydra.Ext.Java.Syntax Methods compare :: SimpleTypeName -> SimpleTypeName -> Ordering # (<) :: SimpleTypeName -> SimpleTypeName -> Bool # (<=) :: SimpleTypeName -> SimpleTypeName -> Bool # (>) :: SimpleTypeName -> SimpleTypeName -> Bool # (>=) :: SimpleTypeName -> SimpleTypeName -> Bool # max :: SimpleTypeName -> SimpleTypeName -> SimpleTypeName # min :: SimpleTypeName -> SimpleTypeName -> SimpleTypeName # |
data ConstructorBody Source #
Constructors
ConstructorBody | |
Instances
Read ConstructorBody Source # | |
Defined in Hydra.Ext.Java.Syntax Methods readsPrec :: Int -> ReadS ConstructorBody # readList :: ReadS [ConstructorBody] # | |
Show ConstructorBody Source # | |
Defined in Hydra.Ext.Java.Syntax Methods showsPrec :: Int -> ConstructorBody -> ShowS # show :: ConstructorBody -> String # showList :: [ConstructorBody] -> ShowS # | |
Eq ConstructorBody Source # | |
Defined in Hydra.Ext.Java.Syntax Methods (==) :: ConstructorBody -> ConstructorBody -> Bool # (/=) :: ConstructorBody -> ConstructorBody -> Bool # | |
Ord ConstructorBody Source # | |
Defined in Hydra.Ext.Java.Syntax Methods compare :: ConstructorBody -> ConstructorBody -> Ordering # (<) :: ConstructorBody -> ConstructorBody -> Bool # (<=) :: ConstructorBody -> ConstructorBody -> Bool # (>) :: ConstructorBody -> ConstructorBody -> Bool # (>=) :: ConstructorBody -> ConstructorBody -> Bool # max :: ConstructorBody -> ConstructorBody -> ConstructorBody # min :: ConstructorBody -> ConstructorBody -> ConstructorBody # |
data ExplicitConstructorInvocation Source #
Constructors
ExplicitConstructorInvocation | |
Instances
data ExplicitConstructorInvocation_Variant Source #
Constructors
ExplicitConstructorInvocation_VariantThis | |
ExplicitConstructorInvocation_VariantSuper (Maybe ExpressionName) | |
ExplicitConstructorInvocation_VariantPrimary Primary |
Instances
data EnumDeclaration Source #
Constructors
EnumDeclaration | |
Instances
Read EnumDeclaration Source # | |
Defined in Hydra.Ext.Java.Syntax Methods readsPrec :: Int -> ReadS EnumDeclaration # readList :: ReadS [EnumDeclaration] # | |
Show EnumDeclaration Source # | |
Defined in Hydra.Ext.Java.Syntax Methods showsPrec :: Int -> EnumDeclaration -> ShowS # show :: EnumDeclaration -> String # showList :: [EnumDeclaration] -> ShowS # | |
Eq EnumDeclaration Source # | |
Defined in Hydra.Ext.Java.Syntax Methods (==) :: EnumDeclaration -> EnumDeclaration -> Bool # (/=) :: EnumDeclaration -> EnumDeclaration -> Bool # | |
Ord EnumDeclaration Source # | |
Defined in Hydra.Ext.Java.Syntax Methods compare :: EnumDeclaration -> EnumDeclaration -> Ordering # (<) :: EnumDeclaration -> EnumDeclaration -> Bool # (<=) :: EnumDeclaration -> EnumDeclaration -> Bool # (>) :: EnumDeclaration -> EnumDeclaration -> Bool # (>=) :: EnumDeclaration -> EnumDeclaration -> Bool # max :: EnumDeclaration -> EnumDeclaration -> EnumDeclaration # min :: EnumDeclaration -> EnumDeclaration -> EnumDeclaration # |
Constructors
EnumBody | |
Fields |
data EnumBody_Element Source #
Constructors
EnumBody_Element | |
Instances
data EnumConstant Source #
Constructors
EnumConstant | |
Instances
Read EnumConstant Source # | |
Defined in Hydra.Ext.Java.Syntax Methods readsPrec :: Int -> ReadS EnumConstant # readList :: ReadS [EnumConstant] # | |
Show EnumConstant Source # | |
Defined in Hydra.Ext.Java.Syntax Methods showsPrec :: Int -> EnumConstant -> ShowS # show :: EnumConstant -> String # showList :: [EnumConstant] -> ShowS # | |
Eq EnumConstant Source # | |
Defined in Hydra.Ext.Java.Syntax | |
Ord EnumConstant Source # | |
Defined in Hydra.Ext.Java.Syntax Methods compare :: EnumConstant -> EnumConstant -> Ordering # (<) :: EnumConstant -> EnumConstant -> Bool # (<=) :: EnumConstant -> EnumConstant -> Bool # (>) :: EnumConstant -> EnumConstant -> Bool # (>=) :: EnumConstant -> EnumConstant -> Bool # max :: EnumConstant -> EnumConstant -> EnumConstant # min :: EnumConstant -> EnumConstant -> EnumConstant # |
_EnumConstant :: Name Source #
newtype EnumConstantModifier Source #
Constructors
EnumConstantModifier | |
Fields |
Instances
data InterfaceDeclaration Source #
Constructors
InterfaceDeclarationNormalInterface NormalInterfaceDeclaration | |
InterfaceDeclarationAnnotationType AnnotationTypeDeclaration |
Instances
data NormalInterfaceDeclaration Source #
Constructors
NormalInterfaceDeclaration | |
Instances
data InterfaceModifier Source #
Constructors
InterfaceModifierAnnotation Annotation | |
InterfaceModifierPublic | |
InterfaceModifierProtected | |
InterfaceModifierPrivate | |
InterfaceModifierAbstract | |
InterfaceModifierStatic | |
InterfaceModifierStrictfb |
Instances
newtype InterfaceBody Source #
Constructors
InterfaceBody | |
Fields |
Instances
Read InterfaceBody Source # | |
Defined in Hydra.Ext.Java.Syntax Methods readsPrec :: Int -> ReadS InterfaceBody # readList :: ReadS [InterfaceBody] # | |
Show InterfaceBody Source # | |
Defined in Hydra.Ext.Java.Syntax Methods showsPrec :: Int -> InterfaceBody -> ShowS # show :: InterfaceBody -> String # showList :: [InterfaceBody] -> ShowS # | |
Eq InterfaceBody Source # | |
Defined in Hydra.Ext.Java.Syntax Methods (==) :: InterfaceBody -> InterfaceBody -> Bool # (/=) :: InterfaceBody -> InterfaceBody -> Bool # | |
Ord InterfaceBody Source # | |
Defined in Hydra.Ext.Java.Syntax Methods compare :: InterfaceBody -> InterfaceBody -> Ordering # (<) :: InterfaceBody -> InterfaceBody -> Bool # (<=) :: InterfaceBody -> InterfaceBody -> Bool # (>) :: InterfaceBody -> InterfaceBody -> Bool # (>=) :: InterfaceBody -> InterfaceBody -> Bool # max :: InterfaceBody -> InterfaceBody -> InterfaceBody # min :: InterfaceBody -> InterfaceBody -> InterfaceBody # |
data InterfaceMemberDeclaration Source #
Constructors
Instances
data ConstantDeclaration Source #
Constructors
ConstantDeclaration | |
Instances
data ConstantModifier Source #
Constructors
ConstantModifierAnnotation Annotation | |
ConstantModifierPublic | |
ConstantModifierStatic | |
ConstantModifierFinal |
Instances
data InterfaceMethodDeclaration Source #
Constructors
InterfaceMethodDeclaration | |
Instances
data InterfaceMethodModifier Source #
Constructors
Instances
data AnnotationTypeDeclaration Source #
Constructors
AnnotationTypeDeclaration | |
Instances
newtype AnnotationTypeBody Source #
Constructors
AnnotationTypeBody | |
Fields |
Instances
data AnnotationTypeMemberDeclaration Source #
Constructors
Instances
data AnnotationTypeElementDeclaration Source #
Constructors
AnnotationTypeElementDeclaration | |
Fields |
Instances
data AnnotationTypeElementModifier Source #
Instances
newtype DefaultValue Source #
Constructors
DefaultValue | |
Fields |
Instances
Read DefaultValue Source # | |
Defined in Hydra.Ext.Java.Syntax Methods readsPrec :: Int -> ReadS DefaultValue # readList :: ReadS [DefaultValue] # | |
Show DefaultValue Source # | |
Defined in Hydra.Ext.Java.Syntax Methods showsPrec :: Int -> DefaultValue -> ShowS # show :: DefaultValue -> String # showList :: [DefaultValue] -> ShowS # | |
Eq DefaultValue Source # | |
Defined in Hydra.Ext.Java.Syntax | |
Ord DefaultValue Source # | |
Defined in Hydra.Ext.Java.Syntax Methods compare :: DefaultValue -> DefaultValue -> Ordering # (<) :: DefaultValue -> DefaultValue -> Bool # (<=) :: DefaultValue -> DefaultValue -> Bool # (>) :: DefaultValue -> DefaultValue -> Bool # (>=) :: DefaultValue -> DefaultValue -> Bool # max :: DefaultValue -> DefaultValue -> DefaultValue # min :: DefaultValue -> DefaultValue -> DefaultValue # |
_DefaultValue :: Name Source #
data Annotation Source #
Constructors
AnnotationNormal NormalAnnotation | |
AnnotationMarker MarkerAnnotation | |
AnnotationSingleElement SingleElementAnnotation |
Instances
Read Annotation Source # | |
Defined in Hydra.Ext.Java.Syntax Methods readsPrec :: Int -> ReadS Annotation # readList :: ReadS [Annotation] # readPrec :: ReadPrec Annotation # readListPrec :: ReadPrec [Annotation] # | |
Show Annotation Source # | |
Defined in Hydra.Ext.Java.Syntax Methods showsPrec :: Int -> Annotation -> ShowS # show :: Annotation -> String # showList :: [Annotation] -> ShowS # | |
Eq Annotation Source # | |
Defined in Hydra.Ext.Java.Syntax | |
Ord Annotation Source # | |
Defined in Hydra.Ext.Java.Syntax Methods compare :: Annotation -> Annotation -> Ordering # (<) :: Annotation -> Annotation -> Bool # (<=) :: Annotation -> Annotation -> Bool # (>) :: Annotation -> Annotation -> Bool # (>=) :: Annotation -> Annotation -> Bool # max :: Annotation -> Annotation -> Annotation # min :: Annotation -> Annotation -> Annotation # |
_Annotation :: Name Source #
data NormalAnnotation Source #
Constructors
NormalAnnotation | |
Instances
data ElementValuePair Source #
Constructors
ElementValuePair | |
Instances
data ElementValue Source #
Constructors
ElementValueConditionalExpression ConditionalExpression | |
ElementValueElementValueArrayInitializer ElementValueArrayInitializer | |
ElementValueAnnotation Annotation |
Instances
Read ElementValue Source # | |
Defined in Hydra.Ext.Java.Syntax Methods readsPrec :: Int -> ReadS ElementValue # readList :: ReadS [ElementValue] # | |
Show ElementValue Source # | |
Defined in Hydra.Ext.Java.Syntax Methods showsPrec :: Int -> ElementValue -> ShowS # show :: ElementValue -> String # showList :: [ElementValue] -> ShowS # | |
Eq ElementValue Source # | |
Defined in Hydra.Ext.Java.Syntax | |
Ord ElementValue Source # | |
Defined in Hydra.Ext.Java.Syntax Methods compare :: ElementValue -> ElementValue -> Ordering # (<) :: ElementValue -> ElementValue -> Bool # (<=) :: ElementValue -> ElementValue -> Bool # (>) :: ElementValue -> ElementValue -> Bool # (>=) :: ElementValue -> ElementValue -> Bool # max :: ElementValue -> ElementValue -> ElementValue # min :: ElementValue -> ElementValue -> ElementValue # |
_ElementValue :: Name Source #
newtype ElementValueArrayInitializer Source #
Constructors
ElementValueArrayInitializer | |
Fields |
Instances
newtype MarkerAnnotation Source #
Constructors
MarkerAnnotation | |
Fields |
Instances
data SingleElementAnnotation Source #
Constructors
SingleElementAnnotation | |
Instances
newtype ArrayInitializer Source #
Constructors
ArrayInitializer | |
Fields |
Instances
Constructors
Block | |
Fields
|
data BlockStatement Source #
Constructors
BlockStatementLocalVariableDeclaration LocalVariableDeclarationStatement | |
BlockStatementClass ClassDeclaration | |
BlockStatementStatement Statement |
Instances
Read BlockStatement Source # | |
Defined in Hydra.Ext.Java.Syntax Methods readsPrec :: Int -> ReadS BlockStatement # readList :: ReadS [BlockStatement] # | |
Show BlockStatement Source # | |
Defined in Hydra.Ext.Java.Syntax Methods showsPrec :: Int -> BlockStatement -> ShowS # show :: BlockStatement -> String # showList :: [BlockStatement] -> ShowS # | |
Eq BlockStatement Source # | |
Defined in Hydra.Ext.Java.Syntax Methods (==) :: BlockStatement -> BlockStatement -> Bool # (/=) :: BlockStatement -> BlockStatement -> Bool # | |
Ord BlockStatement Source # | |
Defined in Hydra.Ext.Java.Syntax Methods compare :: BlockStatement -> BlockStatement -> Ordering # (<) :: BlockStatement -> BlockStatement -> Bool # (<=) :: BlockStatement -> BlockStatement -> Bool # (>) :: BlockStatement -> BlockStatement -> Bool # (>=) :: BlockStatement -> BlockStatement -> Bool # max :: BlockStatement -> BlockStatement -> BlockStatement # min :: BlockStatement -> BlockStatement -> BlockStatement # |
newtype LocalVariableDeclarationStatement Source #
Constructors
LocalVariableDeclarationStatement | |
Instances
data LocalVariableDeclaration Source #
Constructors
LocalVariableDeclaration | |
Instances
data LocalVariableType Source #
Constructors
LocalVariableTypeType UnannType | |
LocalVariableTypeVar |
Instances
Constructors
Instances
Read Statement Source # | |
Show Statement Source # | |
Eq Statement Source # | |
Ord Statement Source # | |
_Statement :: Name Source #
data StatementNoShortIf Source #
Constructors
Instances
data StatementWithoutTrailingSubstatement Source #
Constructors
Instances
data EmptyStatement Source #
Constructors
EmptyStatement | |
Instances
Read EmptyStatement Source # | |
Defined in Hydra.Ext.Java.Syntax Methods readsPrec :: Int -> ReadS EmptyStatement # readList :: ReadS [EmptyStatement] # | |
Show EmptyStatement Source # | |
Defined in Hydra.Ext.Java.Syntax Methods showsPrec :: Int -> EmptyStatement -> ShowS # show :: EmptyStatement -> String # showList :: [EmptyStatement] -> ShowS # | |
Eq EmptyStatement Source # | |
Defined in Hydra.Ext.Java.Syntax Methods (==) :: EmptyStatement -> EmptyStatement -> Bool # (/=) :: EmptyStatement -> EmptyStatement -> Bool # | |
Ord EmptyStatement Source # | |
Defined in Hydra.Ext.Java.Syntax Methods compare :: EmptyStatement -> EmptyStatement -> Ordering # (<) :: EmptyStatement -> EmptyStatement -> Bool # (<=) :: EmptyStatement -> EmptyStatement -> Bool # (>) :: EmptyStatement -> EmptyStatement -> Bool # (>=) :: EmptyStatement -> EmptyStatement -> Bool # max :: EmptyStatement -> EmptyStatement -> EmptyStatement # min :: EmptyStatement -> EmptyStatement -> EmptyStatement # |
data LabeledStatement Source #
Constructors
LabeledStatement | |
Instances
data LabeledStatementNoShortIf Source #
Constructors
LabeledStatementNoShortIf | |
Instances
newtype ExpressionStatement Source #
Constructors
ExpressionStatement | |
Fields |
Instances
data StatementExpression Source #
Constructors
Instances
data IfThenStatement Source #
Constructors
IfThenStatement | |
Instances
Read IfThenStatement Source # | |
Defined in Hydra.Ext.Java.Syntax Methods readsPrec :: Int -> ReadS IfThenStatement # readList :: ReadS [IfThenStatement] # | |
Show IfThenStatement Source # | |
Defined in Hydra.Ext.Java.Syntax Methods showsPrec :: Int -> IfThenStatement -> ShowS # show :: IfThenStatement -> String # showList :: [IfThenStatement] -> ShowS # | |
Eq IfThenStatement Source # | |
Defined in Hydra.Ext.Java.Syntax Methods (==) :: IfThenStatement -> IfThenStatement -> Bool # (/=) :: IfThenStatement -> IfThenStatement -> Bool # | |
Ord IfThenStatement Source # | |
Defined in Hydra.Ext.Java.Syntax Methods compare :: IfThenStatement -> IfThenStatement -> Ordering # (<) :: IfThenStatement -> IfThenStatement -> Bool # (<=) :: IfThenStatement -> IfThenStatement -> Bool # (>) :: IfThenStatement -> IfThenStatement -> Bool # (>=) :: IfThenStatement -> IfThenStatement -> Bool # max :: IfThenStatement -> IfThenStatement -> IfThenStatement # min :: IfThenStatement -> IfThenStatement -> IfThenStatement # |
data IfThenElseStatement Source #
Constructors
IfThenElseStatement | |
Instances
data IfThenElseStatementNoShortIf Source #
Constructors
IfThenElseStatementNoShortIf | |
Instances
data AssertStatement Source #
Instances
Read AssertStatement Source # | |
Defined in Hydra.Ext.Java.Syntax Methods readsPrec :: Int -> ReadS AssertStatement # readList :: ReadS [AssertStatement] # | |
Show AssertStatement Source # | |
Defined in Hydra.Ext.Java.Syntax Methods showsPrec :: Int -> AssertStatement -> ShowS # show :: AssertStatement -> String # showList :: [AssertStatement] -> ShowS # | |
Eq AssertStatement Source # | |
Defined in Hydra.Ext.Java.Syntax Methods (==) :: AssertStatement -> AssertStatement -> Bool # (/=) :: AssertStatement -> AssertStatement -> Bool # | |
Ord AssertStatement Source # | |
Defined in Hydra.Ext.Java.Syntax Methods compare :: AssertStatement -> AssertStatement -> Ordering # (<) :: AssertStatement -> AssertStatement -> Bool # (<=) :: AssertStatement -> AssertStatement -> Bool # (>) :: AssertStatement -> AssertStatement -> Bool # (>=) :: AssertStatement -> AssertStatement -> Bool # max :: AssertStatement -> AssertStatement -> AssertStatement # min :: AssertStatement -> AssertStatement -> AssertStatement # |
data AssertStatement_Pair Source #
Constructors
AssertStatement_Pair | |
Instances
data SwitchStatement Source #
Constructors
SwitchStatement | |
Fields |
Instances
Read SwitchStatement Source # | |
Defined in Hydra.Ext.Java.Syntax Methods readsPrec :: Int -> ReadS SwitchStatement # readList :: ReadS [SwitchStatement] # | |
Show SwitchStatement Source # | |
Defined in Hydra.Ext.Java.Syntax Methods showsPrec :: Int -> SwitchStatement -> ShowS # show :: SwitchStatement -> String # showList :: [SwitchStatement] -> ShowS # | |
Eq SwitchStatement Source # | |
Defined in Hydra.Ext.Java.Syntax Methods (==) :: SwitchStatement -> SwitchStatement -> Bool # (/=) :: SwitchStatement -> SwitchStatement -> Bool # | |
Ord SwitchStatement Source # | |
Defined in Hydra.Ext.Java.Syntax Methods compare :: SwitchStatement -> SwitchStatement -> Ordering # (<) :: SwitchStatement -> SwitchStatement -> Bool # (<=) :: SwitchStatement -> SwitchStatement -> Bool # (>) :: SwitchStatement -> SwitchStatement -> Bool # (>=) :: SwitchStatement -> SwitchStatement -> Bool # max :: SwitchStatement -> SwitchStatement -> SwitchStatement # min :: SwitchStatement -> SwitchStatement -> SwitchStatement # |
newtype SwitchBlock Source #
Constructors
SwitchBlock | |
Fields |
Instances
Read SwitchBlock Source # | |
Defined in Hydra.Ext.Java.Syntax Methods readsPrec :: Int -> ReadS SwitchBlock # readList :: ReadS [SwitchBlock] # readPrec :: ReadPrec SwitchBlock # readListPrec :: ReadPrec [SwitchBlock] # | |
Show SwitchBlock Source # | |
Defined in Hydra.Ext.Java.Syntax Methods showsPrec :: Int -> SwitchBlock -> ShowS # show :: SwitchBlock -> String # showList :: [SwitchBlock] -> ShowS # | |
Eq SwitchBlock Source # | |
Defined in Hydra.Ext.Java.Syntax | |
Ord SwitchBlock Source # | |
Defined in Hydra.Ext.Java.Syntax Methods compare :: SwitchBlock -> SwitchBlock -> Ordering # (<) :: SwitchBlock -> SwitchBlock -> Bool # (<=) :: SwitchBlock -> SwitchBlock -> Bool # (>) :: SwitchBlock -> SwitchBlock -> Bool # (>=) :: SwitchBlock -> SwitchBlock -> Bool # max :: SwitchBlock -> SwitchBlock -> SwitchBlock # min :: SwitchBlock -> SwitchBlock -> SwitchBlock # |
_SwitchBlock :: Name Source #
data SwitchBlock_Pair Source #
Constructors
SwitchBlock_Pair | |
Instances
data SwitchBlockStatementGroup Source #
Constructors
SwitchBlockStatementGroup | |
Instances
data SwitchLabel Source #
Constructors
SwitchLabelConstant ConstantExpression | |
SwitchLabelEnumConstant EnumConstantName | |
SwitchLabelDefault |
Instances
Read SwitchLabel Source # | |
Defined in Hydra.Ext.Java.Syntax Methods readsPrec :: Int -> ReadS SwitchLabel # readList :: ReadS [SwitchLabel] # readPrec :: ReadPrec SwitchLabel # readListPrec :: ReadPrec [SwitchLabel] # | |
Show SwitchLabel Source # | |
Defined in Hydra.Ext.Java.Syntax Methods showsPrec :: Int -> SwitchLabel -> ShowS # show :: SwitchLabel -> String # showList :: [SwitchLabel] -> ShowS # | |
Eq SwitchLabel Source # | |
Defined in Hydra.Ext.Java.Syntax | |
Ord SwitchLabel Source # | |
Defined in Hydra.Ext.Java.Syntax Methods compare :: SwitchLabel -> SwitchLabel -> Ordering # (<) :: SwitchLabel -> SwitchLabel -> Bool # (<=) :: SwitchLabel -> SwitchLabel -> Bool # (>) :: SwitchLabel -> SwitchLabel -> Bool # (>=) :: SwitchLabel -> SwitchLabel -> Bool # max :: SwitchLabel -> SwitchLabel -> SwitchLabel # min :: SwitchLabel -> SwitchLabel -> SwitchLabel # |
_SwitchLabel :: Name Source #
newtype EnumConstantName Source #
Constructors
EnumConstantName | |
Fields |
Instances
data WhileStatement Source #
Constructors
WhileStatement | |
Fields |
Instances
Read WhileStatement Source # | |
Defined in Hydra.Ext.Java.Syntax Methods readsPrec :: Int -> ReadS WhileStatement # readList :: ReadS [WhileStatement] # | |
Show WhileStatement Source # | |
Defined in Hydra.Ext.Java.Syntax Methods showsPrec :: Int -> WhileStatement -> ShowS # show :: WhileStatement -> String # showList :: [WhileStatement] -> ShowS # | |
Eq WhileStatement Source # | |
Defined in Hydra.Ext.Java.Syntax Methods (==) :: WhileStatement -> WhileStatement -> Bool # (/=) :: WhileStatement -> WhileStatement -> Bool # | |
Ord WhileStatement Source # | |
Defined in Hydra.Ext.Java.Syntax Methods compare :: WhileStatement -> WhileStatement -> Ordering # (<) :: WhileStatement -> WhileStatement -> Bool # (<=) :: WhileStatement -> WhileStatement -> Bool # (>) :: WhileStatement -> WhileStatement -> Bool # (>=) :: WhileStatement -> WhileStatement -> Bool # max :: WhileStatement -> WhileStatement -> WhileStatement # min :: WhileStatement -> WhileStatement -> WhileStatement # |
data WhileStatementNoShortIf Source #
Constructors
WhileStatementNoShortIf | |
Instances
data DoStatement Source #
Constructors
DoStatement | |
Fields |
Instances
Read DoStatement Source # | |
Defined in Hydra.Ext.Java.Syntax Methods readsPrec :: Int -> ReadS DoStatement # readList :: ReadS [DoStatement] # readPrec :: ReadPrec DoStatement # readListPrec :: ReadPrec [DoStatement] # | |
Show DoStatement Source # | |
Defined in Hydra.Ext.Java.Syntax Methods showsPrec :: Int -> DoStatement -> ShowS # show :: DoStatement -> String # showList :: [DoStatement] -> ShowS # | |
Eq DoStatement Source # | |
Defined in Hydra.Ext.Java.Syntax | |
Ord DoStatement Source # | |
Defined in Hydra.Ext.Java.Syntax Methods compare :: DoStatement -> DoStatement -> Ordering # (<) :: DoStatement -> DoStatement -> Bool # (<=) :: DoStatement -> DoStatement -> Bool # (>) :: DoStatement -> DoStatement -> Bool # (>=) :: DoStatement -> DoStatement -> Bool # max :: DoStatement -> DoStatement -> DoStatement # min :: DoStatement -> DoStatement -> DoStatement # |
_DoStatement :: Name Source #
data ForStatement Source #
Instances
Read ForStatement Source # | |
Defined in Hydra.Ext.Java.Syntax Methods readsPrec :: Int -> ReadS ForStatement # readList :: ReadS [ForStatement] # | |
Show ForStatement Source # | |
Defined in Hydra.Ext.Java.Syntax Methods showsPrec :: Int -> ForStatement -> ShowS # show :: ForStatement -> String # showList :: [ForStatement] -> ShowS # | |
Eq ForStatement Source # | |
Defined in Hydra.Ext.Java.Syntax | |
Ord ForStatement Source # | |
Defined in Hydra.Ext.Java.Syntax Methods compare :: ForStatement -> ForStatement -> Ordering # (<) :: ForStatement -> ForStatement -> Bool # (<=) :: ForStatement -> ForStatement -> Bool # (>) :: ForStatement -> ForStatement -> Bool # (>=) :: ForStatement -> ForStatement -> Bool # max :: ForStatement -> ForStatement -> ForStatement # min :: ForStatement -> ForStatement -> ForStatement # |
_ForStatement :: Name Source #
data ForStatementNoShortIf Source #
Constructors
ForStatementNoShortIfBasic BasicForStatementNoShortIf | |
ForStatementNoShortIfEnhanced EnhancedForStatementNoShortIf |
Instances
data BasicForStatement Source #
Constructors
BasicForStatement | |
Fields |
Instances
Constructors
ForCond | |
Fields |
data BasicForStatementNoShortIf Source #
Constructors
BasicForStatementNoShortIf | |
Instances
Constructors
ForUpdate | |
Fields |
Instances
Read ForUpdate Source # | |
Show ForUpdate Source # | |
Eq ForUpdate Source # | |
Ord ForUpdate Source # | |
_ForUpdate :: Name Source #
data EnhancedForStatement Source #
Constructors
EnhancedForStatement | |
Instances
data EnhancedForCond Source #
Constructors
EnhancedForCond | |
Instances
Read EnhancedForCond Source # | |
Defined in Hydra.Ext.Java.Syntax Methods readsPrec :: Int -> ReadS EnhancedForCond # readList :: ReadS [EnhancedForCond] # | |
Show EnhancedForCond Source # | |
Defined in Hydra.Ext.Java.Syntax Methods showsPrec :: Int -> EnhancedForCond -> ShowS # show :: EnhancedForCond -> String # showList :: [EnhancedForCond] -> ShowS # | |
Eq EnhancedForCond Source # | |
Defined in Hydra.Ext.Java.Syntax Methods (==) :: EnhancedForCond -> EnhancedForCond -> Bool # (/=) :: EnhancedForCond -> EnhancedForCond -> Bool # | |
Ord EnhancedForCond Source # | |
Defined in Hydra.Ext.Java.Syntax Methods compare :: EnhancedForCond -> EnhancedForCond -> Ordering # (<) :: EnhancedForCond -> EnhancedForCond -> Bool # (<=) :: EnhancedForCond -> EnhancedForCond -> Bool # (>) :: EnhancedForCond -> EnhancedForCond -> Bool # (>=) :: EnhancedForCond -> EnhancedForCond -> Bool # max :: EnhancedForCond -> EnhancedForCond -> EnhancedForCond # min :: EnhancedForCond -> EnhancedForCond -> EnhancedForCond # |
data EnhancedForStatementNoShortIf Source #
Constructors
EnhancedForStatementNoShortIf | |
Instances
newtype BreakStatement Source #
Constructors
BreakStatement | |
Fields |
Instances
Read BreakStatement Source # | |
Defined in Hydra.Ext.Java.Syntax Methods readsPrec :: Int -> ReadS BreakStatement # readList :: ReadS [BreakStatement] # | |
Show BreakStatement Source # | |
Defined in Hydra.Ext.Java.Syntax Methods showsPrec :: Int -> BreakStatement -> ShowS # show :: BreakStatement -> String # showList :: [BreakStatement] -> ShowS # | |
Eq BreakStatement Source # | |
Defined in Hydra.Ext.Java.Syntax Methods (==) :: BreakStatement -> BreakStatement -> Bool # (/=) :: BreakStatement -> BreakStatement -> Bool # | |
Ord BreakStatement Source # | |
Defined in Hydra.Ext.Java.Syntax Methods compare :: BreakStatement -> BreakStatement -> Ordering # (<) :: BreakStatement -> BreakStatement -> Bool # (<=) :: BreakStatement -> BreakStatement -> Bool # (>) :: BreakStatement -> BreakStatement -> Bool # (>=) :: BreakStatement -> BreakStatement -> Bool # max :: BreakStatement -> BreakStatement -> BreakStatement # min :: BreakStatement -> BreakStatement -> BreakStatement # |
newtype ContinueStatement Source #
Constructors
ContinueStatement | |
Fields |
Instances
newtype ReturnStatement Source #
Constructors
ReturnStatement | |
Fields |
Instances
Read ReturnStatement Source # | |
Defined in Hydra.Ext.Java.Syntax Methods readsPrec :: Int -> ReadS ReturnStatement # readList :: ReadS [ReturnStatement] # | |
Show ReturnStatement Source # | |
Defined in Hydra.Ext.Java.Syntax Methods showsPrec :: Int -> ReturnStatement -> ShowS # show :: ReturnStatement -> String # showList :: [ReturnStatement] -> ShowS # | |
Eq ReturnStatement Source # | |
Defined in Hydra.Ext.Java.Syntax Methods (==) :: ReturnStatement -> ReturnStatement -> Bool # (/=) :: ReturnStatement -> ReturnStatement -> Bool # | |
Ord ReturnStatement Source # | |
Defined in Hydra.Ext.Java.Syntax Methods compare :: ReturnStatement -> ReturnStatement -> Ordering # (<) :: ReturnStatement -> ReturnStatement -> Bool # (<=) :: ReturnStatement -> ReturnStatement -> Bool # (>) :: ReturnStatement -> ReturnStatement -> Bool # (>=) :: ReturnStatement -> ReturnStatement -> Bool # max :: ReturnStatement -> ReturnStatement -> ReturnStatement # min :: ReturnStatement -> ReturnStatement -> ReturnStatement # |
newtype ThrowStatement Source #
Constructors
ThrowStatement | |
Fields |
Instances
Read ThrowStatement Source # | |
Defined in Hydra.Ext.Java.Syntax Methods readsPrec :: Int -> ReadS ThrowStatement # readList :: ReadS [ThrowStatement] # | |
Show ThrowStatement Source # | |
Defined in Hydra.Ext.Java.Syntax Methods showsPrec :: Int -> ThrowStatement -> ShowS # show :: ThrowStatement -> String # showList :: [ThrowStatement] -> ShowS # | |
Eq ThrowStatement Source # | |
Defined in Hydra.Ext.Java.Syntax Methods (==) :: ThrowStatement -> ThrowStatement -> Bool # (/=) :: ThrowStatement -> ThrowStatement -> Bool # | |
Ord ThrowStatement Source # | |
Defined in Hydra.Ext.Java.Syntax Methods compare :: ThrowStatement -> ThrowStatement -> Ordering # (<) :: ThrowStatement -> ThrowStatement -> Bool # (<=) :: ThrowStatement -> ThrowStatement -> Bool # (>) :: ThrowStatement -> ThrowStatement -> Bool # (>=) :: ThrowStatement -> ThrowStatement -> Bool # max :: ThrowStatement -> ThrowStatement -> ThrowStatement # min :: ThrowStatement -> ThrowStatement -> ThrowStatement # |
data SynchronizedStatement Source #
Constructors
SynchronizedStatement | |
Instances
data TryStatement Source #
Constructors
TryStatementSimple TryStatement_Simple | |
TryStatementWithFinally TryStatement_WithFinally | |
TryStatementWithResources TryWithResourcesStatement |
Instances
Read TryStatement Source # | |
Defined in Hydra.Ext.Java.Syntax Methods readsPrec :: Int -> ReadS TryStatement # readList :: ReadS [TryStatement] # | |
Show TryStatement Source # | |
Defined in Hydra.Ext.Java.Syntax Methods showsPrec :: Int -> TryStatement -> ShowS # show :: TryStatement -> String # showList :: [TryStatement] -> ShowS # | |
Eq TryStatement Source # | |
Defined in Hydra.Ext.Java.Syntax | |
Ord TryStatement Source # | |
Defined in Hydra.Ext.Java.Syntax Methods compare :: TryStatement -> TryStatement -> Ordering # (<) :: TryStatement -> TryStatement -> Bool # (<=) :: TryStatement -> TryStatement -> Bool # (>) :: TryStatement -> TryStatement -> Bool # (>=) :: TryStatement -> TryStatement -> Bool # max :: TryStatement -> TryStatement -> TryStatement # min :: TryStatement -> TryStatement -> TryStatement # |
_TryStatement :: Name Source #
data TryStatement_Simple Source #
Constructors
TryStatement_Simple | |
Instances
data TryStatement_WithFinally Source #
Constructors
TryStatement_WithFinally | |
Instances
Constructors
Catches | |
Fields
|
data CatchClause Source #
Constructors
CatchClause | |
Instances
Read CatchClause Source # | |
Defined in Hydra.Ext.Java.Syntax Methods readsPrec :: Int -> ReadS CatchClause # readList :: ReadS [CatchClause] # readPrec :: ReadPrec CatchClause # readListPrec :: ReadPrec [CatchClause] # | |
Show CatchClause Source # | |
Defined in Hydra.Ext.Java.Syntax Methods showsPrec :: Int -> CatchClause -> ShowS # show :: CatchClause -> String # showList :: [CatchClause] -> ShowS # | |
Eq CatchClause Source # | |
Defined in Hydra.Ext.Java.Syntax | |
Ord CatchClause Source # | |
Defined in Hydra.Ext.Java.Syntax Methods compare :: CatchClause -> CatchClause -> Ordering # (<) :: CatchClause -> CatchClause -> Bool # (<=) :: CatchClause -> CatchClause -> Bool # (>) :: CatchClause -> CatchClause -> Bool # (>=) :: CatchClause -> CatchClause -> Bool # max :: CatchClause -> CatchClause -> CatchClause # min :: CatchClause -> CatchClause -> CatchClause # |
_CatchClause :: Name Source #
data CatchFormalParameter Source #
Constructors
CatchFormalParameter | |
Instances
Constructors
CatchType | |
Fields |
Instances
Read CatchType Source # | |
Show CatchType Source # | |
Eq CatchType Source # | |
Ord CatchType Source # | |
_CatchType :: Name Source #
data TryWithResourcesStatement Source #
Constructors
TryWithResourcesStatement | |
Instances
newtype ResourceSpecification Source #
Constructors
ResourceSpecification | |
Fields |
Instances
Constructors
ResourceLocal Resource_Local | |
ResourceVariable VariableAccess |
data Resource_Local Source #
Constructors
Resource_Local | |
Instances
Read Resource_Local Source # | |
Defined in Hydra.Ext.Java.Syntax Methods readsPrec :: Int -> ReadS Resource_Local # readList :: ReadS [Resource_Local] # | |
Show Resource_Local Source # | |
Defined in Hydra.Ext.Java.Syntax Methods showsPrec :: Int -> Resource_Local -> ShowS # show :: Resource_Local -> String # showList :: [Resource_Local] -> ShowS # | |
Eq Resource_Local Source # | |
Defined in Hydra.Ext.Java.Syntax Methods (==) :: Resource_Local -> Resource_Local -> Bool # (/=) :: Resource_Local -> Resource_Local -> Bool # | |
Ord Resource_Local Source # | |
Defined in Hydra.Ext.Java.Syntax Methods compare :: Resource_Local -> Resource_Local -> Ordering # (<) :: Resource_Local -> Resource_Local -> Bool # (<=) :: Resource_Local -> Resource_Local -> Bool # (>) :: Resource_Local -> Resource_Local -> Bool # (>=) :: Resource_Local -> Resource_Local -> Bool # max :: Resource_Local -> Resource_Local -> Resource_Local # min :: Resource_Local -> Resource_Local -> Resource_Local # |
data VariableAccess Source #
Instances
Read VariableAccess Source # | |
Defined in Hydra.Ext.Java.Syntax Methods readsPrec :: Int -> ReadS VariableAccess # readList :: ReadS [VariableAccess] # | |
Show VariableAccess Source # | |
Defined in Hydra.Ext.Java.Syntax Methods showsPrec :: Int -> VariableAccess -> ShowS # show :: VariableAccess -> String # showList :: [VariableAccess] -> ShowS # | |
Eq VariableAccess Source # | |
Defined in Hydra.Ext.Java.Syntax Methods (==) :: VariableAccess -> VariableAccess -> Bool # (/=) :: VariableAccess -> VariableAccess -> Bool # | |
Ord VariableAccess Source # | |
Defined in Hydra.Ext.Java.Syntax Methods compare :: VariableAccess -> VariableAccess -> Ordering # (<) :: VariableAccess -> VariableAccess -> Bool # (<=) :: VariableAccess -> VariableAccess -> Bool # (>) :: VariableAccess -> VariableAccess -> Bool # (>=) :: VariableAccess -> VariableAccess -> Bool # max :: VariableAccess -> VariableAccess -> VariableAccess # min :: VariableAccess -> VariableAccess -> VariableAccess # |
data PrimaryNoNewArray Source #
Constructors
Instances
data ClassLiteral Source #
Constructors
ClassLiteralType TypeNameArray | |
ClassLiteralNumericType NumericTypeArray | |
ClassLiteralBoolean BooleanArray | |
ClassLiteralVoid |
Instances
Read ClassLiteral Source # | |
Defined in Hydra.Ext.Java.Syntax Methods readsPrec :: Int -> ReadS ClassLiteral # readList :: ReadS [ClassLiteral] # | |
Show ClassLiteral Source # | |
Defined in Hydra.Ext.Java.Syntax Methods showsPrec :: Int -> ClassLiteral -> ShowS # show :: ClassLiteral -> String # showList :: [ClassLiteral] -> ShowS # | |
Eq ClassLiteral Source # | |
Defined in Hydra.Ext.Java.Syntax | |
Ord ClassLiteral Source # | |
Defined in Hydra.Ext.Java.Syntax Methods compare :: ClassLiteral -> ClassLiteral -> Ordering # (<) :: ClassLiteral -> ClassLiteral -> Bool # (<=) :: ClassLiteral -> ClassLiteral -> Bool # (>) :: ClassLiteral -> ClassLiteral -> Bool # (>=) :: ClassLiteral -> ClassLiteral -> Bool # max :: ClassLiteral -> ClassLiteral -> ClassLiteral # min :: ClassLiteral -> ClassLiteral -> ClassLiteral # |
_ClassLiteral :: Name Source #
data TypeNameArray Source #
Constructors
TypeNameArraySimple TypeName | |
TypeNameArrayArray TypeNameArray |
Instances
Read TypeNameArray Source # | |
Defined in Hydra.Ext.Java.Syntax Methods readsPrec :: Int -> ReadS TypeNameArray # readList :: ReadS [TypeNameArray] # | |
Show TypeNameArray Source # | |
Defined in Hydra.Ext.Java.Syntax Methods showsPrec :: Int -> TypeNameArray -> ShowS # show :: TypeNameArray -> String # showList :: [TypeNameArray] -> ShowS # | |
Eq TypeNameArray Source # | |
Defined in Hydra.Ext.Java.Syntax Methods (==) :: TypeNameArray -> TypeNameArray -> Bool # (/=) :: TypeNameArray -> TypeNameArray -> Bool # | |
Ord TypeNameArray Source # | |
Defined in Hydra.Ext.Java.Syntax Methods compare :: TypeNameArray -> TypeNameArray -> Ordering # (<) :: TypeNameArray -> TypeNameArray -> Bool # (<=) :: TypeNameArray -> TypeNameArray -> Bool # (>) :: TypeNameArray -> TypeNameArray -> Bool # (>=) :: TypeNameArray -> TypeNameArray -> Bool # max :: TypeNameArray -> TypeNameArray -> TypeNameArray # min :: TypeNameArray -> TypeNameArray -> TypeNameArray # |
data NumericTypeArray Source #
Instances
data BooleanArray Source #
Constructors
BooleanArraySimple | |
BooleanArrayArray BooleanArray |
Instances
Read BooleanArray Source # | |
Defined in Hydra.Ext.Java.Syntax Methods readsPrec :: Int -> ReadS BooleanArray # readList :: ReadS [BooleanArray] # | |
Show BooleanArray Source # | |
Defined in Hydra.Ext.Java.Syntax Methods showsPrec :: Int -> BooleanArray -> ShowS # show :: BooleanArray -> String # showList :: [BooleanArray] -> ShowS # | |
Eq BooleanArray Source # | |
Defined in Hydra.Ext.Java.Syntax | |
Ord BooleanArray Source # | |
Defined in Hydra.Ext.Java.Syntax Methods compare :: BooleanArray -> BooleanArray -> Ordering # (<) :: BooleanArray -> BooleanArray -> Bool # (<=) :: BooleanArray -> BooleanArray -> Bool # (>) :: BooleanArray -> BooleanArray -> Bool # (>=) :: BooleanArray -> BooleanArray -> Bool # max :: BooleanArray -> BooleanArray -> BooleanArray # min :: BooleanArray -> BooleanArray -> BooleanArray # |
_BooleanArray :: Name Source #
data ClassInstanceCreationExpression Source #
Constructors
ClassInstanceCreationExpression | |
Instances
data ClassInstanceCreationExpression_Qualifier Source #
Constructors
ClassInstanceCreationExpression_QualifierExpression ExpressionName | |
ClassInstanceCreationExpression_QualifierPrimary Primary |
Instances
data UnqualifiedClassInstanceCreationExpression Source #
Constructors
Instances
data ClassOrInterfaceTypeToInstantiate Source #
Constructors
ClassOrInterfaceTypeToInstantiate | |
Instances
data AnnotatedIdentifier Source #
Constructors
AnnotatedIdentifier | |
Instances
data TypeArgumentsOrDiamond Source #
Instances
data FieldAccess Source #
Constructors
FieldAccess | |
Instances
Read FieldAccess Source # | |
Defined in Hydra.Ext.Java.Syntax Methods readsPrec :: Int -> ReadS FieldAccess # readList :: ReadS [FieldAccess] # readPrec :: ReadPrec FieldAccess # readListPrec :: ReadPrec [FieldAccess] # | |
Show FieldAccess Source # | |
Defined in Hydra.Ext.Java.Syntax Methods showsPrec :: Int -> FieldAccess -> ShowS # show :: FieldAccess -> String # showList :: [FieldAccess] -> ShowS # | |
Eq FieldAccess Source # | |
Defined in Hydra.Ext.Java.Syntax | |
Ord FieldAccess Source # | |
Defined in Hydra.Ext.Java.Syntax Methods compare :: FieldAccess -> FieldAccess -> Ordering # (<) :: FieldAccess -> FieldAccess -> Bool # (<=) :: FieldAccess -> FieldAccess -> Bool # (>) :: FieldAccess -> FieldAccess -> Bool # (>=) :: FieldAccess -> FieldAccess -> Bool # max :: FieldAccess -> FieldAccess -> FieldAccess # min :: FieldAccess -> FieldAccess -> FieldAccess # |
_FieldAccess :: Name Source #
data FieldAccess_Qualifier Source #
Constructors
FieldAccess_QualifierPrimary Primary | |
FieldAccess_QualifierSuper | |
FieldAccess_QualifierTyped TypeName |
Instances
data ArrayAccess Source #
Constructors
ArrayAccess | |
Instances
Read ArrayAccess Source # | |
Defined in Hydra.Ext.Java.Syntax Methods readsPrec :: Int -> ReadS ArrayAccess # readList :: ReadS [ArrayAccess] # readPrec :: ReadPrec ArrayAccess # readListPrec :: ReadPrec [ArrayAccess] # | |
Show ArrayAccess Source # | |
Defined in Hydra.Ext.Java.Syntax Methods showsPrec :: Int -> ArrayAccess -> ShowS # show :: ArrayAccess -> String # showList :: [ArrayAccess] -> ShowS # | |
Eq ArrayAccess Source # | |
Defined in Hydra.Ext.Java.Syntax | |
Ord ArrayAccess Source # | |
Defined in Hydra.Ext.Java.Syntax Methods compare :: ArrayAccess -> ArrayAccess -> Ordering # (<) :: ArrayAccess -> ArrayAccess -> Bool # (<=) :: ArrayAccess -> ArrayAccess -> Bool # (>) :: ArrayAccess -> ArrayAccess -> Bool # (>=) :: ArrayAccess -> ArrayAccess -> Bool # max :: ArrayAccess -> ArrayAccess -> ArrayAccess # min :: ArrayAccess -> ArrayAccess -> ArrayAccess # |
_ArrayAccess :: Name Source #
data ArrayAccess_Variant Source #
Instances
data MethodInvocation Source #
Constructors
MethodInvocation | |
Instances
data MethodInvocation_Header Source #
Constructors
MethodInvocation_HeaderSimple MethodName | |
MethodInvocation_HeaderComplex MethodInvocation_Complex |
Instances
data MethodInvocation_Complex Source #
Constructors
MethodInvocation_Complex | |
Instances
data MethodInvocation_Variant Source #
Constructors
Instances
data MethodReference Source #
Constructors
Instances
Read MethodReference Source # | |
Defined in Hydra.Ext.Java.Syntax Methods readsPrec :: Int -> ReadS MethodReference # readList :: ReadS [MethodReference] # | |
Show MethodReference Source # | |
Defined in Hydra.Ext.Java.Syntax Methods showsPrec :: Int -> MethodReference -> ShowS # show :: MethodReference -> String # showList :: [MethodReference] -> ShowS # | |
Eq MethodReference Source # | |
Defined in Hydra.Ext.Java.Syntax Methods (==) :: MethodReference -> MethodReference -> Bool # (/=) :: MethodReference -> MethodReference -> Bool # | |
Ord MethodReference Source # | |
Defined in Hydra.Ext.Java.Syntax Methods compare :: MethodReference -> MethodReference -> Ordering # (<) :: MethodReference -> MethodReference -> Bool # (<=) :: MethodReference -> MethodReference -> Bool # (>) :: MethodReference -> MethodReference -> Bool # (>=) :: MethodReference -> MethodReference -> Bool # max :: MethodReference -> MethodReference -> MethodReference # min :: MethodReference -> MethodReference -> MethodReference # |
data MethodReference_Expression Source #
Constructors
MethodReference_Expression | |
Instances
data MethodReference_Primary Source #
Constructors
MethodReference_Primary | |
Instances
data MethodReference_ReferenceType Source #
Constructors
MethodReference_ReferenceType | |
Instances
data MethodReference_Super Source #
Constructors
MethodReference_Super | |
Instances
data MethodReference_New Source #
Constructors
MethodReference_New | |
Instances
newtype MethodReference_Array Source #
Constructors
MethodReference_Array | |
Fields |
Instances
data ArrayCreationExpression Source #
Constructors
Instances
data ArrayCreationExpression_Primitive Source #
Constructors
ArrayCreationExpression_Primitive | |
Instances
data ArrayCreationExpression_ClassOrInterface Source #
Constructors
ArrayCreationExpression_ClassOrInterface | |
Instances
data ArrayCreationExpression_PrimitiveArray Source #
Constructors
ArrayCreationExpression_PrimitiveArray | |
Instances
data ArrayCreationExpression_ClassOrInterfaceArray Source #
Constructors
ArrayCreationExpression_ClassOrInterfaceArray | |
Instances
Constructors
DimExpr | |
Fields |
data Expression Source #
Instances
Read Expression Source # | |
Defined in Hydra.Ext.Java.Syntax Methods readsPrec :: Int -> ReadS Expression # readList :: ReadS [Expression] # readPrec :: ReadPrec Expression # readListPrec :: ReadPrec [Expression] # | |
Show Expression Source # | |
Defined in Hydra.Ext.Java.Syntax Methods showsPrec :: Int -> Expression -> ShowS # show :: Expression -> String # showList :: [Expression] -> ShowS # | |
Eq Expression Source # | |
Defined in Hydra.Ext.Java.Syntax | |
Ord Expression Source # | |
Defined in Hydra.Ext.Java.Syntax Methods compare :: Expression -> Expression -> Ordering # (<) :: Expression -> Expression -> Bool # (<=) :: Expression -> Expression -> Bool # (>) :: Expression -> Expression -> Bool # (>=) :: Expression -> Expression -> Bool # max :: Expression -> Expression -> Expression # min :: Expression -> Expression -> Expression # |
_Expression :: Name Source #
data LambdaExpression Source #
Constructors
LambdaExpression | |
Instances
data LambdaParameters Source #
Instances
data LambdaParameter Source #
Constructors
LambdaParameterNormal LambdaParameter_Normal | |
LambdaParameterVariableArity VariableArityParameter |
Instances
Read LambdaParameter Source # | |
Defined in Hydra.Ext.Java.Syntax Methods readsPrec :: Int -> ReadS LambdaParameter # readList :: ReadS [LambdaParameter] # | |
Show LambdaParameter Source # | |
Defined in Hydra.Ext.Java.Syntax Methods showsPrec :: Int -> LambdaParameter -> ShowS # show :: LambdaParameter -> String # showList :: [LambdaParameter] -> ShowS # | |
Eq LambdaParameter Source # | |
Defined in Hydra.Ext.Java.Syntax Methods (==) :: LambdaParameter -> LambdaParameter -> Bool # (/=) :: LambdaParameter -> LambdaParameter -> Bool # | |
Ord LambdaParameter Source # | |
Defined in Hydra.Ext.Java.Syntax Methods compare :: LambdaParameter -> LambdaParameter -> Ordering # (<) :: LambdaParameter -> LambdaParameter -> Bool # (<=) :: LambdaParameter -> LambdaParameter -> Bool # (>) :: LambdaParameter -> LambdaParameter -> Bool # (>=) :: LambdaParameter -> LambdaParameter -> Bool # max :: LambdaParameter -> LambdaParameter -> LambdaParameter # min :: LambdaParameter -> LambdaParameter -> LambdaParameter # |
data LambdaParameter_Normal Source #
Constructors
LambdaParameter_Normal | |
Instances
data LambdaParameterType Source #
Constructors
LambdaParameterTypeType UnannType | |
LambdaParameterTypeVar |
Instances
data LambdaBody Source #
Constructors
LambdaBodyExpression Expression | |
LambdaBodyBlock Block |
Instances
Read LambdaBody Source # | |
Defined in Hydra.Ext.Java.Syntax Methods readsPrec :: Int -> ReadS LambdaBody # readList :: ReadS [LambdaBody] # readPrec :: ReadPrec LambdaBody # readListPrec :: ReadPrec [LambdaBody] # | |
Show LambdaBody Source # | |
Defined in Hydra.Ext.Java.Syntax Methods showsPrec :: Int -> LambdaBody -> ShowS # show :: LambdaBody -> String # showList :: [LambdaBody] -> ShowS # | |
Eq LambdaBody Source # | |
Defined in Hydra.Ext.Java.Syntax | |
Ord LambdaBody Source # | |
Defined in Hydra.Ext.Java.Syntax Methods compare :: LambdaBody -> LambdaBody -> Ordering # (<) :: LambdaBody -> LambdaBody -> Bool # (<=) :: LambdaBody -> LambdaBody -> Bool # (>) :: LambdaBody -> LambdaBody -> Bool # (>=) :: LambdaBody -> LambdaBody -> Bool # max :: LambdaBody -> LambdaBody -> LambdaBody # min :: LambdaBody -> LambdaBody -> LambdaBody # |
_LambdaBody :: Name Source #
data AssignmentExpression Source #
Constructors
AssignmentExpressionConditional ConditionalExpression | |
AssignmentExpressionAssignment Assignment |
Instances
data Assignment Source #
Constructors
Assignment | |
Instances
Read Assignment Source # | |
Defined in Hydra.Ext.Java.Syntax Methods readsPrec :: Int -> ReadS Assignment # readList :: ReadS [Assignment] # readPrec :: ReadPrec Assignment # readListPrec :: ReadPrec [Assignment] # | |
Show Assignment Source # | |
Defined in Hydra.Ext.Java.Syntax Methods showsPrec :: Int -> Assignment -> ShowS # show :: Assignment -> String # showList :: [Assignment] -> ShowS # | |
Eq Assignment Source # | |
Defined in Hydra.Ext.Java.Syntax | |
Ord Assignment Source # | |
Defined in Hydra.Ext.Java.Syntax Methods compare :: Assignment -> Assignment -> Ordering # (<) :: Assignment -> Assignment -> Bool # (<=) :: Assignment -> Assignment -> Bool # (>) :: Assignment -> Assignment -> Bool # (>=) :: Assignment -> Assignment -> Bool # max :: Assignment -> Assignment -> Assignment # min :: Assignment -> Assignment -> Assignment # |
_Assignment :: Name Source #
data LeftHandSide Source #
Constructors
LeftHandSideExpressionName ExpressionName | |
LeftHandSideFieldAccess FieldAccess | |
LeftHandSideArrayAccess ArrayAccess |
Instances
Read LeftHandSide Source # | |
Defined in Hydra.Ext.Java.Syntax Methods readsPrec :: Int -> ReadS LeftHandSide # readList :: ReadS [LeftHandSide] # | |
Show LeftHandSide Source # | |
Defined in Hydra.Ext.Java.Syntax Methods showsPrec :: Int -> LeftHandSide -> ShowS # show :: LeftHandSide -> String # showList :: [LeftHandSide] -> ShowS # | |
Eq LeftHandSide Source # | |
Defined in Hydra.Ext.Java.Syntax | |
Ord LeftHandSide Source # | |
Defined in Hydra.Ext.Java.Syntax Methods compare :: LeftHandSide -> LeftHandSide -> Ordering # (<) :: LeftHandSide -> LeftHandSide -> Bool # (<=) :: LeftHandSide -> LeftHandSide -> Bool # (>) :: LeftHandSide -> LeftHandSide -> Bool # (>=) :: LeftHandSide -> LeftHandSide -> Bool # max :: LeftHandSide -> LeftHandSide -> LeftHandSide # min :: LeftHandSide -> LeftHandSide -> LeftHandSide # |
_LeftHandSide :: Name Source #
data AssignmentOperator Source #
Constructors
Instances
data ConditionalExpression Source #
Constructors
ConditionalExpressionSimple ConditionalOrExpression | |
ConditionalExpressionTernaryCond ConditionalExpression_TernaryCond | |
ConditionalExpressionTernaryLambda ConditionalExpression_TernaryLambda |
Instances
data ConditionalExpression_TernaryCond Source #
Constructors
ConditionalExpression_TernaryCond | |
Instances
data ConditionalExpression_TernaryLambda Source #
Constructors
ConditionalExpression_TernaryLambda | |
Instances
newtype ConditionalOrExpression Source #
Constructors
ConditionalOrExpression | |
Instances
newtype ConditionalAndExpression Source #
Constructors
ConditionalAndExpression | |
Fields |
Instances
newtype InclusiveOrExpression Source #
Constructors
InclusiveOrExpression | |
Fields |
Instances
newtype ExclusiveOrExpression Source #
Constructors
ExclusiveOrExpression | |
Fields |
Instances
newtype AndExpression Source #
Constructors
AndExpression | |
Fields |
Instances
Read AndExpression Source # | |
Defined in Hydra.Ext.Java.Syntax Methods readsPrec :: Int -> ReadS AndExpression # readList :: ReadS [AndExpression] # | |
Show AndExpression Source # | |
Defined in Hydra.Ext.Java.Syntax Methods showsPrec :: Int -> AndExpression -> ShowS # show :: AndExpression -> String # showList :: [AndExpression] -> ShowS # | |
Eq AndExpression Source # | |
Defined in Hydra.Ext.Java.Syntax Methods (==) :: AndExpression -> AndExpression -> Bool # (/=) :: AndExpression -> AndExpression -> Bool # | |
Ord AndExpression Source # | |
Defined in Hydra.Ext.Java.Syntax Methods compare :: AndExpression -> AndExpression -> Ordering # (<) :: AndExpression -> AndExpression -> Bool # (<=) :: AndExpression -> AndExpression -> Bool # (>) :: AndExpression -> AndExpression -> Bool # (>=) :: AndExpression -> AndExpression -> Bool # max :: AndExpression -> AndExpression -> AndExpression # min :: AndExpression -> AndExpression -> AndExpression # |
data EqualityExpression Source #
Constructors
EqualityExpressionUnary RelationalExpression | |
EqualityExpressionEqual EqualityExpression_Binary | |
EqualityExpressionNotEqual EqualityExpression_Binary |
Instances
data EqualityExpression_Binary Source #
Constructors
EqualityExpression_Binary | |
Instances
data RelationalExpression Source #
Constructors
Instances
data RelationalExpression_LessThan Source #
Constructors
RelationalExpression_LessThan | |
Instances
data RelationalExpression_GreaterThan Source #
Constructors
RelationalExpression_GreaterThan | |
Instances
data RelationalExpression_LessThanEqual Source #
Constructors
RelationalExpression_LessThanEqual | |
Instances
data RelationalExpression_GreaterThanEqual Source #
Constructors
RelationalExpression_GreaterThanEqual | |
Instances
data RelationalExpression_InstanceOf Source #
Constructors
RelationalExpression_InstanceOf | |
Instances
data ShiftExpression Source #
Constructors
ShiftExpressionUnary AdditiveExpression | |
ShiftExpressionShiftLeft ShiftExpression_Binary | |
ShiftExpressionShiftRight ShiftExpression_Binary | |
ShiftExpressionShiftRightZeroFill ShiftExpression_Binary |
Instances
Read ShiftExpression Source # | |
Defined in Hydra.Ext.Java.Syntax Methods readsPrec :: Int -> ReadS ShiftExpression # readList :: ReadS [ShiftExpression] # | |
Show ShiftExpression Source # | |
Defined in Hydra.Ext.Java.Syntax Methods showsPrec :: Int -> ShiftExpression -> ShowS # show :: ShiftExpression -> String # showList :: [ShiftExpression] -> ShowS # | |
Eq ShiftExpression Source # | |
Defined in Hydra.Ext.Java.Syntax Methods (==) :: ShiftExpression -> ShiftExpression -> Bool # (/=) :: ShiftExpression -> ShiftExpression -> Bool # | |
Ord ShiftExpression Source # | |
Defined in Hydra.Ext.Java.Syntax Methods compare :: ShiftExpression -> ShiftExpression -> Ordering # (<) :: ShiftExpression -> ShiftExpression -> Bool # (<=) :: ShiftExpression -> ShiftExpression -> Bool # (>) :: ShiftExpression -> ShiftExpression -> Bool # (>=) :: ShiftExpression -> ShiftExpression -> Bool # max :: ShiftExpression -> ShiftExpression -> ShiftExpression # min :: ShiftExpression -> ShiftExpression -> ShiftExpression # |
data ShiftExpression_Binary Source #
Constructors
ShiftExpression_Binary | |
Instances
data AdditiveExpression Source #
Constructors
AdditiveExpressionUnary MultiplicativeExpression | |
AdditiveExpressionPlus AdditiveExpression_Binary | |
AdditiveExpressionMinus AdditiveExpression_Binary |
Instances
data AdditiveExpression_Binary Source #
Constructors
AdditiveExpression_Binary | |
Instances
data MultiplicativeExpression Source #
Constructors
Instances
data MultiplicativeExpression_Binary Source #
Constructors
MultiplicativeExpression_Binary | |
Instances
data UnaryExpression Source #
Constructors
Instances
Read UnaryExpression Source # | |
Defined in Hydra.Ext.Java.Syntax Methods readsPrec :: Int -> ReadS UnaryExpression # readList :: ReadS [UnaryExpression] # | |
Show UnaryExpression Source # | |
Defined in Hydra.Ext.Java.Syntax Methods showsPrec :: Int -> UnaryExpression -> ShowS # show :: UnaryExpression -> String # showList :: [UnaryExpression] -> ShowS # | |
Eq UnaryExpression Source # | |
Defined in Hydra.Ext.Java.Syntax Methods (==) :: UnaryExpression -> UnaryExpression -> Bool # (/=) :: UnaryExpression -> UnaryExpression -> Bool # | |
Ord UnaryExpression Source # | |
Defined in Hydra.Ext.Java.Syntax Methods compare :: UnaryExpression -> UnaryExpression -> Ordering # (<) :: UnaryExpression -> UnaryExpression -> Bool # (<=) :: UnaryExpression -> UnaryExpression -> Bool # (>) :: UnaryExpression -> UnaryExpression -> Bool # (>=) :: UnaryExpression -> UnaryExpression -> Bool # max :: UnaryExpression -> UnaryExpression -> UnaryExpression # min :: UnaryExpression -> UnaryExpression -> UnaryExpression # |
newtype PreIncrementExpression Source #
Constructors
PreIncrementExpression | |
Fields |
Instances
newtype PreDecrementExpression Source #
Constructors
PreDecrementExpression | |
Fields |
Instances
data UnaryExpressionNotPlusMinus Source #
Constructors
UnaryExpressionNotPlusMinusPostfix PostfixExpression | |
UnaryExpressionNotPlusMinusTilde UnaryExpression | |
UnaryExpressionNotPlusMinusNot UnaryExpression | |
UnaryExpressionNotPlusMinusCast CastExpression |
Instances
data PostfixExpression Source #
Constructors
PostfixExpressionPrimary Primary | |
PostfixExpressionName ExpressionName | |
PostfixExpressionPostIncrement PostIncrementExpression | |
PostfixExpressionPostDecrement PostDecrementExpression |
Instances
newtype PostIncrementExpression Source #
Constructors
PostIncrementExpression | |
Instances
newtype PostDecrementExpression Source #
Constructors
PostDecrementExpression | |
Instances
data CastExpression Source #
Constructors
CastExpressionPrimitive CastExpression_Primitive | |
CastExpressionNotPlusMinus CastExpression_NotPlusMinus | |
CastExpressionLambda CastExpression_Lambda |
Instances
Read CastExpression Source # | |
Defined in Hydra.Ext.Java.Syntax Methods readsPrec :: Int -> ReadS CastExpression # readList :: ReadS [CastExpression] # | |
Show CastExpression Source # | |
Defined in Hydra.Ext.Java.Syntax Methods showsPrec :: Int -> CastExpression -> ShowS # show :: CastExpression -> String # showList :: [CastExpression] -> ShowS # | |
Eq CastExpression Source # | |
Defined in Hydra.Ext.Java.Syntax Methods (==) :: CastExpression -> CastExpression -> Bool # (/=) :: CastExpression -> CastExpression -> Bool # | |
Ord CastExpression Source # | |
Defined in Hydra.Ext.Java.Syntax Methods compare :: CastExpression -> CastExpression -> Ordering # (<) :: CastExpression -> CastExpression -> Bool # (<=) :: CastExpression -> CastExpression -> Bool # (>) :: CastExpression -> CastExpression -> Bool # (>=) :: CastExpression -> CastExpression -> Bool # max :: CastExpression -> CastExpression -> CastExpression # min :: CastExpression -> CastExpression -> CastExpression # |
data CastExpression_Primitive Source #
Constructors
CastExpression_Primitive | |
Instances
data CastExpression_NotPlusMinus Source #
Constructors
CastExpression_NotPlusMinus | |
Instances
data CastExpression_Lambda Source #
Constructors
CastExpression_Lambda | |
Instances
data CastExpression_RefAndBounds Source #
Constructors
CastExpression_RefAndBounds | |
Instances
newtype ConstantExpression Source #
Constructors
ConstantExpression | |
Fields |