-- | 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.

module Hydra.Ext.Java.Syntax where

import qualified Hydra.Core as Core
import Data.List
import Data.Map
import Data.Set

newtype Identifier = 
  Identifier {
    Identifier -> String
unIdentifier :: String}
  deriving (Identifier -> Identifier -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Identifier -> Identifier -> Bool
$c/= :: Identifier -> Identifier -> Bool
== :: Identifier -> Identifier -> Bool
$c== :: Identifier -> Identifier -> Bool
Eq, Eq Identifier
Identifier -> Identifier -> Bool
Identifier -> Identifier -> Ordering
Identifier -> Identifier -> Identifier
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Identifier -> Identifier -> Identifier
$cmin :: Identifier -> Identifier -> Identifier
max :: Identifier -> Identifier -> Identifier
$cmax :: Identifier -> Identifier -> Identifier
>= :: Identifier -> Identifier -> Bool
$c>= :: Identifier -> Identifier -> Bool
> :: Identifier -> Identifier -> Bool
$c> :: Identifier -> Identifier -> Bool
<= :: Identifier -> Identifier -> Bool
$c<= :: Identifier -> Identifier -> Bool
< :: Identifier -> Identifier -> Bool
$c< :: Identifier -> Identifier -> Bool
compare :: Identifier -> Identifier -> Ordering
$ccompare :: Identifier -> Identifier -> Ordering
Ord, ReadPrec [Identifier]
ReadPrec Identifier
Int -> ReadS Identifier
ReadS [Identifier]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Identifier]
$creadListPrec :: ReadPrec [Identifier]
readPrec :: ReadPrec Identifier
$creadPrec :: ReadPrec Identifier
readList :: ReadS [Identifier]
$creadList :: ReadS [Identifier]
readsPrec :: Int -> ReadS Identifier
$creadsPrec :: Int -> ReadS Identifier
Read, Int -> Identifier -> String -> String
[Identifier] -> String -> String
Identifier -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [Identifier] -> String -> String
$cshowList :: [Identifier] -> String -> String
show :: Identifier -> String
$cshow :: Identifier -> String
showsPrec :: Int -> Identifier -> String -> String
$cshowsPrec :: Int -> Identifier -> String -> String
Show)

_Identifier :: Name
_Identifier = (String -> Name
Core.Name String
"hydra/ext/java/syntax.Identifier")

newtype TypeIdentifier = 
  TypeIdentifier {
    TypeIdentifier -> Identifier
unTypeIdentifier :: Identifier}
  deriving (TypeIdentifier -> TypeIdentifier -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TypeIdentifier -> TypeIdentifier -> Bool
$c/= :: TypeIdentifier -> TypeIdentifier -> Bool
== :: TypeIdentifier -> TypeIdentifier -> Bool
$c== :: TypeIdentifier -> TypeIdentifier -> Bool
Eq, Eq TypeIdentifier
TypeIdentifier -> TypeIdentifier -> Bool
TypeIdentifier -> TypeIdentifier -> Ordering
TypeIdentifier -> TypeIdentifier -> TypeIdentifier
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: TypeIdentifier -> TypeIdentifier -> TypeIdentifier
$cmin :: TypeIdentifier -> TypeIdentifier -> TypeIdentifier
max :: TypeIdentifier -> TypeIdentifier -> TypeIdentifier
$cmax :: TypeIdentifier -> TypeIdentifier -> TypeIdentifier
>= :: TypeIdentifier -> TypeIdentifier -> Bool
$c>= :: TypeIdentifier -> TypeIdentifier -> Bool
> :: TypeIdentifier -> TypeIdentifier -> Bool
$c> :: TypeIdentifier -> TypeIdentifier -> Bool
<= :: TypeIdentifier -> TypeIdentifier -> Bool
$c<= :: TypeIdentifier -> TypeIdentifier -> Bool
< :: TypeIdentifier -> TypeIdentifier -> Bool
$c< :: TypeIdentifier -> TypeIdentifier -> Bool
compare :: TypeIdentifier -> TypeIdentifier -> Ordering
$ccompare :: TypeIdentifier -> TypeIdentifier -> Ordering
Ord, ReadPrec [TypeIdentifier]
ReadPrec TypeIdentifier
Int -> ReadS TypeIdentifier
ReadS [TypeIdentifier]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [TypeIdentifier]
$creadListPrec :: ReadPrec [TypeIdentifier]
readPrec :: ReadPrec TypeIdentifier
$creadPrec :: ReadPrec TypeIdentifier
readList :: ReadS [TypeIdentifier]
$creadList :: ReadS [TypeIdentifier]
readsPrec :: Int -> ReadS TypeIdentifier
$creadsPrec :: Int -> ReadS TypeIdentifier
Read, Int -> TypeIdentifier -> String -> String
[TypeIdentifier] -> String -> String
TypeIdentifier -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [TypeIdentifier] -> String -> String
$cshowList :: [TypeIdentifier] -> String -> String
show :: TypeIdentifier -> String
$cshow :: TypeIdentifier -> String
showsPrec :: Int -> TypeIdentifier -> String -> String
$cshowsPrec :: Int -> TypeIdentifier -> String -> String
Show)

_TypeIdentifier :: Name
_TypeIdentifier = (String -> Name
Core.Name String
"hydra/ext/java/syntax.TypeIdentifier")

data Literal = 
  LiteralNull  |
  LiteralInteger IntegerLiteral |
  LiteralFloatingPoint FloatingPointLiteral |
  LiteralBoolean Bool |
  LiteralCharacter Int |
  LiteralString StringLiteral
  deriving (Literal -> Literal -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Literal -> Literal -> Bool
$c/= :: Literal -> Literal -> Bool
== :: Literal -> Literal -> Bool
$c== :: Literal -> Literal -> Bool
Eq, Eq Literal
Literal -> Literal -> Bool
Literal -> Literal -> Ordering
Literal -> Literal -> Literal
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Literal -> Literal -> Literal
$cmin :: Literal -> Literal -> Literal
max :: Literal -> Literal -> Literal
$cmax :: Literal -> Literal -> Literal
>= :: Literal -> Literal -> Bool
$c>= :: Literal -> Literal -> Bool
> :: Literal -> Literal -> Bool
$c> :: Literal -> Literal -> Bool
<= :: Literal -> Literal -> Bool
$c<= :: Literal -> Literal -> Bool
< :: Literal -> Literal -> Bool
$c< :: Literal -> Literal -> Bool
compare :: Literal -> Literal -> Ordering
$ccompare :: Literal -> Literal -> Ordering
Ord, ReadPrec [Literal]
ReadPrec Literal
Int -> ReadS Literal
ReadS [Literal]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Literal]
$creadListPrec :: ReadPrec [Literal]
readPrec :: ReadPrec Literal
$creadPrec :: ReadPrec Literal
readList :: ReadS [Literal]
$creadList :: ReadS [Literal]
readsPrec :: Int -> ReadS Literal
$creadsPrec :: Int -> ReadS Literal
Read, Int -> Literal -> String -> String
[Literal] -> String -> String
Literal -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [Literal] -> String -> String
$cshowList :: [Literal] -> String -> String
show :: Literal -> String
$cshow :: Literal -> String
showsPrec :: Int -> Literal -> String -> String
$cshowsPrec :: Int -> Literal -> String -> String
Show)

_Literal :: Name
_Literal = (String -> Name
Core.Name String
"hydra/ext/java/syntax.Literal")

_Literal_null :: FieldName
_Literal_null = (String -> FieldName
Core.FieldName String
"null")

_Literal_integer :: FieldName
_Literal_integer = (String -> FieldName
Core.FieldName String
"integer")

_Literal_floatingPoint :: FieldName
_Literal_floatingPoint = (String -> FieldName
Core.FieldName String
"floatingPoint")

_Literal_boolean :: FieldName
_Literal_boolean = (String -> FieldName
Core.FieldName String
"boolean")

_Literal_character :: FieldName
_Literal_character = (String -> FieldName
Core.FieldName String
"character")

_Literal_string :: FieldName
_Literal_string = (String -> FieldName
Core.FieldName String
"string")

-- | Note: this is an approximation which ignores encoding
newtype IntegerLiteral = 
  IntegerLiteral {
    -- | Note: this is an approximation which ignores encoding
    IntegerLiteral -> Integer
unIntegerLiteral :: Integer}
  deriving (IntegerLiteral -> IntegerLiteral -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IntegerLiteral -> IntegerLiteral -> Bool
$c/= :: IntegerLiteral -> IntegerLiteral -> Bool
== :: IntegerLiteral -> IntegerLiteral -> Bool
$c== :: IntegerLiteral -> IntegerLiteral -> Bool
Eq, Eq IntegerLiteral
IntegerLiteral -> IntegerLiteral -> Bool
IntegerLiteral -> IntegerLiteral -> Ordering
IntegerLiteral -> IntegerLiteral -> IntegerLiteral
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: IntegerLiteral -> IntegerLiteral -> IntegerLiteral
$cmin :: IntegerLiteral -> IntegerLiteral -> IntegerLiteral
max :: IntegerLiteral -> IntegerLiteral -> IntegerLiteral
$cmax :: IntegerLiteral -> IntegerLiteral -> IntegerLiteral
>= :: IntegerLiteral -> IntegerLiteral -> Bool
$c>= :: IntegerLiteral -> IntegerLiteral -> Bool
> :: IntegerLiteral -> IntegerLiteral -> Bool
$c> :: IntegerLiteral -> IntegerLiteral -> Bool
<= :: IntegerLiteral -> IntegerLiteral -> Bool
$c<= :: IntegerLiteral -> IntegerLiteral -> Bool
< :: IntegerLiteral -> IntegerLiteral -> Bool
$c< :: IntegerLiteral -> IntegerLiteral -> Bool
compare :: IntegerLiteral -> IntegerLiteral -> Ordering
$ccompare :: IntegerLiteral -> IntegerLiteral -> Ordering
Ord, ReadPrec [IntegerLiteral]
ReadPrec IntegerLiteral
Int -> ReadS IntegerLiteral
ReadS [IntegerLiteral]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [IntegerLiteral]
$creadListPrec :: ReadPrec [IntegerLiteral]
readPrec :: ReadPrec IntegerLiteral
$creadPrec :: ReadPrec IntegerLiteral
readList :: ReadS [IntegerLiteral]
$creadList :: ReadS [IntegerLiteral]
readsPrec :: Int -> ReadS IntegerLiteral
$creadsPrec :: Int -> ReadS IntegerLiteral
Read, Int -> IntegerLiteral -> String -> String
[IntegerLiteral] -> String -> String
IntegerLiteral -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [IntegerLiteral] -> String -> String
$cshowList :: [IntegerLiteral] -> String -> String
show :: IntegerLiteral -> String
$cshow :: IntegerLiteral -> String
showsPrec :: Int -> IntegerLiteral -> String -> String
$cshowsPrec :: Int -> IntegerLiteral -> String -> String
Show)

_IntegerLiteral :: Name
_IntegerLiteral = (String -> Name
Core.Name String
"hydra/ext/java/syntax.IntegerLiteral")

-- | Note: this is an approximation which ignores encoding
newtype FloatingPointLiteral = 
  FloatingPointLiteral {
    -- | Note: this is an approximation which ignores encoding
    FloatingPointLiteral -> Double
unFloatingPointLiteral :: Double}
  deriving (FloatingPointLiteral -> FloatingPointLiteral -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FloatingPointLiteral -> FloatingPointLiteral -> Bool
$c/= :: FloatingPointLiteral -> FloatingPointLiteral -> Bool
== :: FloatingPointLiteral -> FloatingPointLiteral -> Bool
$c== :: FloatingPointLiteral -> FloatingPointLiteral -> Bool
Eq, Eq FloatingPointLiteral
FloatingPointLiteral -> FloatingPointLiteral -> Bool
FloatingPointLiteral -> FloatingPointLiteral -> Ordering
FloatingPointLiteral
-> FloatingPointLiteral -> FloatingPointLiteral
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: FloatingPointLiteral
-> FloatingPointLiteral -> FloatingPointLiteral
$cmin :: FloatingPointLiteral
-> FloatingPointLiteral -> FloatingPointLiteral
max :: FloatingPointLiteral
-> FloatingPointLiteral -> FloatingPointLiteral
$cmax :: FloatingPointLiteral
-> FloatingPointLiteral -> FloatingPointLiteral
>= :: FloatingPointLiteral -> FloatingPointLiteral -> Bool
$c>= :: FloatingPointLiteral -> FloatingPointLiteral -> Bool
> :: FloatingPointLiteral -> FloatingPointLiteral -> Bool
$c> :: FloatingPointLiteral -> FloatingPointLiteral -> Bool
<= :: FloatingPointLiteral -> FloatingPointLiteral -> Bool
$c<= :: FloatingPointLiteral -> FloatingPointLiteral -> Bool
< :: FloatingPointLiteral -> FloatingPointLiteral -> Bool
$c< :: FloatingPointLiteral -> FloatingPointLiteral -> Bool
compare :: FloatingPointLiteral -> FloatingPointLiteral -> Ordering
$ccompare :: FloatingPointLiteral -> FloatingPointLiteral -> Ordering
Ord, ReadPrec [FloatingPointLiteral]
ReadPrec FloatingPointLiteral
Int -> ReadS FloatingPointLiteral
ReadS [FloatingPointLiteral]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [FloatingPointLiteral]
$creadListPrec :: ReadPrec [FloatingPointLiteral]
readPrec :: ReadPrec FloatingPointLiteral
$creadPrec :: ReadPrec FloatingPointLiteral
readList :: ReadS [FloatingPointLiteral]
$creadList :: ReadS [FloatingPointLiteral]
readsPrec :: Int -> ReadS FloatingPointLiteral
$creadsPrec :: Int -> ReadS FloatingPointLiteral
Read, Int -> FloatingPointLiteral -> String -> String
[FloatingPointLiteral] -> String -> String
FloatingPointLiteral -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [FloatingPointLiteral] -> String -> String
$cshowList :: [FloatingPointLiteral] -> String -> String
show :: FloatingPointLiteral -> String
$cshow :: FloatingPointLiteral -> String
showsPrec :: Int -> FloatingPointLiteral -> String -> String
$cshowsPrec :: Int -> FloatingPointLiteral -> String -> String
Show)

_FloatingPointLiteral :: Name
_FloatingPointLiteral = (String -> Name
Core.Name String
"hydra/ext/java/syntax.FloatingPointLiteral")

-- | Note: this is an approximation which ignores encoding
newtype StringLiteral = 
  StringLiteral {
    -- | Note: this is an approximation which ignores encoding
    StringLiteral -> String
unStringLiteral :: String}
  deriving (StringLiteral -> StringLiteral -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StringLiteral -> StringLiteral -> Bool
$c/= :: StringLiteral -> StringLiteral -> Bool
== :: StringLiteral -> StringLiteral -> Bool
$c== :: StringLiteral -> StringLiteral -> Bool
Eq, Eq StringLiteral
StringLiteral -> StringLiteral -> Bool
StringLiteral -> StringLiteral -> Ordering
StringLiteral -> StringLiteral -> StringLiteral
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: StringLiteral -> StringLiteral -> StringLiteral
$cmin :: StringLiteral -> StringLiteral -> StringLiteral
max :: StringLiteral -> StringLiteral -> StringLiteral
$cmax :: StringLiteral -> StringLiteral -> StringLiteral
>= :: StringLiteral -> StringLiteral -> Bool
$c>= :: StringLiteral -> StringLiteral -> Bool
> :: StringLiteral -> StringLiteral -> Bool
$c> :: StringLiteral -> StringLiteral -> Bool
<= :: StringLiteral -> StringLiteral -> Bool
$c<= :: StringLiteral -> StringLiteral -> Bool
< :: StringLiteral -> StringLiteral -> Bool
$c< :: StringLiteral -> StringLiteral -> Bool
compare :: StringLiteral -> StringLiteral -> Ordering
$ccompare :: StringLiteral -> StringLiteral -> Ordering
Ord, ReadPrec [StringLiteral]
ReadPrec StringLiteral
Int -> ReadS StringLiteral
ReadS [StringLiteral]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StringLiteral]
$creadListPrec :: ReadPrec [StringLiteral]
readPrec :: ReadPrec StringLiteral
$creadPrec :: ReadPrec StringLiteral
readList :: ReadS [StringLiteral]
$creadList :: ReadS [StringLiteral]
readsPrec :: Int -> ReadS StringLiteral
$creadsPrec :: Int -> ReadS StringLiteral
Read, Int -> StringLiteral -> String -> String
[StringLiteral] -> String -> String
StringLiteral -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [StringLiteral] -> String -> String
$cshowList :: [StringLiteral] -> String -> String
show :: StringLiteral -> String
$cshow :: StringLiteral -> String
showsPrec :: Int -> StringLiteral -> String -> String
$cshowsPrec :: Int -> StringLiteral -> String -> String
Show)

_StringLiteral :: Name
_StringLiteral = (String -> Name
Core.Name String
"hydra/ext/java/syntax.StringLiteral")

data Type = 
  TypePrimitive PrimitiveTypeWithAnnotations |
  TypeReference ReferenceType
  deriving (Type -> Type -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Type -> Type -> Bool
$c/= :: Type -> Type -> Bool
== :: Type -> Type -> Bool
$c== :: Type -> Type -> Bool
Eq, Eq Type
Type -> Type -> Bool
Type -> Type -> Ordering
Type -> Type -> Type
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Type -> Type -> Type
$cmin :: Type -> Type -> Type
max :: Type -> Type -> Type
$cmax :: Type -> Type -> Type
>= :: Type -> Type -> Bool
$c>= :: Type -> Type -> Bool
> :: Type -> Type -> Bool
$c> :: Type -> Type -> Bool
<= :: Type -> Type -> Bool
$c<= :: Type -> Type -> Bool
< :: Type -> Type -> Bool
$c< :: Type -> Type -> Bool
compare :: Type -> Type -> Ordering
$ccompare :: Type -> Type -> Ordering
Ord, ReadPrec [Type]
ReadPrec Type
Int -> ReadS Type
ReadS [Type]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Type]
$creadListPrec :: ReadPrec [Type]
readPrec :: ReadPrec Type
$creadPrec :: ReadPrec Type
readList :: ReadS [Type]
$creadList :: ReadS [Type]
readsPrec :: Int -> ReadS Type
$creadsPrec :: Int -> ReadS Type
Read, Int -> Type -> String -> String
[Type] -> String -> String
Type -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [Type] -> String -> String
$cshowList :: [Type] -> String -> String
show :: Type -> String
$cshow :: Type -> String
showsPrec :: Int -> Type -> String -> String
$cshowsPrec :: Int -> Type -> String -> String
Show)

_Type :: Name
_Type = (String -> Name
Core.Name String
"hydra/ext/java/syntax.Type")

_Type_primitive :: FieldName
_Type_primitive = (String -> FieldName
Core.FieldName String
"primitive")

_Type_reference :: FieldName
_Type_reference = (String -> FieldName
Core.FieldName String
"reference")

data PrimitiveTypeWithAnnotations = 
  PrimitiveTypeWithAnnotations {
    PrimitiveTypeWithAnnotations -> PrimitiveType
primitiveTypeWithAnnotationsType :: PrimitiveType,
    PrimitiveTypeWithAnnotations -> [Annotation]
primitiveTypeWithAnnotationsAnnotations :: [Annotation]}
  deriving (PrimitiveTypeWithAnnotations
-> PrimitiveTypeWithAnnotations -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PrimitiveTypeWithAnnotations
-> PrimitiveTypeWithAnnotations -> Bool
$c/= :: PrimitiveTypeWithAnnotations
-> PrimitiveTypeWithAnnotations -> Bool
== :: PrimitiveTypeWithAnnotations
-> PrimitiveTypeWithAnnotations -> Bool
$c== :: PrimitiveTypeWithAnnotations
-> PrimitiveTypeWithAnnotations -> Bool
Eq, Eq PrimitiveTypeWithAnnotations
PrimitiveTypeWithAnnotations
-> PrimitiveTypeWithAnnotations -> Bool
PrimitiveTypeWithAnnotations
-> PrimitiveTypeWithAnnotations -> Ordering
PrimitiveTypeWithAnnotations
-> PrimitiveTypeWithAnnotations -> PrimitiveTypeWithAnnotations
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: PrimitiveTypeWithAnnotations
-> PrimitiveTypeWithAnnotations -> PrimitiveTypeWithAnnotations
$cmin :: PrimitiveTypeWithAnnotations
-> PrimitiveTypeWithAnnotations -> PrimitiveTypeWithAnnotations
max :: PrimitiveTypeWithAnnotations
-> PrimitiveTypeWithAnnotations -> PrimitiveTypeWithAnnotations
$cmax :: PrimitiveTypeWithAnnotations
-> PrimitiveTypeWithAnnotations -> PrimitiveTypeWithAnnotations
>= :: PrimitiveTypeWithAnnotations
-> PrimitiveTypeWithAnnotations -> Bool
$c>= :: PrimitiveTypeWithAnnotations
-> PrimitiveTypeWithAnnotations -> Bool
> :: PrimitiveTypeWithAnnotations
-> PrimitiveTypeWithAnnotations -> Bool
$c> :: PrimitiveTypeWithAnnotations
-> PrimitiveTypeWithAnnotations -> Bool
<= :: PrimitiveTypeWithAnnotations
-> PrimitiveTypeWithAnnotations -> Bool
$c<= :: PrimitiveTypeWithAnnotations
-> PrimitiveTypeWithAnnotations -> Bool
< :: PrimitiveTypeWithAnnotations
-> PrimitiveTypeWithAnnotations -> Bool
$c< :: PrimitiveTypeWithAnnotations
-> PrimitiveTypeWithAnnotations -> Bool
compare :: PrimitiveTypeWithAnnotations
-> PrimitiveTypeWithAnnotations -> Ordering
$ccompare :: PrimitiveTypeWithAnnotations
-> PrimitiveTypeWithAnnotations -> Ordering
Ord, ReadPrec [PrimitiveTypeWithAnnotations]
ReadPrec PrimitiveTypeWithAnnotations
Int -> ReadS PrimitiveTypeWithAnnotations
ReadS [PrimitiveTypeWithAnnotations]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [PrimitiveTypeWithAnnotations]
$creadListPrec :: ReadPrec [PrimitiveTypeWithAnnotations]
readPrec :: ReadPrec PrimitiveTypeWithAnnotations
$creadPrec :: ReadPrec PrimitiveTypeWithAnnotations
readList :: ReadS [PrimitiveTypeWithAnnotations]
$creadList :: ReadS [PrimitiveTypeWithAnnotations]
readsPrec :: Int -> ReadS PrimitiveTypeWithAnnotations
$creadsPrec :: Int -> ReadS PrimitiveTypeWithAnnotations
Read, Int -> PrimitiveTypeWithAnnotations -> String -> String
[PrimitiveTypeWithAnnotations] -> String -> String
PrimitiveTypeWithAnnotations -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [PrimitiveTypeWithAnnotations] -> String -> String
$cshowList :: [PrimitiveTypeWithAnnotations] -> String -> String
show :: PrimitiveTypeWithAnnotations -> String
$cshow :: PrimitiveTypeWithAnnotations -> String
showsPrec :: Int -> PrimitiveTypeWithAnnotations -> String -> String
$cshowsPrec :: Int -> PrimitiveTypeWithAnnotations -> String -> String
Show)

_PrimitiveTypeWithAnnotations :: Name
_PrimitiveTypeWithAnnotations = (String -> Name
Core.Name String
"hydra/ext/java/syntax.PrimitiveTypeWithAnnotations")

_PrimitiveTypeWithAnnotations_type :: FieldName
_PrimitiveTypeWithAnnotations_type = (String -> FieldName
Core.FieldName String
"type")

_PrimitiveTypeWithAnnotations_annotations :: FieldName
_PrimitiveTypeWithAnnotations_annotations = (String -> FieldName
Core.FieldName String
"annotations")

data PrimitiveType = 
  PrimitiveTypeNumeric NumericType |
  PrimitiveTypeBoolean 
  deriving (PrimitiveType -> PrimitiveType -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PrimitiveType -> PrimitiveType -> Bool
$c/= :: PrimitiveType -> PrimitiveType -> Bool
== :: PrimitiveType -> PrimitiveType -> Bool
$c== :: PrimitiveType -> PrimitiveType -> Bool
Eq, Eq PrimitiveType
PrimitiveType -> PrimitiveType -> Bool
PrimitiveType -> PrimitiveType -> Ordering
PrimitiveType -> PrimitiveType -> PrimitiveType
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: PrimitiveType -> PrimitiveType -> PrimitiveType
$cmin :: PrimitiveType -> PrimitiveType -> PrimitiveType
max :: PrimitiveType -> PrimitiveType -> PrimitiveType
$cmax :: PrimitiveType -> PrimitiveType -> PrimitiveType
>= :: PrimitiveType -> PrimitiveType -> Bool
$c>= :: PrimitiveType -> PrimitiveType -> Bool
> :: PrimitiveType -> PrimitiveType -> Bool
$c> :: PrimitiveType -> PrimitiveType -> Bool
<= :: PrimitiveType -> PrimitiveType -> Bool
$c<= :: PrimitiveType -> PrimitiveType -> Bool
< :: PrimitiveType -> PrimitiveType -> Bool
$c< :: PrimitiveType -> PrimitiveType -> Bool
compare :: PrimitiveType -> PrimitiveType -> Ordering
$ccompare :: PrimitiveType -> PrimitiveType -> Ordering
Ord, ReadPrec [PrimitiveType]
ReadPrec PrimitiveType
Int -> ReadS PrimitiveType
ReadS [PrimitiveType]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [PrimitiveType]
$creadListPrec :: ReadPrec [PrimitiveType]
readPrec :: ReadPrec PrimitiveType
$creadPrec :: ReadPrec PrimitiveType
readList :: ReadS [PrimitiveType]
$creadList :: ReadS [PrimitiveType]
readsPrec :: Int -> ReadS PrimitiveType
$creadsPrec :: Int -> ReadS PrimitiveType
Read, Int -> PrimitiveType -> String -> String
[PrimitiveType] -> String -> String
PrimitiveType -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [PrimitiveType] -> String -> String
$cshowList :: [PrimitiveType] -> String -> String
show :: PrimitiveType -> String
$cshow :: PrimitiveType -> String
showsPrec :: Int -> PrimitiveType -> String -> String
$cshowsPrec :: Int -> PrimitiveType -> String -> String
Show)

_PrimitiveType :: Name
_PrimitiveType = (String -> Name
Core.Name String
"hydra/ext/java/syntax.PrimitiveType")

_PrimitiveType_numeric :: FieldName
_PrimitiveType_numeric = (String -> FieldName
Core.FieldName String
"numeric")

_PrimitiveType_boolean :: FieldName
_PrimitiveType_boolean = (String -> FieldName
Core.FieldName String
"boolean")

data NumericType = 
  NumericTypeIntegral IntegralType |
  NumericTypeFloatingPoint FloatingPointType
  deriving (NumericType -> NumericType -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NumericType -> NumericType -> Bool
$c/= :: NumericType -> NumericType -> Bool
== :: NumericType -> NumericType -> Bool
$c== :: NumericType -> NumericType -> Bool
Eq, Eq NumericType
NumericType -> NumericType -> Bool
NumericType -> NumericType -> Ordering
NumericType -> NumericType -> NumericType
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: NumericType -> NumericType -> NumericType
$cmin :: NumericType -> NumericType -> NumericType
max :: NumericType -> NumericType -> NumericType
$cmax :: NumericType -> NumericType -> NumericType
>= :: NumericType -> NumericType -> Bool
$c>= :: NumericType -> NumericType -> Bool
> :: NumericType -> NumericType -> Bool
$c> :: NumericType -> NumericType -> Bool
<= :: NumericType -> NumericType -> Bool
$c<= :: NumericType -> NumericType -> Bool
< :: NumericType -> NumericType -> Bool
$c< :: NumericType -> NumericType -> Bool
compare :: NumericType -> NumericType -> Ordering
$ccompare :: NumericType -> NumericType -> Ordering
Ord, ReadPrec [NumericType]
ReadPrec NumericType
Int -> ReadS NumericType
ReadS [NumericType]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [NumericType]
$creadListPrec :: ReadPrec [NumericType]
readPrec :: ReadPrec NumericType
$creadPrec :: ReadPrec NumericType
readList :: ReadS [NumericType]
$creadList :: ReadS [NumericType]
readsPrec :: Int -> ReadS NumericType
$creadsPrec :: Int -> ReadS NumericType
Read, Int -> NumericType -> String -> String
[NumericType] -> String -> String
NumericType -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [NumericType] -> String -> String
$cshowList :: [NumericType] -> String -> String
show :: NumericType -> String
$cshow :: NumericType -> String
showsPrec :: Int -> NumericType -> String -> String
$cshowsPrec :: Int -> NumericType -> String -> String
Show)

_NumericType :: Name
_NumericType = (String -> Name
Core.Name String
"hydra/ext/java/syntax.NumericType")

_NumericType_integral :: FieldName
_NumericType_integral = (String -> FieldName
Core.FieldName String
"integral")

_NumericType_floatingPoint :: FieldName
_NumericType_floatingPoint = (String -> FieldName
Core.FieldName String
"floatingPoint")

data IntegralType = 
  IntegralTypeByte  |
  IntegralTypeShort  |
  IntegralTypeInt  |
  IntegralTypeLong  |
  IntegralTypeChar 
  deriving (IntegralType -> IntegralType -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IntegralType -> IntegralType -> Bool
$c/= :: IntegralType -> IntegralType -> Bool
== :: IntegralType -> IntegralType -> Bool
$c== :: IntegralType -> IntegralType -> Bool
Eq, Eq IntegralType
IntegralType -> IntegralType -> Bool
IntegralType -> IntegralType -> Ordering
IntegralType -> IntegralType -> IntegralType
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: IntegralType -> IntegralType -> IntegralType
$cmin :: IntegralType -> IntegralType -> IntegralType
max :: IntegralType -> IntegralType -> IntegralType
$cmax :: IntegralType -> IntegralType -> IntegralType
>= :: IntegralType -> IntegralType -> Bool
$c>= :: IntegralType -> IntegralType -> Bool
> :: IntegralType -> IntegralType -> Bool
$c> :: IntegralType -> IntegralType -> Bool
<= :: IntegralType -> IntegralType -> Bool
$c<= :: IntegralType -> IntegralType -> Bool
< :: IntegralType -> IntegralType -> Bool
$c< :: IntegralType -> IntegralType -> Bool
compare :: IntegralType -> IntegralType -> Ordering
$ccompare :: IntegralType -> IntegralType -> Ordering
Ord, ReadPrec [IntegralType]
ReadPrec IntegralType
Int -> ReadS IntegralType
ReadS [IntegralType]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [IntegralType]
$creadListPrec :: ReadPrec [IntegralType]
readPrec :: ReadPrec IntegralType
$creadPrec :: ReadPrec IntegralType
readList :: ReadS [IntegralType]
$creadList :: ReadS [IntegralType]
readsPrec :: Int -> ReadS IntegralType
$creadsPrec :: Int -> ReadS IntegralType
Read, Int -> IntegralType -> String -> String
[IntegralType] -> String -> String
IntegralType -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [IntegralType] -> String -> String
$cshowList :: [IntegralType] -> String -> String
show :: IntegralType -> String
$cshow :: IntegralType -> String
showsPrec :: Int -> IntegralType -> String -> String
$cshowsPrec :: Int -> IntegralType -> String -> String
Show)

_IntegralType :: Name
_IntegralType = (String -> Name
Core.Name String
"hydra/ext/java/syntax.IntegralType")

_IntegralType_byte :: FieldName
_IntegralType_byte = (String -> FieldName
Core.FieldName String
"byte")

_IntegralType_short :: FieldName
_IntegralType_short = (String -> FieldName
Core.FieldName String
"short")

_IntegralType_int :: FieldName
_IntegralType_int = (String -> FieldName
Core.FieldName String
"int")

_IntegralType_long :: FieldName
_IntegralType_long = (String -> FieldName
Core.FieldName String
"long")

_IntegralType_char :: FieldName
_IntegralType_char = (String -> FieldName
Core.FieldName String
"char")

data FloatingPointType = 
  FloatingPointTypeFloat  |
  FloatingPointTypeDouble 
  deriving (FloatingPointType -> FloatingPointType -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FloatingPointType -> FloatingPointType -> Bool
$c/= :: FloatingPointType -> FloatingPointType -> Bool
== :: FloatingPointType -> FloatingPointType -> Bool
$c== :: FloatingPointType -> FloatingPointType -> Bool
Eq, Eq FloatingPointType
FloatingPointType -> FloatingPointType -> Bool
FloatingPointType -> FloatingPointType -> Ordering
FloatingPointType -> FloatingPointType -> FloatingPointType
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: FloatingPointType -> FloatingPointType -> FloatingPointType
$cmin :: FloatingPointType -> FloatingPointType -> FloatingPointType
max :: FloatingPointType -> FloatingPointType -> FloatingPointType
$cmax :: FloatingPointType -> FloatingPointType -> FloatingPointType
>= :: FloatingPointType -> FloatingPointType -> Bool
$c>= :: FloatingPointType -> FloatingPointType -> Bool
> :: FloatingPointType -> FloatingPointType -> Bool
$c> :: FloatingPointType -> FloatingPointType -> Bool
<= :: FloatingPointType -> FloatingPointType -> Bool
$c<= :: FloatingPointType -> FloatingPointType -> Bool
< :: FloatingPointType -> FloatingPointType -> Bool
$c< :: FloatingPointType -> FloatingPointType -> Bool
compare :: FloatingPointType -> FloatingPointType -> Ordering
$ccompare :: FloatingPointType -> FloatingPointType -> Ordering
Ord, ReadPrec [FloatingPointType]
ReadPrec FloatingPointType
Int -> ReadS FloatingPointType
ReadS [FloatingPointType]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [FloatingPointType]
$creadListPrec :: ReadPrec [FloatingPointType]
readPrec :: ReadPrec FloatingPointType
$creadPrec :: ReadPrec FloatingPointType
readList :: ReadS [FloatingPointType]
$creadList :: ReadS [FloatingPointType]
readsPrec :: Int -> ReadS FloatingPointType
$creadsPrec :: Int -> ReadS FloatingPointType
Read, Int -> FloatingPointType -> String -> String
[FloatingPointType] -> String -> String
FloatingPointType -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [FloatingPointType] -> String -> String
$cshowList :: [FloatingPointType] -> String -> String
show :: FloatingPointType -> String
$cshow :: FloatingPointType -> String
showsPrec :: Int -> FloatingPointType -> String -> String
$cshowsPrec :: Int -> FloatingPointType -> String -> String
Show)

_FloatingPointType :: Name
_FloatingPointType = (String -> Name
Core.Name String
"hydra/ext/java/syntax.FloatingPointType")

_FloatingPointType_float :: FieldName
_FloatingPointType_float = (String -> FieldName
Core.FieldName String
"float")

_FloatingPointType_double :: FieldName
_FloatingPointType_double = (String -> FieldName
Core.FieldName String
"double")

data ReferenceType = 
  ReferenceTypeClassOrInterface ClassOrInterfaceType |
  ReferenceTypeVariable TypeVariable |
  ReferenceTypeArray ArrayType
  deriving (ReferenceType -> ReferenceType -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ReferenceType -> ReferenceType -> Bool
$c/= :: ReferenceType -> ReferenceType -> Bool
== :: ReferenceType -> ReferenceType -> Bool
$c== :: ReferenceType -> ReferenceType -> Bool
Eq, Eq ReferenceType
ReferenceType -> ReferenceType -> Bool
ReferenceType -> ReferenceType -> Ordering
ReferenceType -> ReferenceType -> ReferenceType
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ReferenceType -> ReferenceType -> ReferenceType
$cmin :: ReferenceType -> ReferenceType -> ReferenceType
max :: ReferenceType -> ReferenceType -> ReferenceType
$cmax :: ReferenceType -> ReferenceType -> ReferenceType
>= :: ReferenceType -> ReferenceType -> Bool
$c>= :: ReferenceType -> ReferenceType -> Bool
> :: ReferenceType -> ReferenceType -> Bool
$c> :: ReferenceType -> ReferenceType -> Bool
<= :: ReferenceType -> ReferenceType -> Bool
$c<= :: ReferenceType -> ReferenceType -> Bool
< :: ReferenceType -> ReferenceType -> Bool
$c< :: ReferenceType -> ReferenceType -> Bool
compare :: ReferenceType -> ReferenceType -> Ordering
$ccompare :: ReferenceType -> ReferenceType -> Ordering
Ord, ReadPrec [ReferenceType]
ReadPrec ReferenceType
Int -> ReadS ReferenceType
ReadS [ReferenceType]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ReferenceType]
$creadListPrec :: ReadPrec [ReferenceType]
readPrec :: ReadPrec ReferenceType
$creadPrec :: ReadPrec ReferenceType
readList :: ReadS [ReferenceType]
$creadList :: ReadS [ReferenceType]
readsPrec :: Int -> ReadS ReferenceType
$creadsPrec :: Int -> ReadS ReferenceType
Read, Int -> ReferenceType -> String -> String
[ReferenceType] -> String -> String
ReferenceType -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ReferenceType] -> String -> String
$cshowList :: [ReferenceType] -> String -> String
show :: ReferenceType -> String
$cshow :: ReferenceType -> String
showsPrec :: Int -> ReferenceType -> String -> String
$cshowsPrec :: Int -> ReferenceType -> String -> String
Show)

_ReferenceType :: Name
_ReferenceType = (String -> Name
Core.Name String
"hydra/ext/java/syntax.ReferenceType")

_ReferenceType_classOrInterface :: FieldName
_ReferenceType_classOrInterface = (String -> FieldName
Core.FieldName String
"classOrInterface")

_ReferenceType_variable :: FieldName
_ReferenceType_variable = (String -> FieldName
Core.FieldName String
"variable")

_ReferenceType_array :: FieldName
_ReferenceType_array = (String -> FieldName
Core.FieldName String
"array")

data ClassOrInterfaceType = 
  ClassOrInterfaceTypeClass ClassType |
  ClassOrInterfaceTypeInterface InterfaceType
  deriving (ClassOrInterfaceType -> ClassOrInterfaceType -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ClassOrInterfaceType -> ClassOrInterfaceType -> Bool
$c/= :: ClassOrInterfaceType -> ClassOrInterfaceType -> Bool
== :: ClassOrInterfaceType -> ClassOrInterfaceType -> Bool
$c== :: ClassOrInterfaceType -> ClassOrInterfaceType -> Bool
Eq, Eq ClassOrInterfaceType
ClassOrInterfaceType -> ClassOrInterfaceType -> Bool
ClassOrInterfaceType -> ClassOrInterfaceType -> Ordering
ClassOrInterfaceType
-> ClassOrInterfaceType -> ClassOrInterfaceType
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ClassOrInterfaceType
-> ClassOrInterfaceType -> ClassOrInterfaceType
$cmin :: ClassOrInterfaceType
-> ClassOrInterfaceType -> ClassOrInterfaceType
max :: ClassOrInterfaceType
-> ClassOrInterfaceType -> ClassOrInterfaceType
$cmax :: ClassOrInterfaceType
-> ClassOrInterfaceType -> ClassOrInterfaceType
>= :: ClassOrInterfaceType -> ClassOrInterfaceType -> Bool
$c>= :: ClassOrInterfaceType -> ClassOrInterfaceType -> Bool
> :: ClassOrInterfaceType -> ClassOrInterfaceType -> Bool
$c> :: ClassOrInterfaceType -> ClassOrInterfaceType -> Bool
<= :: ClassOrInterfaceType -> ClassOrInterfaceType -> Bool
$c<= :: ClassOrInterfaceType -> ClassOrInterfaceType -> Bool
< :: ClassOrInterfaceType -> ClassOrInterfaceType -> Bool
$c< :: ClassOrInterfaceType -> ClassOrInterfaceType -> Bool
compare :: ClassOrInterfaceType -> ClassOrInterfaceType -> Ordering
$ccompare :: ClassOrInterfaceType -> ClassOrInterfaceType -> Ordering
Ord, ReadPrec [ClassOrInterfaceType]
ReadPrec ClassOrInterfaceType
Int -> ReadS ClassOrInterfaceType
ReadS [ClassOrInterfaceType]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ClassOrInterfaceType]
$creadListPrec :: ReadPrec [ClassOrInterfaceType]
readPrec :: ReadPrec ClassOrInterfaceType
$creadPrec :: ReadPrec ClassOrInterfaceType
readList :: ReadS [ClassOrInterfaceType]
$creadList :: ReadS [ClassOrInterfaceType]
readsPrec :: Int -> ReadS ClassOrInterfaceType
$creadsPrec :: Int -> ReadS ClassOrInterfaceType
Read, Int -> ClassOrInterfaceType -> String -> String
[ClassOrInterfaceType] -> String -> String
ClassOrInterfaceType -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ClassOrInterfaceType] -> String -> String
$cshowList :: [ClassOrInterfaceType] -> String -> String
show :: ClassOrInterfaceType -> String
$cshow :: ClassOrInterfaceType -> String
showsPrec :: Int -> ClassOrInterfaceType -> String -> String
$cshowsPrec :: Int -> ClassOrInterfaceType -> String -> String
Show)

_ClassOrInterfaceType :: Name
_ClassOrInterfaceType = (String -> Name
Core.Name String
"hydra/ext/java/syntax.ClassOrInterfaceType")

_ClassOrInterfaceType_class :: FieldName
_ClassOrInterfaceType_class = (String -> FieldName
Core.FieldName String
"class")

_ClassOrInterfaceType_interface :: FieldName
_ClassOrInterfaceType_interface = (String -> FieldName
Core.FieldName String
"interface")

data ClassType = 
  ClassType {
    ClassType -> [Annotation]
classTypeAnnotations :: [Annotation],
    ClassType -> ClassTypeQualifier
classTypeQualifier :: ClassTypeQualifier,
    ClassType -> TypeIdentifier
classTypeIdentifier :: TypeIdentifier,
    ClassType -> [TypeArgument]
classTypeArguments :: [TypeArgument]}
  deriving (ClassType -> ClassType -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ClassType -> ClassType -> Bool
$c/= :: ClassType -> ClassType -> Bool
== :: ClassType -> ClassType -> Bool
$c== :: ClassType -> ClassType -> Bool
Eq, Eq ClassType
ClassType -> ClassType -> Bool
ClassType -> ClassType -> Ordering
ClassType -> ClassType -> ClassType
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ClassType -> ClassType -> ClassType
$cmin :: ClassType -> ClassType -> ClassType
max :: ClassType -> ClassType -> ClassType
$cmax :: ClassType -> ClassType -> ClassType
>= :: ClassType -> ClassType -> Bool
$c>= :: ClassType -> ClassType -> Bool
> :: ClassType -> ClassType -> Bool
$c> :: ClassType -> ClassType -> Bool
<= :: ClassType -> ClassType -> Bool
$c<= :: ClassType -> ClassType -> Bool
< :: ClassType -> ClassType -> Bool
$c< :: ClassType -> ClassType -> Bool
compare :: ClassType -> ClassType -> Ordering
$ccompare :: ClassType -> ClassType -> Ordering
Ord, ReadPrec [ClassType]
ReadPrec ClassType
Int -> ReadS ClassType
ReadS [ClassType]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ClassType]
$creadListPrec :: ReadPrec [ClassType]
readPrec :: ReadPrec ClassType
$creadPrec :: ReadPrec ClassType
readList :: ReadS [ClassType]
$creadList :: ReadS [ClassType]
readsPrec :: Int -> ReadS ClassType
$creadsPrec :: Int -> ReadS ClassType
Read, Int -> ClassType -> String -> String
[ClassType] -> String -> String
ClassType -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ClassType] -> String -> String
$cshowList :: [ClassType] -> String -> String
show :: ClassType -> String
$cshow :: ClassType -> String
showsPrec :: Int -> ClassType -> String -> String
$cshowsPrec :: Int -> ClassType -> String -> String
Show)

_ClassType :: Name
_ClassType = (String -> Name
Core.Name String
"hydra/ext/java/syntax.ClassType")

_ClassType_annotations :: FieldName
_ClassType_annotations = (String -> FieldName
Core.FieldName String
"annotations")

_ClassType_qualifier :: FieldName
_ClassType_qualifier = (String -> FieldName
Core.FieldName String
"qualifier")

_ClassType_identifier :: FieldName
_ClassType_identifier = (String -> FieldName
Core.FieldName String
"identifier")

_ClassType_arguments :: FieldName
_ClassType_arguments = (String -> FieldName
Core.FieldName String
"arguments")

data ClassTypeQualifier = 
  ClassTypeQualifierNone  |
  ClassTypeQualifierPackage PackageName |
  ClassTypeQualifierParent ClassOrInterfaceType
  deriving (ClassTypeQualifier -> ClassTypeQualifier -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ClassTypeQualifier -> ClassTypeQualifier -> Bool
$c/= :: ClassTypeQualifier -> ClassTypeQualifier -> Bool
== :: ClassTypeQualifier -> ClassTypeQualifier -> Bool
$c== :: ClassTypeQualifier -> ClassTypeQualifier -> Bool
Eq, Eq ClassTypeQualifier
ClassTypeQualifier -> ClassTypeQualifier -> Bool
ClassTypeQualifier -> ClassTypeQualifier -> Ordering
ClassTypeQualifier -> ClassTypeQualifier -> ClassTypeQualifier
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ClassTypeQualifier -> ClassTypeQualifier -> ClassTypeQualifier
$cmin :: ClassTypeQualifier -> ClassTypeQualifier -> ClassTypeQualifier
max :: ClassTypeQualifier -> ClassTypeQualifier -> ClassTypeQualifier
$cmax :: ClassTypeQualifier -> ClassTypeQualifier -> ClassTypeQualifier
>= :: ClassTypeQualifier -> ClassTypeQualifier -> Bool
$c>= :: ClassTypeQualifier -> ClassTypeQualifier -> Bool
> :: ClassTypeQualifier -> ClassTypeQualifier -> Bool
$c> :: ClassTypeQualifier -> ClassTypeQualifier -> Bool
<= :: ClassTypeQualifier -> ClassTypeQualifier -> Bool
$c<= :: ClassTypeQualifier -> ClassTypeQualifier -> Bool
< :: ClassTypeQualifier -> ClassTypeQualifier -> Bool
$c< :: ClassTypeQualifier -> ClassTypeQualifier -> Bool
compare :: ClassTypeQualifier -> ClassTypeQualifier -> Ordering
$ccompare :: ClassTypeQualifier -> ClassTypeQualifier -> Ordering
Ord, ReadPrec [ClassTypeQualifier]
ReadPrec ClassTypeQualifier
Int -> ReadS ClassTypeQualifier
ReadS [ClassTypeQualifier]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ClassTypeQualifier]
$creadListPrec :: ReadPrec [ClassTypeQualifier]
readPrec :: ReadPrec ClassTypeQualifier
$creadPrec :: ReadPrec ClassTypeQualifier
readList :: ReadS [ClassTypeQualifier]
$creadList :: ReadS [ClassTypeQualifier]
readsPrec :: Int -> ReadS ClassTypeQualifier
$creadsPrec :: Int -> ReadS ClassTypeQualifier
Read, Int -> ClassTypeQualifier -> String -> String
[ClassTypeQualifier] -> String -> String
ClassTypeQualifier -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ClassTypeQualifier] -> String -> String
$cshowList :: [ClassTypeQualifier] -> String -> String
show :: ClassTypeQualifier -> String
$cshow :: ClassTypeQualifier -> String
showsPrec :: Int -> ClassTypeQualifier -> String -> String
$cshowsPrec :: Int -> ClassTypeQualifier -> String -> String
Show)

_ClassTypeQualifier :: Name
_ClassTypeQualifier = (String -> Name
Core.Name String
"hydra/ext/java/syntax.ClassTypeQualifier")

_ClassTypeQualifier_none :: FieldName
_ClassTypeQualifier_none = (String -> FieldName
Core.FieldName String
"none")

_ClassTypeQualifier_package :: FieldName
_ClassTypeQualifier_package = (String -> FieldName
Core.FieldName String
"package")

_ClassTypeQualifier_parent :: FieldName
_ClassTypeQualifier_parent = (String -> FieldName
Core.FieldName String
"parent")

newtype InterfaceType = 
  InterfaceType {
    InterfaceType -> ClassType
unInterfaceType :: ClassType}
  deriving (InterfaceType -> InterfaceType -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InterfaceType -> InterfaceType -> Bool
$c/= :: InterfaceType -> InterfaceType -> Bool
== :: InterfaceType -> InterfaceType -> Bool
$c== :: InterfaceType -> InterfaceType -> Bool
Eq, Eq InterfaceType
InterfaceType -> InterfaceType -> Bool
InterfaceType -> InterfaceType -> Ordering
InterfaceType -> InterfaceType -> InterfaceType
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: InterfaceType -> InterfaceType -> InterfaceType
$cmin :: InterfaceType -> InterfaceType -> InterfaceType
max :: InterfaceType -> InterfaceType -> InterfaceType
$cmax :: InterfaceType -> InterfaceType -> InterfaceType
>= :: InterfaceType -> InterfaceType -> Bool
$c>= :: InterfaceType -> InterfaceType -> Bool
> :: InterfaceType -> InterfaceType -> Bool
$c> :: InterfaceType -> InterfaceType -> Bool
<= :: InterfaceType -> InterfaceType -> Bool
$c<= :: InterfaceType -> InterfaceType -> Bool
< :: InterfaceType -> InterfaceType -> Bool
$c< :: InterfaceType -> InterfaceType -> Bool
compare :: InterfaceType -> InterfaceType -> Ordering
$ccompare :: InterfaceType -> InterfaceType -> Ordering
Ord, ReadPrec [InterfaceType]
ReadPrec InterfaceType
Int -> ReadS InterfaceType
ReadS [InterfaceType]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [InterfaceType]
$creadListPrec :: ReadPrec [InterfaceType]
readPrec :: ReadPrec InterfaceType
$creadPrec :: ReadPrec InterfaceType
readList :: ReadS [InterfaceType]
$creadList :: ReadS [InterfaceType]
readsPrec :: Int -> ReadS InterfaceType
$creadsPrec :: Int -> ReadS InterfaceType
Read, Int -> InterfaceType -> String -> String
[InterfaceType] -> String -> String
InterfaceType -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [InterfaceType] -> String -> String
$cshowList :: [InterfaceType] -> String -> String
show :: InterfaceType -> String
$cshow :: InterfaceType -> String
showsPrec :: Int -> InterfaceType -> String -> String
$cshowsPrec :: Int -> InterfaceType -> String -> String
Show)

_InterfaceType :: Name
_InterfaceType = (String -> Name
Core.Name String
"hydra/ext/java/syntax.InterfaceType")

data TypeVariable = 
  TypeVariable {
    TypeVariable -> [Annotation]
typeVariableAnnotations :: [Annotation],
    TypeVariable -> TypeIdentifier
typeVariableIdentifier :: TypeIdentifier}
  deriving (TypeVariable -> TypeVariable -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TypeVariable -> TypeVariable -> Bool
$c/= :: TypeVariable -> TypeVariable -> Bool
== :: TypeVariable -> TypeVariable -> Bool
$c== :: TypeVariable -> TypeVariable -> Bool
Eq, Eq TypeVariable
TypeVariable -> TypeVariable -> Bool
TypeVariable -> TypeVariable -> Ordering
TypeVariable -> TypeVariable -> TypeVariable
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: TypeVariable -> TypeVariable -> TypeVariable
$cmin :: TypeVariable -> TypeVariable -> TypeVariable
max :: TypeVariable -> TypeVariable -> TypeVariable
$cmax :: TypeVariable -> TypeVariable -> TypeVariable
>= :: TypeVariable -> TypeVariable -> Bool
$c>= :: TypeVariable -> TypeVariable -> Bool
> :: TypeVariable -> TypeVariable -> Bool
$c> :: TypeVariable -> TypeVariable -> Bool
<= :: TypeVariable -> TypeVariable -> Bool
$c<= :: TypeVariable -> TypeVariable -> Bool
< :: TypeVariable -> TypeVariable -> Bool
$c< :: TypeVariable -> TypeVariable -> Bool
compare :: TypeVariable -> TypeVariable -> Ordering
$ccompare :: TypeVariable -> TypeVariable -> Ordering
Ord, ReadPrec [TypeVariable]
ReadPrec TypeVariable
Int -> ReadS TypeVariable
ReadS [TypeVariable]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [TypeVariable]
$creadListPrec :: ReadPrec [TypeVariable]
readPrec :: ReadPrec TypeVariable
$creadPrec :: ReadPrec TypeVariable
readList :: ReadS [TypeVariable]
$creadList :: ReadS [TypeVariable]
readsPrec :: Int -> ReadS TypeVariable
$creadsPrec :: Int -> ReadS TypeVariable
Read, Int -> TypeVariable -> String -> String
[TypeVariable] -> String -> String
TypeVariable -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [TypeVariable] -> String -> String
$cshowList :: [TypeVariable] -> String -> String
show :: TypeVariable -> String
$cshow :: TypeVariable -> String
showsPrec :: Int -> TypeVariable -> String -> String
$cshowsPrec :: Int -> TypeVariable -> String -> String
Show)

_TypeVariable :: Name
_TypeVariable = (String -> Name
Core.Name String
"hydra/ext/java/syntax.TypeVariable")

_TypeVariable_annotations :: FieldName
_TypeVariable_annotations = (String -> FieldName
Core.FieldName String
"annotations")

_TypeVariable_identifier :: FieldName
_TypeVariable_identifier = (String -> FieldName
Core.FieldName String
"identifier")

data ArrayType = 
  ArrayType {
    ArrayType -> Dims
arrayTypeDims :: Dims,
    ArrayType -> ArrayType_Variant
arrayTypeVariant :: ArrayType_Variant}
  deriving (ArrayType -> ArrayType -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ArrayType -> ArrayType -> Bool
$c/= :: ArrayType -> ArrayType -> Bool
== :: ArrayType -> ArrayType -> Bool
$c== :: ArrayType -> ArrayType -> Bool
Eq, Eq ArrayType
ArrayType -> ArrayType -> Bool
ArrayType -> ArrayType -> Ordering
ArrayType -> ArrayType -> ArrayType
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ArrayType -> ArrayType -> ArrayType
$cmin :: ArrayType -> ArrayType -> ArrayType
max :: ArrayType -> ArrayType -> ArrayType
$cmax :: ArrayType -> ArrayType -> ArrayType
>= :: ArrayType -> ArrayType -> Bool
$c>= :: ArrayType -> ArrayType -> Bool
> :: ArrayType -> ArrayType -> Bool
$c> :: ArrayType -> ArrayType -> Bool
<= :: ArrayType -> ArrayType -> Bool
$c<= :: ArrayType -> ArrayType -> Bool
< :: ArrayType -> ArrayType -> Bool
$c< :: ArrayType -> ArrayType -> Bool
compare :: ArrayType -> ArrayType -> Ordering
$ccompare :: ArrayType -> ArrayType -> Ordering
Ord, ReadPrec [ArrayType]
ReadPrec ArrayType
Int -> ReadS ArrayType
ReadS [ArrayType]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ArrayType]
$creadListPrec :: ReadPrec [ArrayType]
readPrec :: ReadPrec ArrayType
$creadPrec :: ReadPrec ArrayType
readList :: ReadS [ArrayType]
$creadList :: ReadS [ArrayType]
readsPrec :: Int -> ReadS ArrayType
$creadsPrec :: Int -> ReadS ArrayType
Read, Int -> ArrayType -> String -> String
[ArrayType] -> String -> String
ArrayType -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ArrayType] -> String -> String
$cshowList :: [ArrayType] -> String -> String
show :: ArrayType -> String
$cshow :: ArrayType -> String
showsPrec :: Int -> ArrayType -> String -> String
$cshowsPrec :: Int -> ArrayType -> String -> String
Show)

_ArrayType :: Name
_ArrayType = (String -> Name
Core.Name String
"hydra/ext/java/syntax.ArrayType")

_ArrayType_dims :: FieldName
_ArrayType_dims = (String -> FieldName
Core.FieldName String
"dims")

_ArrayType_variant :: FieldName
_ArrayType_variant = (String -> FieldName
Core.FieldName String
"variant")

data ArrayType_Variant = 
  ArrayType_VariantPrimitive PrimitiveTypeWithAnnotations |
  ArrayType_VariantClassOrInterface ClassOrInterfaceType |
  ArrayType_VariantVariable TypeVariable
  deriving (ArrayType_Variant -> ArrayType_Variant -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ArrayType_Variant -> ArrayType_Variant -> Bool
$c/= :: ArrayType_Variant -> ArrayType_Variant -> Bool
== :: ArrayType_Variant -> ArrayType_Variant -> Bool
$c== :: ArrayType_Variant -> ArrayType_Variant -> Bool
Eq, Eq ArrayType_Variant
ArrayType_Variant -> ArrayType_Variant -> Bool
ArrayType_Variant -> ArrayType_Variant -> Ordering
ArrayType_Variant -> ArrayType_Variant -> ArrayType_Variant
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ArrayType_Variant -> ArrayType_Variant -> ArrayType_Variant
$cmin :: ArrayType_Variant -> ArrayType_Variant -> ArrayType_Variant
max :: ArrayType_Variant -> ArrayType_Variant -> ArrayType_Variant
$cmax :: ArrayType_Variant -> ArrayType_Variant -> ArrayType_Variant
>= :: ArrayType_Variant -> ArrayType_Variant -> Bool
$c>= :: ArrayType_Variant -> ArrayType_Variant -> Bool
> :: ArrayType_Variant -> ArrayType_Variant -> Bool
$c> :: ArrayType_Variant -> ArrayType_Variant -> Bool
<= :: ArrayType_Variant -> ArrayType_Variant -> Bool
$c<= :: ArrayType_Variant -> ArrayType_Variant -> Bool
< :: ArrayType_Variant -> ArrayType_Variant -> Bool
$c< :: ArrayType_Variant -> ArrayType_Variant -> Bool
compare :: ArrayType_Variant -> ArrayType_Variant -> Ordering
$ccompare :: ArrayType_Variant -> ArrayType_Variant -> Ordering
Ord, ReadPrec [ArrayType_Variant]
ReadPrec ArrayType_Variant
Int -> ReadS ArrayType_Variant
ReadS [ArrayType_Variant]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ArrayType_Variant]
$creadListPrec :: ReadPrec [ArrayType_Variant]
readPrec :: ReadPrec ArrayType_Variant
$creadPrec :: ReadPrec ArrayType_Variant
readList :: ReadS [ArrayType_Variant]
$creadList :: ReadS [ArrayType_Variant]
readsPrec :: Int -> ReadS ArrayType_Variant
$creadsPrec :: Int -> ReadS ArrayType_Variant
Read, Int -> ArrayType_Variant -> String -> String
[ArrayType_Variant] -> String -> String
ArrayType_Variant -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ArrayType_Variant] -> String -> String
$cshowList :: [ArrayType_Variant] -> String -> String
show :: ArrayType_Variant -> String
$cshow :: ArrayType_Variant -> String
showsPrec :: Int -> ArrayType_Variant -> String -> String
$cshowsPrec :: Int -> ArrayType_Variant -> String -> String
Show)

_ArrayType_Variant :: Name
_ArrayType_Variant = (String -> Name
Core.Name String
"hydra/ext/java/syntax.ArrayType.Variant")

_ArrayType_Variant_primitive :: FieldName
_ArrayType_Variant_primitive = (String -> FieldName
Core.FieldName String
"primitive")

_ArrayType_Variant_classOrInterface :: FieldName
_ArrayType_Variant_classOrInterface = (String -> FieldName
Core.FieldName String
"classOrInterface")

_ArrayType_Variant_variable :: FieldName
_ArrayType_Variant_variable = (String -> FieldName
Core.FieldName String
"variable")

newtype Dims = 
  Dims {
    Dims -> [[Annotation]]
unDims :: [[Annotation]]}
  deriving (Dims -> Dims -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Dims -> Dims -> Bool
$c/= :: Dims -> Dims -> Bool
== :: Dims -> Dims -> Bool
$c== :: Dims -> Dims -> Bool
Eq, Eq Dims
Dims -> Dims -> Bool
Dims -> Dims -> Ordering
Dims -> Dims -> Dims
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Dims -> Dims -> Dims
$cmin :: Dims -> Dims -> Dims
max :: Dims -> Dims -> Dims
$cmax :: Dims -> Dims -> Dims
>= :: Dims -> Dims -> Bool
$c>= :: Dims -> Dims -> Bool
> :: Dims -> Dims -> Bool
$c> :: Dims -> Dims -> Bool
<= :: Dims -> Dims -> Bool
$c<= :: Dims -> Dims -> Bool
< :: Dims -> Dims -> Bool
$c< :: Dims -> Dims -> Bool
compare :: Dims -> Dims -> Ordering
$ccompare :: Dims -> Dims -> Ordering
Ord, ReadPrec [Dims]
ReadPrec Dims
Int -> ReadS Dims
ReadS [Dims]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Dims]
$creadListPrec :: ReadPrec [Dims]
readPrec :: ReadPrec Dims
$creadPrec :: ReadPrec Dims
readList :: ReadS [Dims]
$creadList :: ReadS [Dims]
readsPrec :: Int -> ReadS Dims
$creadsPrec :: Int -> ReadS Dims
Read, Int -> Dims -> String -> String
[Dims] -> String -> String
Dims -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [Dims] -> String -> String
$cshowList :: [Dims] -> String -> String
show :: Dims -> String
$cshow :: Dims -> String
showsPrec :: Int -> Dims -> String -> String
$cshowsPrec :: Int -> Dims -> String -> String
Show)

_Dims :: Name
_Dims = (String -> Name
Core.Name String
"hydra/ext/java/syntax.Dims")

data TypeParameter = 
  TypeParameter {
    TypeParameter -> [TypeParameterModifier]
typeParameterModifiers :: [TypeParameterModifier],
    TypeParameter -> TypeIdentifier
typeParameterIdentifier :: TypeIdentifier,
    TypeParameter -> Maybe TypeBound
typeParameterBound :: (Maybe TypeBound)}
  deriving (TypeParameter -> TypeParameter -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TypeParameter -> TypeParameter -> Bool
$c/= :: TypeParameter -> TypeParameter -> Bool
== :: TypeParameter -> TypeParameter -> Bool
$c== :: TypeParameter -> TypeParameter -> Bool
Eq, Eq TypeParameter
TypeParameter -> TypeParameter -> Bool
TypeParameter -> TypeParameter -> Ordering
TypeParameter -> TypeParameter -> TypeParameter
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: TypeParameter -> TypeParameter -> TypeParameter
$cmin :: TypeParameter -> TypeParameter -> TypeParameter
max :: TypeParameter -> TypeParameter -> TypeParameter
$cmax :: TypeParameter -> TypeParameter -> TypeParameter
>= :: TypeParameter -> TypeParameter -> Bool
$c>= :: TypeParameter -> TypeParameter -> Bool
> :: TypeParameter -> TypeParameter -> Bool
$c> :: TypeParameter -> TypeParameter -> Bool
<= :: TypeParameter -> TypeParameter -> Bool
$c<= :: TypeParameter -> TypeParameter -> Bool
< :: TypeParameter -> TypeParameter -> Bool
$c< :: TypeParameter -> TypeParameter -> Bool
compare :: TypeParameter -> TypeParameter -> Ordering
$ccompare :: TypeParameter -> TypeParameter -> Ordering
Ord, ReadPrec [TypeParameter]
ReadPrec TypeParameter
Int -> ReadS TypeParameter
ReadS [TypeParameter]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [TypeParameter]
$creadListPrec :: ReadPrec [TypeParameter]
readPrec :: ReadPrec TypeParameter
$creadPrec :: ReadPrec TypeParameter
readList :: ReadS [TypeParameter]
$creadList :: ReadS [TypeParameter]
readsPrec :: Int -> ReadS TypeParameter
$creadsPrec :: Int -> ReadS TypeParameter
Read, Int -> TypeParameter -> String -> String
[TypeParameter] -> String -> String
TypeParameter -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [TypeParameter] -> String -> String
$cshowList :: [TypeParameter] -> String -> String
show :: TypeParameter -> String
$cshow :: TypeParameter -> String
showsPrec :: Int -> TypeParameter -> String -> String
$cshowsPrec :: Int -> TypeParameter -> String -> String
Show)

_TypeParameter :: Name
_TypeParameter = (String -> Name
Core.Name String
"hydra/ext/java/syntax.TypeParameter")

_TypeParameter_modifiers :: FieldName
_TypeParameter_modifiers = (String -> FieldName
Core.FieldName String
"modifiers")

_TypeParameter_identifier :: FieldName
_TypeParameter_identifier = (String -> FieldName
Core.FieldName String
"identifier")

_TypeParameter_bound :: FieldName
_TypeParameter_bound = (String -> FieldName
Core.FieldName String
"bound")

newtype TypeParameterModifier = 
  TypeParameterModifier {
    TypeParameterModifier -> Annotation
unTypeParameterModifier :: Annotation}
  deriving (TypeParameterModifier -> TypeParameterModifier -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TypeParameterModifier -> TypeParameterModifier -> Bool
$c/= :: TypeParameterModifier -> TypeParameterModifier -> Bool
== :: TypeParameterModifier -> TypeParameterModifier -> Bool
$c== :: TypeParameterModifier -> TypeParameterModifier -> Bool
Eq, Eq TypeParameterModifier
TypeParameterModifier -> TypeParameterModifier -> Bool
TypeParameterModifier -> TypeParameterModifier -> Ordering
TypeParameterModifier
-> TypeParameterModifier -> TypeParameterModifier
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: TypeParameterModifier
-> TypeParameterModifier -> TypeParameterModifier
$cmin :: TypeParameterModifier
-> TypeParameterModifier -> TypeParameterModifier
max :: TypeParameterModifier
-> TypeParameterModifier -> TypeParameterModifier
$cmax :: TypeParameterModifier
-> TypeParameterModifier -> TypeParameterModifier
>= :: TypeParameterModifier -> TypeParameterModifier -> Bool
$c>= :: TypeParameterModifier -> TypeParameterModifier -> Bool
> :: TypeParameterModifier -> TypeParameterModifier -> Bool
$c> :: TypeParameterModifier -> TypeParameterModifier -> Bool
<= :: TypeParameterModifier -> TypeParameterModifier -> Bool
$c<= :: TypeParameterModifier -> TypeParameterModifier -> Bool
< :: TypeParameterModifier -> TypeParameterModifier -> Bool
$c< :: TypeParameterModifier -> TypeParameterModifier -> Bool
compare :: TypeParameterModifier -> TypeParameterModifier -> Ordering
$ccompare :: TypeParameterModifier -> TypeParameterModifier -> Ordering
Ord, ReadPrec [TypeParameterModifier]
ReadPrec TypeParameterModifier
Int -> ReadS TypeParameterModifier
ReadS [TypeParameterModifier]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [TypeParameterModifier]
$creadListPrec :: ReadPrec [TypeParameterModifier]
readPrec :: ReadPrec TypeParameterModifier
$creadPrec :: ReadPrec TypeParameterModifier
readList :: ReadS [TypeParameterModifier]
$creadList :: ReadS [TypeParameterModifier]
readsPrec :: Int -> ReadS TypeParameterModifier
$creadsPrec :: Int -> ReadS TypeParameterModifier
Read, Int -> TypeParameterModifier -> String -> String
[TypeParameterModifier] -> String -> String
TypeParameterModifier -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [TypeParameterModifier] -> String -> String
$cshowList :: [TypeParameterModifier] -> String -> String
show :: TypeParameterModifier -> String
$cshow :: TypeParameterModifier -> String
showsPrec :: Int -> TypeParameterModifier -> String -> String
$cshowsPrec :: Int -> TypeParameterModifier -> String -> String
Show)

_TypeParameterModifier :: Name
_TypeParameterModifier = (String -> Name
Core.Name String
"hydra/ext/java/syntax.TypeParameterModifier")

data TypeBound = 
  TypeBoundVariable TypeVariable |
  TypeBoundClassOrInterface TypeBound_ClassOrInterface
  deriving (TypeBound -> TypeBound -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TypeBound -> TypeBound -> Bool
$c/= :: TypeBound -> TypeBound -> Bool
== :: TypeBound -> TypeBound -> Bool
$c== :: TypeBound -> TypeBound -> Bool
Eq, Eq TypeBound
TypeBound -> TypeBound -> Bool
TypeBound -> TypeBound -> Ordering
TypeBound -> TypeBound -> TypeBound
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: TypeBound -> TypeBound -> TypeBound
$cmin :: TypeBound -> TypeBound -> TypeBound
max :: TypeBound -> TypeBound -> TypeBound
$cmax :: TypeBound -> TypeBound -> TypeBound
>= :: TypeBound -> TypeBound -> Bool
$c>= :: TypeBound -> TypeBound -> Bool
> :: TypeBound -> TypeBound -> Bool
$c> :: TypeBound -> TypeBound -> Bool
<= :: TypeBound -> TypeBound -> Bool
$c<= :: TypeBound -> TypeBound -> Bool
< :: TypeBound -> TypeBound -> Bool
$c< :: TypeBound -> TypeBound -> Bool
compare :: TypeBound -> TypeBound -> Ordering
$ccompare :: TypeBound -> TypeBound -> Ordering
Ord, ReadPrec [TypeBound]
ReadPrec TypeBound
Int -> ReadS TypeBound
ReadS [TypeBound]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [TypeBound]
$creadListPrec :: ReadPrec [TypeBound]
readPrec :: ReadPrec TypeBound
$creadPrec :: ReadPrec TypeBound
readList :: ReadS [TypeBound]
$creadList :: ReadS [TypeBound]
readsPrec :: Int -> ReadS TypeBound
$creadsPrec :: Int -> ReadS TypeBound
Read, Int -> TypeBound -> String -> String
[TypeBound] -> String -> String
TypeBound -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [TypeBound] -> String -> String
$cshowList :: [TypeBound] -> String -> String
show :: TypeBound -> String
$cshow :: TypeBound -> String
showsPrec :: Int -> TypeBound -> String -> String
$cshowsPrec :: Int -> TypeBound -> String -> String
Show)

_TypeBound :: Name
_TypeBound = (String -> Name
Core.Name String
"hydra/ext/java/syntax.TypeBound")

_TypeBound_variable :: FieldName
_TypeBound_variable = (String -> FieldName
Core.FieldName String
"variable")

_TypeBound_classOrInterface :: FieldName
_TypeBound_classOrInterface = (String -> FieldName
Core.FieldName String
"classOrInterface")

data TypeBound_ClassOrInterface = 
  TypeBound_ClassOrInterface {
    TypeBound_ClassOrInterface -> ClassOrInterfaceType
typeBound_ClassOrInterfaceType :: ClassOrInterfaceType,
    TypeBound_ClassOrInterface -> [AdditionalBound]
typeBound_ClassOrInterfaceAdditional :: [AdditionalBound]}
  deriving (TypeBound_ClassOrInterface -> TypeBound_ClassOrInterface -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TypeBound_ClassOrInterface -> TypeBound_ClassOrInterface -> Bool
$c/= :: TypeBound_ClassOrInterface -> TypeBound_ClassOrInterface -> Bool
== :: TypeBound_ClassOrInterface -> TypeBound_ClassOrInterface -> Bool
$c== :: TypeBound_ClassOrInterface -> TypeBound_ClassOrInterface -> Bool
Eq, Eq TypeBound_ClassOrInterface
TypeBound_ClassOrInterface -> TypeBound_ClassOrInterface -> Bool
TypeBound_ClassOrInterface
-> TypeBound_ClassOrInterface -> Ordering
TypeBound_ClassOrInterface
-> TypeBound_ClassOrInterface -> TypeBound_ClassOrInterface
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: TypeBound_ClassOrInterface
-> TypeBound_ClassOrInterface -> TypeBound_ClassOrInterface
$cmin :: TypeBound_ClassOrInterface
-> TypeBound_ClassOrInterface -> TypeBound_ClassOrInterface
max :: TypeBound_ClassOrInterface
-> TypeBound_ClassOrInterface -> TypeBound_ClassOrInterface
$cmax :: TypeBound_ClassOrInterface
-> TypeBound_ClassOrInterface -> TypeBound_ClassOrInterface
>= :: TypeBound_ClassOrInterface -> TypeBound_ClassOrInterface -> Bool
$c>= :: TypeBound_ClassOrInterface -> TypeBound_ClassOrInterface -> Bool
> :: TypeBound_ClassOrInterface -> TypeBound_ClassOrInterface -> Bool
$c> :: TypeBound_ClassOrInterface -> TypeBound_ClassOrInterface -> Bool
<= :: TypeBound_ClassOrInterface -> TypeBound_ClassOrInterface -> Bool
$c<= :: TypeBound_ClassOrInterface -> TypeBound_ClassOrInterface -> Bool
< :: TypeBound_ClassOrInterface -> TypeBound_ClassOrInterface -> Bool
$c< :: TypeBound_ClassOrInterface -> TypeBound_ClassOrInterface -> Bool
compare :: TypeBound_ClassOrInterface
-> TypeBound_ClassOrInterface -> Ordering
$ccompare :: TypeBound_ClassOrInterface
-> TypeBound_ClassOrInterface -> Ordering
Ord, ReadPrec [TypeBound_ClassOrInterface]
ReadPrec TypeBound_ClassOrInterface
Int -> ReadS TypeBound_ClassOrInterface
ReadS [TypeBound_ClassOrInterface]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [TypeBound_ClassOrInterface]
$creadListPrec :: ReadPrec [TypeBound_ClassOrInterface]
readPrec :: ReadPrec TypeBound_ClassOrInterface
$creadPrec :: ReadPrec TypeBound_ClassOrInterface
readList :: ReadS [TypeBound_ClassOrInterface]
$creadList :: ReadS [TypeBound_ClassOrInterface]
readsPrec :: Int -> ReadS TypeBound_ClassOrInterface
$creadsPrec :: Int -> ReadS TypeBound_ClassOrInterface
Read, Int -> TypeBound_ClassOrInterface -> String -> String
[TypeBound_ClassOrInterface] -> String -> String
TypeBound_ClassOrInterface -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [TypeBound_ClassOrInterface] -> String -> String
$cshowList :: [TypeBound_ClassOrInterface] -> String -> String
show :: TypeBound_ClassOrInterface -> String
$cshow :: TypeBound_ClassOrInterface -> String
showsPrec :: Int -> TypeBound_ClassOrInterface -> String -> String
$cshowsPrec :: Int -> TypeBound_ClassOrInterface -> String -> String
Show)

_TypeBound_ClassOrInterface :: Name
_TypeBound_ClassOrInterface = (String -> Name
Core.Name String
"hydra/ext/java/syntax.TypeBound.ClassOrInterface")

_TypeBound_ClassOrInterface_type :: FieldName
_TypeBound_ClassOrInterface_type = (String -> FieldName
Core.FieldName String
"type")

_TypeBound_ClassOrInterface_additional :: FieldName
_TypeBound_ClassOrInterface_additional = (String -> FieldName
Core.FieldName String
"additional")

newtype AdditionalBound = 
  AdditionalBound {
    AdditionalBound -> InterfaceType
unAdditionalBound :: InterfaceType}
  deriving (AdditionalBound -> AdditionalBound -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AdditionalBound -> AdditionalBound -> Bool
$c/= :: AdditionalBound -> AdditionalBound -> Bool
== :: AdditionalBound -> AdditionalBound -> Bool
$c== :: AdditionalBound -> AdditionalBound -> Bool
Eq, Eq AdditionalBound
AdditionalBound -> AdditionalBound -> Bool
AdditionalBound -> AdditionalBound -> Ordering
AdditionalBound -> AdditionalBound -> AdditionalBound
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: AdditionalBound -> AdditionalBound -> AdditionalBound
$cmin :: AdditionalBound -> AdditionalBound -> AdditionalBound
max :: AdditionalBound -> AdditionalBound -> AdditionalBound
$cmax :: AdditionalBound -> AdditionalBound -> AdditionalBound
>= :: AdditionalBound -> AdditionalBound -> Bool
$c>= :: AdditionalBound -> AdditionalBound -> Bool
> :: AdditionalBound -> AdditionalBound -> Bool
$c> :: AdditionalBound -> AdditionalBound -> Bool
<= :: AdditionalBound -> AdditionalBound -> Bool
$c<= :: AdditionalBound -> AdditionalBound -> Bool
< :: AdditionalBound -> AdditionalBound -> Bool
$c< :: AdditionalBound -> AdditionalBound -> Bool
compare :: AdditionalBound -> AdditionalBound -> Ordering
$ccompare :: AdditionalBound -> AdditionalBound -> Ordering
Ord, ReadPrec [AdditionalBound]
ReadPrec AdditionalBound
Int -> ReadS AdditionalBound
ReadS [AdditionalBound]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AdditionalBound]
$creadListPrec :: ReadPrec [AdditionalBound]
readPrec :: ReadPrec AdditionalBound
$creadPrec :: ReadPrec AdditionalBound
readList :: ReadS [AdditionalBound]
$creadList :: ReadS [AdditionalBound]
readsPrec :: Int -> ReadS AdditionalBound
$creadsPrec :: Int -> ReadS AdditionalBound
Read, Int -> AdditionalBound -> String -> String
[AdditionalBound] -> String -> String
AdditionalBound -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [AdditionalBound] -> String -> String
$cshowList :: [AdditionalBound] -> String -> String
show :: AdditionalBound -> String
$cshow :: AdditionalBound -> String
showsPrec :: Int -> AdditionalBound -> String -> String
$cshowsPrec :: Int -> AdditionalBound -> String -> String
Show)

_AdditionalBound :: Name
_AdditionalBound = (String -> Name
Core.Name String
"hydra/ext/java/syntax.AdditionalBound")

data TypeArgument = 
  TypeArgumentReference ReferenceType |
  TypeArgumentWildcard Wildcard
  deriving (TypeArgument -> TypeArgument -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TypeArgument -> TypeArgument -> Bool
$c/= :: TypeArgument -> TypeArgument -> Bool
== :: TypeArgument -> TypeArgument -> Bool
$c== :: TypeArgument -> TypeArgument -> Bool
Eq, Eq TypeArgument
TypeArgument -> TypeArgument -> Bool
TypeArgument -> TypeArgument -> Ordering
TypeArgument -> TypeArgument -> TypeArgument
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: TypeArgument -> TypeArgument -> TypeArgument
$cmin :: TypeArgument -> TypeArgument -> TypeArgument
max :: TypeArgument -> TypeArgument -> TypeArgument
$cmax :: TypeArgument -> TypeArgument -> TypeArgument
>= :: TypeArgument -> TypeArgument -> Bool
$c>= :: TypeArgument -> TypeArgument -> Bool
> :: TypeArgument -> TypeArgument -> Bool
$c> :: TypeArgument -> TypeArgument -> Bool
<= :: TypeArgument -> TypeArgument -> Bool
$c<= :: TypeArgument -> TypeArgument -> Bool
< :: TypeArgument -> TypeArgument -> Bool
$c< :: TypeArgument -> TypeArgument -> Bool
compare :: TypeArgument -> TypeArgument -> Ordering
$ccompare :: TypeArgument -> TypeArgument -> Ordering
Ord, ReadPrec [TypeArgument]
ReadPrec TypeArgument
Int -> ReadS TypeArgument
ReadS [TypeArgument]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [TypeArgument]
$creadListPrec :: ReadPrec [TypeArgument]
readPrec :: ReadPrec TypeArgument
$creadPrec :: ReadPrec TypeArgument
readList :: ReadS [TypeArgument]
$creadList :: ReadS [TypeArgument]
readsPrec :: Int -> ReadS TypeArgument
$creadsPrec :: Int -> ReadS TypeArgument
Read, Int -> TypeArgument -> String -> String
[TypeArgument] -> String -> String
TypeArgument -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [TypeArgument] -> String -> String
$cshowList :: [TypeArgument] -> String -> String
show :: TypeArgument -> String
$cshow :: TypeArgument -> String
showsPrec :: Int -> TypeArgument -> String -> String
$cshowsPrec :: Int -> TypeArgument -> String -> String
Show)

_TypeArgument :: Name
_TypeArgument = (String -> Name
Core.Name String
"hydra/ext/java/syntax.TypeArgument")

_TypeArgument_reference :: FieldName
_TypeArgument_reference = (String -> FieldName
Core.FieldName String
"reference")

_TypeArgument_wildcard :: FieldName
_TypeArgument_wildcard = (String -> FieldName
Core.FieldName String
"wildcard")

data Wildcard = 
  Wildcard {
    Wildcard -> [Annotation]
wildcardAnnotations :: [Annotation],
    Wildcard -> Maybe WildcardBounds
wildcardWildcard :: (Maybe WildcardBounds)}
  deriving (Wildcard -> Wildcard -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Wildcard -> Wildcard -> Bool
$c/= :: Wildcard -> Wildcard -> Bool
== :: Wildcard -> Wildcard -> Bool
$c== :: Wildcard -> Wildcard -> Bool
Eq, Eq Wildcard
Wildcard -> Wildcard -> Bool
Wildcard -> Wildcard -> Ordering
Wildcard -> Wildcard -> Wildcard
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Wildcard -> Wildcard -> Wildcard
$cmin :: Wildcard -> Wildcard -> Wildcard
max :: Wildcard -> Wildcard -> Wildcard
$cmax :: Wildcard -> Wildcard -> Wildcard
>= :: Wildcard -> Wildcard -> Bool
$c>= :: Wildcard -> Wildcard -> Bool
> :: Wildcard -> Wildcard -> Bool
$c> :: Wildcard -> Wildcard -> Bool
<= :: Wildcard -> Wildcard -> Bool
$c<= :: Wildcard -> Wildcard -> Bool
< :: Wildcard -> Wildcard -> Bool
$c< :: Wildcard -> Wildcard -> Bool
compare :: Wildcard -> Wildcard -> Ordering
$ccompare :: Wildcard -> Wildcard -> Ordering
Ord, ReadPrec [Wildcard]
ReadPrec Wildcard
Int -> ReadS Wildcard
ReadS [Wildcard]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Wildcard]
$creadListPrec :: ReadPrec [Wildcard]
readPrec :: ReadPrec Wildcard
$creadPrec :: ReadPrec Wildcard
readList :: ReadS [Wildcard]
$creadList :: ReadS [Wildcard]
readsPrec :: Int -> ReadS Wildcard
$creadsPrec :: Int -> ReadS Wildcard
Read, Int -> Wildcard -> String -> String
[Wildcard] -> String -> String
Wildcard -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [Wildcard] -> String -> String
$cshowList :: [Wildcard] -> String -> String
show :: Wildcard -> String
$cshow :: Wildcard -> String
showsPrec :: Int -> Wildcard -> String -> String
$cshowsPrec :: Int -> Wildcard -> String -> String
Show)

_Wildcard :: Name
_Wildcard = (String -> Name
Core.Name String
"hydra/ext/java/syntax.Wildcard")

_Wildcard_annotations :: FieldName
_Wildcard_annotations = (String -> FieldName
Core.FieldName String
"annotations")

_Wildcard_wildcard :: FieldName
_Wildcard_wildcard = (String -> FieldName
Core.FieldName String
"wildcard")

data WildcardBounds = 
  WildcardBoundsExtends ReferenceType |
  WildcardBoundsSuper ReferenceType
  deriving (WildcardBounds -> WildcardBounds -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WildcardBounds -> WildcardBounds -> Bool
$c/= :: WildcardBounds -> WildcardBounds -> Bool
== :: WildcardBounds -> WildcardBounds -> Bool
$c== :: WildcardBounds -> WildcardBounds -> Bool
Eq, Eq WildcardBounds
WildcardBounds -> WildcardBounds -> Bool
WildcardBounds -> WildcardBounds -> Ordering
WildcardBounds -> WildcardBounds -> WildcardBounds
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: WildcardBounds -> WildcardBounds -> WildcardBounds
$cmin :: WildcardBounds -> WildcardBounds -> WildcardBounds
max :: WildcardBounds -> WildcardBounds -> WildcardBounds
$cmax :: WildcardBounds -> WildcardBounds -> WildcardBounds
>= :: WildcardBounds -> WildcardBounds -> Bool
$c>= :: WildcardBounds -> WildcardBounds -> Bool
> :: WildcardBounds -> WildcardBounds -> Bool
$c> :: WildcardBounds -> WildcardBounds -> Bool
<= :: WildcardBounds -> WildcardBounds -> Bool
$c<= :: WildcardBounds -> WildcardBounds -> Bool
< :: WildcardBounds -> WildcardBounds -> Bool
$c< :: WildcardBounds -> WildcardBounds -> Bool
compare :: WildcardBounds -> WildcardBounds -> Ordering
$ccompare :: WildcardBounds -> WildcardBounds -> Ordering
Ord, ReadPrec [WildcardBounds]
ReadPrec WildcardBounds
Int -> ReadS WildcardBounds
ReadS [WildcardBounds]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [WildcardBounds]
$creadListPrec :: ReadPrec [WildcardBounds]
readPrec :: ReadPrec WildcardBounds
$creadPrec :: ReadPrec WildcardBounds
readList :: ReadS [WildcardBounds]
$creadList :: ReadS [WildcardBounds]
readsPrec :: Int -> ReadS WildcardBounds
$creadsPrec :: Int -> ReadS WildcardBounds
Read, Int -> WildcardBounds -> String -> String
[WildcardBounds] -> String -> String
WildcardBounds -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [WildcardBounds] -> String -> String
$cshowList :: [WildcardBounds] -> String -> String
show :: WildcardBounds -> String
$cshow :: WildcardBounds -> String
showsPrec :: Int -> WildcardBounds -> String -> String
$cshowsPrec :: Int -> WildcardBounds -> String -> String
Show)

_WildcardBounds :: Name
_WildcardBounds = (String -> Name
Core.Name String
"hydra/ext/java/syntax.WildcardBounds")

_WildcardBounds_extends :: FieldName
_WildcardBounds_extends = (String -> FieldName
Core.FieldName String
"extends")

_WildcardBounds_super :: FieldName
_WildcardBounds_super = (String -> FieldName
Core.FieldName String
"super")

data ModuleName = 
  ModuleName {
    ModuleName -> Identifier
moduleNameIdentifier :: Identifier,
    ModuleName -> Maybe ModuleName
moduleNameName :: (Maybe ModuleName)}
  deriving (ModuleName -> ModuleName -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ModuleName -> ModuleName -> Bool
$c/= :: ModuleName -> ModuleName -> Bool
== :: ModuleName -> ModuleName -> Bool
$c== :: ModuleName -> ModuleName -> Bool
Eq, Eq ModuleName
ModuleName -> ModuleName -> Bool
ModuleName -> ModuleName -> Ordering
ModuleName -> ModuleName -> ModuleName
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ModuleName -> ModuleName -> ModuleName
$cmin :: ModuleName -> ModuleName -> ModuleName
max :: ModuleName -> ModuleName -> ModuleName
$cmax :: ModuleName -> ModuleName -> ModuleName
>= :: ModuleName -> ModuleName -> Bool
$c>= :: ModuleName -> ModuleName -> Bool
> :: ModuleName -> ModuleName -> Bool
$c> :: ModuleName -> ModuleName -> Bool
<= :: ModuleName -> ModuleName -> Bool
$c<= :: ModuleName -> ModuleName -> Bool
< :: ModuleName -> ModuleName -> Bool
$c< :: ModuleName -> ModuleName -> Bool
compare :: ModuleName -> ModuleName -> Ordering
$ccompare :: ModuleName -> ModuleName -> Ordering
Ord, ReadPrec [ModuleName]
ReadPrec ModuleName
Int -> ReadS ModuleName
ReadS [ModuleName]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ModuleName]
$creadListPrec :: ReadPrec [ModuleName]
readPrec :: ReadPrec ModuleName
$creadPrec :: ReadPrec ModuleName
readList :: ReadS [ModuleName]
$creadList :: ReadS [ModuleName]
readsPrec :: Int -> ReadS ModuleName
$creadsPrec :: Int -> ReadS ModuleName
Read, Int -> ModuleName -> String -> String
[ModuleName] -> String -> String
ModuleName -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ModuleName] -> String -> String
$cshowList :: [ModuleName] -> String -> String
show :: ModuleName -> String
$cshow :: ModuleName -> String
showsPrec :: Int -> ModuleName -> String -> String
$cshowsPrec :: Int -> ModuleName -> String -> String
Show)

_ModuleName :: Name
_ModuleName = (String -> Name
Core.Name String
"hydra/ext/java/syntax.ModuleName")

_ModuleName_identifier :: FieldName
_ModuleName_identifier = (String -> FieldName
Core.FieldName String
"identifier")

_ModuleName_name :: FieldName
_ModuleName_name = (String -> FieldName
Core.FieldName String
"name")

newtype PackageName = 
  PackageName {
    PackageName -> [Identifier]
unPackageName :: [Identifier]}
  deriving (PackageName -> PackageName -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PackageName -> PackageName -> Bool
$c/= :: PackageName -> PackageName -> Bool
== :: PackageName -> PackageName -> Bool
$c== :: PackageName -> PackageName -> Bool
Eq, Eq PackageName
PackageName -> PackageName -> Bool
PackageName -> PackageName -> Ordering
PackageName -> PackageName -> PackageName
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: PackageName -> PackageName -> PackageName
$cmin :: PackageName -> PackageName -> PackageName
max :: PackageName -> PackageName -> PackageName
$cmax :: PackageName -> PackageName -> PackageName
>= :: PackageName -> PackageName -> Bool
$c>= :: PackageName -> PackageName -> Bool
> :: PackageName -> PackageName -> Bool
$c> :: PackageName -> PackageName -> Bool
<= :: PackageName -> PackageName -> Bool
$c<= :: PackageName -> PackageName -> Bool
< :: PackageName -> PackageName -> Bool
$c< :: PackageName -> PackageName -> Bool
compare :: PackageName -> PackageName -> Ordering
$ccompare :: PackageName -> PackageName -> Ordering
Ord, ReadPrec [PackageName]
ReadPrec PackageName
Int -> ReadS PackageName
ReadS [PackageName]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [PackageName]
$creadListPrec :: ReadPrec [PackageName]
readPrec :: ReadPrec PackageName
$creadPrec :: ReadPrec PackageName
readList :: ReadS [PackageName]
$creadList :: ReadS [PackageName]
readsPrec :: Int -> ReadS PackageName
$creadsPrec :: Int -> ReadS PackageName
Read, Int -> PackageName -> String -> String
[PackageName] -> String -> String
PackageName -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [PackageName] -> String -> String
$cshowList :: [PackageName] -> String -> String
show :: PackageName -> String
$cshow :: PackageName -> String
showsPrec :: Int -> PackageName -> String -> String
$cshowsPrec :: Int -> PackageName -> String -> String
Show)

_PackageName :: Name
_PackageName = (String -> Name
Core.Name String
"hydra/ext/java/syntax.PackageName")

data TypeName = 
  TypeName {
    TypeName -> TypeIdentifier
typeNameIdentifier :: TypeIdentifier,
    TypeName -> Maybe PackageOrTypeName
typeNameQualifier :: (Maybe PackageOrTypeName)}
  deriving (TypeName -> TypeName -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TypeName -> TypeName -> Bool
$c/= :: TypeName -> TypeName -> Bool
== :: TypeName -> TypeName -> Bool
$c== :: TypeName -> TypeName -> Bool
Eq, Eq TypeName
TypeName -> TypeName -> Bool
TypeName -> TypeName -> Ordering
TypeName -> TypeName -> TypeName
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: TypeName -> TypeName -> TypeName
$cmin :: TypeName -> TypeName -> TypeName
max :: TypeName -> TypeName -> TypeName
$cmax :: TypeName -> TypeName -> TypeName
>= :: TypeName -> TypeName -> Bool
$c>= :: TypeName -> TypeName -> Bool
> :: TypeName -> TypeName -> Bool
$c> :: TypeName -> TypeName -> Bool
<= :: TypeName -> TypeName -> Bool
$c<= :: TypeName -> TypeName -> Bool
< :: TypeName -> TypeName -> Bool
$c< :: TypeName -> TypeName -> Bool
compare :: TypeName -> TypeName -> Ordering
$ccompare :: TypeName -> TypeName -> Ordering
Ord, ReadPrec [TypeName]
ReadPrec TypeName
Int -> ReadS TypeName
ReadS [TypeName]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [TypeName]
$creadListPrec :: ReadPrec [TypeName]
readPrec :: ReadPrec TypeName
$creadPrec :: ReadPrec TypeName
readList :: ReadS [TypeName]
$creadList :: ReadS [TypeName]
readsPrec :: Int -> ReadS TypeName
$creadsPrec :: Int -> ReadS TypeName
Read, Int -> TypeName -> String -> String
[TypeName] -> String -> String
TypeName -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [TypeName] -> String -> String
$cshowList :: [TypeName] -> String -> String
show :: TypeName -> String
$cshow :: TypeName -> String
showsPrec :: Int -> TypeName -> String -> String
$cshowsPrec :: Int -> TypeName -> String -> String
Show)

_TypeName :: Name
_TypeName = (String -> Name
Core.Name String
"hydra/ext/java/syntax.TypeName")

_TypeName_identifier :: FieldName
_TypeName_identifier = (String -> FieldName
Core.FieldName String
"identifier")

_TypeName_qualifier :: FieldName
_TypeName_qualifier = (String -> FieldName
Core.FieldName String
"qualifier")

data ExpressionName = 
  ExpressionName {
    ExpressionName -> Maybe AmbiguousName
expressionNameQualifier :: (Maybe AmbiguousName),
    ExpressionName -> Identifier
expressionNameIdentifier :: Identifier}
  deriving (ExpressionName -> ExpressionName -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ExpressionName -> ExpressionName -> Bool
$c/= :: ExpressionName -> ExpressionName -> Bool
== :: ExpressionName -> ExpressionName -> Bool
$c== :: ExpressionName -> ExpressionName -> Bool
Eq, Eq ExpressionName
ExpressionName -> ExpressionName -> Bool
ExpressionName -> ExpressionName -> Ordering
ExpressionName -> ExpressionName -> ExpressionName
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ExpressionName -> ExpressionName -> ExpressionName
$cmin :: ExpressionName -> ExpressionName -> ExpressionName
max :: ExpressionName -> ExpressionName -> ExpressionName
$cmax :: ExpressionName -> ExpressionName -> ExpressionName
>= :: ExpressionName -> ExpressionName -> Bool
$c>= :: ExpressionName -> ExpressionName -> Bool
> :: ExpressionName -> ExpressionName -> Bool
$c> :: ExpressionName -> ExpressionName -> Bool
<= :: ExpressionName -> ExpressionName -> Bool
$c<= :: ExpressionName -> ExpressionName -> Bool
< :: ExpressionName -> ExpressionName -> Bool
$c< :: ExpressionName -> ExpressionName -> Bool
compare :: ExpressionName -> ExpressionName -> Ordering
$ccompare :: ExpressionName -> ExpressionName -> Ordering
Ord, ReadPrec [ExpressionName]
ReadPrec ExpressionName
Int -> ReadS ExpressionName
ReadS [ExpressionName]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ExpressionName]
$creadListPrec :: ReadPrec [ExpressionName]
readPrec :: ReadPrec ExpressionName
$creadPrec :: ReadPrec ExpressionName
readList :: ReadS [ExpressionName]
$creadList :: ReadS [ExpressionName]
readsPrec :: Int -> ReadS ExpressionName
$creadsPrec :: Int -> ReadS ExpressionName
Read, Int -> ExpressionName -> String -> String
[ExpressionName] -> String -> String
ExpressionName -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ExpressionName] -> String -> String
$cshowList :: [ExpressionName] -> String -> String
show :: ExpressionName -> String
$cshow :: ExpressionName -> String
showsPrec :: Int -> ExpressionName -> String -> String
$cshowsPrec :: Int -> ExpressionName -> String -> String
Show)

_ExpressionName :: Name
_ExpressionName = (String -> Name
Core.Name String
"hydra/ext/java/syntax.ExpressionName")

_ExpressionName_qualifier :: FieldName
_ExpressionName_qualifier = (String -> FieldName
Core.FieldName String
"qualifier")

_ExpressionName_identifier :: FieldName
_ExpressionName_identifier = (String -> FieldName
Core.FieldName String
"identifier")

newtype MethodName = 
  MethodName {
    MethodName -> Identifier
unMethodName :: Identifier}
  deriving (MethodName -> MethodName -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MethodName -> MethodName -> Bool
$c/= :: MethodName -> MethodName -> Bool
== :: MethodName -> MethodName -> Bool
$c== :: MethodName -> MethodName -> Bool
Eq, Eq MethodName
MethodName -> MethodName -> Bool
MethodName -> MethodName -> Ordering
MethodName -> MethodName -> MethodName
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: MethodName -> MethodName -> MethodName
$cmin :: MethodName -> MethodName -> MethodName
max :: MethodName -> MethodName -> MethodName
$cmax :: MethodName -> MethodName -> MethodName
>= :: MethodName -> MethodName -> Bool
$c>= :: MethodName -> MethodName -> Bool
> :: MethodName -> MethodName -> Bool
$c> :: MethodName -> MethodName -> Bool
<= :: MethodName -> MethodName -> Bool
$c<= :: MethodName -> MethodName -> Bool
< :: MethodName -> MethodName -> Bool
$c< :: MethodName -> MethodName -> Bool
compare :: MethodName -> MethodName -> Ordering
$ccompare :: MethodName -> MethodName -> Ordering
Ord, ReadPrec [MethodName]
ReadPrec MethodName
Int -> ReadS MethodName
ReadS [MethodName]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [MethodName]
$creadListPrec :: ReadPrec [MethodName]
readPrec :: ReadPrec MethodName
$creadPrec :: ReadPrec MethodName
readList :: ReadS [MethodName]
$creadList :: ReadS [MethodName]
readsPrec :: Int -> ReadS MethodName
$creadsPrec :: Int -> ReadS MethodName
Read, Int -> MethodName -> String -> String
[MethodName] -> String -> String
MethodName -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [MethodName] -> String -> String
$cshowList :: [MethodName] -> String -> String
show :: MethodName -> String
$cshow :: MethodName -> String
showsPrec :: Int -> MethodName -> String -> String
$cshowsPrec :: Int -> MethodName -> String -> String
Show)

_MethodName :: Name
_MethodName = (String -> Name
Core.Name String
"hydra/ext/java/syntax.MethodName")

newtype PackageOrTypeName = 
  PackageOrTypeName {
    PackageOrTypeName -> [Identifier]
unPackageOrTypeName :: [Identifier]}
  deriving (PackageOrTypeName -> PackageOrTypeName -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PackageOrTypeName -> PackageOrTypeName -> Bool
$c/= :: PackageOrTypeName -> PackageOrTypeName -> Bool
== :: PackageOrTypeName -> PackageOrTypeName -> Bool
$c== :: PackageOrTypeName -> PackageOrTypeName -> Bool
Eq, Eq PackageOrTypeName
PackageOrTypeName -> PackageOrTypeName -> Bool
PackageOrTypeName -> PackageOrTypeName -> Ordering
PackageOrTypeName -> PackageOrTypeName -> PackageOrTypeName
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: PackageOrTypeName -> PackageOrTypeName -> PackageOrTypeName
$cmin :: PackageOrTypeName -> PackageOrTypeName -> PackageOrTypeName
max :: PackageOrTypeName -> PackageOrTypeName -> PackageOrTypeName
$cmax :: PackageOrTypeName -> PackageOrTypeName -> PackageOrTypeName
>= :: PackageOrTypeName -> PackageOrTypeName -> Bool
$c>= :: PackageOrTypeName -> PackageOrTypeName -> Bool
> :: PackageOrTypeName -> PackageOrTypeName -> Bool
$c> :: PackageOrTypeName -> PackageOrTypeName -> Bool
<= :: PackageOrTypeName -> PackageOrTypeName -> Bool
$c<= :: PackageOrTypeName -> PackageOrTypeName -> Bool
< :: PackageOrTypeName -> PackageOrTypeName -> Bool
$c< :: PackageOrTypeName -> PackageOrTypeName -> Bool
compare :: PackageOrTypeName -> PackageOrTypeName -> Ordering
$ccompare :: PackageOrTypeName -> PackageOrTypeName -> Ordering
Ord, ReadPrec [PackageOrTypeName]
ReadPrec PackageOrTypeName
Int -> ReadS PackageOrTypeName
ReadS [PackageOrTypeName]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [PackageOrTypeName]
$creadListPrec :: ReadPrec [PackageOrTypeName]
readPrec :: ReadPrec PackageOrTypeName
$creadPrec :: ReadPrec PackageOrTypeName
readList :: ReadS [PackageOrTypeName]
$creadList :: ReadS [PackageOrTypeName]
readsPrec :: Int -> ReadS PackageOrTypeName
$creadsPrec :: Int -> ReadS PackageOrTypeName
Read, Int -> PackageOrTypeName -> String -> String
[PackageOrTypeName] -> String -> String
PackageOrTypeName -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [PackageOrTypeName] -> String -> String
$cshowList :: [PackageOrTypeName] -> String -> String
show :: PackageOrTypeName -> String
$cshow :: PackageOrTypeName -> String
showsPrec :: Int -> PackageOrTypeName -> String -> String
$cshowsPrec :: Int -> PackageOrTypeName -> String -> String
Show)

_PackageOrTypeName :: Name
_PackageOrTypeName = (String -> Name
Core.Name String
"hydra/ext/java/syntax.PackageOrTypeName")

newtype AmbiguousName = 
  AmbiguousName {
    AmbiguousName -> [Identifier]
unAmbiguousName :: [Identifier]}
  deriving (AmbiguousName -> AmbiguousName -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AmbiguousName -> AmbiguousName -> Bool
$c/= :: AmbiguousName -> AmbiguousName -> Bool
== :: AmbiguousName -> AmbiguousName -> Bool
$c== :: AmbiguousName -> AmbiguousName -> Bool
Eq, Eq AmbiguousName
AmbiguousName -> AmbiguousName -> Bool
AmbiguousName -> AmbiguousName -> Ordering
AmbiguousName -> AmbiguousName -> AmbiguousName
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: AmbiguousName -> AmbiguousName -> AmbiguousName
$cmin :: AmbiguousName -> AmbiguousName -> AmbiguousName
max :: AmbiguousName -> AmbiguousName -> AmbiguousName
$cmax :: AmbiguousName -> AmbiguousName -> AmbiguousName
>= :: AmbiguousName -> AmbiguousName -> Bool
$c>= :: AmbiguousName -> AmbiguousName -> Bool
> :: AmbiguousName -> AmbiguousName -> Bool
$c> :: AmbiguousName -> AmbiguousName -> Bool
<= :: AmbiguousName -> AmbiguousName -> Bool
$c<= :: AmbiguousName -> AmbiguousName -> Bool
< :: AmbiguousName -> AmbiguousName -> Bool
$c< :: AmbiguousName -> AmbiguousName -> Bool
compare :: AmbiguousName -> AmbiguousName -> Ordering
$ccompare :: AmbiguousName -> AmbiguousName -> Ordering
Ord, ReadPrec [AmbiguousName]
ReadPrec AmbiguousName
Int -> ReadS AmbiguousName
ReadS [AmbiguousName]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AmbiguousName]
$creadListPrec :: ReadPrec [AmbiguousName]
readPrec :: ReadPrec AmbiguousName
$creadPrec :: ReadPrec AmbiguousName
readList :: ReadS [AmbiguousName]
$creadList :: ReadS [AmbiguousName]
readsPrec :: Int -> ReadS AmbiguousName
$creadsPrec :: Int -> ReadS AmbiguousName
Read, Int -> AmbiguousName -> String -> String
[AmbiguousName] -> String -> String
AmbiguousName -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [AmbiguousName] -> String -> String
$cshowList :: [AmbiguousName] -> String -> String
show :: AmbiguousName -> String
$cshow :: AmbiguousName -> String
showsPrec :: Int -> AmbiguousName -> String -> String
$cshowsPrec :: Int -> AmbiguousName -> String -> String
Show)

_AmbiguousName :: Name
_AmbiguousName = (String -> Name
Core.Name String
"hydra/ext/java/syntax.AmbiguousName")

data CompilationUnit = 
  CompilationUnitOrdinary OrdinaryCompilationUnit |
  CompilationUnitModular ModularCompilationUnit
  deriving (CompilationUnit -> CompilationUnit -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CompilationUnit -> CompilationUnit -> Bool
$c/= :: CompilationUnit -> CompilationUnit -> Bool
== :: CompilationUnit -> CompilationUnit -> Bool
$c== :: CompilationUnit -> CompilationUnit -> Bool
Eq, Eq CompilationUnit
CompilationUnit -> CompilationUnit -> Bool
CompilationUnit -> CompilationUnit -> Ordering
CompilationUnit -> CompilationUnit -> CompilationUnit
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CompilationUnit -> CompilationUnit -> CompilationUnit
$cmin :: CompilationUnit -> CompilationUnit -> CompilationUnit
max :: CompilationUnit -> CompilationUnit -> CompilationUnit
$cmax :: CompilationUnit -> CompilationUnit -> CompilationUnit
>= :: CompilationUnit -> CompilationUnit -> Bool
$c>= :: CompilationUnit -> CompilationUnit -> Bool
> :: CompilationUnit -> CompilationUnit -> Bool
$c> :: CompilationUnit -> CompilationUnit -> Bool
<= :: CompilationUnit -> CompilationUnit -> Bool
$c<= :: CompilationUnit -> CompilationUnit -> Bool
< :: CompilationUnit -> CompilationUnit -> Bool
$c< :: CompilationUnit -> CompilationUnit -> Bool
compare :: CompilationUnit -> CompilationUnit -> Ordering
$ccompare :: CompilationUnit -> CompilationUnit -> Ordering
Ord, ReadPrec [CompilationUnit]
ReadPrec CompilationUnit
Int -> ReadS CompilationUnit
ReadS [CompilationUnit]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CompilationUnit]
$creadListPrec :: ReadPrec [CompilationUnit]
readPrec :: ReadPrec CompilationUnit
$creadPrec :: ReadPrec CompilationUnit
readList :: ReadS [CompilationUnit]
$creadList :: ReadS [CompilationUnit]
readsPrec :: Int -> ReadS CompilationUnit
$creadsPrec :: Int -> ReadS CompilationUnit
Read, Int -> CompilationUnit -> String -> String
[CompilationUnit] -> String -> String
CompilationUnit -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [CompilationUnit] -> String -> String
$cshowList :: [CompilationUnit] -> String -> String
show :: CompilationUnit -> String
$cshow :: CompilationUnit -> String
showsPrec :: Int -> CompilationUnit -> String -> String
$cshowsPrec :: Int -> CompilationUnit -> String -> String
Show)

_CompilationUnit :: Name
_CompilationUnit = (String -> Name
Core.Name String
"hydra/ext/java/syntax.CompilationUnit")

_CompilationUnit_ordinary :: FieldName
_CompilationUnit_ordinary = (String -> FieldName
Core.FieldName String
"ordinary")

_CompilationUnit_modular :: FieldName
_CompilationUnit_modular = (String -> FieldName
Core.FieldName String
"modular")

data OrdinaryCompilationUnit = 
  OrdinaryCompilationUnit {
    OrdinaryCompilationUnit -> Maybe PackageDeclaration
ordinaryCompilationUnitPackage :: (Maybe PackageDeclaration),
    OrdinaryCompilationUnit -> [ImportDeclaration]
ordinaryCompilationUnitImports :: [ImportDeclaration],
    OrdinaryCompilationUnit -> [TypeDeclarationWithComments]
ordinaryCompilationUnitTypes :: [TypeDeclarationWithComments]}
  deriving (OrdinaryCompilationUnit -> OrdinaryCompilationUnit -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: OrdinaryCompilationUnit -> OrdinaryCompilationUnit -> Bool
$c/= :: OrdinaryCompilationUnit -> OrdinaryCompilationUnit -> Bool
== :: OrdinaryCompilationUnit -> OrdinaryCompilationUnit -> Bool
$c== :: OrdinaryCompilationUnit -> OrdinaryCompilationUnit -> Bool
Eq, Eq OrdinaryCompilationUnit
OrdinaryCompilationUnit -> OrdinaryCompilationUnit -> Bool
OrdinaryCompilationUnit -> OrdinaryCompilationUnit -> Ordering
OrdinaryCompilationUnit
-> OrdinaryCompilationUnit -> OrdinaryCompilationUnit
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: OrdinaryCompilationUnit
-> OrdinaryCompilationUnit -> OrdinaryCompilationUnit
$cmin :: OrdinaryCompilationUnit
-> OrdinaryCompilationUnit -> OrdinaryCompilationUnit
max :: OrdinaryCompilationUnit
-> OrdinaryCompilationUnit -> OrdinaryCompilationUnit
$cmax :: OrdinaryCompilationUnit
-> OrdinaryCompilationUnit -> OrdinaryCompilationUnit
>= :: OrdinaryCompilationUnit -> OrdinaryCompilationUnit -> Bool
$c>= :: OrdinaryCompilationUnit -> OrdinaryCompilationUnit -> Bool
> :: OrdinaryCompilationUnit -> OrdinaryCompilationUnit -> Bool
$c> :: OrdinaryCompilationUnit -> OrdinaryCompilationUnit -> Bool
<= :: OrdinaryCompilationUnit -> OrdinaryCompilationUnit -> Bool
$c<= :: OrdinaryCompilationUnit -> OrdinaryCompilationUnit -> Bool
< :: OrdinaryCompilationUnit -> OrdinaryCompilationUnit -> Bool
$c< :: OrdinaryCompilationUnit -> OrdinaryCompilationUnit -> Bool
compare :: OrdinaryCompilationUnit -> OrdinaryCompilationUnit -> Ordering
$ccompare :: OrdinaryCompilationUnit -> OrdinaryCompilationUnit -> Ordering
Ord, ReadPrec [OrdinaryCompilationUnit]
ReadPrec OrdinaryCompilationUnit
Int -> ReadS OrdinaryCompilationUnit
ReadS [OrdinaryCompilationUnit]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [OrdinaryCompilationUnit]
$creadListPrec :: ReadPrec [OrdinaryCompilationUnit]
readPrec :: ReadPrec OrdinaryCompilationUnit
$creadPrec :: ReadPrec OrdinaryCompilationUnit
readList :: ReadS [OrdinaryCompilationUnit]
$creadList :: ReadS [OrdinaryCompilationUnit]
readsPrec :: Int -> ReadS OrdinaryCompilationUnit
$creadsPrec :: Int -> ReadS OrdinaryCompilationUnit
Read, Int -> OrdinaryCompilationUnit -> String -> String
[OrdinaryCompilationUnit] -> String -> String
OrdinaryCompilationUnit -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [OrdinaryCompilationUnit] -> String -> String
$cshowList :: [OrdinaryCompilationUnit] -> String -> String
show :: OrdinaryCompilationUnit -> String
$cshow :: OrdinaryCompilationUnit -> String
showsPrec :: Int -> OrdinaryCompilationUnit -> String -> String
$cshowsPrec :: Int -> OrdinaryCompilationUnit -> String -> String
Show)

_OrdinaryCompilationUnit :: Name
_OrdinaryCompilationUnit = (String -> Name
Core.Name String
"hydra/ext/java/syntax.OrdinaryCompilationUnit")

_OrdinaryCompilationUnit_package :: FieldName
_OrdinaryCompilationUnit_package = (String -> FieldName
Core.FieldName String
"package")

_OrdinaryCompilationUnit_imports :: FieldName
_OrdinaryCompilationUnit_imports = (String -> FieldName
Core.FieldName String
"imports")

_OrdinaryCompilationUnit_types :: FieldName
_OrdinaryCompilationUnit_types = (String -> FieldName
Core.FieldName String
"types")

data ModularCompilationUnit = 
  ModularCompilationUnit {
    ModularCompilationUnit -> [ImportDeclaration]
modularCompilationUnitImports :: [ImportDeclaration],
    ModularCompilationUnit -> ModuleDeclaration
modularCompilationUnitModule :: ModuleDeclaration}
  deriving (ModularCompilationUnit -> ModularCompilationUnit -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ModularCompilationUnit -> ModularCompilationUnit -> Bool
$c/= :: ModularCompilationUnit -> ModularCompilationUnit -> Bool
== :: ModularCompilationUnit -> ModularCompilationUnit -> Bool
$c== :: ModularCompilationUnit -> ModularCompilationUnit -> Bool
Eq, Eq ModularCompilationUnit
ModularCompilationUnit -> ModularCompilationUnit -> Bool
ModularCompilationUnit -> ModularCompilationUnit -> Ordering
ModularCompilationUnit
-> ModularCompilationUnit -> ModularCompilationUnit
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ModularCompilationUnit
-> ModularCompilationUnit -> ModularCompilationUnit
$cmin :: ModularCompilationUnit
-> ModularCompilationUnit -> ModularCompilationUnit
max :: ModularCompilationUnit
-> ModularCompilationUnit -> ModularCompilationUnit
$cmax :: ModularCompilationUnit
-> ModularCompilationUnit -> ModularCompilationUnit
>= :: ModularCompilationUnit -> ModularCompilationUnit -> Bool
$c>= :: ModularCompilationUnit -> ModularCompilationUnit -> Bool
> :: ModularCompilationUnit -> ModularCompilationUnit -> Bool
$c> :: ModularCompilationUnit -> ModularCompilationUnit -> Bool
<= :: ModularCompilationUnit -> ModularCompilationUnit -> Bool
$c<= :: ModularCompilationUnit -> ModularCompilationUnit -> Bool
< :: ModularCompilationUnit -> ModularCompilationUnit -> Bool
$c< :: ModularCompilationUnit -> ModularCompilationUnit -> Bool
compare :: ModularCompilationUnit -> ModularCompilationUnit -> Ordering
$ccompare :: ModularCompilationUnit -> ModularCompilationUnit -> Ordering
Ord, ReadPrec [ModularCompilationUnit]
ReadPrec ModularCompilationUnit
Int -> ReadS ModularCompilationUnit
ReadS [ModularCompilationUnit]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ModularCompilationUnit]
$creadListPrec :: ReadPrec [ModularCompilationUnit]
readPrec :: ReadPrec ModularCompilationUnit
$creadPrec :: ReadPrec ModularCompilationUnit
readList :: ReadS [ModularCompilationUnit]
$creadList :: ReadS [ModularCompilationUnit]
readsPrec :: Int -> ReadS ModularCompilationUnit
$creadsPrec :: Int -> ReadS ModularCompilationUnit
Read, Int -> ModularCompilationUnit -> String -> String
[ModularCompilationUnit] -> String -> String
ModularCompilationUnit -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ModularCompilationUnit] -> String -> String
$cshowList :: [ModularCompilationUnit] -> String -> String
show :: ModularCompilationUnit -> String
$cshow :: ModularCompilationUnit -> String
showsPrec :: Int -> ModularCompilationUnit -> String -> String
$cshowsPrec :: Int -> ModularCompilationUnit -> String -> String
Show)

_ModularCompilationUnit :: Name
_ModularCompilationUnit = (String -> Name
Core.Name String
"hydra/ext/java/syntax.ModularCompilationUnit")

_ModularCompilationUnit_imports :: FieldName
_ModularCompilationUnit_imports = (String -> FieldName
Core.FieldName String
"imports")

_ModularCompilationUnit_module :: FieldName
_ModularCompilationUnit_module = (String -> FieldName
Core.FieldName String
"module")

data PackageDeclaration = 
  PackageDeclaration {
    PackageDeclaration -> [PackageModifier]
packageDeclarationModifiers :: [PackageModifier],
    PackageDeclaration -> [Identifier]
packageDeclarationIdentifiers :: [Identifier]}
  deriving (PackageDeclaration -> PackageDeclaration -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PackageDeclaration -> PackageDeclaration -> Bool
$c/= :: PackageDeclaration -> PackageDeclaration -> Bool
== :: PackageDeclaration -> PackageDeclaration -> Bool
$c== :: PackageDeclaration -> PackageDeclaration -> Bool
Eq, Eq PackageDeclaration
PackageDeclaration -> PackageDeclaration -> Bool
PackageDeclaration -> PackageDeclaration -> Ordering
PackageDeclaration -> PackageDeclaration -> PackageDeclaration
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: PackageDeclaration -> PackageDeclaration -> PackageDeclaration
$cmin :: PackageDeclaration -> PackageDeclaration -> PackageDeclaration
max :: PackageDeclaration -> PackageDeclaration -> PackageDeclaration
$cmax :: PackageDeclaration -> PackageDeclaration -> PackageDeclaration
>= :: PackageDeclaration -> PackageDeclaration -> Bool
$c>= :: PackageDeclaration -> PackageDeclaration -> Bool
> :: PackageDeclaration -> PackageDeclaration -> Bool
$c> :: PackageDeclaration -> PackageDeclaration -> Bool
<= :: PackageDeclaration -> PackageDeclaration -> Bool
$c<= :: PackageDeclaration -> PackageDeclaration -> Bool
< :: PackageDeclaration -> PackageDeclaration -> Bool
$c< :: PackageDeclaration -> PackageDeclaration -> Bool
compare :: PackageDeclaration -> PackageDeclaration -> Ordering
$ccompare :: PackageDeclaration -> PackageDeclaration -> Ordering
Ord, ReadPrec [PackageDeclaration]
ReadPrec PackageDeclaration
Int -> ReadS PackageDeclaration
ReadS [PackageDeclaration]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [PackageDeclaration]
$creadListPrec :: ReadPrec [PackageDeclaration]
readPrec :: ReadPrec PackageDeclaration
$creadPrec :: ReadPrec PackageDeclaration
readList :: ReadS [PackageDeclaration]
$creadList :: ReadS [PackageDeclaration]
readsPrec :: Int -> ReadS PackageDeclaration
$creadsPrec :: Int -> ReadS PackageDeclaration
Read, Int -> PackageDeclaration -> String -> String
[PackageDeclaration] -> String -> String
PackageDeclaration -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [PackageDeclaration] -> String -> String
$cshowList :: [PackageDeclaration] -> String -> String
show :: PackageDeclaration -> String
$cshow :: PackageDeclaration -> String
showsPrec :: Int -> PackageDeclaration -> String -> String
$cshowsPrec :: Int -> PackageDeclaration -> String -> String
Show)

_PackageDeclaration :: Name
_PackageDeclaration = (String -> Name
Core.Name String
"hydra/ext/java/syntax.PackageDeclaration")

_PackageDeclaration_modifiers :: FieldName
_PackageDeclaration_modifiers = (String -> FieldName
Core.FieldName String
"modifiers")

_PackageDeclaration_identifiers :: FieldName
_PackageDeclaration_identifiers = (String -> FieldName
Core.FieldName String
"identifiers")

newtype PackageModifier = 
  PackageModifier {
    PackageModifier -> Annotation
unPackageModifier :: Annotation}
  deriving (PackageModifier -> PackageModifier -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PackageModifier -> PackageModifier -> Bool
$c/= :: PackageModifier -> PackageModifier -> Bool
== :: PackageModifier -> PackageModifier -> Bool
$c== :: PackageModifier -> PackageModifier -> Bool
Eq, Eq PackageModifier
PackageModifier -> PackageModifier -> Bool
PackageModifier -> PackageModifier -> Ordering
PackageModifier -> PackageModifier -> PackageModifier
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: PackageModifier -> PackageModifier -> PackageModifier
$cmin :: PackageModifier -> PackageModifier -> PackageModifier
max :: PackageModifier -> PackageModifier -> PackageModifier
$cmax :: PackageModifier -> PackageModifier -> PackageModifier
>= :: PackageModifier -> PackageModifier -> Bool
$c>= :: PackageModifier -> PackageModifier -> Bool
> :: PackageModifier -> PackageModifier -> Bool
$c> :: PackageModifier -> PackageModifier -> Bool
<= :: PackageModifier -> PackageModifier -> Bool
$c<= :: PackageModifier -> PackageModifier -> Bool
< :: PackageModifier -> PackageModifier -> Bool
$c< :: PackageModifier -> PackageModifier -> Bool
compare :: PackageModifier -> PackageModifier -> Ordering
$ccompare :: PackageModifier -> PackageModifier -> Ordering
Ord, ReadPrec [PackageModifier]
ReadPrec PackageModifier
Int -> ReadS PackageModifier
ReadS [PackageModifier]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [PackageModifier]
$creadListPrec :: ReadPrec [PackageModifier]
readPrec :: ReadPrec PackageModifier
$creadPrec :: ReadPrec PackageModifier
readList :: ReadS [PackageModifier]
$creadList :: ReadS [PackageModifier]
readsPrec :: Int -> ReadS PackageModifier
$creadsPrec :: Int -> ReadS PackageModifier
Read, Int -> PackageModifier -> String -> String
[PackageModifier] -> String -> String
PackageModifier -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [PackageModifier] -> String -> String
$cshowList :: [PackageModifier] -> String -> String
show :: PackageModifier -> String
$cshow :: PackageModifier -> String
showsPrec :: Int -> PackageModifier -> String -> String
$cshowsPrec :: Int -> PackageModifier -> String -> String
Show)

_PackageModifier :: Name
_PackageModifier = (String -> Name
Core.Name String
"hydra/ext/java/syntax.PackageModifier")

data ImportDeclaration = 
  ImportDeclarationSingleType SingleTypeImportDeclaration |
  ImportDeclarationTypeImportOnDemand TypeImportOnDemandDeclaration |
  ImportDeclarationSingleStaticImport SingleStaticImportDeclaration |
  ImportDeclarationStaticImportOnDemand StaticImportOnDemandDeclaration
  deriving (ImportDeclaration -> ImportDeclaration -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ImportDeclaration -> ImportDeclaration -> Bool
$c/= :: ImportDeclaration -> ImportDeclaration -> Bool
== :: ImportDeclaration -> ImportDeclaration -> Bool
$c== :: ImportDeclaration -> ImportDeclaration -> Bool
Eq, Eq ImportDeclaration
ImportDeclaration -> ImportDeclaration -> Bool
ImportDeclaration -> ImportDeclaration -> Ordering
ImportDeclaration -> ImportDeclaration -> ImportDeclaration
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ImportDeclaration -> ImportDeclaration -> ImportDeclaration
$cmin :: ImportDeclaration -> ImportDeclaration -> ImportDeclaration
max :: ImportDeclaration -> ImportDeclaration -> ImportDeclaration
$cmax :: ImportDeclaration -> ImportDeclaration -> ImportDeclaration
>= :: ImportDeclaration -> ImportDeclaration -> Bool
$c>= :: ImportDeclaration -> ImportDeclaration -> Bool
> :: ImportDeclaration -> ImportDeclaration -> Bool
$c> :: ImportDeclaration -> ImportDeclaration -> Bool
<= :: ImportDeclaration -> ImportDeclaration -> Bool
$c<= :: ImportDeclaration -> ImportDeclaration -> Bool
< :: ImportDeclaration -> ImportDeclaration -> Bool
$c< :: ImportDeclaration -> ImportDeclaration -> Bool
compare :: ImportDeclaration -> ImportDeclaration -> Ordering
$ccompare :: ImportDeclaration -> ImportDeclaration -> Ordering
Ord, ReadPrec [ImportDeclaration]
ReadPrec ImportDeclaration
Int -> ReadS ImportDeclaration
ReadS [ImportDeclaration]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ImportDeclaration]
$creadListPrec :: ReadPrec [ImportDeclaration]
readPrec :: ReadPrec ImportDeclaration
$creadPrec :: ReadPrec ImportDeclaration
readList :: ReadS [ImportDeclaration]
$creadList :: ReadS [ImportDeclaration]
readsPrec :: Int -> ReadS ImportDeclaration
$creadsPrec :: Int -> ReadS ImportDeclaration
Read, Int -> ImportDeclaration -> String -> String
[ImportDeclaration] -> String -> String
ImportDeclaration -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ImportDeclaration] -> String -> String
$cshowList :: [ImportDeclaration] -> String -> String
show :: ImportDeclaration -> String
$cshow :: ImportDeclaration -> String
showsPrec :: Int -> ImportDeclaration -> String -> String
$cshowsPrec :: Int -> ImportDeclaration -> String -> String
Show)

_ImportDeclaration :: Name
_ImportDeclaration = (String -> Name
Core.Name String
"hydra/ext/java/syntax.ImportDeclaration")

_ImportDeclaration_singleType :: FieldName
_ImportDeclaration_singleType = (String -> FieldName
Core.FieldName String
"singleType")

_ImportDeclaration_typeImportOnDemand :: FieldName
_ImportDeclaration_typeImportOnDemand = (String -> FieldName
Core.FieldName String
"typeImportOnDemand")

_ImportDeclaration_singleStaticImport :: FieldName
_ImportDeclaration_singleStaticImport = (String -> FieldName
Core.FieldName String
"singleStaticImport")

_ImportDeclaration_staticImportOnDemand :: FieldName
_ImportDeclaration_staticImportOnDemand = (String -> FieldName
Core.FieldName String
"staticImportOnDemand")

newtype SingleTypeImportDeclaration = 
  SingleTypeImportDeclaration {
    SingleTypeImportDeclaration -> TypeName
unSingleTypeImportDeclaration :: TypeName}
  deriving (SingleTypeImportDeclaration -> SingleTypeImportDeclaration -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SingleTypeImportDeclaration -> SingleTypeImportDeclaration -> Bool
$c/= :: SingleTypeImportDeclaration -> SingleTypeImportDeclaration -> Bool
== :: SingleTypeImportDeclaration -> SingleTypeImportDeclaration -> Bool
$c== :: SingleTypeImportDeclaration -> SingleTypeImportDeclaration -> Bool
Eq, Eq SingleTypeImportDeclaration
SingleTypeImportDeclaration -> SingleTypeImportDeclaration -> Bool
SingleTypeImportDeclaration
-> SingleTypeImportDeclaration -> Ordering
SingleTypeImportDeclaration
-> SingleTypeImportDeclaration -> SingleTypeImportDeclaration
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: SingleTypeImportDeclaration
-> SingleTypeImportDeclaration -> SingleTypeImportDeclaration
$cmin :: SingleTypeImportDeclaration
-> SingleTypeImportDeclaration -> SingleTypeImportDeclaration
max :: SingleTypeImportDeclaration
-> SingleTypeImportDeclaration -> SingleTypeImportDeclaration
$cmax :: SingleTypeImportDeclaration
-> SingleTypeImportDeclaration -> SingleTypeImportDeclaration
>= :: SingleTypeImportDeclaration -> SingleTypeImportDeclaration -> Bool
$c>= :: SingleTypeImportDeclaration -> SingleTypeImportDeclaration -> Bool
> :: SingleTypeImportDeclaration -> SingleTypeImportDeclaration -> Bool
$c> :: SingleTypeImportDeclaration -> SingleTypeImportDeclaration -> Bool
<= :: SingleTypeImportDeclaration -> SingleTypeImportDeclaration -> Bool
$c<= :: SingleTypeImportDeclaration -> SingleTypeImportDeclaration -> Bool
< :: SingleTypeImportDeclaration -> SingleTypeImportDeclaration -> Bool
$c< :: SingleTypeImportDeclaration -> SingleTypeImportDeclaration -> Bool
compare :: SingleTypeImportDeclaration
-> SingleTypeImportDeclaration -> Ordering
$ccompare :: SingleTypeImportDeclaration
-> SingleTypeImportDeclaration -> Ordering
Ord, ReadPrec [SingleTypeImportDeclaration]
ReadPrec SingleTypeImportDeclaration
Int -> ReadS SingleTypeImportDeclaration
ReadS [SingleTypeImportDeclaration]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SingleTypeImportDeclaration]
$creadListPrec :: ReadPrec [SingleTypeImportDeclaration]
readPrec :: ReadPrec SingleTypeImportDeclaration
$creadPrec :: ReadPrec SingleTypeImportDeclaration
readList :: ReadS [SingleTypeImportDeclaration]
$creadList :: ReadS [SingleTypeImportDeclaration]
readsPrec :: Int -> ReadS SingleTypeImportDeclaration
$creadsPrec :: Int -> ReadS SingleTypeImportDeclaration
Read, Int -> SingleTypeImportDeclaration -> String -> String
[SingleTypeImportDeclaration] -> String -> String
SingleTypeImportDeclaration -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [SingleTypeImportDeclaration] -> String -> String
$cshowList :: [SingleTypeImportDeclaration] -> String -> String
show :: SingleTypeImportDeclaration -> String
$cshow :: SingleTypeImportDeclaration -> String
showsPrec :: Int -> SingleTypeImportDeclaration -> String -> String
$cshowsPrec :: Int -> SingleTypeImportDeclaration -> String -> String
Show)

_SingleTypeImportDeclaration :: Name
_SingleTypeImportDeclaration = (String -> Name
Core.Name String
"hydra/ext/java/syntax.SingleTypeImportDeclaration")

newtype TypeImportOnDemandDeclaration = 
  TypeImportOnDemandDeclaration {
    TypeImportOnDemandDeclaration -> PackageOrTypeName
unTypeImportOnDemandDeclaration :: PackageOrTypeName}
  deriving (TypeImportOnDemandDeclaration
-> TypeImportOnDemandDeclaration -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TypeImportOnDemandDeclaration
-> TypeImportOnDemandDeclaration -> Bool
$c/= :: TypeImportOnDemandDeclaration
-> TypeImportOnDemandDeclaration -> Bool
== :: TypeImportOnDemandDeclaration
-> TypeImportOnDemandDeclaration -> Bool
$c== :: TypeImportOnDemandDeclaration
-> TypeImportOnDemandDeclaration -> Bool
Eq, Eq TypeImportOnDemandDeclaration
TypeImportOnDemandDeclaration
-> TypeImportOnDemandDeclaration -> Bool
TypeImportOnDemandDeclaration
-> TypeImportOnDemandDeclaration -> Ordering
TypeImportOnDemandDeclaration
-> TypeImportOnDemandDeclaration -> TypeImportOnDemandDeclaration
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: TypeImportOnDemandDeclaration
-> TypeImportOnDemandDeclaration -> TypeImportOnDemandDeclaration
$cmin :: TypeImportOnDemandDeclaration
-> TypeImportOnDemandDeclaration -> TypeImportOnDemandDeclaration
max :: TypeImportOnDemandDeclaration
-> TypeImportOnDemandDeclaration -> TypeImportOnDemandDeclaration
$cmax :: TypeImportOnDemandDeclaration
-> TypeImportOnDemandDeclaration -> TypeImportOnDemandDeclaration
>= :: TypeImportOnDemandDeclaration
-> TypeImportOnDemandDeclaration -> Bool
$c>= :: TypeImportOnDemandDeclaration
-> TypeImportOnDemandDeclaration -> Bool
> :: TypeImportOnDemandDeclaration
-> TypeImportOnDemandDeclaration -> Bool
$c> :: TypeImportOnDemandDeclaration
-> TypeImportOnDemandDeclaration -> Bool
<= :: TypeImportOnDemandDeclaration
-> TypeImportOnDemandDeclaration -> Bool
$c<= :: TypeImportOnDemandDeclaration
-> TypeImportOnDemandDeclaration -> Bool
< :: TypeImportOnDemandDeclaration
-> TypeImportOnDemandDeclaration -> Bool
$c< :: TypeImportOnDemandDeclaration
-> TypeImportOnDemandDeclaration -> Bool
compare :: TypeImportOnDemandDeclaration
-> TypeImportOnDemandDeclaration -> Ordering
$ccompare :: TypeImportOnDemandDeclaration
-> TypeImportOnDemandDeclaration -> Ordering
Ord, ReadPrec [TypeImportOnDemandDeclaration]
ReadPrec TypeImportOnDemandDeclaration
Int -> ReadS TypeImportOnDemandDeclaration
ReadS [TypeImportOnDemandDeclaration]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [TypeImportOnDemandDeclaration]
$creadListPrec :: ReadPrec [TypeImportOnDemandDeclaration]
readPrec :: ReadPrec TypeImportOnDemandDeclaration
$creadPrec :: ReadPrec TypeImportOnDemandDeclaration
readList :: ReadS [TypeImportOnDemandDeclaration]
$creadList :: ReadS [TypeImportOnDemandDeclaration]
readsPrec :: Int -> ReadS TypeImportOnDemandDeclaration
$creadsPrec :: Int -> ReadS TypeImportOnDemandDeclaration
Read, Int -> TypeImportOnDemandDeclaration -> String -> String
[TypeImportOnDemandDeclaration] -> String -> String
TypeImportOnDemandDeclaration -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [TypeImportOnDemandDeclaration] -> String -> String
$cshowList :: [TypeImportOnDemandDeclaration] -> String -> String
show :: TypeImportOnDemandDeclaration -> String
$cshow :: TypeImportOnDemandDeclaration -> String
showsPrec :: Int -> TypeImportOnDemandDeclaration -> String -> String
$cshowsPrec :: Int -> TypeImportOnDemandDeclaration -> String -> String
Show)

_TypeImportOnDemandDeclaration :: Name
_TypeImportOnDemandDeclaration = (String -> Name
Core.Name String
"hydra/ext/java/syntax.TypeImportOnDemandDeclaration")

data SingleStaticImportDeclaration = 
  SingleStaticImportDeclaration {
    SingleStaticImportDeclaration -> TypeName
singleStaticImportDeclarationTypeName :: TypeName,
    SingleStaticImportDeclaration -> Identifier
singleStaticImportDeclarationIdentifier :: Identifier}
  deriving (SingleStaticImportDeclaration
-> SingleStaticImportDeclaration -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SingleStaticImportDeclaration
-> SingleStaticImportDeclaration -> Bool
$c/= :: SingleStaticImportDeclaration
-> SingleStaticImportDeclaration -> Bool
== :: SingleStaticImportDeclaration
-> SingleStaticImportDeclaration -> Bool
$c== :: SingleStaticImportDeclaration
-> SingleStaticImportDeclaration -> Bool
Eq, Eq SingleStaticImportDeclaration
SingleStaticImportDeclaration
-> SingleStaticImportDeclaration -> Bool
SingleStaticImportDeclaration
-> SingleStaticImportDeclaration -> Ordering
SingleStaticImportDeclaration
-> SingleStaticImportDeclaration -> SingleStaticImportDeclaration
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: SingleStaticImportDeclaration
-> SingleStaticImportDeclaration -> SingleStaticImportDeclaration
$cmin :: SingleStaticImportDeclaration
-> SingleStaticImportDeclaration -> SingleStaticImportDeclaration
max :: SingleStaticImportDeclaration
-> SingleStaticImportDeclaration -> SingleStaticImportDeclaration
$cmax :: SingleStaticImportDeclaration
-> SingleStaticImportDeclaration -> SingleStaticImportDeclaration
>= :: SingleStaticImportDeclaration
-> SingleStaticImportDeclaration -> Bool
$c>= :: SingleStaticImportDeclaration
-> SingleStaticImportDeclaration -> Bool
> :: SingleStaticImportDeclaration
-> SingleStaticImportDeclaration -> Bool
$c> :: SingleStaticImportDeclaration
-> SingleStaticImportDeclaration -> Bool
<= :: SingleStaticImportDeclaration
-> SingleStaticImportDeclaration -> Bool
$c<= :: SingleStaticImportDeclaration
-> SingleStaticImportDeclaration -> Bool
< :: SingleStaticImportDeclaration
-> SingleStaticImportDeclaration -> Bool
$c< :: SingleStaticImportDeclaration
-> SingleStaticImportDeclaration -> Bool
compare :: SingleStaticImportDeclaration
-> SingleStaticImportDeclaration -> Ordering
$ccompare :: SingleStaticImportDeclaration
-> SingleStaticImportDeclaration -> Ordering
Ord, ReadPrec [SingleStaticImportDeclaration]
ReadPrec SingleStaticImportDeclaration
Int -> ReadS SingleStaticImportDeclaration
ReadS [SingleStaticImportDeclaration]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SingleStaticImportDeclaration]
$creadListPrec :: ReadPrec [SingleStaticImportDeclaration]
readPrec :: ReadPrec SingleStaticImportDeclaration
$creadPrec :: ReadPrec SingleStaticImportDeclaration
readList :: ReadS [SingleStaticImportDeclaration]
$creadList :: ReadS [SingleStaticImportDeclaration]
readsPrec :: Int -> ReadS SingleStaticImportDeclaration
$creadsPrec :: Int -> ReadS SingleStaticImportDeclaration
Read, Int -> SingleStaticImportDeclaration -> String -> String
[SingleStaticImportDeclaration] -> String -> String
SingleStaticImportDeclaration -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [SingleStaticImportDeclaration] -> String -> String
$cshowList :: [SingleStaticImportDeclaration] -> String -> String
show :: SingleStaticImportDeclaration -> String
$cshow :: SingleStaticImportDeclaration -> String
showsPrec :: Int -> SingleStaticImportDeclaration -> String -> String
$cshowsPrec :: Int -> SingleStaticImportDeclaration -> String -> String
Show)

_SingleStaticImportDeclaration :: Name
_SingleStaticImportDeclaration = (String -> Name
Core.Name String
"hydra/ext/java/syntax.SingleStaticImportDeclaration")

_SingleStaticImportDeclaration_typeName :: FieldName
_SingleStaticImportDeclaration_typeName = (String -> FieldName
Core.FieldName String
"typeName")

_SingleStaticImportDeclaration_identifier :: FieldName
_SingleStaticImportDeclaration_identifier = (String -> FieldName
Core.FieldName String
"identifier")

newtype StaticImportOnDemandDeclaration = 
  StaticImportOnDemandDeclaration {
    StaticImportOnDemandDeclaration -> TypeName
unStaticImportOnDemandDeclaration :: TypeName}
  deriving (StaticImportOnDemandDeclaration
-> StaticImportOnDemandDeclaration -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StaticImportOnDemandDeclaration
-> StaticImportOnDemandDeclaration -> Bool
$c/= :: StaticImportOnDemandDeclaration
-> StaticImportOnDemandDeclaration -> Bool
== :: StaticImportOnDemandDeclaration
-> StaticImportOnDemandDeclaration -> Bool
$c== :: StaticImportOnDemandDeclaration
-> StaticImportOnDemandDeclaration -> Bool
Eq, Eq StaticImportOnDemandDeclaration
StaticImportOnDemandDeclaration
-> StaticImportOnDemandDeclaration -> Bool
StaticImportOnDemandDeclaration
-> StaticImportOnDemandDeclaration -> Ordering
StaticImportOnDemandDeclaration
-> StaticImportOnDemandDeclaration
-> StaticImportOnDemandDeclaration
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: StaticImportOnDemandDeclaration
-> StaticImportOnDemandDeclaration
-> StaticImportOnDemandDeclaration
$cmin :: StaticImportOnDemandDeclaration
-> StaticImportOnDemandDeclaration
-> StaticImportOnDemandDeclaration
max :: StaticImportOnDemandDeclaration
-> StaticImportOnDemandDeclaration
-> StaticImportOnDemandDeclaration
$cmax :: StaticImportOnDemandDeclaration
-> StaticImportOnDemandDeclaration
-> StaticImportOnDemandDeclaration
>= :: StaticImportOnDemandDeclaration
-> StaticImportOnDemandDeclaration -> Bool
$c>= :: StaticImportOnDemandDeclaration
-> StaticImportOnDemandDeclaration -> Bool
> :: StaticImportOnDemandDeclaration
-> StaticImportOnDemandDeclaration -> Bool
$c> :: StaticImportOnDemandDeclaration
-> StaticImportOnDemandDeclaration -> Bool
<= :: StaticImportOnDemandDeclaration
-> StaticImportOnDemandDeclaration -> Bool
$c<= :: StaticImportOnDemandDeclaration
-> StaticImportOnDemandDeclaration -> Bool
< :: StaticImportOnDemandDeclaration
-> StaticImportOnDemandDeclaration -> Bool
$c< :: StaticImportOnDemandDeclaration
-> StaticImportOnDemandDeclaration -> Bool
compare :: StaticImportOnDemandDeclaration
-> StaticImportOnDemandDeclaration -> Ordering
$ccompare :: StaticImportOnDemandDeclaration
-> StaticImportOnDemandDeclaration -> Ordering
Ord, ReadPrec [StaticImportOnDemandDeclaration]
ReadPrec StaticImportOnDemandDeclaration
Int -> ReadS StaticImportOnDemandDeclaration
ReadS [StaticImportOnDemandDeclaration]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StaticImportOnDemandDeclaration]
$creadListPrec :: ReadPrec [StaticImportOnDemandDeclaration]
readPrec :: ReadPrec StaticImportOnDemandDeclaration
$creadPrec :: ReadPrec StaticImportOnDemandDeclaration
readList :: ReadS [StaticImportOnDemandDeclaration]
$creadList :: ReadS [StaticImportOnDemandDeclaration]
readsPrec :: Int -> ReadS StaticImportOnDemandDeclaration
$creadsPrec :: Int -> ReadS StaticImportOnDemandDeclaration
Read, Int -> StaticImportOnDemandDeclaration -> String -> String
[StaticImportOnDemandDeclaration] -> String -> String
StaticImportOnDemandDeclaration -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [StaticImportOnDemandDeclaration] -> String -> String
$cshowList :: [StaticImportOnDemandDeclaration] -> String -> String
show :: StaticImportOnDemandDeclaration -> String
$cshow :: StaticImportOnDemandDeclaration -> String
showsPrec :: Int -> StaticImportOnDemandDeclaration -> String -> String
$cshowsPrec :: Int -> StaticImportOnDemandDeclaration -> String -> String
Show)

_StaticImportOnDemandDeclaration :: Name
_StaticImportOnDemandDeclaration = (String -> Name
Core.Name String
"hydra/ext/java/syntax.StaticImportOnDemandDeclaration")

data TypeDeclaration = 
  TypeDeclarationClass ClassDeclaration |
  TypeDeclarationInterface InterfaceDeclaration |
  TypeDeclarationNone 
  deriving (TypeDeclaration -> TypeDeclaration -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TypeDeclaration -> TypeDeclaration -> Bool
$c/= :: TypeDeclaration -> TypeDeclaration -> Bool
== :: TypeDeclaration -> TypeDeclaration -> Bool
$c== :: TypeDeclaration -> TypeDeclaration -> Bool
Eq, Eq TypeDeclaration
TypeDeclaration -> TypeDeclaration -> Bool
TypeDeclaration -> TypeDeclaration -> Ordering
TypeDeclaration -> TypeDeclaration -> TypeDeclaration
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: TypeDeclaration -> TypeDeclaration -> TypeDeclaration
$cmin :: TypeDeclaration -> TypeDeclaration -> TypeDeclaration
max :: TypeDeclaration -> TypeDeclaration -> TypeDeclaration
$cmax :: TypeDeclaration -> TypeDeclaration -> TypeDeclaration
>= :: TypeDeclaration -> TypeDeclaration -> Bool
$c>= :: TypeDeclaration -> TypeDeclaration -> Bool
> :: TypeDeclaration -> TypeDeclaration -> Bool
$c> :: TypeDeclaration -> TypeDeclaration -> Bool
<= :: TypeDeclaration -> TypeDeclaration -> Bool
$c<= :: TypeDeclaration -> TypeDeclaration -> Bool
< :: TypeDeclaration -> TypeDeclaration -> Bool
$c< :: TypeDeclaration -> TypeDeclaration -> Bool
compare :: TypeDeclaration -> TypeDeclaration -> Ordering
$ccompare :: TypeDeclaration -> TypeDeclaration -> Ordering
Ord, ReadPrec [TypeDeclaration]
ReadPrec TypeDeclaration
Int -> ReadS TypeDeclaration
ReadS [TypeDeclaration]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [TypeDeclaration]
$creadListPrec :: ReadPrec [TypeDeclaration]
readPrec :: ReadPrec TypeDeclaration
$creadPrec :: ReadPrec TypeDeclaration
readList :: ReadS [TypeDeclaration]
$creadList :: ReadS [TypeDeclaration]
readsPrec :: Int -> ReadS TypeDeclaration
$creadsPrec :: Int -> ReadS TypeDeclaration
Read, Int -> TypeDeclaration -> String -> String
[TypeDeclaration] -> String -> String
TypeDeclaration -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [TypeDeclaration] -> String -> String
$cshowList :: [TypeDeclaration] -> String -> String
show :: TypeDeclaration -> String
$cshow :: TypeDeclaration -> String
showsPrec :: Int -> TypeDeclaration -> String -> String
$cshowsPrec :: Int -> TypeDeclaration -> String -> String
Show)

_TypeDeclaration :: Name
_TypeDeclaration = (String -> Name
Core.Name String
"hydra/ext/java/syntax.TypeDeclaration")

_TypeDeclaration_class :: FieldName
_TypeDeclaration_class = (String -> FieldName
Core.FieldName String
"class")

_TypeDeclaration_interface :: FieldName
_TypeDeclaration_interface = (String -> FieldName
Core.FieldName String
"interface")

_TypeDeclaration_none :: FieldName
_TypeDeclaration_none = (String -> FieldName
Core.FieldName String
"none")

data TypeDeclarationWithComments = 
  TypeDeclarationWithComments {
    TypeDeclarationWithComments -> TypeDeclaration
typeDeclarationWithCommentsValue :: TypeDeclaration,
    TypeDeclarationWithComments -> Maybe String
typeDeclarationWithCommentsComments :: (Maybe String)}
  deriving (TypeDeclarationWithComments -> TypeDeclarationWithComments -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TypeDeclarationWithComments -> TypeDeclarationWithComments -> Bool
$c/= :: TypeDeclarationWithComments -> TypeDeclarationWithComments -> Bool
== :: TypeDeclarationWithComments -> TypeDeclarationWithComments -> Bool
$c== :: TypeDeclarationWithComments -> TypeDeclarationWithComments -> Bool
Eq, Eq TypeDeclarationWithComments
TypeDeclarationWithComments -> TypeDeclarationWithComments -> Bool
TypeDeclarationWithComments
-> TypeDeclarationWithComments -> Ordering
TypeDeclarationWithComments
-> TypeDeclarationWithComments -> TypeDeclarationWithComments
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: TypeDeclarationWithComments
-> TypeDeclarationWithComments -> TypeDeclarationWithComments
$cmin :: TypeDeclarationWithComments
-> TypeDeclarationWithComments -> TypeDeclarationWithComments
max :: TypeDeclarationWithComments
-> TypeDeclarationWithComments -> TypeDeclarationWithComments
$cmax :: TypeDeclarationWithComments
-> TypeDeclarationWithComments -> TypeDeclarationWithComments
>= :: TypeDeclarationWithComments -> TypeDeclarationWithComments -> Bool
$c>= :: TypeDeclarationWithComments -> TypeDeclarationWithComments -> Bool
> :: TypeDeclarationWithComments -> TypeDeclarationWithComments -> Bool
$c> :: TypeDeclarationWithComments -> TypeDeclarationWithComments -> Bool
<= :: TypeDeclarationWithComments -> TypeDeclarationWithComments -> Bool
$c<= :: TypeDeclarationWithComments -> TypeDeclarationWithComments -> Bool
< :: TypeDeclarationWithComments -> TypeDeclarationWithComments -> Bool
$c< :: TypeDeclarationWithComments -> TypeDeclarationWithComments -> Bool
compare :: TypeDeclarationWithComments
-> TypeDeclarationWithComments -> Ordering
$ccompare :: TypeDeclarationWithComments
-> TypeDeclarationWithComments -> Ordering
Ord, ReadPrec [TypeDeclarationWithComments]
ReadPrec TypeDeclarationWithComments
Int -> ReadS TypeDeclarationWithComments
ReadS [TypeDeclarationWithComments]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [TypeDeclarationWithComments]
$creadListPrec :: ReadPrec [TypeDeclarationWithComments]
readPrec :: ReadPrec TypeDeclarationWithComments
$creadPrec :: ReadPrec TypeDeclarationWithComments
readList :: ReadS [TypeDeclarationWithComments]
$creadList :: ReadS [TypeDeclarationWithComments]
readsPrec :: Int -> ReadS TypeDeclarationWithComments
$creadsPrec :: Int -> ReadS TypeDeclarationWithComments
Read, Int -> TypeDeclarationWithComments -> String -> String
[TypeDeclarationWithComments] -> String -> String
TypeDeclarationWithComments -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [TypeDeclarationWithComments] -> String -> String
$cshowList :: [TypeDeclarationWithComments] -> String -> String
show :: TypeDeclarationWithComments -> String
$cshow :: TypeDeclarationWithComments -> String
showsPrec :: Int -> TypeDeclarationWithComments -> String -> String
$cshowsPrec :: Int -> TypeDeclarationWithComments -> String -> String
Show)

_TypeDeclarationWithComments :: Name
_TypeDeclarationWithComments = (String -> Name
Core.Name String
"hydra/ext/java/syntax.TypeDeclarationWithComments")

_TypeDeclarationWithComments_value :: FieldName
_TypeDeclarationWithComments_value = (String -> FieldName
Core.FieldName String
"value")

_TypeDeclarationWithComments_comments :: FieldName
_TypeDeclarationWithComments_comments = (String -> FieldName
Core.FieldName String
"comments")

data ModuleDeclaration = 
  ModuleDeclaration {
    ModuleDeclaration -> [Annotation]
moduleDeclarationAnnotations :: [Annotation],
    ModuleDeclaration -> Bool
moduleDeclarationOpen :: Bool,
    ModuleDeclaration -> [Identifier]
moduleDeclarationIdentifiers :: [Identifier],
    ModuleDeclaration -> [[ModuleDirective]]
moduleDeclarationDirectives :: [[ModuleDirective]]}
  deriving (ModuleDeclaration -> ModuleDeclaration -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ModuleDeclaration -> ModuleDeclaration -> Bool
$c/= :: ModuleDeclaration -> ModuleDeclaration -> Bool
== :: ModuleDeclaration -> ModuleDeclaration -> Bool
$c== :: ModuleDeclaration -> ModuleDeclaration -> Bool
Eq, Eq ModuleDeclaration
ModuleDeclaration -> ModuleDeclaration -> Bool
ModuleDeclaration -> ModuleDeclaration -> Ordering
ModuleDeclaration -> ModuleDeclaration -> ModuleDeclaration
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ModuleDeclaration -> ModuleDeclaration -> ModuleDeclaration
$cmin :: ModuleDeclaration -> ModuleDeclaration -> ModuleDeclaration
max :: ModuleDeclaration -> ModuleDeclaration -> ModuleDeclaration
$cmax :: ModuleDeclaration -> ModuleDeclaration -> ModuleDeclaration
>= :: ModuleDeclaration -> ModuleDeclaration -> Bool
$c>= :: ModuleDeclaration -> ModuleDeclaration -> Bool
> :: ModuleDeclaration -> ModuleDeclaration -> Bool
$c> :: ModuleDeclaration -> ModuleDeclaration -> Bool
<= :: ModuleDeclaration -> ModuleDeclaration -> Bool
$c<= :: ModuleDeclaration -> ModuleDeclaration -> Bool
< :: ModuleDeclaration -> ModuleDeclaration -> Bool
$c< :: ModuleDeclaration -> ModuleDeclaration -> Bool
compare :: ModuleDeclaration -> ModuleDeclaration -> Ordering
$ccompare :: ModuleDeclaration -> ModuleDeclaration -> Ordering
Ord, ReadPrec [ModuleDeclaration]
ReadPrec ModuleDeclaration
Int -> ReadS ModuleDeclaration
ReadS [ModuleDeclaration]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ModuleDeclaration]
$creadListPrec :: ReadPrec [ModuleDeclaration]
readPrec :: ReadPrec ModuleDeclaration
$creadPrec :: ReadPrec ModuleDeclaration
readList :: ReadS [ModuleDeclaration]
$creadList :: ReadS [ModuleDeclaration]
readsPrec :: Int -> ReadS ModuleDeclaration
$creadsPrec :: Int -> ReadS ModuleDeclaration
Read, Int -> ModuleDeclaration -> String -> String
[ModuleDeclaration] -> String -> String
ModuleDeclaration -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ModuleDeclaration] -> String -> String
$cshowList :: [ModuleDeclaration] -> String -> String
show :: ModuleDeclaration -> String
$cshow :: ModuleDeclaration -> String
showsPrec :: Int -> ModuleDeclaration -> String -> String
$cshowsPrec :: Int -> ModuleDeclaration -> String -> String
Show)

_ModuleDeclaration :: Name
_ModuleDeclaration = (String -> Name
Core.Name String
"hydra/ext/java/syntax.ModuleDeclaration")

_ModuleDeclaration_annotations :: FieldName
_ModuleDeclaration_annotations = (String -> FieldName
Core.FieldName String
"annotations")

_ModuleDeclaration_open :: FieldName
_ModuleDeclaration_open = (String -> FieldName
Core.FieldName String
"open")

_ModuleDeclaration_identifiers :: FieldName
_ModuleDeclaration_identifiers = (String -> FieldName
Core.FieldName String
"identifiers")

_ModuleDeclaration_directives :: FieldName
_ModuleDeclaration_directives = (String -> FieldName
Core.FieldName String
"directives")

data ModuleDirective = 
  ModuleDirectiveRequires ModuleDirective_Requires |
  ModuleDirectiveExports ModuleDirective_ExportsOrOpens |
  ModuleDirectiveOpens ModuleDirective_ExportsOrOpens |
  ModuleDirectiveUses TypeName |
  ModuleDirectiveProvides ModuleDirective_Provides
  deriving (ModuleDirective -> ModuleDirective -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ModuleDirective -> ModuleDirective -> Bool
$c/= :: ModuleDirective -> ModuleDirective -> Bool
== :: ModuleDirective -> ModuleDirective -> Bool
$c== :: ModuleDirective -> ModuleDirective -> Bool
Eq, Eq ModuleDirective
ModuleDirective -> ModuleDirective -> Bool
ModuleDirective -> ModuleDirective -> Ordering
ModuleDirective -> ModuleDirective -> ModuleDirective
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ModuleDirective -> ModuleDirective -> ModuleDirective
$cmin :: ModuleDirective -> ModuleDirective -> ModuleDirective
max :: ModuleDirective -> ModuleDirective -> ModuleDirective
$cmax :: ModuleDirective -> ModuleDirective -> ModuleDirective
>= :: ModuleDirective -> ModuleDirective -> Bool
$c>= :: ModuleDirective -> ModuleDirective -> Bool
> :: ModuleDirective -> ModuleDirective -> Bool
$c> :: ModuleDirective -> ModuleDirective -> Bool
<= :: ModuleDirective -> ModuleDirective -> Bool
$c<= :: ModuleDirective -> ModuleDirective -> Bool
< :: ModuleDirective -> ModuleDirective -> Bool
$c< :: ModuleDirective -> ModuleDirective -> Bool
compare :: ModuleDirective -> ModuleDirective -> Ordering
$ccompare :: ModuleDirective -> ModuleDirective -> Ordering
Ord, ReadPrec [ModuleDirective]
ReadPrec ModuleDirective
Int -> ReadS ModuleDirective
ReadS [ModuleDirective]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ModuleDirective]
$creadListPrec :: ReadPrec [ModuleDirective]
readPrec :: ReadPrec ModuleDirective
$creadPrec :: ReadPrec ModuleDirective
readList :: ReadS [ModuleDirective]
$creadList :: ReadS [ModuleDirective]
readsPrec :: Int -> ReadS ModuleDirective
$creadsPrec :: Int -> ReadS ModuleDirective
Read, Int -> ModuleDirective -> String -> String
[ModuleDirective] -> String -> String
ModuleDirective -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ModuleDirective] -> String -> String
$cshowList :: [ModuleDirective] -> String -> String
show :: ModuleDirective -> String
$cshow :: ModuleDirective -> String
showsPrec :: Int -> ModuleDirective -> String -> String
$cshowsPrec :: Int -> ModuleDirective -> String -> String
Show)

_ModuleDirective :: Name
_ModuleDirective = (String -> Name
Core.Name String
"hydra/ext/java/syntax.ModuleDirective")

_ModuleDirective_requires :: FieldName
_ModuleDirective_requires = (String -> FieldName
Core.FieldName String
"requires")

_ModuleDirective_exports :: FieldName
_ModuleDirective_exports = (String -> FieldName
Core.FieldName String
"exports")

_ModuleDirective_opens :: FieldName
_ModuleDirective_opens = (String -> FieldName
Core.FieldName String
"opens")

_ModuleDirective_uses :: FieldName
_ModuleDirective_uses = (String -> FieldName
Core.FieldName String
"uses")

_ModuleDirective_provides :: FieldName
_ModuleDirective_provides = (String -> FieldName
Core.FieldName String
"provides")

data ModuleDirective_Requires = 
  ModuleDirective_Requires {
    ModuleDirective_Requires -> [RequiresModifier]
moduleDirective_RequiresModifiers :: [RequiresModifier],
    ModuleDirective_Requires -> ModuleName
moduleDirective_RequiresModule :: ModuleName}
  deriving (ModuleDirective_Requires -> ModuleDirective_Requires -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ModuleDirective_Requires -> ModuleDirective_Requires -> Bool
$c/= :: ModuleDirective_Requires -> ModuleDirective_Requires -> Bool
== :: ModuleDirective_Requires -> ModuleDirective_Requires -> Bool
$c== :: ModuleDirective_Requires -> ModuleDirective_Requires -> Bool
Eq, Eq ModuleDirective_Requires
ModuleDirective_Requires -> ModuleDirective_Requires -> Bool
ModuleDirective_Requires -> ModuleDirective_Requires -> Ordering
ModuleDirective_Requires
-> ModuleDirective_Requires -> ModuleDirective_Requires
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ModuleDirective_Requires
-> ModuleDirective_Requires -> ModuleDirective_Requires
$cmin :: ModuleDirective_Requires
-> ModuleDirective_Requires -> ModuleDirective_Requires
max :: ModuleDirective_Requires
-> ModuleDirective_Requires -> ModuleDirective_Requires
$cmax :: ModuleDirective_Requires
-> ModuleDirective_Requires -> ModuleDirective_Requires
>= :: ModuleDirective_Requires -> ModuleDirective_Requires -> Bool
$c>= :: ModuleDirective_Requires -> ModuleDirective_Requires -> Bool
> :: ModuleDirective_Requires -> ModuleDirective_Requires -> Bool
$c> :: ModuleDirective_Requires -> ModuleDirective_Requires -> Bool
<= :: ModuleDirective_Requires -> ModuleDirective_Requires -> Bool
$c<= :: ModuleDirective_Requires -> ModuleDirective_Requires -> Bool
< :: ModuleDirective_Requires -> ModuleDirective_Requires -> Bool
$c< :: ModuleDirective_Requires -> ModuleDirective_Requires -> Bool
compare :: ModuleDirective_Requires -> ModuleDirective_Requires -> Ordering
$ccompare :: ModuleDirective_Requires -> ModuleDirective_Requires -> Ordering
Ord, ReadPrec [ModuleDirective_Requires]
ReadPrec ModuleDirective_Requires
Int -> ReadS ModuleDirective_Requires
ReadS [ModuleDirective_Requires]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ModuleDirective_Requires]
$creadListPrec :: ReadPrec [ModuleDirective_Requires]
readPrec :: ReadPrec ModuleDirective_Requires
$creadPrec :: ReadPrec ModuleDirective_Requires
readList :: ReadS [ModuleDirective_Requires]
$creadList :: ReadS [ModuleDirective_Requires]
readsPrec :: Int -> ReadS ModuleDirective_Requires
$creadsPrec :: Int -> ReadS ModuleDirective_Requires
Read, Int -> ModuleDirective_Requires -> String -> String
[ModuleDirective_Requires] -> String -> String
ModuleDirective_Requires -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ModuleDirective_Requires] -> String -> String
$cshowList :: [ModuleDirective_Requires] -> String -> String
show :: ModuleDirective_Requires -> String
$cshow :: ModuleDirective_Requires -> String
showsPrec :: Int -> ModuleDirective_Requires -> String -> String
$cshowsPrec :: Int -> ModuleDirective_Requires -> String -> String
Show)

_ModuleDirective_Requires :: Name
_ModuleDirective_Requires = (String -> Name
Core.Name String
"hydra/ext/java/syntax.ModuleDirective.Requires")

_ModuleDirective_Requires_modifiers :: FieldName
_ModuleDirective_Requires_modifiers = (String -> FieldName
Core.FieldName String
"modifiers")

_ModuleDirective_Requires_module :: FieldName
_ModuleDirective_Requires_module = (String -> FieldName
Core.FieldName String
"module")

data ModuleDirective_ExportsOrOpens = 
  ModuleDirective_ExportsOrOpens {
    ModuleDirective_ExportsOrOpens -> PackageName
moduleDirective_ExportsOrOpensPackage :: PackageName,
    -- | At least one module
    ModuleDirective_ExportsOrOpens -> [ModuleName]
moduleDirective_ExportsOrOpensModules :: [ModuleName]}
  deriving (ModuleDirective_ExportsOrOpens
-> ModuleDirective_ExportsOrOpens -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ModuleDirective_ExportsOrOpens
-> ModuleDirective_ExportsOrOpens -> Bool
$c/= :: ModuleDirective_ExportsOrOpens
-> ModuleDirective_ExportsOrOpens -> Bool
== :: ModuleDirective_ExportsOrOpens
-> ModuleDirective_ExportsOrOpens -> Bool
$c== :: ModuleDirective_ExportsOrOpens
-> ModuleDirective_ExportsOrOpens -> Bool
Eq, Eq ModuleDirective_ExportsOrOpens
ModuleDirective_ExportsOrOpens
-> ModuleDirective_ExportsOrOpens -> Bool
ModuleDirective_ExportsOrOpens
-> ModuleDirective_ExportsOrOpens -> Ordering
ModuleDirective_ExportsOrOpens
-> ModuleDirective_ExportsOrOpens -> ModuleDirective_ExportsOrOpens
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ModuleDirective_ExportsOrOpens
-> ModuleDirective_ExportsOrOpens -> ModuleDirective_ExportsOrOpens
$cmin :: ModuleDirective_ExportsOrOpens
-> ModuleDirective_ExportsOrOpens -> ModuleDirective_ExportsOrOpens
max :: ModuleDirective_ExportsOrOpens
-> ModuleDirective_ExportsOrOpens -> ModuleDirective_ExportsOrOpens
$cmax :: ModuleDirective_ExportsOrOpens
-> ModuleDirective_ExportsOrOpens -> ModuleDirective_ExportsOrOpens
>= :: ModuleDirective_ExportsOrOpens
-> ModuleDirective_ExportsOrOpens -> Bool
$c>= :: ModuleDirective_ExportsOrOpens
-> ModuleDirective_ExportsOrOpens -> Bool
> :: ModuleDirective_ExportsOrOpens
-> ModuleDirective_ExportsOrOpens -> Bool
$c> :: ModuleDirective_ExportsOrOpens
-> ModuleDirective_ExportsOrOpens -> Bool
<= :: ModuleDirective_ExportsOrOpens
-> ModuleDirective_ExportsOrOpens -> Bool
$c<= :: ModuleDirective_ExportsOrOpens
-> ModuleDirective_ExportsOrOpens -> Bool
< :: ModuleDirective_ExportsOrOpens
-> ModuleDirective_ExportsOrOpens -> Bool
$c< :: ModuleDirective_ExportsOrOpens
-> ModuleDirective_ExportsOrOpens -> Bool
compare :: ModuleDirective_ExportsOrOpens
-> ModuleDirective_ExportsOrOpens -> Ordering
$ccompare :: ModuleDirective_ExportsOrOpens
-> ModuleDirective_ExportsOrOpens -> Ordering
Ord, ReadPrec [ModuleDirective_ExportsOrOpens]
ReadPrec ModuleDirective_ExportsOrOpens
Int -> ReadS ModuleDirective_ExportsOrOpens
ReadS [ModuleDirective_ExportsOrOpens]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ModuleDirective_ExportsOrOpens]
$creadListPrec :: ReadPrec [ModuleDirective_ExportsOrOpens]
readPrec :: ReadPrec ModuleDirective_ExportsOrOpens
$creadPrec :: ReadPrec ModuleDirective_ExportsOrOpens
readList :: ReadS [ModuleDirective_ExportsOrOpens]
$creadList :: ReadS [ModuleDirective_ExportsOrOpens]
readsPrec :: Int -> ReadS ModuleDirective_ExportsOrOpens
$creadsPrec :: Int -> ReadS ModuleDirective_ExportsOrOpens
Read, Int -> ModuleDirective_ExportsOrOpens -> String -> String
[ModuleDirective_ExportsOrOpens] -> String -> String
ModuleDirective_ExportsOrOpens -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ModuleDirective_ExportsOrOpens] -> String -> String
$cshowList :: [ModuleDirective_ExportsOrOpens] -> String -> String
show :: ModuleDirective_ExportsOrOpens -> String
$cshow :: ModuleDirective_ExportsOrOpens -> String
showsPrec :: Int -> ModuleDirective_ExportsOrOpens -> String -> String
$cshowsPrec :: Int -> ModuleDirective_ExportsOrOpens -> String -> String
Show)

_ModuleDirective_ExportsOrOpens :: Name
_ModuleDirective_ExportsOrOpens = (String -> Name
Core.Name String
"hydra/ext/java/syntax.ModuleDirective.ExportsOrOpens")

_ModuleDirective_ExportsOrOpens_package :: FieldName
_ModuleDirective_ExportsOrOpens_package = (String -> FieldName
Core.FieldName String
"package")

_ModuleDirective_ExportsOrOpens_modules :: FieldName
_ModuleDirective_ExportsOrOpens_modules = (String -> FieldName
Core.FieldName String
"modules")

data ModuleDirective_Provides = 
  ModuleDirective_Provides {
    ModuleDirective_Provides -> TypeName
moduleDirective_ProvidesTo :: TypeName,
    -- | At least one type
    ModuleDirective_Provides -> [TypeName]
moduleDirective_ProvidesWith :: [TypeName]}
  deriving (ModuleDirective_Provides -> ModuleDirective_Provides -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ModuleDirective_Provides -> ModuleDirective_Provides -> Bool
$c/= :: ModuleDirective_Provides -> ModuleDirective_Provides -> Bool
== :: ModuleDirective_Provides -> ModuleDirective_Provides -> Bool
$c== :: ModuleDirective_Provides -> ModuleDirective_Provides -> Bool
Eq, Eq ModuleDirective_Provides
ModuleDirective_Provides -> ModuleDirective_Provides -> Bool
ModuleDirective_Provides -> ModuleDirective_Provides -> Ordering
ModuleDirective_Provides
-> ModuleDirective_Provides -> ModuleDirective_Provides
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ModuleDirective_Provides
-> ModuleDirective_Provides -> ModuleDirective_Provides
$cmin :: ModuleDirective_Provides
-> ModuleDirective_Provides -> ModuleDirective_Provides
max :: ModuleDirective_Provides
-> ModuleDirective_Provides -> ModuleDirective_Provides
$cmax :: ModuleDirective_Provides
-> ModuleDirective_Provides -> ModuleDirective_Provides
>= :: ModuleDirective_Provides -> ModuleDirective_Provides -> Bool
$c>= :: ModuleDirective_Provides -> ModuleDirective_Provides -> Bool
> :: ModuleDirective_Provides -> ModuleDirective_Provides -> Bool
$c> :: ModuleDirective_Provides -> ModuleDirective_Provides -> Bool
<= :: ModuleDirective_Provides -> ModuleDirective_Provides -> Bool
$c<= :: ModuleDirective_Provides -> ModuleDirective_Provides -> Bool
< :: ModuleDirective_Provides -> ModuleDirective_Provides -> Bool
$c< :: ModuleDirective_Provides -> ModuleDirective_Provides -> Bool
compare :: ModuleDirective_Provides -> ModuleDirective_Provides -> Ordering
$ccompare :: ModuleDirective_Provides -> ModuleDirective_Provides -> Ordering
Ord, ReadPrec [ModuleDirective_Provides]
ReadPrec ModuleDirective_Provides
Int -> ReadS ModuleDirective_Provides
ReadS [ModuleDirective_Provides]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ModuleDirective_Provides]
$creadListPrec :: ReadPrec [ModuleDirective_Provides]
readPrec :: ReadPrec ModuleDirective_Provides
$creadPrec :: ReadPrec ModuleDirective_Provides
readList :: ReadS [ModuleDirective_Provides]
$creadList :: ReadS [ModuleDirective_Provides]
readsPrec :: Int -> ReadS ModuleDirective_Provides
$creadsPrec :: Int -> ReadS ModuleDirective_Provides
Read, Int -> ModuleDirective_Provides -> String -> String
[ModuleDirective_Provides] -> String -> String
ModuleDirective_Provides -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ModuleDirective_Provides] -> String -> String
$cshowList :: [ModuleDirective_Provides] -> String -> String
show :: ModuleDirective_Provides -> String
$cshow :: ModuleDirective_Provides -> String
showsPrec :: Int -> ModuleDirective_Provides -> String -> String
$cshowsPrec :: Int -> ModuleDirective_Provides -> String -> String
Show)

_ModuleDirective_Provides :: Name
_ModuleDirective_Provides = (String -> Name
Core.Name String
"hydra/ext/java/syntax.ModuleDirective.Provides")

_ModuleDirective_Provides_to :: FieldName
_ModuleDirective_Provides_to = (String -> FieldName
Core.FieldName String
"to")

_ModuleDirective_Provides_with :: FieldName
_ModuleDirective_Provides_with = (String -> FieldName
Core.FieldName String
"with")

data RequiresModifier = 
  RequiresModifierTransitive  |
  RequiresModifierStatic 
  deriving (RequiresModifier -> RequiresModifier -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RequiresModifier -> RequiresModifier -> Bool
$c/= :: RequiresModifier -> RequiresModifier -> Bool
== :: RequiresModifier -> RequiresModifier -> Bool
$c== :: RequiresModifier -> RequiresModifier -> Bool
Eq, Eq RequiresModifier
RequiresModifier -> RequiresModifier -> Bool
RequiresModifier -> RequiresModifier -> Ordering
RequiresModifier -> RequiresModifier -> RequiresModifier
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: RequiresModifier -> RequiresModifier -> RequiresModifier
$cmin :: RequiresModifier -> RequiresModifier -> RequiresModifier
max :: RequiresModifier -> RequiresModifier -> RequiresModifier
$cmax :: RequiresModifier -> RequiresModifier -> RequiresModifier
>= :: RequiresModifier -> RequiresModifier -> Bool
$c>= :: RequiresModifier -> RequiresModifier -> Bool
> :: RequiresModifier -> RequiresModifier -> Bool
$c> :: RequiresModifier -> RequiresModifier -> Bool
<= :: RequiresModifier -> RequiresModifier -> Bool
$c<= :: RequiresModifier -> RequiresModifier -> Bool
< :: RequiresModifier -> RequiresModifier -> Bool
$c< :: RequiresModifier -> RequiresModifier -> Bool
compare :: RequiresModifier -> RequiresModifier -> Ordering
$ccompare :: RequiresModifier -> RequiresModifier -> Ordering
Ord, ReadPrec [RequiresModifier]
ReadPrec RequiresModifier
Int -> ReadS RequiresModifier
ReadS [RequiresModifier]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RequiresModifier]
$creadListPrec :: ReadPrec [RequiresModifier]
readPrec :: ReadPrec RequiresModifier
$creadPrec :: ReadPrec RequiresModifier
readList :: ReadS [RequiresModifier]
$creadList :: ReadS [RequiresModifier]
readsPrec :: Int -> ReadS RequiresModifier
$creadsPrec :: Int -> ReadS RequiresModifier
Read, Int -> RequiresModifier -> String -> String
[RequiresModifier] -> String -> String
RequiresModifier -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [RequiresModifier] -> String -> String
$cshowList :: [RequiresModifier] -> String -> String
show :: RequiresModifier -> String
$cshow :: RequiresModifier -> String
showsPrec :: Int -> RequiresModifier -> String -> String
$cshowsPrec :: Int -> RequiresModifier -> String -> String
Show)

_RequiresModifier :: Name
_RequiresModifier = (String -> Name
Core.Name String
"hydra/ext/java/syntax.RequiresModifier")

_RequiresModifier_transitive :: FieldName
_RequiresModifier_transitive = (String -> FieldName
Core.FieldName String
"transitive")

_RequiresModifier_static :: FieldName
_RequiresModifier_static = (String -> FieldName
Core.FieldName String
"static")

data ClassDeclaration = 
  ClassDeclarationNormal NormalClassDeclaration |
  ClassDeclarationEnum EnumDeclaration
  deriving (ClassDeclaration -> ClassDeclaration -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ClassDeclaration -> ClassDeclaration -> Bool
$c/= :: ClassDeclaration -> ClassDeclaration -> Bool
== :: ClassDeclaration -> ClassDeclaration -> Bool
$c== :: ClassDeclaration -> ClassDeclaration -> Bool
Eq, Eq ClassDeclaration
ClassDeclaration -> ClassDeclaration -> Bool
ClassDeclaration -> ClassDeclaration -> Ordering
ClassDeclaration -> ClassDeclaration -> ClassDeclaration
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ClassDeclaration -> ClassDeclaration -> ClassDeclaration
$cmin :: ClassDeclaration -> ClassDeclaration -> ClassDeclaration
max :: ClassDeclaration -> ClassDeclaration -> ClassDeclaration
$cmax :: ClassDeclaration -> ClassDeclaration -> ClassDeclaration
>= :: ClassDeclaration -> ClassDeclaration -> Bool
$c>= :: ClassDeclaration -> ClassDeclaration -> Bool
> :: ClassDeclaration -> ClassDeclaration -> Bool
$c> :: ClassDeclaration -> ClassDeclaration -> Bool
<= :: ClassDeclaration -> ClassDeclaration -> Bool
$c<= :: ClassDeclaration -> ClassDeclaration -> Bool
< :: ClassDeclaration -> ClassDeclaration -> Bool
$c< :: ClassDeclaration -> ClassDeclaration -> Bool
compare :: ClassDeclaration -> ClassDeclaration -> Ordering
$ccompare :: ClassDeclaration -> ClassDeclaration -> Ordering
Ord, ReadPrec [ClassDeclaration]
ReadPrec ClassDeclaration
Int -> ReadS ClassDeclaration
ReadS [ClassDeclaration]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ClassDeclaration]
$creadListPrec :: ReadPrec [ClassDeclaration]
readPrec :: ReadPrec ClassDeclaration
$creadPrec :: ReadPrec ClassDeclaration
readList :: ReadS [ClassDeclaration]
$creadList :: ReadS [ClassDeclaration]
readsPrec :: Int -> ReadS ClassDeclaration
$creadsPrec :: Int -> ReadS ClassDeclaration
Read, Int -> ClassDeclaration -> String -> String
[ClassDeclaration] -> String -> String
ClassDeclaration -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ClassDeclaration] -> String -> String
$cshowList :: [ClassDeclaration] -> String -> String
show :: ClassDeclaration -> String
$cshow :: ClassDeclaration -> String
showsPrec :: Int -> ClassDeclaration -> String -> String
$cshowsPrec :: Int -> ClassDeclaration -> String -> String
Show)

_ClassDeclaration :: Name
_ClassDeclaration = (String -> Name
Core.Name String
"hydra/ext/java/syntax.ClassDeclaration")

_ClassDeclaration_normal :: FieldName
_ClassDeclaration_normal = (String -> FieldName
Core.FieldName String
"normal")

_ClassDeclaration_enum :: FieldName
_ClassDeclaration_enum = (String -> FieldName
Core.FieldName String
"enum")

data NormalClassDeclaration = 
  NormalClassDeclaration {
    NormalClassDeclaration -> [ClassModifier]
normalClassDeclarationModifiers :: [ClassModifier],
    NormalClassDeclaration -> TypeIdentifier
normalClassDeclarationIdentifier :: TypeIdentifier,
    NormalClassDeclaration -> [TypeParameter]
normalClassDeclarationParameters :: [TypeParameter],
    NormalClassDeclaration -> Maybe ClassType
normalClassDeclarationExtends :: (Maybe ClassType),
    NormalClassDeclaration -> [InterfaceType]
normalClassDeclarationImplements :: [InterfaceType],
    NormalClassDeclaration -> ClassBody
normalClassDeclarationBody :: ClassBody}
  deriving (NormalClassDeclaration -> NormalClassDeclaration -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NormalClassDeclaration -> NormalClassDeclaration -> Bool
$c/= :: NormalClassDeclaration -> NormalClassDeclaration -> Bool
== :: NormalClassDeclaration -> NormalClassDeclaration -> Bool
$c== :: NormalClassDeclaration -> NormalClassDeclaration -> Bool
Eq, Eq NormalClassDeclaration
NormalClassDeclaration -> NormalClassDeclaration -> Bool
NormalClassDeclaration -> NormalClassDeclaration -> Ordering
NormalClassDeclaration
-> NormalClassDeclaration -> NormalClassDeclaration
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: NormalClassDeclaration
-> NormalClassDeclaration -> NormalClassDeclaration
$cmin :: NormalClassDeclaration
-> NormalClassDeclaration -> NormalClassDeclaration
max :: NormalClassDeclaration
-> NormalClassDeclaration -> NormalClassDeclaration
$cmax :: NormalClassDeclaration
-> NormalClassDeclaration -> NormalClassDeclaration
>= :: NormalClassDeclaration -> NormalClassDeclaration -> Bool
$c>= :: NormalClassDeclaration -> NormalClassDeclaration -> Bool
> :: NormalClassDeclaration -> NormalClassDeclaration -> Bool
$c> :: NormalClassDeclaration -> NormalClassDeclaration -> Bool
<= :: NormalClassDeclaration -> NormalClassDeclaration -> Bool
$c<= :: NormalClassDeclaration -> NormalClassDeclaration -> Bool
< :: NormalClassDeclaration -> NormalClassDeclaration -> Bool
$c< :: NormalClassDeclaration -> NormalClassDeclaration -> Bool
compare :: NormalClassDeclaration -> NormalClassDeclaration -> Ordering
$ccompare :: NormalClassDeclaration -> NormalClassDeclaration -> Ordering
Ord, ReadPrec [NormalClassDeclaration]
ReadPrec NormalClassDeclaration
Int -> ReadS NormalClassDeclaration
ReadS [NormalClassDeclaration]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [NormalClassDeclaration]
$creadListPrec :: ReadPrec [NormalClassDeclaration]
readPrec :: ReadPrec NormalClassDeclaration
$creadPrec :: ReadPrec NormalClassDeclaration
readList :: ReadS [NormalClassDeclaration]
$creadList :: ReadS [NormalClassDeclaration]
readsPrec :: Int -> ReadS NormalClassDeclaration
$creadsPrec :: Int -> ReadS NormalClassDeclaration
Read, Int -> NormalClassDeclaration -> String -> String
[NormalClassDeclaration] -> String -> String
NormalClassDeclaration -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [NormalClassDeclaration] -> String -> String
$cshowList :: [NormalClassDeclaration] -> String -> String
show :: NormalClassDeclaration -> String
$cshow :: NormalClassDeclaration -> String
showsPrec :: Int -> NormalClassDeclaration -> String -> String
$cshowsPrec :: Int -> NormalClassDeclaration -> String -> String
Show)

_NormalClassDeclaration :: Name
_NormalClassDeclaration = (String -> Name
Core.Name String
"hydra/ext/java/syntax.NormalClassDeclaration")

_NormalClassDeclaration_modifiers :: FieldName
_NormalClassDeclaration_modifiers = (String -> FieldName
Core.FieldName String
"modifiers")

_NormalClassDeclaration_identifier :: FieldName
_NormalClassDeclaration_identifier = (String -> FieldName
Core.FieldName String
"identifier")

_NormalClassDeclaration_parameters :: FieldName
_NormalClassDeclaration_parameters = (String -> FieldName
Core.FieldName String
"parameters")

_NormalClassDeclaration_extends :: FieldName
_NormalClassDeclaration_extends = (String -> FieldName
Core.FieldName String
"extends")

_NormalClassDeclaration_implements :: FieldName
_NormalClassDeclaration_implements = (String -> FieldName
Core.FieldName String
"implements")

_NormalClassDeclaration_body :: FieldName
_NormalClassDeclaration_body = (String -> FieldName
Core.FieldName String
"body")

data ClassModifier = 
  ClassModifierAnnotation Annotation |
  ClassModifierPublic  |
  ClassModifierProtected  |
  ClassModifierPrivate  |
  ClassModifierAbstract  |
  ClassModifierStatic  |
  ClassModifierFinal  |
  ClassModifierStrictfp 
  deriving (ClassModifier -> ClassModifier -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ClassModifier -> ClassModifier -> Bool
$c/= :: ClassModifier -> ClassModifier -> Bool
== :: ClassModifier -> ClassModifier -> Bool
$c== :: ClassModifier -> ClassModifier -> Bool
Eq, Eq ClassModifier
ClassModifier -> ClassModifier -> Bool
ClassModifier -> ClassModifier -> Ordering
ClassModifier -> ClassModifier -> ClassModifier
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ClassModifier -> ClassModifier -> ClassModifier
$cmin :: ClassModifier -> ClassModifier -> ClassModifier
max :: ClassModifier -> ClassModifier -> ClassModifier
$cmax :: ClassModifier -> ClassModifier -> ClassModifier
>= :: ClassModifier -> ClassModifier -> Bool
$c>= :: ClassModifier -> ClassModifier -> Bool
> :: ClassModifier -> ClassModifier -> Bool
$c> :: ClassModifier -> ClassModifier -> Bool
<= :: ClassModifier -> ClassModifier -> Bool
$c<= :: ClassModifier -> ClassModifier -> Bool
< :: ClassModifier -> ClassModifier -> Bool
$c< :: ClassModifier -> ClassModifier -> Bool
compare :: ClassModifier -> ClassModifier -> Ordering
$ccompare :: ClassModifier -> ClassModifier -> Ordering
Ord, ReadPrec [ClassModifier]
ReadPrec ClassModifier
Int -> ReadS ClassModifier
ReadS [ClassModifier]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ClassModifier]
$creadListPrec :: ReadPrec [ClassModifier]
readPrec :: ReadPrec ClassModifier
$creadPrec :: ReadPrec ClassModifier
readList :: ReadS [ClassModifier]
$creadList :: ReadS [ClassModifier]
readsPrec :: Int -> ReadS ClassModifier
$creadsPrec :: Int -> ReadS ClassModifier
Read, Int -> ClassModifier -> String -> String
[ClassModifier] -> String -> String
ClassModifier -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ClassModifier] -> String -> String
$cshowList :: [ClassModifier] -> String -> String
show :: ClassModifier -> String
$cshow :: ClassModifier -> String
showsPrec :: Int -> ClassModifier -> String -> String
$cshowsPrec :: Int -> ClassModifier -> String -> String
Show)

_ClassModifier :: Name
_ClassModifier = (String -> Name
Core.Name String
"hydra/ext/java/syntax.ClassModifier")

_ClassModifier_annotation :: FieldName
_ClassModifier_annotation = (String -> FieldName
Core.FieldName String
"annotation")

_ClassModifier_public :: FieldName
_ClassModifier_public = (String -> FieldName
Core.FieldName String
"public")

_ClassModifier_protected :: FieldName
_ClassModifier_protected = (String -> FieldName
Core.FieldName String
"protected")

_ClassModifier_private :: FieldName
_ClassModifier_private = (String -> FieldName
Core.FieldName String
"private")

_ClassModifier_abstract :: FieldName
_ClassModifier_abstract = (String -> FieldName
Core.FieldName String
"abstract")

_ClassModifier_static :: FieldName
_ClassModifier_static = (String -> FieldName
Core.FieldName String
"static")

_ClassModifier_final :: FieldName
_ClassModifier_final = (String -> FieldName
Core.FieldName String
"final")

_ClassModifier_strictfp :: FieldName
_ClassModifier_strictfp = (String -> FieldName
Core.FieldName String
"strictfp")

newtype ClassBody = 
  ClassBody {
    ClassBody -> [ClassBodyDeclarationWithComments]
unClassBody :: [ClassBodyDeclarationWithComments]}
  deriving (ClassBody -> ClassBody -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ClassBody -> ClassBody -> Bool
$c/= :: ClassBody -> ClassBody -> Bool
== :: ClassBody -> ClassBody -> Bool
$c== :: ClassBody -> ClassBody -> Bool
Eq, Eq ClassBody
ClassBody -> ClassBody -> Bool
ClassBody -> ClassBody -> Ordering
ClassBody -> ClassBody -> ClassBody
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ClassBody -> ClassBody -> ClassBody
$cmin :: ClassBody -> ClassBody -> ClassBody
max :: ClassBody -> ClassBody -> ClassBody
$cmax :: ClassBody -> ClassBody -> ClassBody
>= :: ClassBody -> ClassBody -> Bool
$c>= :: ClassBody -> ClassBody -> Bool
> :: ClassBody -> ClassBody -> Bool
$c> :: ClassBody -> ClassBody -> Bool
<= :: ClassBody -> ClassBody -> Bool
$c<= :: ClassBody -> ClassBody -> Bool
< :: ClassBody -> ClassBody -> Bool
$c< :: ClassBody -> ClassBody -> Bool
compare :: ClassBody -> ClassBody -> Ordering
$ccompare :: ClassBody -> ClassBody -> Ordering
Ord, ReadPrec [ClassBody]
ReadPrec ClassBody
Int -> ReadS ClassBody
ReadS [ClassBody]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ClassBody]
$creadListPrec :: ReadPrec [ClassBody]
readPrec :: ReadPrec ClassBody
$creadPrec :: ReadPrec ClassBody
readList :: ReadS [ClassBody]
$creadList :: ReadS [ClassBody]
readsPrec :: Int -> ReadS ClassBody
$creadsPrec :: Int -> ReadS ClassBody
Read, Int -> ClassBody -> String -> String
[ClassBody] -> String -> String
ClassBody -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ClassBody] -> String -> String
$cshowList :: [ClassBody] -> String -> String
show :: ClassBody -> String
$cshow :: ClassBody -> String
showsPrec :: Int -> ClassBody -> String -> String
$cshowsPrec :: Int -> ClassBody -> String -> String
Show)

_ClassBody :: Name
_ClassBody = (String -> Name
Core.Name String
"hydra/ext/java/syntax.ClassBody")

data ClassBodyDeclaration = 
  ClassBodyDeclarationClassMember ClassMemberDeclaration |
  ClassBodyDeclarationInstanceInitializer InstanceInitializer |
  ClassBodyDeclarationStaticInitializer StaticInitializer |
  ClassBodyDeclarationConstructorDeclaration ConstructorDeclaration
  deriving (ClassBodyDeclaration -> ClassBodyDeclaration -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ClassBodyDeclaration -> ClassBodyDeclaration -> Bool
$c/= :: ClassBodyDeclaration -> ClassBodyDeclaration -> Bool
== :: ClassBodyDeclaration -> ClassBodyDeclaration -> Bool
$c== :: ClassBodyDeclaration -> ClassBodyDeclaration -> Bool
Eq, Eq ClassBodyDeclaration
ClassBodyDeclaration -> ClassBodyDeclaration -> Bool
ClassBodyDeclaration -> ClassBodyDeclaration -> Ordering
ClassBodyDeclaration
-> ClassBodyDeclaration -> ClassBodyDeclaration
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ClassBodyDeclaration
-> ClassBodyDeclaration -> ClassBodyDeclaration
$cmin :: ClassBodyDeclaration
-> ClassBodyDeclaration -> ClassBodyDeclaration
max :: ClassBodyDeclaration
-> ClassBodyDeclaration -> ClassBodyDeclaration
$cmax :: ClassBodyDeclaration
-> ClassBodyDeclaration -> ClassBodyDeclaration
>= :: ClassBodyDeclaration -> ClassBodyDeclaration -> Bool
$c>= :: ClassBodyDeclaration -> ClassBodyDeclaration -> Bool
> :: ClassBodyDeclaration -> ClassBodyDeclaration -> Bool
$c> :: ClassBodyDeclaration -> ClassBodyDeclaration -> Bool
<= :: ClassBodyDeclaration -> ClassBodyDeclaration -> Bool
$c<= :: ClassBodyDeclaration -> ClassBodyDeclaration -> Bool
< :: ClassBodyDeclaration -> ClassBodyDeclaration -> Bool
$c< :: ClassBodyDeclaration -> ClassBodyDeclaration -> Bool
compare :: ClassBodyDeclaration -> ClassBodyDeclaration -> Ordering
$ccompare :: ClassBodyDeclaration -> ClassBodyDeclaration -> Ordering
Ord, ReadPrec [ClassBodyDeclaration]
ReadPrec ClassBodyDeclaration
Int -> ReadS ClassBodyDeclaration
ReadS [ClassBodyDeclaration]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ClassBodyDeclaration]
$creadListPrec :: ReadPrec [ClassBodyDeclaration]
readPrec :: ReadPrec ClassBodyDeclaration
$creadPrec :: ReadPrec ClassBodyDeclaration
readList :: ReadS [ClassBodyDeclaration]
$creadList :: ReadS [ClassBodyDeclaration]
readsPrec :: Int -> ReadS ClassBodyDeclaration
$creadsPrec :: Int -> ReadS ClassBodyDeclaration
Read, Int -> ClassBodyDeclaration -> String -> String
[ClassBodyDeclaration] -> String -> String
ClassBodyDeclaration -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ClassBodyDeclaration] -> String -> String
$cshowList :: [ClassBodyDeclaration] -> String -> String
show :: ClassBodyDeclaration -> String
$cshow :: ClassBodyDeclaration -> String
showsPrec :: Int -> ClassBodyDeclaration -> String -> String
$cshowsPrec :: Int -> ClassBodyDeclaration -> String -> String
Show)

_ClassBodyDeclaration :: Name
_ClassBodyDeclaration = (String -> Name
Core.Name String
"hydra/ext/java/syntax.ClassBodyDeclaration")

_ClassBodyDeclaration_classMember :: FieldName
_ClassBodyDeclaration_classMember = (String -> FieldName
Core.FieldName String
"classMember")

_ClassBodyDeclaration_instanceInitializer :: FieldName
_ClassBodyDeclaration_instanceInitializer = (String -> FieldName
Core.FieldName String
"instanceInitializer")

_ClassBodyDeclaration_staticInitializer :: FieldName
_ClassBodyDeclaration_staticInitializer = (String -> FieldName
Core.FieldName String
"staticInitializer")

_ClassBodyDeclaration_constructorDeclaration :: FieldName
_ClassBodyDeclaration_constructorDeclaration = (String -> FieldName
Core.FieldName String
"constructorDeclaration")

data ClassBodyDeclarationWithComments = 
  ClassBodyDeclarationWithComments {
    ClassBodyDeclarationWithComments -> ClassBodyDeclaration
classBodyDeclarationWithCommentsValue :: ClassBodyDeclaration,
    ClassBodyDeclarationWithComments -> Maybe String
classBodyDeclarationWithCommentsComments :: (Maybe String)}
  deriving (ClassBodyDeclarationWithComments
-> ClassBodyDeclarationWithComments -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ClassBodyDeclarationWithComments
-> ClassBodyDeclarationWithComments -> Bool
$c/= :: ClassBodyDeclarationWithComments
-> ClassBodyDeclarationWithComments -> Bool
== :: ClassBodyDeclarationWithComments
-> ClassBodyDeclarationWithComments -> Bool
$c== :: ClassBodyDeclarationWithComments
-> ClassBodyDeclarationWithComments -> Bool
Eq, Eq ClassBodyDeclarationWithComments
ClassBodyDeclarationWithComments
-> ClassBodyDeclarationWithComments -> Bool
ClassBodyDeclarationWithComments
-> ClassBodyDeclarationWithComments -> Ordering
ClassBodyDeclarationWithComments
-> ClassBodyDeclarationWithComments
-> ClassBodyDeclarationWithComments
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ClassBodyDeclarationWithComments
-> ClassBodyDeclarationWithComments
-> ClassBodyDeclarationWithComments
$cmin :: ClassBodyDeclarationWithComments
-> ClassBodyDeclarationWithComments
-> ClassBodyDeclarationWithComments
max :: ClassBodyDeclarationWithComments
-> ClassBodyDeclarationWithComments
-> ClassBodyDeclarationWithComments
$cmax :: ClassBodyDeclarationWithComments
-> ClassBodyDeclarationWithComments
-> ClassBodyDeclarationWithComments
>= :: ClassBodyDeclarationWithComments
-> ClassBodyDeclarationWithComments -> Bool
$c>= :: ClassBodyDeclarationWithComments
-> ClassBodyDeclarationWithComments -> Bool
> :: ClassBodyDeclarationWithComments
-> ClassBodyDeclarationWithComments -> Bool
$c> :: ClassBodyDeclarationWithComments
-> ClassBodyDeclarationWithComments -> Bool
<= :: ClassBodyDeclarationWithComments
-> ClassBodyDeclarationWithComments -> Bool
$c<= :: ClassBodyDeclarationWithComments
-> ClassBodyDeclarationWithComments -> Bool
< :: ClassBodyDeclarationWithComments
-> ClassBodyDeclarationWithComments -> Bool
$c< :: ClassBodyDeclarationWithComments
-> ClassBodyDeclarationWithComments -> Bool
compare :: ClassBodyDeclarationWithComments
-> ClassBodyDeclarationWithComments -> Ordering
$ccompare :: ClassBodyDeclarationWithComments
-> ClassBodyDeclarationWithComments -> Ordering
Ord, ReadPrec [ClassBodyDeclarationWithComments]
ReadPrec ClassBodyDeclarationWithComments
Int -> ReadS ClassBodyDeclarationWithComments
ReadS [ClassBodyDeclarationWithComments]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ClassBodyDeclarationWithComments]
$creadListPrec :: ReadPrec [ClassBodyDeclarationWithComments]
readPrec :: ReadPrec ClassBodyDeclarationWithComments
$creadPrec :: ReadPrec ClassBodyDeclarationWithComments
readList :: ReadS [ClassBodyDeclarationWithComments]
$creadList :: ReadS [ClassBodyDeclarationWithComments]
readsPrec :: Int -> ReadS ClassBodyDeclarationWithComments
$creadsPrec :: Int -> ReadS ClassBodyDeclarationWithComments
Read, Int -> ClassBodyDeclarationWithComments -> String -> String
[ClassBodyDeclarationWithComments] -> String -> String
ClassBodyDeclarationWithComments -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ClassBodyDeclarationWithComments] -> String -> String
$cshowList :: [ClassBodyDeclarationWithComments] -> String -> String
show :: ClassBodyDeclarationWithComments -> String
$cshow :: ClassBodyDeclarationWithComments -> String
showsPrec :: Int -> ClassBodyDeclarationWithComments -> String -> String
$cshowsPrec :: Int -> ClassBodyDeclarationWithComments -> String -> String
Show)

_ClassBodyDeclarationWithComments :: Name
_ClassBodyDeclarationWithComments = (String -> Name
Core.Name String
"hydra/ext/java/syntax.ClassBodyDeclarationWithComments")

_ClassBodyDeclarationWithComments_value :: FieldName
_ClassBodyDeclarationWithComments_value = (String -> FieldName
Core.FieldName String
"value")

_ClassBodyDeclarationWithComments_comments :: FieldName
_ClassBodyDeclarationWithComments_comments = (String -> FieldName
Core.FieldName String
"comments")

data ClassMemberDeclaration = 
  ClassMemberDeclarationField FieldDeclaration |
  ClassMemberDeclarationMethod MethodDeclaration |
  ClassMemberDeclarationClass ClassDeclaration |
  ClassMemberDeclarationInterface InterfaceDeclaration |
  ClassMemberDeclarationNone 
  deriving (ClassMemberDeclaration -> ClassMemberDeclaration -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ClassMemberDeclaration -> ClassMemberDeclaration -> Bool
$c/= :: ClassMemberDeclaration -> ClassMemberDeclaration -> Bool
== :: ClassMemberDeclaration -> ClassMemberDeclaration -> Bool
$c== :: ClassMemberDeclaration -> ClassMemberDeclaration -> Bool
Eq, Eq ClassMemberDeclaration
ClassMemberDeclaration -> ClassMemberDeclaration -> Bool
ClassMemberDeclaration -> ClassMemberDeclaration -> Ordering
ClassMemberDeclaration
-> ClassMemberDeclaration -> ClassMemberDeclaration
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ClassMemberDeclaration
-> ClassMemberDeclaration -> ClassMemberDeclaration
$cmin :: ClassMemberDeclaration
-> ClassMemberDeclaration -> ClassMemberDeclaration
max :: ClassMemberDeclaration
-> ClassMemberDeclaration -> ClassMemberDeclaration
$cmax :: ClassMemberDeclaration
-> ClassMemberDeclaration -> ClassMemberDeclaration
>= :: ClassMemberDeclaration -> ClassMemberDeclaration -> Bool
$c>= :: ClassMemberDeclaration -> ClassMemberDeclaration -> Bool
> :: ClassMemberDeclaration -> ClassMemberDeclaration -> Bool
$c> :: ClassMemberDeclaration -> ClassMemberDeclaration -> Bool
<= :: ClassMemberDeclaration -> ClassMemberDeclaration -> Bool
$c<= :: ClassMemberDeclaration -> ClassMemberDeclaration -> Bool
< :: ClassMemberDeclaration -> ClassMemberDeclaration -> Bool
$c< :: ClassMemberDeclaration -> ClassMemberDeclaration -> Bool
compare :: ClassMemberDeclaration -> ClassMemberDeclaration -> Ordering
$ccompare :: ClassMemberDeclaration -> ClassMemberDeclaration -> Ordering
Ord, ReadPrec [ClassMemberDeclaration]
ReadPrec ClassMemberDeclaration
Int -> ReadS ClassMemberDeclaration
ReadS [ClassMemberDeclaration]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ClassMemberDeclaration]
$creadListPrec :: ReadPrec [ClassMemberDeclaration]
readPrec :: ReadPrec ClassMemberDeclaration
$creadPrec :: ReadPrec ClassMemberDeclaration
readList :: ReadS [ClassMemberDeclaration]
$creadList :: ReadS [ClassMemberDeclaration]
readsPrec :: Int -> ReadS ClassMemberDeclaration
$creadsPrec :: Int -> ReadS ClassMemberDeclaration
Read, Int -> ClassMemberDeclaration -> String -> String
[ClassMemberDeclaration] -> String -> String
ClassMemberDeclaration -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ClassMemberDeclaration] -> String -> String
$cshowList :: [ClassMemberDeclaration] -> String -> String
show :: ClassMemberDeclaration -> String
$cshow :: ClassMemberDeclaration -> String
showsPrec :: Int -> ClassMemberDeclaration -> String -> String
$cshowsPrec :: Int -> ClassMemberDeclaration -> String -> String
Show)

_ClassMemberDeclaration :: Name
_ClassMemberDeclaration = (String -> Name
Core.Name String
"hydra/ext/java/syntax.ClassMemberDeclaration")

_ClassMemberDeclaration_field :: FieldName
_ClassMemberDeclaration_field = (String -> FieldName
Core.FieldName String
"field")

_ClassMemberDeclaration_method :: FieldName
_ClassMemberDeclaration_method = (String -> FieldName
Core.FieldName String
"method")

_ClassMemberDeclaration_class :: FieldName
_ClassMemberDeclaration_class = (String -> FieldName
Core.FieldName String
"class")

_ClassMemberDeclaration_interface :: FieldName
_ClassMemberDeclaration_interface = (String -> FieldName
Core.FieldName String
"interface")

_ClassMemberDeclaration_none :: FieldName
_ClassMemberDeclaration_none = (String -> FieldName
Core.FieldName String
"none")

data FieldDeclaration = 
  FieldDeclaration {
    FieldDeclaration -> [FieldModifier]
fieldDeclarationModifiers :: [FieldModifier],
    FieldDeclaration -> UnannType
fieldDeclarationUnannType :: UnannType,
    FieldDeclaration -> [VariableDeclarator]
fieldDeclarationVariableDeclarators :: [VariableDeclarator]}
  deriving (FieldDeclaration -> FieldDeclaration -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FieldDeclaration -> FieldDeclaration -> Bool
$c/= :: FieldDeclaration -> FieldDeclaration -> Bool
== :: FieldDeclaration -> FieldDeclaration -> Bool
$c== :: FieldDeclaration -> FieldDeclaration -> Bool
Eq, Eq FieldDeclaration
FieldDeclaration -> FieldDeclaration -> Bool
FieldDeclaration -> FieldDeclaration -> Ordering
FieldDeclaration -> FieldDeclaration -> FieldDeclaration
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: FieldDeclaration -> FieldDeclaration -> FieldDeclaration
$cmin :: FieldDeclaration -> FieldDeclaration -> FieldDeclaration
max :: FieldDeclaration -> FieldDeclaration -> FieldDeclaration
$cmax :: FieldDeclaration -> FieldDeclaration -> FieldDeclaration
>= :: FieldDeclaration -> FieldDeclaration -> Bool
$c>= :: FieldDeclaration -> FieldDeclaration -> Bool
> :: FieldDeclaration -> FieldDeclaration -> Bool
$c> :: FieldDeclaration -> FieldDeclaration -> Bool
<= :: FieldDeclaration -> FieldDeclaration -> Bool
$c<= :: FieldDeclaration -> FieldDeclaration -> Bool
< :: FieldDeclaration -> FieldDeclaration -> Bool
$c< :: FieldDeclaration -> FieldDeclaration -> Bool
compare :: FieldDeclaration -> FieldDeclaration -> Ordering
$ccompare :: FieldDeclaration -> FieldDeclaration -> Ordering
Ord, ReadPrec [FieldDeclaration]
ReadPrec FieldDeclaration
Int -> ReadS FieldDeclaration
ReadS [FieldDeclaration]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [FieldDeclaration]
$creadListPrec :: ReadPrec [FieldDeclaration]
readPrec :: ReadPrec FieldDeclaration
$creadPrec :: ReadPrec FieldDeclaration
readList :: ReadS [FieldDeclaration]
$creadList :: ReadS [FieldDeclaration]
readsPrec :: Int -> ReadS FieldDeclaration
$creadsPrec :: Int -> ReadS FieldDeclaration
Read, Int -> FieldDeclaration -> String -> String
[FieldDeclaration] -> String -> String
FieldDeclaration -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [FieldDeclaration] -> String -> String
$cshowList :: [FieldDeclaration] -> String -> String
show :: FieldDeclaration -> String
$cshow :: FieldDeclaration -> String
showsPrec :: Int -> FieldDeclaration -> String -> String
$cshowsPrec :: Int -> FieldDeclaration -> String -> String
Show)

_FieldDeclaration :: Name
_FieldDeclaration = (String -> Name
Core.Name String
"hydra/ext/java/syntax.FieldDeclaration")

_FieldDeclaration_modifiers :: FieldName
_FieldDeclaration_modifiers = (String -> FieldName
Core.FieldName String
"modifiers")

_FieldDeclaration_unannType :: FieldName
_FieldDeclaration_unannType = (String -> FieldName
Core.FieldName String
"unannType")

_FieldDeclaration_variableDeclarators :: FieldName
_FieldDeclaration_variableDeclarators = (String -> FieldName
Core.FieldName String
"variableDeclarators")

data FieldModifier = 
  FieldModifierAnnotation Annotation |
  FieldModifierPublic  |
  FieldModifierProtected  |
  FieldModifierPrivate  |
  FieldModifierStatic  |
  FieldModifierFinal  |
  FieldModifierTransient  |
  FieldModifierVolatile 
  deriving (FieldModifier -> FieldModifier -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FieldModifier -> FieldModifier -> Bool
$c/= :: FieldModifier -> FieldModifier -> Bool
== :: FieldModifier -> FieldModifier -> Bool
$c== :: FieldModifier -> FieldModifier -> Bool
Eq, Eq FieldModifier
FieldModifier -> FieldModifier -> Bool
FieldModifier -> FieldModifier -> Ordering
FieldModifier -> FieldModifier -> FieldModifier
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: FieldModifier -> FieldModifier -> FieldModifier
$cmin :: FieldModifier -> FieldModifier -> FieldModifier
max :: FieldModifier -> FieldModifier -> FieldModifier
$cmax :: FieldModifier -> FieldModifier -> FieldModifier
>= :: FieldModifier -> FieldModifier -> Bool
$c>= :: FieldModifier -> FieldModifier -> Bool
> :: FieldModifier -> FieldModifier -> Bool
$c> :: FieldModifier -> FieldModifier -> Bool
<= :: FieldModifier -> FieldModifier -> Bool
$c<= :: FieldModifier -> FieldModifier -> Bool
< :: FieldModifier -> FieldModifier -> Bool
$c< :: FieldModifier -> FieldModifier -> Bool
compare :: FieldModifier -> FieldModifier -> Ordering
$ccompare :: FieldModifier -> FieldModifier -> Ordering
Ord, ReadPrec [FieldModifier]
ReadPrec FieldModifier
Int -> ReadS FieldModifier
ReadS [FieldModifier]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [FieldModifier]
$creadListPrec :: ReadPrec [FieldModifier]
readPrec :: ReadPrec FieldModifier
$creadPrec :: ReadPrec FieldModifier
readList :: ReadS [FieldModifier]
$creadList :: ReadS [FieldModifier]
readsPrec :: Int -> ReadS FieldModifier
$creadsPrec :: Int -> ReadS FieldModifier
Read, Int -> FieldModifier -> String -> String
[FieldModifier] -> String -> String
FieldModifier -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [FieldModifier] -> String -> String
$cshowList :: [FieldModifier] -> String -> String
show :: FieldModifier -> String
$cshow :: FieldModifier -> String
showsPrec :: Int -> FieldModifier -> String -> String
$cshowsPrec :: Int -> FieldModifier -> String -> String
Show)

_FieldModifier :: Name
_FieldModifier = (String -> Name
Core.Name String
"hydra/ext/java/syntax.FieldModifier")

_FieldModifier_annotation :: FieldName
_FieldModifier_annotation = (String -> FieldName
Core.FieldName String
"annotation")

_FieldModifier_public :: FieldName
_FieldModifier_public = (String -> FieldName
Core.FieldName String
"public")

_FieldModifier_protected :: FieldName
_FieldModifier_protected = (String -> FieldName
Core.FieldName String
"protected")

_FieldModifier_private :: FieldName
_FieldModifier_private = (String -> FieldName
Core.FieldName String
"private")

_FieldModifier_static :: FieldName
_FieldModifier_static = (String -> FieldName
Core.FieldName String
"static")

_FieldModifier_final :: FieldName
_FieldModifier_final = (String -> FieldName
Core.FieldName String
"final")

_FieldModifier_transient :: FieldName
_FieldModifier_transient = (String -> FieldName
Core.FieldName String
"transient")

_FieldModifier_volatile :: FieldName
_FieldModifier_volatile = (String -> FieldName
Core.FieldName String
"volatile")

data VariableDeclarator = 
  VariableDeclarator {
    VariableDeclarator -> VariableDeclaratorId
variableDeclaratorId :: VariableDeclaratorId,
    VariableDeclarator -> Maybe VariableInitializer
variableDeclaratorInitializer :: (Maybe VariableInitializer)}
  deriving (VariableDeclarator -> VariableDeclarator -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VariableDeclarator -> VariableDeclarator -> Bool
$c/= :: VariableDeclarator -> VariableDeclarator -> Bool
== :: VariableDeclarator -> VariableDeclarator -> Bool
$c== :: VariableDeclarator -> VariableDeclarator -> Bool
Eq, Eq VariableDeclarator
VariableDeclarator -> VariableDeclarator -> Bool
VariableDeclarator -> VariableDeclarator -> Ordering
VariableDeclarator -> VariableDeclarator -> VariableDeclarator
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: VariableDeclarator -> VariableDeclarator -> VariableDeclarator
$cmin :: VariableDeclarator -> VariableDeclarator -> VariableDeclarator
max :: VariableDeclarator -> VariableDeclarator -> VariableDeclarator
$cmax :: VariableDeclarator -> VariableDeclarator -> VariableDeclarator
>= :: VariableDeclarator -> VariableDeclarator -> Bool
$c>= :: VariableDeclarator -> VariableDeclarator -> Bool
> :: VariableDeclarator -> VariableDeclarator -> Bool
$c> :: VariableDeclarator -> VariableDeclarator -> Bool
<= :: VariableDeclarator -> VariableDeclarator -> Bool
$c<= :: VariableDeclarator -> VariableDeclarator -> Bool
< :: VariableDeclarator -> VariableDeclarator -> Bool
$c< :: VariableDeclarator -> VariableDeclarator -> Bool
compare :: VariableDeclarator -> VariableDeclarator -> Ordering
$ccompare :: VariableDeclarator -> VariableDeclarator -> Ordering
Ord, ReadPrec [VariableDeclarator]
ReadPrec VariableDeclarator
Int -> ReadS VariableDeclarator
ReadS [VariableDeclarator]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [VariableDeclarator]
$creadListPrec :: ReadPrec [VariableDeclarator]
readPrec :: ReadPrec VariableDeclarator
$creadPrec :: ReadPrec VariableDeclarator
readList :: ReadS [VariableDeclarator]
$creadList :: ReadS [VariableDeclarator]
readsPrec :: Int -> ReadS VariableDeclarator
$creadsPrec :: Int -> ReadS VariableDeclarator
Read, Int -> VariableDeclarator -> String -> String
[VariableDeclarator] -> String -> String
VariableDeclarator -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [VariableDeclarator] -> String -> String
$cshowList :: [VariableDeclarator] -> String -> String
show :: VariableDeclarator -> String
$cshow :: VariableDeclarator -> String
showsPrec :: Int -> VariableDeclarator -> String -> String
$cshowsPrec :: Int -> VariableDeclarator -> String -> String
Show)

_VariableDeclarator :: Name
_VariableDeclarator = (String -> Name
Core.Name String
"hydra/ext/java/syntax.VariableDeclarator")

_VariableDeclarator_id :: FieldName
_VariableDeclarator_id = (String -> FieldName
Core.FieldName String
"id")

_VariableDeclarator_initializer :: FieldName
_VariableDeclarator_initializer = (String -> FieldName
Core.FieldName String
"initializer")

data VariableDeclaratorId = 
  VariableDeclaratorId {
    VariableDeclaratorId -> Identifier
variableDeclaratorIdIdentifier :: Identifier,
    VariableDeclaratorId -> Maybe Dims
variableDeclaratorIdDims :: (Maybe Dims)}
  deriving (VariableDeclaratorId -> VariableDeclaratorId -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VariableDeclaratorId -> VariableDeclaratorId -> Bool
$c/= :: VariableDeclaratorId -> VariableDeclaratorId -> Bool
== :: VariableDeclaratorId -> VariableDeclaratorId -> Bool
$c== :: VariableDeclaratorId -> VariableDeclaratorId -> Bool
Eq, Eq VariableDeclaratorId
VariableDeclaratorId -> VariableDeclaratorId -> Bool
VariableDeclaratorId -> VariableDeclaratorId -> Ordering
VariableDeclaratorId
-> VariableDeclaratorId -> VariableDeclaratorId
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: VariableDeclaratorId
-> VariableDeclaratorId -> VariableDeclaratorId
$cmin :: VariableDeclaratorId
-> VariableDeclaratorId -> VariableDeclaratorId
max :: VariableDeclaratorId
-> VariableDeclaratorId -> VariableDeclaratorId
$cmax :: VariableDeclaratorId
-> VariableDeclaratorId -> VariableDeclaratorId
>= :: VariableDeclaratorId -> VariableDeclaratorId -> Bool
$c>= :: VariableDeclaratorId -> VariableDeclaratorId -> Bool
> :: VariableDeclaratorId -> VariableDeclaratorId -> Bool
$c> :: VariableDeclaratorId -> VariableDeclaratorId -> Bool
<= :: VariableDeclaratorId -> VariableDeclaratorId -> Bool
$c<= :: VariableDeclaratorId -> VariableDeclaratorId -> Bool
< :: VariableDeclaratorId -> VariableDeclaratorId -> Bool
$c< :: VariableDeclaratorId -> VariableDeclaratorId -> Bool
compare :: VariableDeclaratorId -> VariableDeclaratorId -> Ordering
$ccompare :: VariableDeclaratorId -> VariableDeclaratorId -> Ordering
Ord, ReadPrec [VariableDeclaratorId]
ReadPrec VariableDeclaratorId
Int -> ReadS VariableDeclaratorId
ReadS [VariableDeclaratorId]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [VariableDeclaratorId]
$creadListPrec :: ReadPrec [VariableDeclaratorId]
readPrec :: ReadPrec VariableDeclaratorId
$creadPrec :: ReadPrec VariableDeclaratorId
readList :: ReadS [VariableDeclaratorId]
$creadList :: ReadS [VariableDeclaratorId]
readsPrec :: Int -> ReadS VariableDeclaratorId
$creadsPrec :: Int -> ReadS VariableDeclaratorId
Read, Int -> VariableDeclaratorId -> String -> String
[VariableDeclaratorId] -> String -> String
VariableDeclaratorId -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [VariableDeclaratorId] -> String -> String
$cshowList :: [VariableDeclaratorId] -> String -> String
show :: VariableDeclaratorId -> String
$cshow :: VariableDeclaratorId -> String
showsPrec :: Int -> VariableDeclaratorId -> String -> String
$cshowsPrec :: Int -> VariableDeclaratorId -> String -> String
Show)

_VariableDeclaratorId :: Name
_VariableDeclaratorId = (String -> Name
Core.Name String
"hydra/ext/java/syntax.VariableDeclaratorId")

_VariableDeclaratorId_identifier :: FieldName
_VariableDeclaratorId_identifier = (String -> FieldName
Core.FieldName String
"identifier")

_VariableDeclaratorId_dims :: FieldName
_VariableDeclaratorId_dims = (String -> FieldName
Core.FieldName String
"dims")

data VariableInitializer = 
  VariableInitializerExpression Expression |
  VariableInitializerArrayInitializer ArrayInitializer
  deriving (VariableInitializer -> VariableInitializer -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VariableInitializer -> VariableInitializer -> Bool
$c/= :: VariableInitializer -> VariableInitializer -> Bool
== :: VariableInitializer -> VariableInitializer -> Bool
$c== :: VariableInitializer -> VariableInitializer -> Bool
Eq, Eq VariableInitializer
VariableInitializer -> VariableInitializer -> Bool
VariableInitializer -> VariableInitializer -> Ordering
VariableInitializer -> VariableInitializer -> VariableInitializer
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: VariableInitializer -> VariableInitializer -> VariableInitializer
$cmin :: VariableInitializer -> VariableInitializer -> VariableInitializer
max :: VariableInitializer -> VariableInitializer -> VariableInitializer
$cmax :: VariableInitializer -> VariableInitializer -> VariableInitializer
>= :: VariableInitializer -> VariableInitializer -> Bool
$c>= :: VariableInitializer -> VariableInitializer -> Bool
> :: VariableInitializer -> VariableInitializer -> Bool
$c> :: VariableInitializer -> VariableInitializer -> Bool
<= :: VariableInitializer -> VariableInitializer -> Bool
$c<= :: VariableInitializer -> VariableInitializer -> Bool
< :: VariableInitializer -> VariableInitializer -> Bool
$c< :: VariableInitializer -> VariableInitializer -> Bool
compare :: VariableInitializer -> VariableInitializer -> Ordering
$ccompare :: VariableInitializer -> VariableInitializer -> Ordering
Ord, ReadPrec [VariableInitializer]
ReadPrec VariableInitializer
Int -> ReadS VariableInitializer
ReadS [VariableInitializer]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [VariableInitializer]
$creadListPrec :: ReadPrec [VariableInitializer]
readPrec :: ReadPrec VariableInitializer
$creadPrec :: ReadPrec VariableInitializer
readList :: ReadS [VariableInitializer]
$creadList :: ReadS [VariableInitializer]
readsPrec :: Int -> ReadS VariableInitializer
$creadsPrec :: Int -> ReadS VariableInitializer
Read, Int -> VariableInitializer -> String -> String
[VariableInitializer] -> String -> String
VariableInitializer -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [VariableInitializer] -> String -> String
$cshowList :: [VariableInitializer] -> String -> String
show :: VariableInitializer -> String
$cshow :: VariableInitializer -> String
showsPrec :: Int -> VariableInitializer -> String -> String
$cshowsPrec :: Int -> VariableInitializer -> String -> String
Show)

_VariableInitializer :: Name
_VariableInitializer = (String -> Name
Core.Name String
"hydra/ext/java/syntax.VariableInitializer")

_VariableInitializer_expression :: FieldName
_VariableInitializer_expression = (String -> FieldName
Core.FieldName String
"expression")

_VariableInitializer_arrayInitializer :: FieldName
_VariableInitializer_arrayInitializer = (String -> FieldName
Core.FieldName String
"arrayInitializer")

-- | A Type which does not allow annotations
newtype UnannType = 
  UnannType {
    -- | A Type which does not allow annotations
    UnannType -> Type
unUnannType :: Type}
  deriving (UnannType -> UnannType -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UnannType -> UnannType -> Bool
$c/= :: UnannType -> UnannType -> Bool
== :: UnannType -> UnannType -> Bool
$c== :: UnannType -> UnannType -> Bool
Eq, Eq UnannType
UnannType -> UnannType -> Bool
UnannType -> UnannType -> Ordering
UnannType -> UnannType -> UnannType
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: UnannType -> UnannType -> UnannType
$cmin :: UnannType -> UnannType -> UnannType
max :: UnannType -> UnannType -> UnannType
$cmax :: UnannType -> UnannType -> UnannType
>= :: UnannType -> UnannType -> Bool
$c>= :: UnannType -> UnannType -> Bool
> :: UnannType -> UnannType -> Bool
$c> :: UnannType -> UnannType -> Bool
<= :: UnannType -> UnannType -> Bool
$c<= :: UnannType -> UnannType -> Bool
< :: UnannType -> UnannType -> Bool
$c< :: UnannType -> UnannType -> Bool
compare :: UnannType -> UnannType -> Ordering
$ccompare :: UnannType -> UnannType -> Ordering
Ord, ReadPrec [UnannType]
ReadPrec UnannType
Int -> ReadS UnannType
ReadS [UnannType]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UnannType]
$creadListPrec :: ReadPrec [UnannType]
readPrec :: ReadPrec UnannType
$creadPrec :: ReadPrec UnannType
readList :: ReadS [UnannType]
$creadList :: ReadS [UnannType]
readsPrec :: Int -> ReadS UnannType
$creadsPrec :: Int -> ReadS UnannType
Read, Int -> UnannType -> String -> String
[UnannType] -> String -> String
UnannType -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [UnannType] -> String -> String
$cshowList :: [UnannType] -> String -> String
show :: UnannType -> String
$cshow :: UnannType -> String
showsPrec :: Int -> UnannType -> String -> String
$cshowsPrec :: Int -> UnannType -> String -> String
Show)

_UnannType :: Name
_UnannType = (String -> Name
Core.Name String
"hydra/ext/java/syntax.UnannType")

-- | A ClassType which does not allow annotations
newtype UnannClassType = 
  UnannClassType {
    -- | A ClassType which does not allow annotations
    UnannClassType -> ClassType
unUnannClassType :: ClassType}
  deriving (UnannClassType -> UnannClassType -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UnannClassType -> UnannClassType -> Bool
$c/= :: UnannClassType -> UnannClassType -> Bool
== :: UnannClassType -> UnannClassType -> Bool
$c== :: UnannClassType -> UnannClassType -> Bool
Eq, Eq UnannClassType
UnannClassType -> UnannClassType -> Bool
UnannClassType -> UnannClassType -> Ordering
UnannClassType -> UnannClassType -> UnannClassType
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: UnannClassType -> UnannClassType -> UnannClassType
$cmin :: UnannClassType -> UnannClassType -> UnannClassType
max :: UnannClassType -> UnannClassType -> UnannClassType
$cmax :: UnannClassType -> UnannClassType -> UnannClassType
>= :: UnannClassType -> UnannClassType -> Bool
$c>= :: UnannClassType -> UnannClassType -> Bool
> :: UnannClassType -> UnannClassType -> Bool
$c> :: UnannClassType -> UnannClassType -> Bool
<= :: UnannClassType -> UnannClassType -> Bool
$c<= :: UnannClassType -> UnannClassType -> Bool
< :: UnannClassType -> UnannClassType -> Bool
$c< :: UnannClassType -> UnannClassType -> Bool
compare :: UnannClassType -> UnannClassType -> Ordering
$ccompare :: UnannClassType -> UnannClassType -> Ordering
Ord, ReadPrec [UnannClassType]
ReadPrec UnannClassType
Int -> ReadS UnannClassType
ReadS [UnannClassType]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UnannClassType]
$creadListPrec :: ReadPrec [UnannClassType]
readPrec :: ReadPrec UnannClassType
$creadPrec :: ReadPrec UnannClassType
readList :: ReadS [UnannClassType]
$creadList :: ReadS [UnannClassType]
readsPrec :: Int -> ReadS UnannClassType
$creadsPrec :: Int -> ReadS UnannClassType
Read, Int -> UnannClassType -> String -> String
[UnannClassType] -> String -> String
UnannClassType -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [UnannClassType] -> String -> String
$cshowList :: [UnannClassType] -> String -> String
show :: UnannClassType -> String
$cshow :: UnannClassType -> String
showsPrec :: Int -> UnannClassType -> String -> String
$cshowsPrec :: Int -> UnannClassType -> String -> String
Show)

_UnannClassType :: Name
_UnannClassType = (String -> Name
Core.Name String
"hydra/ext/java/syntax.UnannClassType")

data MethodDeclaration = 
  MethodDeclaration {
    -- | Note: simple methods cannot have annotations
    MethodDeclaration -> [Annotation]
methodDeclarationAnnotations :: [Annotation],
    MethodDeclaration -> [MethodModifier]
methodDeclarationModifiers :: [MethodModifier],
    MethodDeclaration -> MethodHeader
methodDeclarationHeader :: MethodHeader,
    MethodDeclaration -> MethodBody
methodDeclarationBody :: MethodBody}
  deriving (MethodDeclaration -> MethodDeclaration -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MethodDeclaration -> MethodDeclaration -> Bool
$c/= :: MethodDeclaration -> MethodDeclaration -> Bool
== :: MethodDeclaration -> MethodDeclaration -> Bool
$c== :: MethodDeclaration -> MethodDeclaration -> Bool
Eq, Eq MethodDeclaration
MethodDeclaration -> MethodDeclaration -> Bool
MethodDeclaration -> MethodDeclaration -> Ordering
MethodDeclaration -> MethodDeclaration -> MethodDeclaration
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: MethodDeclaration -> MethodDeclaration -> MethodDeclaration
$cmin :: MethodDeclaration -> MethodDeclaration -> MethodDeclaration
max :: MethodDeclaration -> MethodDeclaration -> MethodDeclaration
$cmax :: MethodDeclaration -> MethodDeclaration -> MethodDeclaration
>= :: MethodDeclaration -> MethodDeclaration -> Bool
$c>= :: MethodDeclaration -> MethodDeclaration -> Bool
> :: MethodDeclaration -> MethodDeclaration -> Bool
$c> :: MethodDeclaration -> MethodDeclaration -> Bool
<= :: MethodDeclaration -> MethodDeclaration -> Bool
$c<= :: MethodDeclaration -> MethodDeclaration -> Bool
< :: MethodDeclaration -> MethodDeclaration -> Bool
$c< :: MethodDeclaration -> MethodDeclaration -> Bool
compare :: MethodDeclaration -> MethodDeclaration -> Ordering
$ccompare :: MethodDeclaration -> MethodDeclaration -> Ordering
Ord, ReadPrec [MethodDeclaration]
ReadPrec MethodDeclaration
Int -> ReadS MethodDeclaration
ReadS [MethodDeclaration]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [MethodDeclaration]
$creadListPrec :: ReadPrec [MethodDeclaration]
readPrec :: ReadPrec MethodDeclaration
$creadPrec :: ReadPrec MethodDeclaration
readList :: ReadS [MethodDeclaration]
$creadList :: ReadS [MethodDeclaration]
readsPrec :: Int -> ReadS MethodDeclaration
$creadsPrec :: Int -> ReadS MethodDeclaration
Read, Int -> MethodDeclaration -> String -> String
[MethodDeclaration] -> String -> String
MethodDeclaration -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [MethodDeclaration] -> String -> String
$cshowList :: [MethodDeclaration] -> String -> String
show :: MethodDeclaration -> String
$cshow :: MethodDeclaration -> String
showsPrec :: Int -> MethodDeclaration -> String -> String
$cshowsPrec :: Int -> MethodDeclaration -> String -> String
Show)

_MethodDeclaration :: Name
_MethodDeclaration = (String -> Name
Core.Name String
"hydra/ext/java/syntax.MethodDeclaration")

_MethodDeclaration_annotations :: FieldName
_MethodDeclaration_annotations = (String -> FieldName
Core.FieldName String
"annotations")

_MethodDeclaration_modifiers :: FieldName
_MethodDeclaration_modifiers = (String -> FieldName
Core.FieldName String
"modifiers")

_MethodDeclaration_header :: FieldName
_MethodDeclaration_header = (String -> FieldName
Core.FieldName String
"header")

_MethodDeclaration_body :: FieldName
_MethodDeclaration_body = (String -> FieldName
Core.FieldName String
"body")

data MethodModifier = 
  MethodModifierAnnotation Annotation |
  MethodModifierPublic  |
  MethodModifierProtected  |
  MethodModifierPrivate  |
  MethodModifierAbstract  |
  MethodModifierStatic  |
  MethodModifierFinal  |
  MethodModifierSynchronized  |
  MethodModifierNative  |
  MethodModifierStrictfb 
  deriving (MethodModifier -> MethodModifier -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MethodModifier -> MethodModifier -> Bool
$c/= :: MethodModifier -> MethodModifier -> Bool
== :: MethodModifier -> MethodModifier -> Bool
$c== :: MethodModifier -> MethodModifier -> Bool
Eq, Eq MethodModifier
MethodModifier -> MethodModifier -> Bool
MethodModifier -> MethodModifier -> Ordering
MethodModifier -> MethodModifier -> MethodModifier
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: MethodModifier -> MethodModifier -> MethodModifier
$cmin :: MethodModifier -> MethodModifier -> MethodModifier
max :: MethodModifier -> MethodModifier -> MethodModifier
$cmax :: MethodModifier -> MethodModifier -> MethodModifier
>= :: MethodModifier -> MethodModifier -> Bool
$c>= :: MethodModifier -> MethodModifier -> Bool
> :: MethodModifier -> MethodModifier -> Bool
$c> :: MethodModifier -> MethodModifier -> Bool
<= :: MethodModifier -> MethodModifier -> Bool
$c<= :: MethodModifier -> MethodModifier -> Bool
< :: MethodModifier -> MethodModifier -> Bool
$c< :: MethodModifier -> MethodModifier -> Bool
compare :: MethodModifier -> MethodModifier -> Ordering
$ccompare :: MethodModifier -> MethodModifier -> Ordering
Ord, ReadPrec [MethodModifier]
ReadPrec MethodModifier
Int -> ReadS MethodModifier
ReadS [MethodModifier]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [MethodModifier]
$creadListPrec :: ReadPrec [MethodModifier]
readPrec :: ReadPrec MethodModifier
$creadPrec :: ReadPrec MethodModifier
readList :: ReadS [MethodModifier]
$creadList :: ReadS [MethodModifier]
readsPrec :: Int -> ReadS MethodModifier
$creadsPrec :: Int -> ReadS MethodModifier
Read, Int -> MethodModifier -> String -> String
[MethodModifier] -> String -> String
MethodModifier -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [MethodModifier] -> String -> String
$cshowList :: [MethodModifier] -> String -> String
show :: MethodModifier -> String
$cshow :: MethodModifier -> String
showsPrec :: Int -> MethodModifier -> String -> String
$cshowsPrec :: Int -> MethodModifier -> String -> String
Show)

_MethodModifier :: Name
_MethodModifier = (String -> Name
Core.Name String
"hydra/ext/java/syntax.MethodModifier")

_MethodModifier_annotation :: FieldName
_MethodModifier_annotation = (String -> FieldName
Core.FieldName String
"annotation")

_MethodModifier_public :: FieldName
_MethodModifier_public = (String -> FieldName
Core.FieldName String
"public")

_MethodModifier_protected :: FieldName
_MethodModifier_protected = (String -> FieldName
Core.FieldName String
"protected")

_MethodModifier_private :: FieldName
_MethodModifier_private = (String -> FieldName
Core.FieldName String
"private")

_MethodModifier_abstract :: FieldName
_MethodModifier_abstract = (String -> FieldName
Core.FieldName String
"abstract")

_MethodModifier_static :: FieldName
_MethodModifier_static = (String -> FieldName
Core.FieldName String
"static")

_MethodModifier_final :: FieldName
_MethodModifier_final = (String -> FieldName
Core.FieldName String
"final")

_MethodModifier_synchronized :: FieldName
_MethodModifier_synchronized = (String -> FieldName
Core.FieldName String
"synchronized")

_MethodModifier_native :: FieldName
_MethodModifier_native = (String -> FieldName
Core.FieldName String
"native")

_MethodModifier_strictfb :: FieldName
_MethodModifier_strictfb = (String -> FieldName
Core.FieldName String
"strictfb")

data MethodHeader = 
  MethodHeader {
    MethodHeader -> [TypeParameter]
methodHeaderParameters :: [TypeParameter],
    MethodHeader -> Result
methodHeaderResult :: Result,
    MethodHeader -> MethodDeclarator
methodHeaderDeclarator :: MethodDeclarator,
    MethodHeader -> Maybe Throws
methodHeaderThrows :: (Maybe Throws)}
  deriving (MethodHeader -> MethodHeader -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MethodHeader -> MethodHeader -> Bool
$c/= :: MethodHeader -> MethodHeader -> Bool
== :: MethodHeader -> MethodHeader -> Bool
$c== :: MethodHeader -> MethodHeader -> Bool
Eq, Eq MethodHeader
MethodHeader -> MethodHeader -> Bool
MethodHeader -> MethodHeader -> Ordering
MethodHeader -> MethodHeader -> MethodHeader
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: MethodHeader -> MethodHeader -> MethodHeader
$cmin :: MethodHeader -> MethodHeader -> MethodHeader
max :: MethodHeader -> MethodHeader -> MethodHeader
$cmax :: MethodHeader -> MethodHeader -> MethodHeader
>= :: MethodHeader -> MethodHeader -> Bool
$c>= :: MethodHeader -> MethodHeader -> Bool
> :: MethodHeader -> MethodHeader -> Bool
$c> :: MethodHeader -> MethodHeader -> Bool
<= :: MethodHeader -> MethodHeader -> Bool
$c<= :: MethodHeader -> MethodHeader -> Bool
< :: MethodHeader -> MethodHeader -> Bool
$c< :: MethodHeader -> MethodHeader -> Bool
compare :: MethodHeader -> MethodHeader -> Ordering
$ccompare :: MethodHeader -> MethodHeader -> Ordering
Ord, ReadPrec [MethodHeader]
ReadPrec MethodHeader
Int -> ReadS MethodHeader
ReadS [MethodHeader]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [MethodHeader]
$creadListPrec :: ReadPrec [MethodHeader]
readPrec :: ReadPrec MethodHeader
$creadPrec :: ReadPrec MethodHeader
readList :: ReadS [MethodHeader]
$creadList :: ReadS [MethodHeader]
readsPrec :: Int -> ReadS MethodHeader
$creadsPrec :: Int -> ReadS MethodHeader
Read, Int -> MethodHeader -> String -> String
[MethodHeader] -> String -> String
MethodHeader -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [MethodHeader] -> String -> String
$cshowList :: [MethodHeader] -> String -> String
show :: MethodHeader -> String
$cshow :: MethodHeader -> String
showsPrec :: Int -> MethodHeader -> String -> String
$cshowsPrec :: Int -> MethodHeader -> String -> String
Show)

_MethodHeader :: Name
_MethodHeader = (String -> Name
Core.Name String
"hydra/ext/java/syntax.MethodHeader")

_MethodHeader_parameters :: FieldName
_MethodHeader_parameters = (String -> FieldName
Core.FieldName String
"parameters")

_MethodHeader_result :: FieldName
_MethodHeader_result = (String -> FieldName
Core.FieldName String
"result")

_MethodHeader_declarator :: FieldName
_MethodHeader_declarator = (String -> FieldName
Core.FieldName String
"declarator")

_MethodHeader_throws :: FieldName
_MethodHeader_throws = (String -> FieldName
Core.FieldName String
"throws")

data Result = 
  ResultType UnannType |
  ResultVoid 
  deriving (Result -> Result -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Result -> Result -> Bool
$c/= :: Result -> Result -> Bool
== :: Result -> Result -> Bool
$c== :: Result -> Result -> Bool
Eq, Eq Result
Result -> Result -> Bool
Result -> Result -> Ordering
Result -> Result -> Result
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Result -> Result -> Result
$cmin :: Result -> Result -> Result
max :: Result -> Result -> Result
$cmax :: Result -> Result -> Result
>= :: Result -> Result -> Bool
$c>= :: Result -> Result -> Bool
> :: Result -> Result -> Bool
$c> :: Result -> Result -> Bool
<= :: Result -> Result -> Bool
$c<= :: Result -> Result -> Bool
< :: Result -> Result -> Bool
$c< :: Result -> Result -> Bool
compare :: Result -> Result -> Ordering
$ccompare :: Result -> Result -> Ordering
Ord, ReadPrec [Result]
ReadPrec Result
Int -> ReadS Result
ReadS [Result]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Result]
$creadListPrec :: ReadPrec [Result]
readPrec :: ReadPrec Result
$creadPrec :: ReadPrec Result
readList :: ReadS [Result]
$creadList :: ReadS [Result]
readsPrec :: Int -> ReadS Result
$creadsPrec :: Int -> ReadS Result
Read, Int -> Result -> String -> String
[Result] -> String -> String
Result -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [Result] -> String -> String
$cshowList :: [Result] -> String -> String
show :: Result -> String
$cshow :: Result -> String
showsPrec :: Int -> Result -> String -> String
$cshowsPrec :: Int -> Result -> String -> String
Show)

_Result :: Name
_Result = (String -> Name
Core.Name String
"hydra/ext/java/syntax.Result")

_Result_type :: FieldName
_Result_type = (String -> FieldName
Core.FieldName String
"type")

_Result_void :: FieldName
_Result_void = (String -> FieldName
Core.FieldName String
"void")

data MethodDeclarator = 
  MethodDeclarator {
    MethodDeclarator -> Identifier
methodDeclaratorIdentifier :: Identifier,
    MethodDeclarator -> Maybe ReceiverParameter
methodDeclaratorReceiverParameter :: (Maybe ReceiverParameter),
    MethodDeclarator -> [FormalParameter]
methodDeclaratorFormalParameters :: [FormalParameter]}
  deriving (MethodDeclarator -> MethodDeclarator -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MethodDeclarator -> MethodDeclarator -> Bool
$c/= :: MethodDeclarator -> MethodDeclarator -> Bool
== :: MethodDeclarator -> MethodDeclarator -> Bool
$c== :: MethodDeclarator -> MethodDeclarator -> Bool
Eq, Eq MethodDeclarator
MethodDeclarator -> MethodDeclarator -> Bool
MethodDeclarator -> MethodDeclarator -> Ordering
MethodDeclarator -> MethodDeclarator -> MethodDeclarator
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: MethodDeclarator -> MethodDeclarator -> MethodDeclarator
$cmin :: MethodDeclarator -> MethodDeclarator -> MethodDeclarator
max :: MethodDeclarator -> MethodDeclarator -> MethodDeclarator
$cmax :: MethodDeclarator -> MethodDeclarator -> MethodDeclarator
>= :: MethodDeclarator -> MethodDeclarator -> Bool
$c>= :: MethodDeclarator -> MethodDeclarator -> Bool
> :: MethodDeclarator -> MethodDeclarator -> Bool
$c> :: MethodDeclarator -> MethodDeclarator -> Bool
<= :: MethodDeclarator -> MethodDeclarator -> Bool
$c<= :: MethodDeclarator -> MethodDeclarator -> Bool
< :: MethodDeclarator -> MethodDeclarator -> Bool
$c< :: MethodDeclarator -> MethodDeclarator -> Bool
compare :: MethodDeclarator -> MethodDeclarator -> Ordering
$ccompare :: MethodDeclarator -> MethodDeclarator -> Ordering
Ord, ReadPrec [MethodDeclarator]
ReadPrec MethodDeclarator
Int -> ReadS MethodDeclarator
ReadS [MethodDeclarator]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [MethodDeclarator]
$creadListPrec :: ReadPrec [MethodDeclarator]
readPrec :: ReadPrec MethodDeclarator
$creadPrec :: ReadPrec MethodDeclarator
readList :: ReadS [MethodDeclarator]
$creadList :: ReadS [MethodDeclarator]
readsPrec :: Int -> ReadS MethodDeclarator
$creadsPrec :: Int -> ReadS MethodDeclarator
Read, Int -> MethodDeclarator -> String -> String
[MethodDeclarator] -> String -> String
MethodDeclarator -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [MethodDeclarator] -> String -> String
$cshowList :: [MethodDeclarator] -> String -> String
show :: MethodDeclarator -> String
$cshow :: MethodDeclarator -> String
showsPrec :: Int -> MethodDeclarator -> String -> String
$cshowsPrec :: Int -> MethodDeclarator -> String -> String
Show)

_MethodDeclarator :: Name
_MethodDeclarator = (String -> Name
Core.Name String
"hydra/ext/java/syntax.MethodDeclarator")

_MethodDeclarator_identifier :: FieldName
_MethodDeclarator_identifier = (String -> FieldName
Core.FieldName String
"identifier")

_MethodDeclarator_receiverParameter :: FieldName
_MethodDeclarator_receiverParameter = (String -> FieldName
Core.FieldName String
"receiverParameter")

_MethodDeclarator_formalParameters :: FieldName
_MethodDeclarator_formalParameters = (String -> FieldName
Core.FieldName String
"formalParameters")

data ReceiverParameter = 
  ReceiverParameter {
    ReceiverParameter -> [Annotation]
receiverParameterAnnotations :: [Annotation],
    ReceiverParameter -> UnannType
receiverParameterUnannType :: UnannType,
    ReceiverParameter -> Maybe Identifier
receiverParameterIdentifier :: (Maybe Identifier)}
  deriving (ReceiverParameter -> ReceiverParameter -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ReceiverParameter -> ReceiverParameter -> Bool
$c/= :: ReceiverParameter -> ReceiverParameter -> Bool
== :: ReceiverParameter -> ReceiverParameter -> Bool
$c== :: ReceiverParameter -> ReceiverParameter -> Bool
Eq, Eq ReceiverParameter
ReceiverParameter -> ReceiverParameter -> Bool
ReceiverParameter -> ReceiverParameter -> Ordering
ReceiverParameter -> ReceiverParameter -> ReceiverParameter
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ReceiverParameter -> ReceiverParameter -> ReceiverParameter
$cmin :: ReceiverParameter -> ReceiverParameter -> ReceiverParameter
max :: ReceiverParameter -> ReceiverParameter -> ReceiverParameter
$cmax :: ReceiverParameter -> ReceiverParameter -> ReceiverParameter
>= :: ReceiverParameter -> ReceiverParameter -> Bool
$c>= :: ReceiverParameter -> ReceiverParameter -> Bool
> :: ReceiverParameter -> ReceiverParameter -> Bool
$c> :: ReceiverParameter -> ReceiverParameter -> Bool
<= :: ReceiverParameter -> ReceiverParameter -> Bool
$c<= :: ReceiverParameter -> ReceiverParameter -> Bool
< :: ReceiverParameter -> ReceiverParameter -> Bool
$c< :: ReceiverParameter -> ReceiverParameter -> Bool
compare :: ReceiverParameter -> ReceiverParameter -> Ordering
$ccompare :: ReceiverParameter -> ReceiverParameter -> Ordering
Ord, ReadPrec [ReceiverParameter]
ReadPrec ReceiverParameter
Int -> ReadS ReceiverParameter
ReadS [ReceiverParameter]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ReceiverParameter]
$creadListPrec :: ReadPrec [ReceiverParameter]
readPrec :: ReadPrec ReceiverParameter
$creadPrec :: ReadPrec ReceiverParameter
readList :: ReadS [ReceiverParameter]
$creadList :: ReadS [ReceiverParameter]
readsPrec :: Int -> ReadS ReceiverParameter
$creadsPrec :: Int -> ReadS ReceiverParameter
Read, Int -> ReceiverParameter -> String -> String
[ReceiverParameter] -> String -> String
ReceiverParameter -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ReceiverParameter] -> String -> String
$cshowList :: [ReceiverParameter] -> String -> String
show :: ReceiverParameter -> String
$cshow :: ReceiverParameter -> String
showsPrec :: Int -> ReceiverParameter -> String -> String
$cshowsPrec :: Int -> ReceiverParameter -> String -> String
Show)

_ReceiverParameter :: Name
_ReceiverParameter = (String -> Name
Core.Name String
"hydra/ext/java/syntax.ReceiverParameter")

_ReceiverParameter_annotations :: FieldName
_ReceiverParameter_annotations = (String -> FieldName
Core.FieldName String
"annotations")

_ReceiverParameter_unannType :: FieldName
_ReceiverParameter_unannType = (String -> FieldName
Core.FieldName String
"unannType")

_ReceiverParameter_identifier :: FieldName
_ReceiverParameter_identifier = (String -> FieldName
Core.FieldName String
"identifier")

data FormalParameter = 
  FormalParameterSimple FormalParameter_Simple |
  FormalParameterVariableArity VariableArityParameter
  deriving (FormalParameter -> FormalParameter -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FormalParameter -> FormalParameter -> Bool
$c/= :: FormalParameter -> FormalParameter -> Bool
== :: FormalParameter -> FormalParameter -> Bool
$c== :: FormalParameter -> FormalParameter -> Bool
Eq, Eq FormalParameter
FormalParameter -> FormalParameter -> Bool
FormalParameter -> FormalParameter -> Ordering
FormalParameter -> FormalParameter -> FormalParameter
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: FormalParameter -> FormalParameter -> FormalParameter
$cmin :: FormalParameter -> FormalParameter -> FormalParameter
max :: FormalParameter -> FormalParameter -> FormalParameter
$cmax :: FormalParameter -> FormalParameter -> FormalParameter
>= :: FormalParameter -> FormalParameter -> Bool
$c>= :: FormalParameter -> FormalParameter -> Bool
> :: FormalParameter -> FormalParameter -> Bool
$c> :: FormalParameter -> FormalParameter -> Bool
<= :: FormalParameter -> FormalParameter -> Bool
$c<= :: FormalParameter -> FormalParameter -> Bool
< :: FormalParameter -> FormalParameter -> Bool
$c< :: FormalParameter -> FormalParameter -> Bool
compare :: FormalParameter -> FormalParameter -> Ordering
$ccompare :: FormalParameter -> FormalParameter -> Ordering
Ord, ReadPrec [FormalParameter]
ReadPrec FormalParameter
Int -> ReadS FormalParameter
ReadS [FormalParameter]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [FormalParameter]
$creadListPrec :: ReadPrec [FormalParameter]
readPrec :: ReadPrec FormalParameter
$creadPrec :: ReadPrec FormalParameter
readList :: ReadS [FormalParameter]
$creadList :: ReadS [FormalParameter]
readsPrec :: Int -> ReadS FormalParameter
$creadsPrec :: Int -> ReadS FormalParameter
Read, Int -> FormalParameter -> String -> String
[FormalParameter] -> String -> String
FormalParameter -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [FormalParameter] -> String -> String
$cshowList :: [FormalParameter] -> String -> String
show :: FormalParameter -> String
$cshow :: FormalParameter -> String
showsPrec :: Int -> FormalParameter -> String -> String
$cshowsPrec :: Int -> FormalParameter -> String -> String
Show)

_FormalParameter :: Name
_FormalParameter = (String -> Name
Core.Name String
"hydra/ext/java/syntax.FormalParameter")

_FormalParameter_simple :: FieldName
_FormalParameter_simple = (String -> FieldName
Core.FieldName String
"simple")

_FormalParameter_variableArity :: FieldName
_FormalParameter_variableArity = (String -> FieldName
Core.FieldName String
"variableArity")

data FormalParameter_Simple = 
  FormalParameter_Simple {
    FormalParameter_Simple -> [VariableModifier]
formalParameter_SimpleModifiers :: [VariableModifier],
    FormalParameter_Simple -> UnannType
formalParameter_SimpleType :: UnannType,
    FormalParameter_Simple -> VariableDeclaratorId
formalParameter_SimpleId :: VariableDeclaratorId}
  deriving (FormalParameter_Simple -> FormalParameter_Simple -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FormalParameter_Simple -> FormalParameter_Simple -> Bool
$c/= :: FormalParameter_Simple -> FormalParameter_Simple -> Bool
== :: FormalParameter_Simple -> FormalParameter_Simple -> Bool
$c== :: FormalParameter_Simple -> FormalParameter_Simple -> Bool
Eq, Eq FormalParameter_Simple
FormalParameter_Simple -> FormalParameter_Simple -> Bool
FormalParameter_Simple -> FormalParameter_Simple -> Ordering
FormalParameter_Simple
-> FormalParameter_Simple -> FormalParameter_Simple
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: FormalParameter_Simple
-> FormalParameter_Simple -> FormalParameter_Simple
$cmin :: FormalParameter_Simple
-> FormalParameter_Simple -> FormalParameter_Simple
max :: FormalParameter_Simple
-> FormalParameter_Simple -> FormalParameter_Simple
$cmax :: FormalParameter_Simple
-> FormalParameter_Simple -> FormalParameter_Simple
>= :: FormalParameter_Simple -> FormalParameter_Simple -> Bool
$c>= :: FormalParameter_Simple -> FormalParameter_Simple -> Bool
> :: FormalParameter_Simple -> FormalParameter_Simple -> Bool
$c> :: FormalParameter_Simple -> FormalParameter_Simple -> Bool
<= :: FormalParameter_Simple -> FormalParameter_Simple -> Bool
$c<= :: FormalParameter_Simple -> FormalParameter_Simple -> Bool
< :: FormalParameter_Simple -> FormalParameter_Simple -> Bool
$c< :: FormalParameter_Simple -> FormalParameter_Simple -> Bool
compare :: FormalParameter_Simple -> FormalParameter_Simple -> Ordering
$ccompare :: FormalParameter_Simple -> FormalParameter_Simple -> Ordering
Ord, ReadPrec [FormalParameter_Simple]
ReadPrec FormalParameter_Simple
Int -> ReadS FormalParameter_Simple
ReadS [FormalParameter_Simple]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [FormalParameter_Simple]
$creadListPrec :: ReadPrec [FormalParameter_Simple]
readPrec :: ReadPrec FormalParameter_Simple
$creadPrec :: ReadPrec FormalParameter_Simple
readList :: ReadS [FormalParameter_Simple]
$creadList :: ReadS [FormalParameter_Simple]
readsPrec :: Int -> ReadS FormalParameter_Simple
$creadsPrec :: Int -> ReadS FormalParameter_Simple
Read, Int -> FormalParameter_Simple -> String -> String
[FormalParameter_Simple] -> String -> String
FormalParameter_Simple -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [FormalParameter_Simple] -> String -> String
$cshowList :: [FormalParameter_Simple] -> String -> String
show :: FormalParameter_Simple -> String
$cshow :: FormalParameter_Simple -> String
showsPrec :: Int -> FormalParameter_Simple -> String -> String
$cshowsPrec :: Int -> FormalParameter_Simple -> String -> String
Show)

_FormalParameter_Simple :: Name
_FormalParameter_Simple = (String -> Name
Core.Name String
"hydra/ext/java/syntax.FormalParameter.Simple")

_FormalParameter_Simple_modifiers :: FieldName
_FormalParameter_Simple_modifiers = (String -> FieldName
Core.FieldName String
"modifiers")

_FormalParameter_Simple_type :: FieldName
_FormalParameter_Simple_type = (String -> FieldName
Core.FieldName String
"type")

_FormalParameter_Simple_id :: FieldName
_FormalParameter_Simple_id = (String -> FieldName
Core.FieldName String
"id")

data VariableArityParameter = 
  VariableArityParameter {
    VariableArityParameter -> VariableModifier
variableArityParameterModifiers :: VariableModifier,
    VariableArityParameter -> UnannType
variableArityParameterType :: UnannType,
    VariableArityParameter -> [Annotation]
variableArityParameterAnnotations :: [Annotation],
    VariableArityParameter -> Identifier
variableArityParameterIdentifier :: Identifier}
  deriving (VariableArityParameter -> VariableArityParameter -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VariableArityParameter -> VariableArityParameter -> Bool
$c/= :: VariableArityParameter -> VariableArityParameter -> Bool
== :: VariableArityParameter -> VariableArityParameter -> Bool
$c== :: VariableArityParameter -> VariableArityParameter -> Bool
Eq, Eq VariableArityParameter
VariableArityParameter -> VariableArityParameter -> Bool
VariableArityParameter -> VariableArityParameter -> Ordering
VariableArityParameter
-> VariableArityParameter -> VariableArityParameter
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: VariableArityParameter
-> VariableArityParameter -> VariableArityParameter
$cmin :: VariableArityParameter
-> VariableArityParameter -> VariableArityParameter
max :: VariableArityParameter
-> VariableArityParameter -> VariableArityParameter
$cmax :: VariableArityParameter
-> VariableArityParameter -> VariableArityParameter
>= :: VariableArityParameter -> VariableArityParameter -> Bool
$c>= :: VariableArityParameter -> VariableArityParameter -> Bool
> :: VariableArityParameter -> VariableArityParameter -> Bool
$c> :: VariableArityParameter -> VariableArityParameter -> Bool
<= :: VariableArityParameter -> VariableArityParameter -> Bool
$c<= :: VariableArityParameter -> VariableArityParameter -> Bool
< :: VariableArityParameter -> VariableArityParameter -> Bool
$c< :: VariableArityParameter -> VariableArityParameter -> Bool
compare :: VariableArityParameter -> VariableArityParameter -> Ordering
$ccompare :: VariableArityParameter -> VariableArityParameter -> Ordering
Ord, ReadPrec [VariableArityParameter]
ReadPrec VariableArityParameter
Int -> ReadS VariableArityParameter
ReadS [VariableArityParameter]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [VariableArityParameter]
$creadListPrec :: ReadPrec [VariableArityParameter]
readPrec :: ReadPrec VariableArityParameter
$creadPrec :: ReadPrec VariableArityParameter
readList :: ReadS [VariableArityParameter]
$creadList :: ReadS [VariableArityParameter]
readsPrec :: Int -> ReadS VariableArityParameter
$creadsPrec :: Int -> ReadS VariableArityParameter
Read, Int -> VariableArityParameter -> String -> String
[VariableArityParameter] -> String -> String
VariableArityParameter -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [VariableArityParameter] -> String -> String
$cshowList :: [VariableArityParameter] -> String -> String
show :: VariableArityParameter -> String
$cshow :: VariableArityParameter -> String
showsPrec :: Int -> VariableArityParameter -> String -> String
$cshowsPrec :: Int -> VariableArityParameter -> String -> String
Show)

_VariableArityParameter :: Name
_VariableArityParameter = (String -> Name
Core.Name String
"hydra/ext/java/syntax.VariableArityParameter")

_VariableArityParameter_modifiers :: FieldName
_VariableArityParameter_modifiers = (String -> FieldName
Core.FieldName String
"modifiers")

_VariableArityParameter_type :: FieldName
_VariableArityParameter_type = (String -> FieldName
Core.FieldName String
"type")

_VariableArityParameter_annotations :: FieldName
_VariableArityParameter_annotations = (String -> FieldName
Core.FieldName String
"annotations")

_VariableArityParameter_identifier :: FieldName
_VariableArityParameter_identifier = (String -> FieldName
Core.FieldName String
"identifier")

data VariableModifier = 
  VariableModifierAnnotation Annotation |
  VariableModifierFinal 
  deriving (VariableModifier -> VariableModifier -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VariableModifier -> VariableModifier -> Bool
$c/= :: VariableModifier -> VariableModifier -> Bool
== :: VariableModifier -> VariableModifier -> Bool
$c== :: VariableModifier -> VariableModifier -> Bool
Eq, Eq VariableModifier
VariableModifier -> VariableModifier -> Bool
VariableModifier -> VariableModifier -> Ordering
VariableModifier -> VariableModifier -> VariableModifier
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: VariableModifier -> VariableModifier -> VariableModifier
$cmin :: VariableModifier -> VariableModifier -> VariableModifier
max :: VariableModifier -> VariableModifier -> VariableModifier
$cmax :: VariableModifier -> VariableModifier -> VariableModifier
>= :: VariableModifier -> VariableModifier -> Bool
$c>= :: VariableModifier -> VariableModifier -> Bool
> :: VariableModifier -> VariableModifier -> Bool
$c> :: VariableModifier -> VariableModifier -> Bool
<= :: VariableModifier -> VariableModifier -> Bool
$c<= :: VariableModifier -> VariableModifier -> Bool
< :: VariableModifier -> VariableModifier -> Bool
$c< :: VariableModifier -> VariableModifier -> Bool
compare :: VariableModifier -> VariableModifier -> Ordering
$ccompare :: VariableModifier -> VariableModifier -> Ordering
Ord, ReadPrec [VariableModifier]
ReadPrec VariableModifier
Int -> ReadS VariableModifier
ReadS [VariableModifier]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [VariableModifier]
$creadListPrec :: ReadPrec [VariableModifier]
readPrec :: ReadPrec VariableModifier
$creadPrec :: ReadPrec VariableModifier
readList :: ReadS [VariableModifier]
$creadList :: ReadS [VariableModifier]
readsPrec :: Int -> ReadS VariableModifier
$creadsPrec :: Int -> ReadS VariableModifier
Read, Int -> VariableModifier -> String -> String
[VariableModifier] -> String -> String
VariableModifier -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [VariableModifier] -> String -> String
$cshowList :: [VariableModifier] -> String -> String
show :: VariableModifier -> String
$cshow :: VariableModifier -> String
showsPrec :: Int -> VariableModifier -> String -> String
$cshowsPrec :: Int -> VariableModifier -> String -> String
Show)

_VariableModifier :: Name
_VariableModifier = (String -> Name
Core.Name String
"hydra/ext/java/syntax.VariableModifier")

_VariableModifier_annotation :: FieldName
_VariableModifier_annotation = (String -> FieldName
Core.FieldName String
"annotation")

_VariableModifier_final :: FieldName
_VariableModifier_final = (String -> FieldName
Core.FieldName String
"final")

newtype Throws = 
  Throws {
    Throws -> [ExceptionType]
unThrows :: [ExceptionType]}
  deriving (Throws -> Throws -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Throws -> Throws -> Bool
$c/= :: Throws -> Throws -> Bool
== :: Throws -> Throws -> Bool
$c== :: Throws -> Throws -> Bool
Eq, Eq Throws
Throws -> Throws -> Bool
Throws -> Throws -> Ordering
Throws -> Throws -> Throws
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Throws -> Throws -> Throws
$cmin :: Throws -> Throws -> Throws
max :: Throws -> Throws -> Throws
$cmax :: Throws -> Throws -> Throws
>= :: Throws -> Throws -> Bool
$c>= :: Throws -> Throws -> Bool
> :: Throws -> Throws -> Bool
$c> :: Throws -> Throws -> Bool
<= :: Throws -> Throws -> Bool
$c<= :: Throws -> Throws -> Bool
< :: Throws -> Throws -> Bool
$c< :: Throws -> Throws -> Bool
compare :: Throws -> Throws -> Ordering
$ccompare :: Throws -> Throws -> Ordering
Ord, ReadPrec [Throws]
ReadPrec Throws
Int -> ReadS Throws
ReadS [Throws]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Throws]
$creadListPrec :: ReadPrec [Throws]
readPrec :: ReadPrec Throws
$creadPrec :: ReadPrec Throws
readList :: ReadS [Throws]
$creadList :: ReadS [Throws]
readsPrec :: Int -> ReadS Throws
$creadsPrec :: Int -> ReadS Throws
Read, Int -> Throws -> String -> String
[Throws] -> String -> String
Throws -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [Throws] -> String -> String
$cshowList :: [Throws] -> String -> String
show :: Throws -> String
$cshow :: Throws -> String
showsPrec :: Int -> Throws -> String -> String
$cshowsPrec :: Int -> Throws -> String -> String
Show)

_Throws :: Name
_Throws = (String -> Name
Core.Name String
"hydra/ext/java/syntax.Throws")

data ExceptionType = 
  ExceptionTypeClass ClassType |
  ExceptionTypeVariable TypeVariable
  deriving (ExceptionType -> ExceptionType -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ExceptionType -> ExceptionType -> Bool
$c/= :: ExceptionType -> ExceptionType -> Bool
== :: ExceptionType -> ExceptionType -> Bool
$c== :: ExceptionType -> ExceptionType -> Bool
Eq, Eq ExceptionType
ExceptionType -> ExceptionType -> Bool
ExceptionType -> ExceptionType -> Ordering
ExceptionType -> ExceptionType -> ExceptionType
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ExceptionType -> ExceptionType -> ExceptionType
$cmin :: ExceptionType -> ExceptionType -> ExceptionType
max :: ExceptionType -> ExceptionType -> ExceptionType
$cmax :: ExceptionType -> ExceptionType -> ExceptionType
>= :: ExceptionType -> ExceptionType -> Bool
$c>= :: ExceptionType -> ExceptionType -> Bool
> :: ExceptionType -> ExceptionType -> Bool
$c> :: ExceptionType -> ExceptionType -> Bool
<= :: ExceptionType -> ExceptionType -> Bool
$c<= :: ExceptionType -> ExceptionType -> Bool
< :: ExceptionType -> ExceptionType -> Bool
$c< :: ExceptionType -> ExceptionType -> Bool
compare :: ExceptionType -> ExceptionType -> Ordering
$ccompare :: ExceptionType -> ExceptionType -> Ordering
Ord, ReadPrec [ExceptionType]
ReadPrec ExceptionType
Int -> ReadS ExceptionType
ReadS [ExceptionType]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ExceptionType]
$creadListPrec :: ReadPrec [ExceptionType]
readPrec :: ReadPrec ExceptionType
$creadPrec :: ReadPrec ExceptionType
readList :: ReadS [ExceptionType]
$creadList :: ReadS [ExceptionType]
readsPrec :: Int -> ReadS ExceptionType
$creadsPrec :: Int -> ReadS ExceptionType
Read, Int -> ExceptionType -> String -> String
[ExceptionType] -> String -> String
ExceptionType -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ExceptionType] -> String -> String
$cshowList :: [ExceptionType] -> String -> String
show :: ExceptionType -> String
$cshow :: ExceptionType -> String
showsPrec :: Int -> ExceptionType -> String -> String
$cshowsPrec :: Int -> ExceptionType -> String -> String
Show)

_ExceptionType :: Name
_ExceptionType = (String -> Name
Core.Name String
"hydra/ext/java/syntax.ExceptionType")

_ExceptionType_class :: FieldName
_ExceptionType_class = (String -> FieldName
Core.FieldName String
"class")

_ExceptionType_variable :: FieldName
_ExceptionType_variable = (String -> FieldName
Core.FieldName String
"variable")

data MethodBody = 
  MethodBodyBlock Block |
  MethodBodyNone 
  deriving (MethodBody -> MethodBody -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MethodBody -> MethodBody -> Bool
$c/= :: MethodBody -> MethodBody -> Bool
== :: MethodBody -> MethodBody -> Bool
$c== :: MethodBody -> MethodBody -> Bool
Eq, Eq MethodBody
MethodBody -> MethodBody -> Bool
MethodBody -> MethodBody -> Ordering
MethodBody -> MethodBody -> MethodBody
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: MethodBody -> MethodBody -> MethodBody
$cmin :: MethodBody -> MethodBody -> MethodBody
max :: MethodBody -> MethodBody -> MethodBody
$cmax :: MethodBody -> MethodBody -> MethodBody
>= :: MethodBody -> MethodBody -> Bool
$c>= :: MethodBody -> MethodBody -> Bool
> :: MethodBody -> MethodBody -> Bool
$c> :: MethodBody -> MethodBody -> Bool
<= :: MethodBody -> MethodBody -> Bool
$c<= :: MethodBody -> MethodBody -> Bool
< :: MethodBody -> MethodBody -> Bool
$c< :: MethodBody -> MethodBody -> Bool
compare :: MethodBody -> MethodBody -> Ordering
$ccompare :: MethodBody -> MethodBody -> Ordering
Ord, ReadPrec [MethodBody]
ReadPrec MethodBody
Int -> ReadS MethodBody
ReadS [MethodBody]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [MethodBody]
$creadListPrec :: ReadPrec [MethodBody]
readPrec :: ReadPrec MethodBody
$creadPrec :: ReadPrec MethodBody
readList :: ReadS [MethodBody]
$creadList :: ReadS [MethodBody]
readsPrec :: Int -> ReadS MethodBody
$creadsPrec :: Int -> ReadS MethodBody
Read, Int -> MethodBody -> String -> String
[MethodBody] -> String -> String
MethodBody -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [MethodBody] -> String -> String
$cshowList :: [MethodBody] -> String -> String
show :: MethodBody -> String
$cshow :: MethodBody -> String
showsPrec :: Int -> MethodBody -> String -> String
$cshowsPrec :: Int -> MethodBody -> String -> String
Show)

_MethodBody :: Name
_MethodBody = (String -> Name
Core.Name String
"hydra/ext/java/syntax.MethodBody")

_MethodBody_block :: FieldName
_MethodBody_block = (String -> FieldName
Core.FieldName String
"block")

_MethodBody_none :: FieldName
_MethodBody_none = (String -> FieldName
Core.FieldName String
"none")

newtype InstanceInitializer = 
  InstanceInitializer {
    InstanceInitializer -> Block
unInstanceInitializer :: Block}
  deriving (InstanceInitializer -> InstanceInitializer -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InstanceInitializer -> InstanceInitializer -> Bool
$c/= :: InstanceInitializer -> InstanceInitializer -> Bool
== :: InstanceInitializer -> InstanceInitializer -> Bool
$c== :: InstanceInitializer -> InstanceInitializer -> Bool
Eq, Eq InstanceInitializer
InstanceInitializer -> InstanceInitializer -> Bool
InstanceInitializer -> InstanceInitializer -> Ordering
InstanceInitializer -> InstanceInitializer -> InstanceInitializer
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: InstanceInitializer -> InstanceInitializer -> InstanceInitializer
$cmin :: InstanceInitializer -> InstanceInitializer -> InstanceInitializer
max :: InstanceInitializer -> InstanceInitializer -> InstanceInitializer
$cmax :: InstanceInitializer -> InstanceInitializer -> InstanceInitializer
>= :: InstanceInitializer -> InstanceInitializer -> Bool
$c>= :: InstanceInitializer -> InstanceInitializer -> Bool
> :: InstanceInitializer -> InstanceInitializer -> Bool
$c> :: InstanceInitializer -> InstanceInitializer -> Bool
<= :: InstanceInitializer -> InstanceInitializer -> Bool
$c<= :: InstanceInitializer -> InstanceInitializer -> Bool
< :: InstanceInitializer -> InstanceInitializer -> Bool
$c< :: InstanceInitializer -> InstanceInitializer -> Bool
compare :: InstanceInitializer -> InstanceInitializer -> Ordering
$ccompare :: InstanceInitializer -> InstanceInitializer -> Ordering
Ord, ReadPrec [InstanceInitializer]
ReadPrec InstanceInitializer
Int -> ReadS InstanceInitializer
ReadS [InstanceInitializer]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [InstanceInitializer]
$creadListPrec :: ReadPrec [InstanceInitializer]
readPrec :: ReadPrec InstanceInitializer
$creadPrec :: ReadPrec InstanceInitializer
readList :: ReadS [InstanceInitializer]
$creadList :: ReadS [InstanceInitializer]
readsPrec :: Int -> ReadS InstanceInitializer
$creadsPrec :: Int -> ReadS InstanceInitializer
Read, Int -> InstanceInitializer -> String -> String
[InstanceInitializer] -> String -> String
InstanceInitializer -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [InstanceInitializer] -> String -> String
$cshowList :: [InstanceInitializer] -> String -> String
show :: InstanceInitializer -> String
$cshow :: InstanceInitializer -> String
showsPrec :: Int -> InstanceInitializer -> String -> String
$cshowsPrec :: Int -> InstanceInitializer -> String -> String
Show)

_InstanceInitializer :: Name
_InstanceInitializer = (String -> Name
Core.Name String
"hydra/ext/java/syntax.InstanceInitializer")

newtype StaticInitializer = 
  StaticInitializer {
    StaticInitializer -> Block
unStaticInitializer :: Block}
  deriving (StaticInitializer -> StaticInitializer -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StaticInitializer -> StaticInitializer -> Bool
$c/= :: StaticInitializer -> StaticInitializer -> Bool
== :: StaticInitializer -> StaticInitializer -> Bool
$c== :: StaticInitializer -> StaticInitializer -> Bool
Eq, Eq StaticInitializer
StaticInitializer -> StaticInitializer -> Bool
StaticInitializer -> StaticInitializer -> Ordering
StaticInitializer -> StaticInitializer -> StaticInitializer
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: StaticInitializer -> StaticInitializer -> StaticInitializer
$cmin :: StaticInitializer -> StaticInitializer -> StaticInitializer
max :: StaticInitializer -> StaticInitializer -> StaticInitializer
$cmax :: StaticInitializer -> StaticInitializer -> StaticInitializer
>= :: StaticInitializer -> StaticInitializer -> Bool
$c>= :: StaticInitializer -> StaticInitializer -> Bool
> :: StaticInitializer -> StaticInitializer -> Bool
$c> :: StaticInitializer -> StaticInitializer -> Bool
<= :: StaticInitializer -> StaticInitializer -> Bool
$c<= :: StaticInitializer -> StaticInitializer -> Bool
< :: StaticInitializer -> StaticInitializer -> Bool
$c< :: StaticInitializer -> StaticInitializer -> Bool
compare :: StaticInitializer -> StaticInitializer -> Ordering
$ccompare :: StaticInitializer -> StaticInitializer -> Ordering
Ord, ReadPrec [StaticInitializer]
ReadPrec StaticInitializer
Int -> ReadS StaticInitializer
ReadS [StaticInitializer]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StaticInitializer]
$creadListPrec :: ReadPrec [StaticInitializer]
readPrec :: ReadPrec StaticInitializer
$creadPrec :: ReadPrec StaticInitializer
readList :: ReadS [StaticInitializer]
$creadList :: ReadS [StaticInitializer]
readsPrec :: Int -> ReadS StaticInitializer
$creadsPrec :: Int -> ReadS StaticInitializer
Read, Int -> StaticInitializer -> String -> String
[StaticInitializer] -> String -> String
StaticInitializer -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [StaticInitializer] -> String -> String
$cshowList :: [StaticInitializer] -> String -> String
show :: StaticInitializer -> String
$cshow :: StaticInitializer -> String
showsPrec :: Int -> StaticInitializer -> String -> String
$cshowsPrec :: Int -> StaticInitializer -> String -> String
Show)

_StaticInitializer :: Name
_StaticInitializer = (String -> Name
Core.Name String
"hydra/ext/java/syntax.StaticInitializer")

data ConstructorDeclaration = 
  ConstructorDeclaration {
    ConstructorDeclaration -> [ConstructorModifier]
constructorDeclarationModifiers :: [ConstructorModifier],
    ConstructorDeclaration -> ConstructorDeclarator
constructorDeclarationConstructor :: ConstructorDeclarator,
    ConstructorDeclaration -> Maybe Throws
constructorDeclarationThrows :: (Maybe Throws),
    ConstructorDeclaration -> ConstructorBody
constructorDeclarationBody :: ConstructorBody}
  deriving (ConstructorDeclaration -> ConstructorDeclaration -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ConstructorDeclaration -> ConstructorDeclaration -> Bool
$c/= :: ConstructorDeclaration -> ConstructorDeclaration -> Bool
== :: ConstructorDeclaration -> ConstructorDeclaration -> Bool
$c== :: ConstructorDeclaration -> ConstructorDeclaration -> Bool
Eq, Eq ConstructorDeclaration
ConstructorDeclaration -> ConstructorDeclaration -> Bool
ConstructorDeclaration -> ConstructorDeclaration -> Ordering
ConstructorDeclaration
-> ConstructorDeclaration -> ConstructorDeclaration
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ConstructorDeclaration
-> ConstructorDeclaration -> ConstructorDeclaration
$cmin :: ConstructorDeclaration
-> ConstructorDeclaration -> ConstructorDeclaration
max :: ConstructorDeclaration
-> ConstructorDeclaration -> ConstructorDeclaration
$cmax :: ConstructorDeclaration
-> ConstructorDeclaration -> ConstructorDeclaration
>= :: ConstructorDeclaration -> ConstructorDeclaration -> Bool
$c>= :: ConstructorDeclaration -> ConstructorDeclaration -> Bool
> :: ConstructorDeclaration -> ConstructorDeclaration -> Bool
$c> :: ConstructorDeclaration -> ConstructorDeclaration -> Bool
<= :: ConstructorDeclaration -> ConstructorDeclaration -> Bool
$c<= :: ConstructorDeclaration -> ConstructorDeclaration -> Bool
< :: ConstructorDeclaration -> ConstructorDeclaration -> Bool
$c< :: ConstructorDeclaration -> ConstructorDeclaration -> Bool
compare :: ConstructorDeclaration -> ConstructorDeclaration -> Ordering
$ccompare :: ConstructorDeclaration -> ConstructorDeclaration -> Ordering
Ord, ReadPrec [ConstructorDeclaration]
ReadPrec ConstructorDeclaration
Int -> ReadS ConstructorDeclaration
ReadS [ConstructorDeclaration]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ConstructorDeclaration]
$creadListPrec :: ReadPrec [ConstructorDeclaration]
readPrec :: ReadPrec ConstructorDeclaration
$creadPrec :: ReadPrec ConstructorDeclaration
readList :: ReadS [ConstructorDeclaration]
$creadList :: ReadS [ConstructorDeclaration]
readsPrec :: Int -> ReadS ConstructorDeclaration
$creadsPrec :: Int -> ReadS ConstructorDeclaration
Read, Int -> ConstructorDeclaration -> String -> String
[ConstructorDeclaration] -> String -> String
ConstructorDeclaration -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ConstructorDeclaration] -> String -> String
$cshowList :: [ConstructorDeclaration] -> String -> String
show :: ConstructorDeclaration -> String
$cshow :: ConstructorDeclaration -> String
showsPrec :: Int -> ConstructorDeclaration -> String -> String
$cshowsPrec :: Int -> ConstructorDeclaration -> String -> String
Show)

_ConstructorDeclaration :: Name
_ConstructorDeclaration = (String -> Name
Core.Name String
"hydra/ext/java/syntax.ConstructorDeclaration")

_ConstructorDeclaration_modifiers :: FieldName
_ConstructorDeclaration_modifiers = (String -> FieldName
Core.FieldName String
"modifiers")

_ConstructorDeclaration_constructor :: FieldName
_ConstructorDeclaration_constructor = (String -> FieldName
Core.FieldName String
"constructor")

_ConstructorDeclaration_throws :: FieldName
_ConstructorDeclaration_throws = (String -> FieldName
Core.FieldName String
"throws")

_ConstructorDeclaration_body :: FieldName
_ConstructorDeclaration_body = (String -> FieldName
Core.FieldName String
"body")

data ConstructorModifier = 
  ConstructorModifierAnnotation Annotation |
  ConstructorModifierPublic  |
  ConstructorModifierProtected  |
  ConstructorModifierPrivate 
  deriving (ConstructorModifier -> ConstructorModifier -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ConstructorModifier -> ConstructorModifier -> Bool
$c/= :: ConstructorModifier -> ConstructorModifier -> Bool
== :: ConstructorModifier -> ConstructorModifier -> Bool
$c== :: ConstructorModifier -> ConstructorModifier -> Bool
Eq, Eq ConstructorModifier
ConstructorModifier -> ConstructorModifier -> Bool
ConstructorModifier -> ConstructorModifier -> Ordering
ConstructorModifier -> ConstructorModifier -> ConstructorModifier
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ConstructorModifier -> ConstructorModifier -> ConstructorModifier
$cmin :: ConstructorModifier -> ConstructorModifier -> ConstructorModifier
max :: ConstructorModifier -> ConstructorModifier -> ConstructorModifier
$cmax :: ConstructorModifier -> ConstructorModifier -> ConstructorModifier
>= :: ConstructorModifier -> ConstructorModifier -> Bool
$c>= :: ConstructorModifier -> ConstructorModifier -> Bool
> :: ConstructorModifier -> ConstructorModifier -> Bool
$c> :: ConstructorModifier -> ConstructorModifier -> Bool
<= :: ConstructorModifier -> ConstructorModifier -> Bool
$c<= :: ConstructorModifier -> ConstructorModifier -> Bool
< :: ConstructorModifier -> ConstructorModifier -> Bool
$c< :: ConstructorModifier -> ConstructorModifier -> Bool
compare :: ConstructorModifier -> ConstructorModifier -> Ordering
$ccompare :: ConstructorModifier -> ConstructorModifier -> Ordering
Ord, ReadPrec [ConstructorModifier]
ReadPrec ConstructorModifier
Int -> ReadS ConstructorModifier
ReadS [ConstructorModifier]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ConstructorModifier]
$creadListPrec :: ReadPrec [ConstructorModifier]
readPrec :: ReadPrec ConstructorModifier
$creadPrec :: ReadPrec ConstructorModifier
readList :: ReadS [ConstructorModifier]
$creadList :: ReadS [ConstructorModifier]
readsPrec :: Int -> ReadS ConstructorModifier
$creadsPrec :: Int -> ReadS ConstructorModifier
Read, Int -> ConstructorModifier -> String -> String
[ConstructorModifier] -> String -> String
ConstructorModifier -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ConstructorModifier] -> String -> String
$cshowList :: [ConstructorModifier] -> String -> String
show :: ConstructorModifier -> String
$cshow :: ConstructorModifier -> String
showsPrec :: Int -> ConstructorModifier -> String -> String
$cshowsPrec :: Int -> ConstructorModifier -> String -> String
Show)

_ConstructorModifier :: Name
_ConstructorModifier = (String -> Name
Core.Name String
"hydra/ext/java/syntax.ConstructorModifier")

_ConstructorModifier_annotation :: FieldName
_ConstructorModifier_annotation = (String -> FieldName
Core.FieldName String
"annotation")

_ConstructorModifier_public :: FieldName
_ConstructorModifier_public = (String -> FieldName
Core.FieldName String
"public")

_ConstructorModifier_protected :: FieldName
_ConstructorModifier_protected = (String -> FieldName
Core.FieldName String
"protected")

_ConstructorModifier_private :: FieldName
_ConstructorModifier_private = (String -> FieldName
Core.FieldName String
"private")

data ConstructorDeclarator = 
  ConstructorDeclarator {
    ConstructorDeclarator -> [TypeParameter]
constructorDeclaratorParameters :: [TypeParameter],
    ConstructorDeclarator -> SimpleTypeName
constructorDeclaratorName :: SimpleTypeName,
    ConstructorDeclarator -> Maybe ReceiverParameter
constructorDeclaratorReceiverParameter :: (Maybe ReceiverParameter),
    ConstructorDeclarator -> [FormalParameter]
constructorDeclaratorFormalParameters :: [FormalParameter]}
  deriving (ConstructorDeclarator -> ConstructorDeclarator -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ConstructorDeclarator -> ConstructorDeclarator -> Bool
$c/= :: ConstructorDeclarator -> ConstructorDeclarator -> Bool
== :: ConstructorDeclarator -> ConstructorDeclarator -> Bool
$c== :: ConstructorDeclarator -> ConstructorDeclarator -> Bool
Eq, Eq ConstructorDeclarator
ConstructorDeclarator -> ConstructorDeclarator -> Bool
ConstructorDeclarator -> ConstructorDeclarator -> Ordering
ConstructorDeclarator
-> ConstructorDeclarator -> ConstructorDeclarator
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ConstructorDeclarator
-> ConstructorDeclarator -> ConstructorDeclarator
$cmin :: ConstructorDeclarator
-> ConstructorDeclarator -> ConstructorDeclarator
max :: ConstructorDeclarator
-> ConstructorDeclarator -> ConstructorDeclarator
$cmax :: ConstructorDeclarator
-> ConstructorDeclarator -> ConstructorDeclarator
>= :: ConstructorDeclarator -> ConstructorDeclarator -> Bool
$c>= :: ConstructorDeclarator -> ConstructorDeclarator -> Bool
> :: ConstructorDeclarator -> ConstructorDeclarator -> Bool
$c> :: ConstructorDeclarator -> ConstructorDeclarator -> Bool
<= :: ConstructorDeclarator -> ConstructorDeclarator -> Bool
$c<= :: ConstructorDeclarator -> ConstructorDeclarator -> Bool
< :: ConstructorDeclarator -> ConstructorDeclarator -> Bool
$c< :: ConstructorDeclarator -> ConstructorDeclarator -> Bool
compare :: ConstructorDeclarator -> ConstructorDeclarator -> Ordering
$ccompare :: ConstructorDeclarator -> ConstructorDeclarator -> Ordering
Ord, ReadPrec [ConstructorDeclarator]
ReadPrec ConstructorDeclarator
Int -> ReadS ConstructorDeclarator
ReadS [ConstructorDeclarator]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ConstructorDeclarator]
$creadListPrec :: ReadPrec [ConstructorDeclarator]
readPrec :: ReadPrec ConstructorDeclarator
$creadPrec :: ReadPrec ConstructorDeclarator
readList :: ReadS [ConstructorDeclarator]
$creadList :: ReadS [ConstructorDeclarator]
readsPrec :: Int -> ReadS ConstructorDeclarator
$creadsPrec :: Int -> ReadS ConstructorDeclarator
Read, Int -> ConstructorDeclarator -> String -> String
[ConstructorDeclarator] -> String -> String
ConstructorDeclarator -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ConstructorDeclarator] -> String -> String
$cshowList :: [ConstructorDeclarator] -> String -> String
show :: ConstructorDeclarator -> String
$cshow :: ConstructorDeclarator -> String
showsPrec :: Int -> ConstructorDeclarator -> String -> String
$cshowsPrec :: Int -> ConstructorDeclarator -> String -> String
Show)

_ConstructorDeclarator :: Name
_ConstructorDeclarator = (String -> Name
Core.Name String
"hydra/ext/java/syntax.ConstructorDeclarator")

_ConstructorDeclarator_parameters :: FieldName
_ConstructorDeclarator_parameters = (String -> FieldName
Core.FieldName String
"parameters")

_ConstructorDeclarator_name :: FieldName
_ConstructorDeclarator_name = (String -> FieldName
Core.FieldName String
"name")

_ConstructorDeclarator_receiverParameter :: FieldName
_ConstructorDeclarator_receiverParameter = (String -> FieldName
Core.FieldName String
"receiverParameter")

_ConstructorDeclarator_formalParameters :: FieldName
_ConstructorDeclarator_formalParameters = (String -> FieldName
Core.FieldName String
"formalParameters")

newtype SimpleTypeName = 
  SimpleTypeName {
    SimpleTypeName -> TypeIdentifier
unSimpleTypeName :: TypeIdentifier}
  deriving (SimpleTypeName -> SimpleTypeName -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SimpleTypeName -> SimpleTypeName -> Bool
$c/= :: SimpleTypeName -> SimpleTypeName -> Bool
== :: SimpleTypeName -> SimpleTypeName -> Bool
$c== :: SimpleTypeName -> SimpleTypeName -> Bool
Eq, Eq SimpleTypeName
SimpleTypeName -> SimpleTypeName -> Bool
SimpleTypeName -> SimpleTypeName -> Ordering
SimpleTypeName -> SimpleTypeName -> SimpleTypeName
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: SimpleTypeName -> SimpleTypeName -> SimpleTypeName
$cmin :: SimpleTypeName -> SimpleTypeName -> SimpleTypeName
max :: SimpleTypeName -> SimpleTypeName -> SimpleTypeName
$cmax :: SimpleTypeName -> SimpleTypeName -> SimpleTypeName
>= :: SimpleTypeName -> SimpleTypeName -> Bool
$c>= :: SimpleTypeName -> SimpleTypeName -> Bool
> :: SimpleTypeName -> SimpleTypeName -> Bool
$c> :: SimpleTypeName -> SimpleTypeName -> Bool
<= :: SimpleTypeName -> SimpleTypeName -> Bool
$c<= :: SimpleTypeName -> SimpleTypeName -> Bool
< :: SimpleTypeName -> SimpleTypeName -> Bool
$c< :: SimpleTypeName -> SimpleTypeName -> Bool
compare :: SimpleTypeName -> SimpleTypeName -> Ordering
$ccompare :: SimpleTypeName -> SimpleTypeName -> Ordering
Ord, ReadPrec [SimpleTypeName]
ReadPrec SimpleTypeName
Int -> ReadS SimpleTypeName
ReadS [SimpleTypeName]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SimpleTypeName]
$creadListPrec :: ReadPrec [SimpleTypeName]
readPrec :: ReadPrec SimpleTypeName
$creadPrec :: ReadPrec SimpleTypeName
readList :: ReadS [SimpleTypeName]
$creadList :: ReadS [SimpleTypeName]
readsPrec :: Int -> ReadS SimpleTypeName
$creadsPrec :: Int -> ReadS SimpleTypeName
Read, Int -> SimpleTypeName -> String -> String
[SimpleTypeName] -> String -> String
SimpleTypeName -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [SimpleTypeName] -> String -> String
$cshowList :: [SimpleTypeName] -> String -> String
show :: SimpleTypeName -> String
$cshow :: SimpleTypeName -> String
showsPrec :: Int -> SimpleTypeName -> String -> String
$cshowsPrec :: Int -> SimpleTypeName -> String -> String
Show)

_SimpleTypeName :: Name
_SimpleTypeName = (String -> Name
Core.Name String
"hydra/ext/java/syntax.SimpleTypeName")

data ConstructorBody = 
  ConstructorBody {
    ConstructorBody -> Maybe ExplicitConstructorInvocation
constructorBodyInvocation :: (Maybe ExplicitConstructorInvocation),
    ConstructorBody -> [BlockStatement]
constructorBodyStatements :: [BlockStatement]}
  deriving (ConstructorBody -> ConstructorBody -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ConstructorBody -> ConstructorBody -> Bool
$c/= :: ConstructorBody -> ConstructorBody -> Bool
== :: ConstructorBody -> ConstructorBody -> Bool
$c== :: ConstructorBody -> ConstructorBody -> Bool
Eq, Eq ConstructorBody
ConstructorBody -> ConstructorBody -> Bool
ConstructorBody -> ConstructorBody -> Ordering
ConstructorBody -> ConstructorBody -> ConstructorBody
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ConstructorBody -> ConstructorBody -> ConstructorBody
$cmin :: ConstructorBody -> ConstructorBody -> ConstructorBody
max :: ConstructorBody -> ConstructorBody -> ConstructorBody
$cmax :: ConstructorBody -> ConstructorBody -> ConstructorBody
>= :: ConstructorBody -> ConstructorBody -> Bool
$c>= :: ConstructorBody -> ConstructorBody -> Bool
> :: ConstructorBody -> ConstructorBody -> Bool
$c> :: ConstructorBody -> ConstructorBody -> Bool
<= :: ConstructorBody -> ConstructorBody -> Bool
$c<= :: ConstructorBody -> ConstructorBody -> Bool
< :: ConstructorBody -> ConstructorBody -> Bool
$c< :: ConstructorBody -> ConstructorBody -> Bool
compare :: ConstructorBody -> ConstructorBody -> Ordering
$ccompare :: ConstructorBody -> ConstructorBody -> Ordering
Ord, ReadPrec [ConstructorBody]
ReadPrec ConstructorBody
Int -> ReadS ConstructorBody
ReadS [ConstructorBody]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ConstructorBody]
$creadListPrec :: ReadPrec [ConstructorBody]
readPrec :: ReadPrec ConstructorBody
$creadPrec :: ReadPrec ConstructorBody
readList :: ReadS [ConstructorBody]
$creadList :: ReadS [ConstructorBody]
readsPrec :: Int -> ReadS ConstructorBody
$creadsPrec :: Int -> ReadS ConstructorBody
Read, Int -> ConstructorBody -> String -> String
[ConstructorBody] -> String -> String
ConstructorBody -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ConstructorBody] -> String -> String
$cshowList :: [ConstructorBody] -> String -> String
show :: ConstructorBody -> String
$cshow :: ConstructorBody -> String
showsPrec :: Int -> ConstructorBody -> String -> String
$cshowsPrec :: Int -> ConstructorBody -> String -> String
Show)

_ConstructorBody :: Name
_ConstructorBody = (String -> Name
Core.Name String
"hydra/ext/java/syntax.ConstructorBody")

_ConstructorBody_invocation :: FieldName
_ConstructorBody_invocation = (String -> FieldName
Core.FieldName String
"invocation")

_ConstructorBody_statements :: FieldName
_ConstructorBody_statements = (String -> FieldName
Core.FieldName String
"statements")

data ExplicitConstructorInvocation = 
  ExplicitConstructorInvocation {
    ExplicitConstructorInvocation -> [TypeArgument]
explicitConstructorInvocationTypeArguments :: [TypeArgument],
    ExplicitConstructorInvocation -> [Expression]
explicitConstructorInvocationArguments :: [Expression],
    ExplicitConstructorInvocation
-> ExplicitConstructorInvocation_Variant
explicitConstructorInvocationVariant :: ExplicitConstructorInvocation_Variant}
  deriving (ExplicitConstructorInvocation
-> ExplicitConstructorInvocation -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ExplicitConstructorInvocation
-> ExplicitConstructorInvocation -> Bool
$c/= :: ExplicitConstructorInvocation
-> ExplicitConstructorInvocation -> Bool
== :: ExplicitConstructorInvocation
-> ExplicitConstructorInvocation -> Bool
$c== :: ExplicitConstructorInvocation
-> ExplicitConstructorInvocation -> Bool
Eq, Eq ExplicitConstructorInvocation
ExplicitConstructorInvocation
-> ExplicitConstructorInvocation -> Bool
ExplicitConstructorInvocation
-> ExplicitConstructorInvocation -> Ordering
ExplicitConstructorInvocation
-> ExplicitConstructorInvocation -> ExplicitConstructorInvocation
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ExplicitConstructorInvocation
-> ExplicitConstructorInvocation -> ExplicitConstructorInvocation
$cmin :: ExplicitConstructorInvocation
-> ExplicitConstructorInvocation -> ExplicitConstructorInvocation
max :: ExplicitConstructorInvocation
-> ExplicitConstructorInvocation -> ExplicitConstructorInvocation
$cmax :: ExplicitConstructorInvocation
-> ExplicitConstructorInvocation -> ExplicitConstructorInvocation
>= :: ExplicitConstructorInvocation
-> ExplicitConstructorInvocation -> Bool
$c>= :: ExplicitConstructorInvocation
-> ExplicitConstructorInvocation -> Bool
> :: ExplicitConstructorInvocation
-> ExplicitConstructorInvocation -> Bool
$c> :: ExplicitConstructorInvocation
-> ExplicitConstructorInvocation -> Bool
<= :: ExplicitConstructorInvocation
-> ExplicitConstructorInvocation -> Bool
$c<= :: ExplicitConstructorInvocation
-> ExplicitConstructorInvocation -> Bool
< :: ExplicitConstructorInvocation
-> ExplicitConstructorInvocation -> Bool
$c< :: ExplicitConstructorInvocation
-> ExplicitConstructorInvocation -> Bool
compare :: ExplicitConstructorInvocation
-> ExplicitConstructorInvocation -> Ordering
$ccompare :: ExplicitConstructorInvocation
-> ExplicitConstructorInvocation -> Ordering
Ord, ReadPrec [ExplicitConstructorInvocation]
ReadPrec ExplicitConstructorInvocation
Int -> ReadS ExplicitConstructorInvocation
ReadS [ExplicitConstructorInvocation]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ExplicitConstructorInvocation]
$creadListPrec :: ReadPrec [ExplicitConstructorInvocation]
readPrec :: ReadPrec ExplicitConstructorInvocation
$creadPrec :: ReadPrec ExplicitConstructorInvocation
readList :: ReadS [ExplicitConstructorInvocation]
$creadList :: ReadS [ExplicitConstructorInvocation]
readsPrec :: Int -> ReadS ExplicitConstructorInvocation
$creadsPrec :: Int -> ReadS ExplicitConstructorInvocation
Read, Int -> ExplicitConstructorInvocation -> String -> String
[ExplicitConstructorInvocation] -> String -> String
ExplicitConstructorInvocation -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ExplicitConstructorInvocation] -> String -> String
$cshowList :: [ExplicitConstructorInvocation] -> String -> String
show :: ExplicitConstructorInvocation -> String
$cshow :: ExplicitConstructorInvocation -> String
showsPrec :: Int -> ExplicitConstructorInvocation -> String -> String
$cshowsPrec :: Int -> ExplicitConstructorInvocation -> String -> String
Show)

_ExplicitConstructorInvocation :: Name
_ExplicitConstructorInvocation = (String -> Name
Core.Name String
"hydra/ext/java/syntax.ExplicitConstructorInvocation")

_ExplicitConstructorInvocation_typeArguments :: FieldName
_ExplicitConstructorInvocation_typeArguments = (String -> FieldName
Core.FieldName String
"typeArguments")

_ExplicitConstructorInvocation_arguments :: FieldName
_ExplicitConstructorInvocation_arguments = (String -> FieldName
Core.FieldName String
"arguments")

_ExplicitConstructorInvocation_variant :: FieldName
_ExplicitConstructorInvocation_variant = (String -> FieldName
Core.FieldName String
"variant")

data ExplicitConstructorInvocation_Variant = 
  ExplicitConstructorInvocation_VariantThis  |
  ExplicitConstructorInvocation_VariantSuper (Maybe ExpressionName) |
  ExplicitConstructorInvocation_VariantPrimary Primary
  deriving (ExplicitConstructorInvocation_Variant
-> ExplicitConstructorInvocation_Variant -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ExplicitConstructorInvocation_Variant
-> ExplicitConstructorInvocation_Variant -> Bool
$c/= :: ExplicitConstructorInvocation_Variant
-> ExplicitConstructorInvocation_Variant -> Bool
== :: ExplicitConstructorInvocation_Variant
-> ExplicitConstructorInvocation_Variant -> Bool
$c== :: ExplicitConstructorInvocation_Variant
-> ExplicitConstructorInvocation_Variant -> Bool
Eq, Eq ExplicitConstructorInvocation_Variant
ExplicitConstructorInvocation_Variant
-> ExplicitConstructorInvocation_Variant -> Bool
ExplicitConstructorInvocation_Variant
-> ExplicitConstructorInvocation_Variant -> Ordering
ExplicitConstructorInvocation_Variant
-> ExplicitConstructorInvocation_Variant
-> ExplicitConstructorInvocation_Variant
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ExplicitConstructorInvocation_Variant
-> ExplicitConstructorInvocation_Variant
-> ExplicitConstructorInvocation_Variant
$cmin :: ExplicitConstructorInvocation_Variant
-> ExplicitConstructorInvocation_Variant
-> ExplicitConstructorInvocation_Variant
max :: ExplicitConstructorInvocation_Variant
-> ExplicitConstructorInvocation_Variant
-> ExplicitConstructorInvocation_Variant
$cmax :: ExplicitConstructorInvocation_Variant
-> ExplicitConstructorInvocation_Variant
-> ExplicitConstructorInvocation_Variant
>= :: ExplicitConstructorInvocation_Variant
-> ExplicitConstructorInvocation_Variant -> Bool
$c>= :: ExplicitConstructorInvocation_Variant
-> ExplicitConstructorInvocation_Variant -> Bool
> :: ExplicitConstructorInvocation_Variant
-> ExplicitConstructorInvocation_Variant -> Bool
$c> :: ExplicitConstructorInvocation_Variant
-> ExplicitConstructorInvocation_Variant -> Bool
<= :: ExplicitConstructorInvocation_Variant
-> ExplicitConstructorInvocation_Variant -> Bool
$c<= :: ExplicitConstructorInvocation_Variant
-> ExplicitConstructorInvocation_Variant -> Bool
< :: ExplicitConstructorInvocation_Variant
-> ExplicitConstructorInvocation_Variant -> Bool
$c< :: ExplicitConstructorInvocation_Variant
-> ExplicitConstructorInvocation_Variant -> Bool
compare :: ExplicitConstructorInvocation_Variant
-> ExplicitConstructorInvocation_Variant -> Ordering
$ccompare :: ExplicitConstructorInvocation_Variant
-> ExplicitConstructorInvocation_Variant -> Ordering
Ord, ReadPrec [ExplicitConstructorInvocation_Variant]
ReadPrec ExplicitConstructorInvocation_Variant
Int -> ReadS ExplicitConstructorInvocation_Variant
ReadS [ExplicitConstructorInvocation_Variant]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ExplicitConstructorInvocation_Variant]
$creadListPrec :: ReadPrec [ExplicitConstructorInvocation_Variant]
readPrec :: ReadPrec ExplicitConstructorInvocation_Variant
$creadPrec :: ReadPrec ExplicitConstructorInvocation_Variant
readList :: ReadS [ExplicitConstructorInvocation_Variant]
$creadList :: ReadS [ExplicitConstructorInvocation_Variant]
readsPrec :: Int -> ReadS ExplicitConstructorInvocation_Variant
$creadsPrec :: Int -> ReadS ExplicitConstructorInvocation_Variant
Read, Int -> ExplicitConstructorInvocation_Variant -> String -> String
[ExplicitConstructorInvocation_Variant] -> String -> String
ExplicitConstructorInvocation_Variant -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ExplicitConstructorInvocation_Variant] -> String -> String
$cshowList :: [ExplicitConstructorInvocation_Variant] -> String -> String
show :: ExplicitConstructorInvocation_Variant -> String
$cshow :: ExplicitConstructorInvocation_Variant -> String
showsPrec :: Int -> ExplicitConstructorInvocation_Variant -> String -> String
$cshowsPrec :: Int -> ExplicitConstructorInvocation_Variant -> String -> String
Show)

_ExplicitConstructorInvocation_Variant :: Name
_ExplicitConstructorInvocation_Variant = (String -> Name
Core.Name String
"hydra/ext/java/syntax.ExplicitConstructorInvocation.Variant")

_ExplicitConstructorInvocation_Variant_this :: FieldName
_ExplicitConstructorInvocation_Variant_this = (String -> FieldName
Core.FieldName String
"this")

_ExplicitConstructorInvocation_Variant_super :: FieldName
_ExplicitConstructorInvocation_Variant_super = (String -> FieldName
Core.FieldName String
"super")

_ExplicitConstructorInvocation_Variant_primary :: FieldName
_ExplicitConstructorInvocation_Variant_primary = (String -> FieldName
Core.FieldName String
"primary")

data EnumDeclaration = 
  EnumDeclaration {
    EnumDeclaration -> [ClassModifier]
enumDeclarationModifiers :: [ClassModifier],
    EnumDeclaration -> TypeIdentifier
enumDeclarationIdentifier :: TypeIdentifier,
    EnumDeclaration -> [InterfaceType]
enumDeclarationImplements :: [InterfaceType],
    EnumDeclaration -> EnumBody
enumDeclarationBody :: EnumBody}
  deriving (EnumDeclaration -> EnumDeclaration -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EnumDeclaration -> EnumDeclaration -> Bool
$c/= :: EnumDeclaration -> EnumDeclaration -> Bool
== :: EnumDeclaration -> EnumDeclaration -> Bool
$c== :: EnumDeclaration -> EnumDeclaration -> Bool
Eq, Eq EnumDeclaration
EnumDeclaration -> EnumDeclaration -> Bool
EnumDeclaration -> EnumDeclaration -> Ordering
EnumDeclaration -> EnumDeclaration -> EnumDeclaration
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: EnumDeclaration -> EnumDeclaration -> EnumDeclaration
$cmin :: EnumDeclaration -> EnumDeclaration -> EnumDeclaration
max :: EnumDeclaration -> EnumDeclaration -> EnumDeclaration
$cmax :: EnumDeclaration -> EnumDeclaration -> EnumDeclaration
>= :: EnumDeclaration -> EnumDeclaration -> Bool
$c>= :: EnumDeclaration -> EnumDeclaration -> Bool
> :: EnumDeclaration -> EnumDeclaration -> Bool
$c> :: EnumDeclaration -> EnumDeclaration -> Bool
<= :: EnumDeclaration -> EnumDeclaration -> Bool
$c<= :: EnumDeclaration -> EnumDeclaration -> Bool
< :: EnumDeclaration -> EnumDeclaration -> Bool
$c< :: EnumDeclaration -> EnumDeclaration -> Bool
compare :: EnumDeclaration -> EnumDeclaration -> Ordering
$ccompare :: EnumDeclaration -> EnumDeclaration -> Ordering
Ord, ReadPrec [EnumDeclaration]
ReadPrec EnumDeclaration
Int -> ReadS EnumDeclaration
ReadS [EnumDeclaration]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [EnumDeclaration]
$creadListPrec :: ReadPrec [EnumDeclaration]
readPrec :: ReadPrec EnumDeclaration
$creadPrec :: ReadPrec EnumDeclaration
readList :: ReadS [EnumDeclaration]
$creadList :: ReadS [EnumDeclaration]
readsPrec :: Int -> ReadS EnumDeclaration
$creadsPrec :: Int -> ReadS EnumDeclaration
Read, Int -> EnumDeclaration -> String -> String
[EnumDeclaration] -> String -> String
EnumDeclaration -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [EnumDeclaration] -> String -> String
$cshowList :: [EnumDeclaration] -> String -> String
show :: EnumDeclaration -> String
$cshow :: EnumDeclaration -> String
showsPrec :: Int -> EnumDeclaration -> String -> String
$cshowsPrec :: Int -> EnumDeclaration -> String -> String
Show)

_EnumDeclaration :: Name
_EnumDeclaration = (String -> Name
Core.Name String
"hydra/ext/java/syntax.EnumDeclaration")

_EnumDeclaration_modifiers :: FieldName
_EnumDeclaration_modifiers = (String -> FieldName
Core.FieldName String
"modifiers")

_EnumDeclaration_identifier :: FieldName
_EnumDeclaration_identifier = (String -> FieldName
Core.FieldName String
"identifier")

_EnumDeclaration_implements :: FieldName
_EnumDeclaration_implements = (String -> FieldName
Core.FieldName String
"implements")

_EnumDeclaration_body :: FieldName
_EnumDeclaration_body = (String -> FieldName
Core.FieldName String
"body")

newtype EnumBody = 
  EnumBody {
    EnumBody -> [EnumBody_Element]
unEnumBody :: [EnumBody_Element]}
  deriving (EnumBody -> EnumBody -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EnumBody -> EnumBody -> Bool
$c/= :: EnumBody -> EnumBody -> Bool
== :: EnumBody -> EnumBody -> Bool
$c== :: EnumBody -> EnumBody -> Bool
Eq, Eq EnumBody
EnumBody -> EnumBody -> Bool
EnumBody -> EnumBody -> Ordering
EnumBody -> EnumBody -> EnumBody
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: EnumBody -> EnumBody -> EnumBody
$cmin :: EnumBody -> EnumBody -> EnumBody
max :: EnumBody -> EnumBody -> EnumBody
$cmax :: EnumBody -> EnumBody -> EnumBody
>= :: EnumBody -> EnumBody -> Bool
$c>= :: EnumBody -> EnumBody -> Bool
> :: EnumBody -> EnumBody -> Bool
$c> :: EnumBody -> EnumBody -> Bool
<= :: EnumBody -> EnumBody -> Bool
$c<= :: EnumBody -> EnumBody -> Bool
< :: EnumBody -> EnumBody -> Bool
$c< :: EnumBody -> EnumBody -> Bool
compare :: EnumBody -> EnumBody -> Ordering
$ccompare :: EnumBody -> EnumBody -> Ordering
Ord, ReadPrec [EnumBody]
ReadPrec EnumBody
Int -> ReadS EnumBody
ReadS [EnumBody]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [EnumBody]
$creadListPrec :: ReadPrec [EnumBody]
readPrec :: ReadPrec EnumBody
$creadPrec :: ReadPrec EnumBody
readList :: ReadS [EnumBody]
$creadList :: ReadS [EnumBody]
readsPrec :: Int -> ReadS EnumBody
$creadsPrec :: Int -> ReadS EnumBody
Read, Int -> EnumBody -> String -> String
[EnumBody] -> String -> String
EnumBody -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [EnumBody] -> String -> String
$cshowList :: [EnumBody] -> String -> String
show :: EnumBody -> String
$cshow :: EnumBody -> String
showsPrec :: Int -> EnumBody -> String -> String
$cshowsPrec :: Int -> EnumBody -> String -> String
Show)

_EnumBody :: Name
_EnumBody = (String -> Name
Core.Name String
"hydra/ext/java/syntax.EnumBody")

data EnumBody_Element = 
  EnumBody_Element {
    EnumBody_Element -> [EnumConstant]
enumBody_ElementConstants :: [EnumConstant],
    EnumBody_Element -> [ClassBodyDeclaration]
enumBody_ElementBodyDeclarations :: [ClassBodyDeclaration]}
  deriving (EnumBody_Element -> EnumBody_Element -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EnumBody_Element -> EnumBody_Element -> Bool
$c/= :: EnumBody_Element -> EnumBody_Element -> Bool
== :: EnumBody_Element -> EnumBody_Element -> Bool
$c== :: EnumBody_Element -> EnumBody_Element -> Bool
Eq, Eq EnumBody_Element
EnumBody_Element -> EnumBody_Element -> Bool
EnumBody_Element -> EnumBody_Element -> Ordering
EnumBody_Element -> EnumBody_Element -> EnumBody_Element
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: EnumBody_Element -> EnumBody_Element -> EnumBody_Element
$cmin :: EnumBody_Element -> EnumBody_Element -> EnumBody_Element
max :: EnumBody_Element -> EnumBody_Element -> EnumBody_Element
$cmax :: EnumBody_Element -> EnumBody_Element -> EnumBody_Element
>= :: EnumBody_Element -> EnumBody_Element -> Bool
$c>= :: EnumBody_Element -> EnumBody_Element -> Bool
> :: EnumBody_Element -> EnumBody_Element -> Bool
$c> :: EnumBody_Element -> EnumBody_Element -> Bool
<= :: EnumBody_Element -> EnumBody_Element -> Bool
$c<= :: EnumBody_Element -> EnumBody_Element -> Bool
< :: EnumBody_Element -> EnumBody_Element -> Bool
$c< :: EnumBody_Element -> EnumBody_Element -> Bool
compare :: EnumBody_Element -> EnumBody_Element -> Ordering
$ccompare :: EnumBody_Element -> EnumBody_Element -> Ordering
Ord, ReadPrec [EnumBody_Element]
ReadPrec EnumBody_Element
Int -> ReadS EnumBody_Element
ReadS [EnumBody_Element]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [EnumBody_Element]
$creadListPrec :: ReadPrec [EnumBody_Element]
readPrec :: ReadPrec EnumBody_Element
$creadPrec :: ReadPrec EnumBody_Element
readList :: ReadS [EnumBody_Element]
$creadList :: ReadS [EnumBody_Element]
readsPrec :: Int -> ReadS EnumBody_Element
$creadsPrec :: Int -> ReadS EnumBody_Element
Read, Int -> EnumBody_Element -> String -> String
[EnumBody_Element] -> String -> String
EnumBody_Element -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [EnumBody_Element] -> String -> String
$cshowList :: [EnumBody_Element] -> String -> String
show :: EnumBody_Element -> String
$cshow :: EnumBody_Element -> String
showsPrec :: Int -> EnumBody_Element -> String -> String
$cshowsPrec :: Int -> EnumBody_Element -> String -> String
Show)

_EnumBody_Element :: Name
_EnumBody_Element = (String -> Name
Core.Name String
"hydra/ext/java/syntax.EnumBody.Element")

_EnumBody_Element_constants :: FieldName
_EnumBody_Element_constants = (String -> FieldName
Core.FieldName String
"constants")

_EnumBody_Element_bodyDeclarations :: FieldName
_EnumBody_Element_bodyDeclarations = (String -> FieldName
Core.FieldName String
"bodyDeclarations")

data EnumConstant = 
  EnumConstant {
    EnumConstant -> [EnumConstantModifier]
enumConstantModifiers :: [EnumConstantModifier],
    EnumConstant -> Identifier
enumConstantIdentifier :: Identifier,
    EnumConstant -> [[Expression]]
enumConstantArguments :: [[Expression]],
    EnumConstant -> Maybe ClassBody
enumConstantBody :: (Maybe ClassBody)}
  deriving (EnumConstant -> EnumConstant -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EnumConstant -> EnumConstant -> Bool
$c/= :: EnumConstant -> EnumConstant -> Bool
== :: EnumConstant -> EnumConstant -> Bool
$c== :: EnumConstant -> EnumConstant -> Bool
Eq, Eq EnumConstant
EnumConstant -> EnumConstant -> Bool
EnumConstant -> EnumConstant -> Ordering
EnumConstant -> EnumConstant -> EnumConstant
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: EnumConstant -> EnumConstant -> EnumConstant
$cmin :: EnumConstant -> EnumConstant -> EnumConstant
max :: EnumConstant -> EnumConstant -> EnumConstant
$cmax :: EnumConstant -> EnumConstant -> EnumConstant
>= :: EnumConstant -> EnumConstant -> Bool
$c>= :: EnumConstant -> EnumConstant -> Bool
> :: EnumConstant -> EnumConstant -> Bool
$c> :: EnumConstant -> EnumConstant -> Bool
<= :: EnumConstant -> EnumConstant -> Bool
$c<= :: EnumConstant -> EnumConstant -> Bool
< :: EnumConstant -> EnumConstant -> Bool
$c< :: EnumConstant -> EnumConstant -> Bool
compare :: EnumConstant -> EnumConstant -> Ordering
$ccompare :: EnumConstant -> EnumConstant -> Ordering
Ord, ReadPrec [EnumConstant]
ReadPrec EnumConstant
Int -> ReadS EnumConstant
ReadS [EnumConstant]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [EnumConstant]
$creadListPrec :: ReadPrec [EnumConstant]
readPrec :: ReadPrec EnumConstant
$creadPrec :: ReadPrec EnumConstant
readList :: ReadS [EnumConstant]
$creadList :: ReadS [EnumConstant]
readsPrec :: Int -> ReadS EnumConstant
$creadsPrec :: Int -> ReadS EnumConstant
Read, Int -> EnumConstant -> String -> String
[EnumConstant] -> String -> String
EnumConstant -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [EnumConstant] -> String -> String
$cshowList :: [EnumConstant] -> String -> String
show :: EnumConstant -> String
$cshow :: EnumConstant -> String
showsPrec :: Int -> EnumConstant -> String -> String
$cshowsPrec :: Int -> EnumConstant -> String -> String
Show)

_EnumConstant :: Name
_EnumConstant = (String -> Name
Core.Name String
"hydra/ext/java/syntax.EnumConstant")

_EnumConstant_modifiers :: FieldName
_EnumConstant_modifiers = (String -> FieldName
Core.FieldName String
"modifiers")

_EnumConstant_identifier :: FieldName
_EnumConstant_identifier = (String -> FieldName
Core.FieldName String
"identifier")

_EnumConstant_arguments :: FieldName
_EnumConstant_arguments = (String -> FieldName
Core.FieldName String
"arguments")

_EnumConstant_body :: FieldName
_EnumConstant_body = (String -> FieldName
Core.FieldName String
"body")

newtype EnumConstantModifier = 
  EnumConstantModifier {
    EnumConstantModifier -> Annotation
unEnumConstantModifier :: Annotation}
  deriving (EnumConstantModifier -> EnumConstantModifier -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EnumConstantModifier -> EnumConstantModifier -> Bool
$c/= :: EnumConstantModifier -> EnumConstantModifier -> Bool
== :: EnumConstantModifier -> EnumConstantModifier -> Bool
$c== :: EnumConstantModifier -> EnumConstantModifier -> Bool
Eq, Eq EnumConstantModifier
EnumConstantModifier -> EnumConstantModifier -> Bool
EnumConstantModifier -> EnumConstantModifier -> Ordering
EnumConstantModifier
-> EnumConstantModifier -> EnumConstantModifier
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: EnumConstantModifier
-> EnumConstantModifier -> EnumConstantModifier
$cmin :: EnumConstantModifier
-> EnumConstantModifier -> EnumConstantModifier
max :: EnumConstantModifier
-> EnumConstantModifier -> EnumConstantModifier
$cmax :: EnumConstantModifier
-> EnumConstantModifier -> EnumConstantModifier
>= :: EnumConstantModifier -> EnumConstantModifier -> Bool
$c>= :: EnumConstantModifier -> EnumConstantModifier -> Bool
> :: EnumConstantModifier -> EnumConstantModifier -> Bool
$c> :: EnumConstantModifier -> EnumConstantModifier -> Bool
<= :: EnumConstantModifier -> EnumConstantModifier -> Bool
$c<= :: EnumConstantModifier -> EnumConstantModifier -> Bool
< :: EnumConstantModifier -> EnumConstantModifier -> Bool
$c< :: EnumConstantModifier -> EnumConstantModifier -> Bool
compare :: EnumConstantModifier -> EnumConstantModifier -> Ordering
$ccompare :: EnumConstantModifier -> EnumConstantModifier -> Ordering
Ord, ReadPrec [EnumConstantModifier]
ReadPrec EnumConstantModifier
Int -> ReadS EnumConstantModifier
ReadS [EnumConstantModifier]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [EnumConstantModifier]
$creadListPrec :: ReadPrec [EnumConstantModifier]
readPrec :: ReadPrec EnumConstantModifier
$creadPrec :: ReadPrec EnumConstantModifier
readList :: ReadS [EnumConstantModifier]
$creadList :: ReadS [EnumConstantModifier]
readsPrec :: Int -> ReadS EnumConstantModifier
$creadsPrec :: Int -> ReadS EnumConstantModifier
Read, Int -> EnumConstantModifier -> String -> String
[EnumConstantModifier] -> String -> String
EnumConstantModifier -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [EnumConstantModifier] -> String -> String
$cshowList :: [EnumConstantModifier] -> String -> String
show :: EnumConstantModifier -> String
$cshow :: EnumConstantModifier -> String
showsPrec :: Int -> EnumConstantModifier -> String -> String
$cshowsPrec :: Int -> EnumConstantModifier -> String -> String
Show)

_EnumConstantModifier :: Name
_EnumConstantModifier = (String -> Name
Core.Name String
"hydra/ext/java/syntax.EnumConstantModifier")

data InterfaceDeclaration = 
  InterfaceDeclarationNormalInterface NormalInterfaceDeclaration |
  InterfaceDeclarationAnnotationType AnnotationTypeDeclaration
  deriving (InterfaceDeclaration -> InterfaceDeclaration -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InterfaceDeclaration -> InterfaceDeclaration -> Bool
$c/= :: InterfaceDeclaration -> InterfaceDeclaration -> Bool
== :: InterfaceDeclaration -> InterfaceDeclaration -> Bool
$c== :: InterfaceDeclaration -> InterfaceDeclaration -> Bool
Eq, Eq InterfaceDeclaration
InterfaceDeclaration -> InterfaceDeclaration -> Bool
InterfaceDeclaration -> InterfaceDeclaration -> Ordering
InterfaceDeclaration
-> InterfaceDeclaration -> InterfaceDeclaration
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: InterfaceDeclaration
-> InterfaceDeclaration -> InterfaceDeclaration
$cmin :: InterfaceDeclaration
-> InterfaceDeclaration -> InterfaceDeclaration
max :: InterfaceDeclaration
-> InterfaceDeclaration -> InterfaceDeclaration
$cmax :: InterfaceDeclaration
-> InterfaceDeclaration -> InterfaceDeclaration
>= :: InterfaceDeclaration -> InterfaceDeclaration -> Bool
$c>= :: InterfaceDeclaration -> InterfaceDeclaration -> Bool
> :: InterfaceDeclaration -> InterfaceDeclaration -> Bool
$c> :: InterfaceDeclaration -> InterfaceDeclaration -> Bool
<= :: InterfaceDeclaration -> InterfaceDeclaration -> Bool
$c<= :: InterfaceDeclaration -> InterfaceDeclaration -> Bool
< :: InterfaceDeclaration -> InterfaceDeclaration -> Bool
$c< :: InterfaceDeclaration -> InterfaceDeclaration -> Bool
compare :: InterfaceDeclaration -> InterfaceDeclaration -> Ordering
$ccompare :: InterfaceDeclaration -> InterfaceDeclaration -> Ordering
Ord, ReadPrec [InterfaceDeclaration]
ReadPrec InterfaceDeclaration
Int -> ReadS InterfaceDeclaration
ReadS [InterfaceDeclaration]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [InterfaceDeclaration]
$creadListPrec :: ReadPrec [InterfaceDeclaration]
readPrec :: ReadPrec InterfaceDeclaration
$creadPrec :: ReadPrec InterfaceDeclaration
readList :: ReadS [InterfaceDeclaration]
$creadList :: ReadS [InterfaceDeclaration]
readsPrec :: Int -> ReadS InterfaceDeclaration
$creadsPrec :: Int -> ReadS InterfaceDeclaration
Read, Int -> InterfaceDeclaration -> String -> String
[InterfaceDeclaration] -> String -> String
InterfaceDeclaration -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [InterfaceDeclaration] -> String -> String
$cshowList :: [InterfaceDeclaration] -> String -> String
show :: InterfaceDeclaration -> String
$cshow :: InterfaceDeclaration -> String
showsPrec :: Int -> InterfaceDeclaration -> String -> String
$cshowsPrec :: Int -> InterfaceDeclaration -> String -> String
Show)

_InterfaceDeclaration :: Name
_InterfaceDeclaration = (String -> Name
Core.Name String
"hydra/ext/java/syntax.InterfaceDeclaration")

_InterfaceDeclaration_normalInterface :: FieldName
_InterfaceDeclaration_normalInterface = (String -> FieldName
Core.FieldName String
"normalInterface")

_InterfaceDeclaration_annotationType :: FieldName
_InterfaceDeclaration_annotationType = (String -> FieldName
Core.FieldName String
"annotationType")

data NormalInterfaceDeclaration = 
  NormalInterfaceDeclaration {
    NormalInterfaceDeclaration -> [InterfaceModifier]
normalInterfaceDeclarationModifiers :: [InterfaceModifier],
    NormalInterfaceDeclaration -> TypeIdentifier
normalInterfaceDeclarationIdentifier :: TypeIdentifier,
    NormalInterfaceDeclaration -> [TypeParameter]
normalInterfaceDeclarationParameters :: [TypeParameter],
    NormalInterfaceDeclaration -> [InterfaceType]
normalInterfaceDeclarationExtends :: [InterfaceType],
    NormalInterfaceDeclaration -> InterfaceBody
normalInterfaceDeclarationBody :: InterfaceBody}
  deriving (NormalInterfaceDeclaration -> NormalInterfaceDeclaration -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NormalInterfaceDeclaration -> NormalInterfaceDeclaration -> Bool
$c/= :: NormalInterfaceDeclaration -> NormalInterfaceDeclaration -> Bool
== :: NormalInterfaceDeclaration -> NormalInterfaceDeclaration -> Bool
$c== :: NormalInterfaceDeclaration -> NormalInterfaceDeclaration -> Bool
Eq, Eq NormalInterfaceDeclaration
NormalInterfaceDeclaration -> NormalInterfaceDeclaration -> Bool
NormalInterfaceDeclaration
-> NormalInterfaceDeclaration -> Ordering
NormalInterfaceDeclaration
-> NormalInterfaceDeclaration -> NormalInterfaceDeclaration
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: NormalInterfaceDeclaration
-> NormalInterfaceDeclaration -> NormalInterfaceDeclaration
$cmin :: NormalInterfaceDeclaration
-> NormalInterfaceDeclaration -> NormalInterfaceDeclaration
max :: NormalInterfaceDeclaration
-> NormalInterfaceDeclaration -> NormalInterfaceDeclaration
$cmax :: NormalInterfaceDeclaration
-> NormalInterfaceDeclaration -> NormalInterfaceDeclaration
>= :: NormalInterfaceDeclaration -> NormalInterfaceDeclaration -> Bool
$c>= :: NormalInterfaceDeclaration -> NormalInterfaceDeclaration -> Bool
> :: NormalInterfaceDeclaration -> NormalInterfaceDeclaration -> Bool
$c> :: NormalInterfaceDeclaration -> NormalInterfaceDeclaration -> Bool
<= :: NormalInterfaceDeclaration -> NormalInterfaceDeclaration -> Bool
$c<= :: NormalInterfaceDeclaration -> NormalInterfaceDeclaration -> Bool
< :: NormalInterfaceDeclaration -> NormalInterfaceDeclaration -> Bool
$c< :: NormalInterfaceDeclaration -> NormalInterfaceDeclaration -> Bool
compare :: NormalInterfaceDeclaration
-> NormalInterfaceDeclaration -> Ordering
$ccompare :: NormalInterfaceDeclaration
-> NormalInterfaceDeclaration -> Ordering
Ord, ReadPrec [NormalInterfaceDeclaration]
ReadPrec NormalInterfaceDeclaration
Int -> ReadS NormalInterfaceDeclaration
ReadS [NormalInterfaceDeclaration]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [NormalInterfaceDeclaration]
$creadListPrec :: ReadPrec [NormalInterfaceDeclaration]
readPrec :: ReadPrec NormalInterfaceDeclaration
$creadPrec :: ReadPrec NormalInterfaceDeclaration
readList :: ReadS [NormalInterfaceDeclaration]
$creadList :: ReadS [NormalInterfaceDeclaration]
readsPrec :: Int -> ReadS NormalInterfaceDeclaration
$creadsPrec :: Int -> ReadS NormalInterfaceDeclaration
Read, Int -> NormalInterfaceDeclaration -> String -> String
[NormalInterfaceDeclaration] -> String -> String
NormalInterfaceDeclaration -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [NormalInterfaceDeclaration] -> String -> String
$cshowList :: [NormalInterfaceDeclaration] -> String -> String
show :: NormalInterfaceDeclaration -> String
$cshow :: NormalInterfaceDeclaration -> String
showsPrec :: Int -> NormalInterfaceDeclaration -> String -> String
$cshowsPrec :: Int -> NormalInterfaceDeclaration -> String -> String
Show)

_NormalInterfaceDeclaration :: Name
_NormalInterfaceDeclaration = (String -> Name
Core.Name String
"hydra/ext/java/syntax.NormalInterfaceDeclaration")

_NormalInterfaceDeclaration_modifiers :: FieldName
_NormalInterfaceDeclaration_modifiers = (String -> FieldName
Core.FieldName String
"modifiers")

_NormalInterfaceDeclaration_identifier :: FieldName
_NormalInterfaceDeclaration_identifier = (String -> FieldName
Core.FieldName String
"identifier")

_NormalInterfaceDeclaration_parameters :: FieldName
_NormalInterfaceDeclaration_parameters = (String -> FieldName
Core.FieldName String
"parameters")

_NormalInterfaceDeclaration_extends :: FieldName
_NormalInterfaceDeclaration_extends = (String -> FieldName
Core.FieldName String
"extends")

_NormalInterfaceDeclaration_body :: FieldName
_NormalInterfaceDeclaration_body = (String -> FieldName
Core.FieldName String
"body")

data InterfaceModifier = 
  InterfaceModifierAnnotation Annotation |
  InterfaceModifierPublic  |
  InterfaceModifierProtected  |
  InterfaceModifierPrivate  |
  InterfaceModifierAbstract  |
  InterfaceModifierStatic  |
  InterfaceModifierStrictfb 
  deriving (InterfaceModifier -> InterfaceModifier -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InterfaceModifier -> InterfaceModifier -> Bool
$c/= :: InterfaceModifier -> InterfaceModifier -> Bool
== :: InterfaceModifier -> InterfaceModifier -> Bool
$c== :: InterfaceModifier -> InterfaceModifier -> Bool
Eq, Eq InterfaceModifier
InterfaceModifier -> InterfaceModifier -> Bool
InterfaceModifier -> InterfaceModifier -> Ordering
InterfaceModifier -> InterfaceModifier -> InterfaceModifier
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: InterfaceModifier -> InterfaceModifier -> InterfaceModifier
$cmin :: InterfaceModifier -> InterfaceModifier -> InterfaceModifier
max :: InterfaceModifier -> InterfaceModifier -> InterfaceModifier
$cmax :: InterfaceModifier -> InterfaceModifier -> InterfaceModifier
>= :: InterfaceModifier -> InterfaceModifier -> Bool
$c>= :: InterfaceModifier -> InterfaceModifier -> Bool
> :: InterfaceModifier -> InterfaceModifier -> Bool
$c> :: InterfaceModifier -> InterfaceModifier -> Bool
<= :: InterfaceModifier -> InterfaceModifier -> Bool
$c<= :: InterfaceModifier -> InterfaceModifier -> Bool
< :: InterfaceModifier -> InterfaceModifier -> Bool
$c< :: InterfaceModifier -> InterfaceModifier -> Bool
compare :: InterfaceModifier -> InterfaceModifier -> Ordering
$ccompare :: InterfaceModifier -> InterfaceModifier -> Ordering
Ord, ReadPrec [InterfaceModifier]
ReadPrec InterfaceModifier
Int -> ReadS InterfaceModifier
ReadS [InterfaceModifier]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [InterfaceModifier]
$creadListPrec :: ReadPrec [InterfaceModifier]
readPrec :: ReadPrec InterfaceModifier
$creadPrec :: ReadPrec InterfaceModifier
readList :: ReadS [InterfaceModifier]
$creadList :: ReadS [InterfaceModifier]
readsPrec :: Int -> ReadS InterfaceModifier
$creadsPrec :: Int -> ReadS InterfaceModifier
Read, Int -> InterfaceModifier -> String -> String
[InterfaceModifier] -> String -> String
InterfaceModifier -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [InterfaceModifier] -> String -> String
$cshowList :: [InterfaceModifier] -> String -> String
show :: InterfaceModifier -> String
$cshow :: InterfaceModifier -> String
showsPrec :: Int -> InterfaceModifier -> String -> String
$cshowsPrec :: Int -> InterfaceModifier -> String -> String
Show)

_InterfaceModifier :: Name
_InterfaceModifier = (String -> Name
Core.Name String
"hydra/ext/java/syntax.InterfaceModifier")

_InterfaceModifier_annotation :: FieldName
_InterfaceModifier_annotation = (String -> FieldName
Core.FieldName String
"annotation")

_InterfaceModifier_public :: FieldName
_InterfaceModifier_public = (String -> FieldName
Core.FieldName String
"public")

_InterfaceModifier_protected :: FieldName
_InterfaceModifier_protected = (String -> FieldName
Core.FieldName String
"protected")

_InterfaceModifier_private :: FieldName
_InterfaceModifier_private = (String -> FieldName
Core.FieldName String
"private")

_InterfaceModifier_abstract :: FieldName
_InterfaceModifier_abstract = (String -> FieldName
Core.FieldName String
"abstract")

_InterfaceModifier_static :: FieldName
_InterfaceModifier_static = (String -> FieldName
Core.FieldName String
"static")

_InterfaceModifier_strictfb :: FieldName
_InterfaceModifier_strictfb = (String -> FieldName
Core.FieldName String
"strictfb")

newtype InterfaceBody = 
  InterfaceBody {
    InterfaceBody -> [InterfaceMemberDeclaration]
unInterfaceBody :: [InterfaceMemberDeclaration]}
  deriving (InterfaceBody -> InterfaceBody -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InterfaceBody -> InterfaceBody -> Bool
$c/= :: InterfaceBody -> InterfaceBody -> Bool
== :: InterfaceBody -> InterfaceBody -> Bool
$c== :: InterfaceBody -> InterfaceBody -> Bool
Eq, Eq InterfaceBody
InterfaceBody -> InterfaceBody -> Bool
InterfaceBody -> InterfaceBody -> Ordering
InterfaceBody -> InterfaceBody -> InterfaceBody
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: InterfaceBody -> InterfaceBody -> InterfaceBody
$cmin :: InterfaceBody -> InterfaceBody -> InterfaceBody
max :: InterfaceBody -> InterfaceBody -> InterfaceBody
$cmax :: InterfaceBody -> InterfaceBody -> InterfaceBody
>= :: InterfaceBody -> InterfaceBody -> Bool
$c>= :: InterfaceBody -> InterfaceBody -> Bool
> :: InterfaceBody -> InterfaceBody -> Bool
$c> :: InterfaceBody -> InterfaceBody -> Bool
<= :: InterfaceBody -> InterfaceBody -> Bool
$c<= :: InterfaceBody -> InterfaceBody -> Bool
< :: InterfaceBody -> InterfaceBody -> Bool
$c< :: InterfaceBody -> InterfaceBody -> Bool
compare :: InterfaceBody -> InterfaceBody -> Ordering
$ccompare :: InterfaceBody -> InterfaceBody -> Ordering
Ord, ReadPrec [InterfaceBody]
ReadPrec InterfaceBody
Int -> ReadS InterfaceBody
ReadS [InterfaceBody]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [InterfaceBody]
$creadListPrec :: ReadPrec [InterfaceBody]
readPrec :: ReadPrec InterfaceBody
$creadPrec :: ReadPrec InterfaceBody
readList :: ReadS [InterfaceBody]
$creadList :: ReadS [InterfaceBody]
readsPrec :: Int -> ReadS InterfaceBody
$creadsPrec :: Int -> ReadS InterfaceBody
Read, Int -> InterfaceBody -> String -> String
[InterfaceBody] -> String -> String
InterfaceBody -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [InterfaceBody] -> String -> String
$cshowList :: [InterfaceBody] -> String -> String
show :: InterfaceBody -> String
$cshow :: InterfaceBody -> String
showsPrec :: Int -> InterfaceBody -> String -> String
$cshowsPrec :: Int -> InterfaceBody -> String -> String
Show)

_InterfaceBody :: Name
_InterfaceBody = (String -> Name
Core.Name String
"hydra/ext/java/syntax.InterfaceBody")

data InterfaceMemberDeclaration = 
  InterfaceMemberDeclarationConstant ConstantDeclaration |
  InterfaceMemberDeclarationInterfaceMethod InterfaceMethodDeclaration |
  InterfaceMemberDeclarationClass ClassDeclaration |
  InterfaceMemberDeclarationInterface InterfaceDeclaration
  deriving (InterfaceMemberDeclaration -> InterfaceMemberDeclaration -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InterfaceMemberDeclaration -> InterfaceMemberDeclaration -> Bool
$c/= :: InterfaceMemberDeclaration -> InterfaceMemberDeclaration -> Bool
== :: InterfaceMemberDeclaration -> InterfaceMemberDeclaration -> Bool
$c== :: InterfaceMemberDeclaration -> InterfaceMemberDeclaration -> Bool
Eq, Eq InterfaceMemberDeclaration
InterfaceMemberDeclaration -> InterfaceMemberDeclaration -> Bool
InterfaceMemberDeclaration
-> InterfaceMemberDeclaration -> Ordering
InterfaceMemberDeclaration
-> InterfaceMemberDeclaration -> InterfaceMemberDeclaration
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: InterfaceMemberDeclaration
-> InterfaceMemberDeclaration -> InterfaceMemberDeclaration
$cmin :: InterfaceMemberDeclaration
-> InterfaceMemberDeclaration -> InterfaceMemberDeclaration
max :: InterfaceMemberDeclaration
-> InterfaceMemberDeclaration -> InterfaceMemberDeclaration
$cmax :: InterfaceMemberDeclaration
-> InterfaceMemberDeclaration -> InterfaceMemberDeclaration
>= :: InterfaceMemberDeclaration -> InterfaceMemberDeclaration -> Bool
$c>= :: InterfaceMemberDeclaration -> InterfaceMemberDeclaration -> Bool
> :: InterfaceMemberDeclaration -> InterfaceMemberDeclaration -> Bool
$c> :: InterfaceMemberDeclaration -> InterfaceMemberDeclaration -> Bool
<= :: InterfaceMemberDeclaration -> InterfaceMemberDeclaration -> Bool
$c<= :: InterfaceMemberDeclaration -> InterfaceMemberDeclaration -> Bool
< :: InterfaceMemberDeclaration -> InterfaceMemberDeclaration -> Bool
$c< :: InterfaceMemberDeclaration -> InterfaceMemberDeclaration -> Bool
compare :: InterfaceMemberDeclaration
-> InterfaceMemberDeclaration -> Ordering
$ccompare :: InterfaceMemberDeclaration
-> InterfaceMemberDeclaration -> Ordering
Ord, ReadPrec [InterfaceMemberDeclaration]
ReadPrec InterfaceMemberDeclaration
Int -> ReadS InterfaceMemberDeclaration
ReadS [InterfaceMemberDeclaration]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [InterfaceMemberDeclaration]
$creadListPrec :: ReadPrec [InterfaceMemberDeclaration]
readPrec :: ReadPrec InterfaceMemberDeclaration
$creadPrec :: ReadPrec InterfaceMemberDeclaration
readList :: ReadS [InterfaceMemberDeclaration]
$creadList :: ReadS [InterfaceMemberDeclaration]
readsPrec :: Int -> ReadS InterfaceMemberDeclaration
$creadsPrec :: Int -> ReadS InterfaceMemberDeclaration
Read, Int -> InterfaceMemberDeclaration -> String -> String
[InterfaceMemberDeclaration] -> String -> String
InterfaceMemberDeclaration -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [InterfaceMemberDeclaration] -> String -> String
$cshowList :: [InterfaceMemberDeclaration] -> String -> String
show :: InterfaceMemberDeclaration -> String
$cshow :: InterfaceMemberDeclaration -> String
showsPrec :: Int -> InterfaceMemberDeclaration -> String -> String
$cshowsPrec :: Int -> InterfaceMemberDeclaration -> String -> String
Show)

_InterfaceMemberDeclaration :: Name
_InterfaceMemberDeclaration = (String -> Name
Core.Name String
"hydra/ext/java/syntax.InterfaceMemberDeclaration")

_InterfaceMemberDeclaration_constant :: FieldName
_InterfaceMemberDeclaration_constant = (String -> FieldName
Core.FieldName String
"constant")

_InterfaceMemberDeclaration_interfaceMethod :: FieldName
_InterfaceMemberDeclaration_interfaceMethod = (String -> FieldName
Core.FieldName String
"interfaceMethod")

_InterfaceMemberDeclaration_class :: FieldName
_InterfaceMemberDeclaration_class = (String -> FieldName
Core.FieldName String
"class")

_InterfaceMemberDeclaration_interface :: FieldName
_InterfaceMemberDeclaration_interface = (String -> FieldName
Core.FieldName String
"interface")

data ConstantDeclaration = 
  ConstantDeclaration {
    ConstantDeclaration -> [ConstantModifier]
constantDeclarationModifiers :: [ConstantModifier],
    ConstantDeclaration -> UnannType
constantDeclarationType :: UnannType,
    ConstantDeclaration -> [VariableDeclarator]
constantDeclarationVariables :: [VariableDeclarator]}
  deriving (ConstantDeclaration -> ConstantDeclaration -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ConstantDeclaration -> ConstantDeclaration -> Bool
$c/= :: ConstantDeclaration -> ConstantDeclaration -> Bool
== :: ConstantDeclaration -> ConstantDeclaration -> Bool
$c== :: ConstantDeclaration -> ConstantDeclaration -> Bool
Eq, Eq ConstantDeclaration
ConstantDeclaration -> ConstantDeclaration -> Bool
ConstantDeclaration -> ConstantDeclaration -> Ordering
ConstantDeclaration -> ConstantDeclaration -> ConstantDeclaration
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ConstantDeclaration -> ConstantDeclaration -> ConstantDeclaration
$cmin :: ConstantDeclaration -> ConstantDeclaration -> ConstantDeclaration
max :: ConstantDeclaration -> ConstantDeclaration -> ConstantDeclaration
$cmax :: ConstantDeclaration -> ConstantDeclaration -> ConstantDeclaration
>= :: ConstantDeclaration -> ConstantDeclaration -> Bool
$c>= :: ConstantDeclaration -> ConstantDeclaration -> Bool
> :: ConstantDeclaration -> ConstantDeclaration -> Bool
$c> :: ConstantDeclaration -> ConstantDeclaration -> Bool
<= :: ConstantDeclaration -> ConstantDeclaration -> Bool
$c<= :: ConstantDeclaration -> ConstantDeclaration -> Bool
< :: ConstantDeclaration -> ConstantDeclaration -> Bool
$c< :: ConstantDeclaration -> ConstantDeclaration -> Bool
compare :: ConstantDeclaration -> ConstantDeclaration -> Ordering
$ccompare :: ConstantDeclaration -> ConstantDeclaration -> Ordering
Ord, ReadPrec [ConstantDeclaration]
ReadPrec ConstantDeclaration
Int -> ReadS ConstantDeclaration
ReadS [ConstantDeclaration]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ConstantDeclaration]
$creadListPrec :: ReadPrec [ConstantDeclaration]
readPrec :: ReadPrec ConstantDeclaration
$creadPrec :: ReadPrec ConstantDeclaration
readList :: ReadS [ConstantDeclaration]
$creadList :: ReadS [ConstantDeclaration]
readsPrec :: Int -> ReadS ConstantDeclaration
$creadsPrec :: Int -> ReadS ConstantDeclaration
Read, Int -> ConstantDeclaration -> String -> String
[ConstantDeclaration] -> String -> String
ConstantDeclaration -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ConstantDeclaration] -> String -> String
$cshowList :: [ConstantDeclaration] -> String -> String
show :: ConstantDeclaration -> String
$cshow :: ConstantDeclaration -> String
showsPrec :: Int -> ConstantDeclaration -> String -> String
$cshowsPrec :: Int -> ConstantDeclaration -> String -> String
Show)

_ConstantDeclaration :: Name
_ConstantDeclaration = (String -> Name
Core.Name String
"hydra/ext/java/syntax.ConstantDeclaration")

_ConstantDeclaration_modifiers :: FieldName
_ConstantDeclaration_modifiers = (String -> FieldName
Core.FieldName String
"modifiers")

_ConstantDeclaration_type :: FieldName
_ConstantDeclaration_type = (String -> FieldName
Core.FieldName String
"type")

_ConstantDeclaration_variables :: FieldName
_ConstantDeclaration_variables = (String -> FieldName
Core.FieldName String
"variables")

data ConstantModifier = 
  ConstantModifierAnnotation Annotation |
  ConstantModifierPublic  |
  ConstantModifierStatic  |
  ConstantModifierFinal 
  deriving (ConstantModifier -> ConstantModifier -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ConstantModifier -> ConstantModifier -> Bool
$c/= :: ConstantModifier -> ConstantModifier -> Bool
== :: ConstantModifier -> ConstantModifier -> Bool
$c== :: ConstantModifier -> ConstantModifier -> Bool
Eq, Eq ConstantModifier
ConstantModifier -> ConstantModifier -> Bool
ConstantModifier -> ConstantModifier -> Ordering
ConstantModifier -> ConstantModifier -> ConstantModifier
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ConstantModifier -> ConstantModifier -> ConstantModifier
$cmin :: ConstantModifier -> ConstantModifier -> ConstantModifier
max :: ConstantModifier -> ConstantModifier -> ConstantModifier
$cmax :: ConstantModifier -> ConstantModifier -> ConstantModifier
>= :: ConstantModifier -> ConstantModifier -> Bool
$c>= :: ConstantModifier -> ConstantModifier -> Bool
> :: ConstantModifier -> ConstantModifier -> Bool
$c> :: ConstantModifier -> ConstantModifier -> Bool
<= :: ConstantModifier -> ConstantModifier -> Bool
$c<= :: ConstantModifier -> ConstantModifier -> Bool
< :: ConstantModifier -> ConstantModifier -> Bool
$c< :: ConstantModifier -> ConstantModifier -> Bool
compare :: ConstantModifier -> ConstantModifier -> Ordering
$ccompare :: ConstantModifier -> ConstantModifier -> Ordering
Ord, ReadPrec [ConstantModifier]
ReadPrec ConstantModifier
Int -> ReadS ConstantModifier
ReadS [ConstantModifier]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ConstantModifier]
$creadListPrec :: ReadPrec [ConstantModifier]
readPrec :: ReadPrec ConstantModifier
$creadPrec :: ReadPrec ConstantModifier
readList :: ReadS [ConstantModifier]
$creadList :: ReadS [ConstantModifier]
readsPrec :: Int -> ReadS ConstantModifier
$creadsPrec :: Int -> ReadS ConstantModifier
Read, Int -> ConstantModifier -> String -> String
[ConstantModifier] -> String -> String
ConstantModifier -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ConstantModifier] -> String -> String
$cshowList :: [ConstantModifier] -> String -> String
show :: ConstantModifier -> String
$cshow :: ConstantModifier -> String
showsPrec :: Int -> ConstantModifier -> String -> String
$cshowsPrec :: Int -> ConstantModifier -> String -> String
Show)

_ConstantModifier :: Name
_ConstantModifier = (String -> Name
Core.Name String
"hydra/ext/java/syntax.ConstantModifier")

_ConstantModifier_annotation :: FieldName
_ConstantModifier_annotation = (String -> FieldName
Core.FieldName String
"annotation")

_ConstantModifier_public :: FieldName
_ConstantModifier_public = (String -> FieldName
Core.FieldName String
"public")

_ConstantModifier_static :: FieldName
_ConstantModifier_static = (String -> FieldName
Core.FieldName String
"static")

_ConstantModifier_final :: FieldName
_ConstantModifier_final = (String -> FieldName
Core.FieldName String
"final")

data InterfaceMethodDeclaration = 
  InterfaceMethodDeclaration {
    InterfaceMethodDeclaration -> [InterfaceMethodModifier]
interfaceMethodDeclarationModifiers :: [InterfaceMethodModifier],
    InterfaceMethodDeclaration -> MethodHeader
interfaceMethodDeclarationHeader :: MethodHeader,
    InterfaceMethodDeclaration -> MethodBody
interfaceMethodDeclarationBody :: MethodBody}
  deriving (InterfaceMethodDeclaration -> InterfaceMethodDeclaration -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InterfaceMethodDeclaration -> InterfaceMethodDeclaration -> Bool
$c/= :: InterfaceMethodDeclaration -> InterfaceMethodDeclaration -> Bool
== :: InterfaceMethodDeclaration -> InterfaceMethodDeclaration -> Bool
$c== :: InterfaceMethodDeclaration -> InterfaceMethodDeclaration -> Bool
Eq, Eq InterfaceMethodDeclaration
InterfaceMethodDeclaration -> InterfaceMethodDeclaration -> Bool
InterfaceMethodDeclaration
-> InterfaceMethodDeclaration -> Ordering
InterfaceMethodDeclaration
-> InterfaceMethodDeclaration -> InterfaceMethodDeclaration
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: InterfaceMethodDeclaration
-> InterfaceMethodDeclaration -> InterfaceMethodDeclaration
$cmin :: InterfaceMethodDeclaration
-> InterfaceMethodDeclaration -> InterfaceMethodDeclaration
max :: InterfaceMethodDeclaration
-> InterfaceMethodDeclaration -> InterfaceMethodDeclaration
$cmax :: InterfaceMethodDeclaration
-> InterfaceMethodDeclaration -> InterfaceMethodDeclaration
>= :: InterfaceMethodDeclaration -> InterfaceMethodDeclaration -> Bool
$c>= :: InterfaceMethodDeclaration -> InterfaceMethodDeclaration -> Bool
> :: InterfaceMethodDeclaration -> InterfaceMethodDeclaration -> Bool
$c> :: InterfaceMethodDeclaration -> InterfaceMethodDeclaration -> Bool
<= :: InterfaceMethodDeclaration -> InterfaceMethodDeclaration -> Bool
$c<= :: InterfaceMethodDeclaration -> InterfaceMethodDeclaration -> Bool
< :: InterfaceMethodDeclaration -> InterfaceMethodDeclaration -> Bool
$c< :: InterfaceMethodDeclaration -> InterfaceMethodDeclaration -> Bool
compare :: InterfaceMethodDeclaration
-> InterfaceMethodDeclaration -> Ordering
$ccompare :: InterfaceMethodDeclaration
-> InterfaceMethodDeclaration -> Ordering
Ord, ReadPrec [InterfaceMethodDeclaration]
ReadPrec InterfaceMethodDeclaration
Int -> ReadS InterfaceMethodDeclaration
ReadS [InterfaceMethodDeclaration]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [InterfaceMethodDeclaration]
$creadListPrec :: ReadPrec [InterfaceMethodDeclaration]
readPrec :: ReadPrec InterfaceMethodDeclaration
$creadPrec :: ReadPrec InterfaceMethodDeclaration
readList :: ReadS [InterfaceMethodDeclaration]
$creadList :: ReadS [InterfaceMethodDeclaration]
readsPrec :: Int -> ReadS InterfaceMethodDeclaration
$creadsPrec :: Int -> ReadS InterfaceMethodDeclaration
Read, Int -> InterfaceMethodDeclaration -> String -> String
[InterfaceMethodDeclaration] -> String -> String
InterfaceMethodDeclaration -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [InterfaceMethodDeclaration] -> String -> String
$cshowList :: [InterfaceMethodDeclaration] -> String -> String
show :: InterfaceMethodDeclaration -> String
$cshow :: InterfaceMethodDeclaration -> String
showsPrec :: Int -> InterfaceMethodDeclaration -> String -> String
$cshowsPrec :: Int -> InterfaceMethodDeclaration -> String -> String
Show)

_InterfaceMethodDeclaration :: Name
_InterfaceMethodDeclaration = (String -> Name
Core.Name String
"hydra/ext/java/syntax.InterfaceMethodDeclaration")

_InterfaceMethodDeclaration_modifiers :: FieldName
_InterfaceMethodDeclaration_modifiers = (String -> FieldName
Core.FieldName String
"modifiers")

_InterfaceMethodDeclaration_header :: FieldName
_InterfaceMethodDeclaration_header = (String -> FieldName
Core.FieldName String
"header")

_InterfaceMethodDeclaration_body :: FieldName
_InterfaceMethodDeclaration_body = (String -> FieldName
Core.FieldName String
"body")

data InterfaceMethodModifier = 
  InterfaceMethodModifierAnnotation Annotation |
  InterfaceMethodModifierPublic  |
  InterfaceMethodModifierPrivate  |
  InterfaceMethodModifierAbstract  |
  InterfaceMethodModifierDefault  |
  InterfaceMethodModifierStatic  |
  InterfaceMethodModifierStrictfp 
  deriving (InterfaceMethodModifier -> InterfaceMethodModifier -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InterfaceMethodModifier -> InterfaceMethodModifier -> Bool
$c/= :: InterfaceMethodModifier -> InterfaceMethodModifier -> Bool
== :: InterfaceMethodModifier -> InterfaceMethodModifier -> Bool
$c== :: InterfaceMethodModifier -> InterfaceMethodModifier -> Bool
Eq, Eq InterfaceMethodModifier
InterfaceMethodModifier -> InterfaceMethodModifier -> Bool
InterfaceMethodModifier -> InterfaceMethodModifier -> Ordering
InterfaceMethodModifier
-> InterfaceMethodModifier -> InterfaceMethodModifier
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: InterfaceMethodModifier
-> InterfaceMethodModifier -> InterfaceMethodModifier
$cmin :: InterfaceMethodModifier
-> InterfaceMethodModifier -> InterfaceMethodModifier
max :: InterfaceMethodModifier
-> InterfaceMethodModifier -> InterfaceMethodModifier
$cmax :: InterfaceMethodModifier
-> InterfaceMethodModifier -> InterfaceMethodModifier
>= :: InterfaceMethodModifier -> InterfaceMethodModifier -> Bool
$c>= :: InterfaceMethodModifier -> InterfaceMethodModifier -> Bool
> :: InterfaceMethodModifier -> InterfaceMethodModifier -> Bool
$c> :: InterfaceMethodModifier -> InterfaceMethodModifier -> Bool
<= :: InterfaceMethodModifier -> InterfaceMethodModifier -> Bool
$c<= :: InterfaceMethodModifier -> InterfaceMethodModifier -> Bool
< :: InterfaceMethodModifier -> InterfaceMethodModifier -> Bool
$c< :: InterfaceMethodModifier -> InterfaceMethodModifier -> Bool
compare :: InterfaceMethodModifier -> InterfaceMethodModifier -> Ordering
$ccompare :: InterfaceMethodModifier -> InterfaceMethodModifier -> Ordering
Ord, ReadPrec [InterfaceMethodModifier]
ReadPrec InterfaceMethodModifier
Int -> ReadS InterfaceMethodModifier
ReadS [InterfaceMethodModifier]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [InterfaceMethodModifier]
$creadListPrec :: ReadPrec [InterfaceMethodModifier]
readPrec :: ReadPrec InterfaceMethodModifier
$creadPrec :: ReadPrec InterfaceMethodModifier
readList :: ReadS [InterfaceMethodModifier]
$creadList :: ReadS [InterfaceMethodModifier]
readsPrec :: Int -> ReadS InterfaceMethodModifier
$creadsPrec :: Int -> ReadS InterfaceMethodModifier
Read, Int -> InterfaceMethodModifier -> String -> String
[InterfaceMethodModifier] -> String -> String
InterfaceMethodModifier -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [InterfaceMethodModifier] -> String -> String
$cshowList :: [InterfaceMethodModifier] -> String -> String
show :: InterfaceMethodModifier -> String
$cshow :: InterfaceMethodModifier -> String
showsPrec :: Int -> InterfaceMethodModifier -> String -> String
$cshowsPrec :: Int -> InterfaceMethodModifier -> String -> String
Show)

_InterfaceMethodModifier :: Name
_InterfaceMethodModifier = (String -> Name
Core.Name String
"hydra/ext/java/syntax.InterfaceMethodModifier")

_InterfaceMethodModifier_annotation :: FieldName
_InterfaceMethodModifier_annotation = (String -> FieldName
Core.FieldName String
"annotation")

_InterfaceMethodModifier_public :: FieldName
_InterfaceMethodModifier_public = (String -> FieldName
Core.FieldName String
"public")

_InterfaceMethodModifier_private :: FieldName
_InterfaceMethodModifier_private = (String -> FieldName
Core.FieldName String
"private")

_InterfaceMethodModifier_abstract :: FieldName
_InterfaceMethodModifier_abstract = (String -> FieldName
Core.FieldName String
"abstract")

_InterfaceMethodModifier_default :: FieldName
_InterfaceMethodModifier_default = (String -> FieldName
Core.FieldName String
"default")

_InterfaceMethodModifier_static :: FieldName
_InterfaceMethodModifier_static = (String -> FieldName
Core.FieldName String
"static")

_InterfaceMethodModifier_strictfp :: FieldName
_InterfaceMethodModifier_strictfp = (String -> FieldName
Core.FieldName String
"strictfp")

data AnnotationTypeDeclaration = 
  AnnotationTypeDeclaration {
    AnnotationTypeDeclaration -> [InterfaceModifier]
annotationTypeDeclarationModifiers :: [InterfaceModifier],
    AnnotationTypeDeclaration -> TypeIdentifier
annotationTypeDeclarationIdentifier :: TypeIdentifier,
    AnnotationTypeDeclaration -> AnnotationTypeBody
annotationTypeDeclarationBody :: AnnotationTypeBody}
  deriving (AnnotationTypeDeclaration -> AnnotationTypeDeclaration -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AnnotationTypeDeclaration -> AnnotationTypeDeclaration -> Bool
$c/= :: AnnotationTypeDeclaration -> AnnotationTypeDeclaration -> Bool
== :: AnnotationTypeDeclaration -> AnnotationTypeDeclaration -> Bool
$c== :: AnnotationTypeDeclaration -> AnnotationTypeDeclaration -> Bool
Eq, Eq AnnotationTypeDeclaration
AnnotationTypeDeclaration -> AnnotationTypeDeclaration -> Bool
AnnotationTypeDeclaration -> AnnotationTypeDeclaration -> Ordering
AnnotationTypeDeclaration
-> AnnotationTypeDeclaration -> AnnotationTypeDeclaration
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: AnnotationTypeDeclaration
-> AnnotationTypeDeclaration -> AnnotationTypeDeclaration
$cmin :: AnnotationTypeDeclaration
-> AnnotationTypeDeclaration -> AnnotationTypeDeclaration
max :: AnnotationTypeDeclaration
-> AnnotationTypeDeclaration -> AnnotationTypeDeclaration
$cmax :: AnnotationTypeDeclaration
-> AnnotationTypeDeclaration -> AnnotationTypeDeclaration
>= :: AnnotationTypeDeclaration -> AnnotationTypeDeclaration -> Bool
$c>= :: AnnotationTypeDeclaration -> AnnotationTypeDeclaration -> Bool
> :: AnnotationTypeDeclaration -> AnnotationTypeDeclaration -> Bool
$c> :: AnnotationTypeDeclaration -> AnnotationTypeDeclaration -> Bool
<= :: AnnotationTypeDeclaration -> AnnotationTypeDeclaration -> Bool
$c<= :: AnnotationTypeDeclaration -> AnnotationTypeDeclaration -> Bool
< :: AnnotationTypeDeclaration -> AnnotationTypeDeclaration -> Bool
$c< :: AnnotationTypeDeclaration -> AnnotationTypeDeclaration -> Bool
compare :: AnnotationTypeDeclaration -> AnnotationTypeDeclaration -> Ordering
$ccompare :: AnnotationTypeDeclaration -> AnnotationTypeDeclaration -> Ordering
Ord, ReadPrec [AnnotationTypeDeclaration]
ReadPrec AnnotationTypeDeclaration
Int -> ReadS AnnotationTypeDeclaration
ReadS [AnnotationTypeDeclaration]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AnnotationTypeDeclaration]
$creadListPrec :: ReadPrec [AnnotationTypeDeclaration]
readPrec :: ReadPrec AnnotationTypeDeclaration
$creadPrec :: ReadPrec AnnotationTypeDeclaration
readList :: ReadS [AnnotationTypeDeclaration]
$creadList :: ReadS [AnnotationTypeDeclaration]
readsPrec :: Int -> ReadS AnnotationTypeDeclaration
$creadsPrec :: Int -> ReadS AnnotationTypeDeclaration
Read, Int -> AnnotationTypeDeclaration -> String -> String
[AnnotationTypeDeclaration] -> String -> String
AnnotationTypeDeclaration -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [AnnotationTypeDeclaration] -> String -> String
$cshowList :: [AnnotationTypeDeclaration] -> String -> String
show :: AnnotationTypeDeclaration -> String
$cshow :: AnnotationTypeDeclaration -> String
showsPrec :: Int -> AnnotationTypeDeclaration -> String -> String
$cshowsPrec :: Int -> AnnotationTypeDeclaration -> String -> String
Show)

_AnnotationTypeDeclaration :: Name
_AnnotationTypeDeclaration = (String -> Name
Core.Name String
"hydra/ext/java/syntax.AnnotationTypeDeclaration")

_AnnotationTypeDeclaration_modifiers :: FieldName
_AnnotationTypeDeclaration_modifiers = (String -> FieldName
Core.FieldName String
"modifiers")

_AnnotationTypeDeclaration_identifier :: FieldName
_AnnotationTypeDeclaration_identifier = (String -> FieldName
Core.FieldName String
"identifier")

_AnnotationTypeDeclaration_body :: FieldName
_AnnotationTypeDeclaration_body = (String -> FieldName
Core.FieldName String
"body")

newtype AnnotationTypeBody = 
  AnnotationTypeBody {
    AnnotationTypeBody -> [[AnnotationTypeMemberDeclaration]]
unAnnotationTypeBody :: [[AnnotationTypeMemberDeclaration]]}
  deriving (AnnotationTypeBody -> AnnotationTypeBody -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AnnotationTypeBody -> AnnotationTypeBody -> Bool
$c/= :: AnnotationTypeBody -> AnnotationTypeBody -> Bool
== :: AnnotationTypeBody -> AnnotationTypeBody -> Bool
$c== :: AnnotationTypeBody -> AnnotationTypeBody -> Bool
Eq, Eq AnnotationTypeBody
AnnotationTypeBody -> AnnotationTypeBody -> Bool
AnnotationTypeBody -> AnnotationTypeBody -> Ordering
AnnotationTypeBody -> AnnotationTypeBody -> AnnotationTypeBody
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: AnnotationTypeBody -> AnnotationTypeBody -> AnnotationTypeBody
$cmin :: AnnotationTypeBody -> AnnotationTypeBody -> AnnotationTypeBody
max :: AnnotationTypeBody -> AnnotationTypeBody -> AnnotationTypeBody
$cmax :: AnnotationTypeBody -> AnnotationTypeBody -> AnnotationTypeBody
>= :: AnnotationTypeBody -> AnnotationTypeBody -> Bool
$c>= :: AnnotationTypeBody -> AnnotationTypeBody -> Bool
> :: AnnotationTypeBody -> AnnotationTypeBody -> Bool
$c> :: AnnotationTypeBody -> AnnotationTypeBody -> Bool
<= :: AnnotationTypeBody -> AnnotationTypeBody -> Bool
$c<= :: AnnotationTypeBody -> AnnotationTypeBody -> Bool
< :: AnnotationTypeBody -> AnnotationTypeBody -> Bool
$c< :: AnnotationTypeBody -> AnnotationTypeBody -> Bool
compare :: AnnotationTypeBody -> AnnotationTypeBody -> Ordering
$ccompare :: AnnotationTypeBody -> AnnotationTypeBody -> Ordering
Ord, ReadPrec [AnnotationTypeBody]
ReadPrec AnnotationTypeBody
Int -> ReadS AnnotationTypeBody
ReadS [AnnotationTypeBody]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AnnotationTypeBody]
$creadListPrec :: ReadPrec [AnnotationTypeBody]
readPrec :: ReadPrec AnnotationTypeBody
$creadPrec :: ReadPrec AnnotationTypeBody
readList :: ReadS [AnnotationTypeBody]
$creadList :: ReadS [AnnotationTypeBody]
readsPrec :: Int -> ReadS AnnotationTypeBody
$creadsPrec :: Int -> ReadS AnnotationTypeBody
Read, Int -> AnnotationTypeBody -> String -> String
[AnnotationTypeBody] -> String -> String
AnnotationTypeBody -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [AnnotationTypeBody] -> String -> String
$cshowList :: [AnnotationTypeBody] -> String -> String
show :: AnnotationTypeBody -> String
$cshow :: AnnotationTypeBody -> String
showsPrec :: Int -> AnnotationTypeBody -> String -> String
$cshowsPrec :: Int -> AnnotationTypeBody -> String -> String
Show)

_AnnotationTypeBody :: Name
_AnnotationTypeBody = (String -> Name
Core.Name String
"hydra/ext/java/syntax.AnnotationTypeBody")

data AnnotationTypeMemberDeclaration = 
  AnnotationTypeMemberDeclarationAnnotationType AnnotationTypeElementDeclaration |
  AnnotationTypeMemberDeclarationConstant ConstantDeclaration |
  AnnotationTypeMemberDeclarationClass ClassDeclaration |
  AnnotationTypeMemberDeclarationInterface InterfaceDeclaration
  deriving (AnnotationTypeMemberDeclaration
-> AnnotationTypeMemberDeclaration -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AnnotationTypeMemberDeclaration
-> AnnotationTypeMemberDeclaration -> Bool
$c/= :: AnnotationTypeMemberDeclaration
-> AnnotationTypeMemberDeclaration -> Bool
== :: AnnotationTypeMemberDeclaration
-> AnnotationTypeMemberDeclaration -> Bool
$c== :: AnnotationTypeMemberDeclaration
-> AnnotationTypeMemberDeclaration -> Bool
Eq, Eq AnnotationTypeMemberDeclaration
AnnotationTypeMemberDeclaration
-> AnnotationTypeMemberDeclaration -> Bool
AnnotationTypeMemberDeclaration
-> AnnotationTypeMemberDeclaration -> Ordering
AnnotationTypeMemberDeclaration
-> AnnotationTypeMemberDeclaration
-> AnnotationTypeMemberDeclaration
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: AnnotationTypeMemberDeclaration
-> AnnotationTypeMemberDeclaration
-> AnnotationTypeMemberDeclaration
$cmin :: AnnotationTypeMemberDeclaration
-> AnnotationTypeMemberDeclaration
-> AnnotationTypeMemberDeclaration
max :: AnnotationTypeMemberDeclaration
-> AnnotationTypeMemberDeclaration
-> AnnotationTypeMemberDeclaration
$cmax :: AnnotationTypeMemberDeclaration
-> AnnotationTypeMemberDeclaration
-> AnnotationTypeMemberDeclaration
>= :: AnnotationTypeMemberDeclaration
-> AnnotationTypeMemberDeclaration -> Bool
$c>= :: AnnotationTypeMemberDeclaration
-> AnnotationTypeMemberDeclaration -> Bool
> :: AnnotationTypeMemberDeclaration
-> AnnotationTypeMemberDeclaration -> Bool
$c> :: AnnotationTypeMemberDeclaration
-> AnnotationTypeMemberDeclaration -> Bool
<= :: AnnotationTypeMemberDeclaration
-> AnnotationTypeMemberDeclaration -> Bool
$c<= :: AnnotationTypeMemberDeclaration
-> AnnotationTypeMemberDeclaration -> Bool
< :: AnnotationTypeMemberDeclaration
-> AnnotationTypeMemberDeclaration -> Bool
$c< :: AnnotationTypeMemberDeclaration
-> AnnotationTypeMemberDeclaration -> Bool
compare :: AnnotationTypeMemberDeclaration
-> AnnotationTypeMemberDeclaration -> Ordering
$ccompare :: AnnotationTypeMemberDeclaration
-> AnnotationTypeMemberDeclaration -> Ordering
Ord, ReadPrec [AnnotationTypeMemberDeclaration]
ReadPrec AnnotationTypeMemberDeclaration
Int -> ReadS AnnotationTypeMemberDeclaration
ReadS [AnnotationTypeMemberDeclaration]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AnnotationTypeMemberDeclaration]
$creadListPrec :: ReadPrec [AnnotationTypeMemberDeclaration]
readPrec :: ReadPrec AnnotationTypeMemberDeclaration
$creadPrec :: ReadPrec AnnotationTypeMemberDeclaration
readList :: ReadS [AnnotationTypeMemberDeclaration]
$creadList :: ReadS [AnnotationTypeMemberDeclaration]
readsPrec :: Int -> ReadS AnnotationTypeMemberDeclaration
$creadsPrec :: Int -> ReadS AnnotationTypeMemberDeclaration
Read, Int -> AnnotationTypeMemberDeclaration -> String -> String
[AnnotationTypeMemberDeclaration] -> String -> String
AnnotationTypeMemberDeclaration -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [AnnotationTypeMemberDeclaration] -> String -> String
$cshowList :: [AnnotationTypeMemberDeclaration] -> String -> String
show :: AnnotationTypeMemberDeclaration -> String
$cshow :: AnnotationTypeMemberDeclaration -> String
showsPrec :: Int -> AnnotationTypeMemberDeclaration -> String -> String
$cshowsPrec :: Int -> AnnotationTypeMemberDeclaration -> String -> String
Show)

_AnnotationTypeMemberDeclaration :: Name
_AnnotationTypeMemberDeclaration = (String -> Name
Core.Name String
"hydra/ext/java/syntax.AnnotationTypeMemberDeclaration")

_AnnotationTypeMemberDeclaration_annotationType :: FieldName
_AnnotationTypeMemberDeclaration_annotationType = (String -> FieldName
Core.FieldName String
"annotationType")

_AnnotationTypeMemberDeclaration_constant :: FieldName
_AnnotationTypeMemberDeclaration_constant = (String -> FieldName
Core.FieldName String
"constant")

_AnnotationTypeMemberDeclaration_class :: FieldName
_AnnotationTypeMemberDeclaration_class = (String -> FieldName
Core.FieldName String
"class")

_AnnotationTypeMemberDeclaration_interface :: FieldName
_AnnotationTypeMemberDeclaration_interface = (String -> FieldName
Core.FieldName String
"interface")

data AnnotationTypeElementDeclaration = 
  AnnotationTypeElementDeclaration {
    AnnotationTypeElementDeclaration -> [AnnotationTypeElementModifier]
annotationTypeElementDeclarationModifiers :: [AnnotationTypeElementModifier],
    AnnotationTypeElementDeclaration -> UnannType
annotationTypeElementDeclarationType :: UnannType,
    AnnotationTypeElementDeclaration -> Identifier
annotationTypeElementDeclarationIdentifier :: Identifier,
    AnnotationTypeElementDeclaration -> Maybe Dims
annotationTypeElementDeclarationDims :: (Maybe Dims),
    AnnotationTypeElementDeclaration -> Maybe DefaultValue
annotationTypeElementDeclarationDefault :: (Maybe DefaultValue)}
  deriving (AnnotationTypeElementDeclaration
-> AnnotationTypeElementDeclaration -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AnnotationTypeElementDeclaration
-> AnnotationTypeElementDeclaration -> Bool
$c/= :: AnnotationTypeElementDeclaration
-> AnnotationTypeElementDeclaration -> Bool
== :: AnnotationTypeElementDeclaration
-> AnnotationTypeElementDeclaration -> Bool
$c== :: AnnotationTypeElementDeclaration
-> AnnotationTypeElementDeclaration -> Bool
Eq, Eq AnnotationTypeElementDeclaration
AnnotationTypeElementDeclaration
-> AnnotationTypeElementDeclaration -> Bool
AnnotationTypeElementDeclaration
-> AnnotationTypeElementDeclaration -> Ordering
AnnotationTypeElementDeclaration
-> AnnotationTypeElementDeclaration
-> AnnotationTypeElementDeclaration
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: AnnotationTypeElementDeclaration
-> AnnotationTypeElementDeclaration
-> AnnotationTypeElementDeclaration
$cmin :: AnnotationTypeElementDeclaration
-> AnnotationTypeElementDeclaration
-> AnnotationTypeElementDeclaration
max :: AnnotationTypeElementDeclaration
-> AnnotationTypeElementDeclaration
-> AnnotationTypeElementDeclaration
$cmax :: AnnotationTypeElementDeclaration
-> AnnotationTypeElementDeclaration
-> AnnotationTypeElementDeclaration
>= :: AnnotationTypeElementDeclaration
-> AnnotationTypeElementDeclaration -> Bool
$c>= :: AnnotationTypeElementDeclaration
-> AnnotationTypeElementDeclaration -> Bool
> :: AnnotationTypeElementDeclaration
-> AnnotationTypeElementDeclaration -> Bool
$c> :: AnnotationTypeElementDeclaration
-> AnnotationTypeElementDeclaration -> Bool
<= :: AnnotationTypeElementDeclaration
-> AnnotationTypeElementDeclaration -> Bool
$c<= :: AnnotationTypeElementDeclaration
-> AnnotationTypeElementDeclaration -> Bool
< :: AnnotationTypeElementDeclaration
-> AnnotationTypeElementDeclaration -> Bool
$c< :: AnnotationTypeElementDeclaration
-> AnnotationTypeElementDeclaration -> Bool
compare :: AnnotationTypeElementDeclaration
-> AnnotationTypeElementDeclaration -> Ordering
$ccompare :: AnnotationTypeElementDeclaration
-> AnnotationTypeElementDeclaration -> Ordering
Ord, ReadPrec [AnnotationTypeElementDeclaration]
ReadPrec AnnotationTypeElementDeclaration
Int -> ReadS AnnotationTypeElementDeclaration
ReadS [AnnotationTypeElementDeclaration]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AnnotationTypeElementDeclaration]
$creadListPrec :: ReadPrec [AnnotationTypeElementDeclaration]
readPrec :: ReadPrec AnnotationTypeElementDeclaration
$creadPrec :: ReadPrec AnnotationTypeElementDeclaration
readList :: ReadS [AnnotationTypeElementDeclaration]
$creadList :: ReadS [AnnotationTypeElementDeclaration]
readsPrec :: Int -> ReadS AnnotationTypeElementDeclaration
$creadsPrec :: Int -> ReadS AnnotationTypeElementDeclaration
Read, Int -> AnnotationTypeElementDeclaration -> String -> String
[AnnotationTypeElementDeclaration] -> String -> String
AnnotationTypeElementDeclaration -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [AnnotationTypeElementDeclaration] -> String -> String
$cshowList :: [AnnotationTypeElementDeclaration] -> String -> String
show :: AnnotationTypeElementDeclaration -> String
$cshow :: AnnotationTypeElementDeclaration -> String
showsPrec :: Int -> AnnotationTypeElementDeclaration -> String -> String
$cshowsPrec :: Int -> AnnotationTypeElementDeclaration -> String -> String
Show)

_AnnotationTypeElementDeclaration :: Name
_AnnotationTypeElementDeclaration = (String -> Name
Core.Name String
"hydra/ext/java/syntax.AnnotationTypeElementDeclaration")

_AnnotationTypeElementDeclaration_modifiers :: FieldName
_AnnotationTypeElementDeclaration_modifiers = (String -> FieldName
Core.FieldName String
"modifiers")

_AnnotationTypeElementDeclaration_type :: FieldName
_AnnotationTypeElementDeclaration_type = (String -> FieldName
Core.FieldName String
"type")

_AnnotationTypeElementDeclaration_identifier :: FieldName
_AnnotationTypeElementDeclaration_identifier = (String -> FieldName
Core.FieldName String
"identifier")

_AnnotationTypeElementDeclaration_dims :: FieldName
_AnnotationTypeElementDeclaration_dims = (String -> FieldName
Core.FieldName String
"dims")

_AnnotationTypeElementDeclaration_default :: FieldName
_AnnotationTypeElementDeclaration_default = (String -> FieldName
Core.FieldName String
"default")

data AnnotationTypeElementModifier = 
  AnnotationTypeElementModifierPublic Annotation |
  AnnotationTypeElementModifierAbstract 
  deriving (AnnotationTypeElementModifier
-> AnnotationTypeElementModifier -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AnnotationTypeElementModifier
-> AnnotationTypeElementModifier -> Bool
$c/= :: AnnotationTypeElementModifier
-> AnnotationTypeElementModifier -> Bool
== :: AnnotationTypeElementModifier
-> AnnotationTypeElementModifier -> Bool
$c== :: AnnotationTypeElementModifier
-> AnnotationTypeElementModifier -> Bool
Eq, Eq AnnotationTypeElementModifier
AnnotationTypeElementModifier
-> AnnotationTypeElementModifier -> Bool
AnnotationTypeElementModifier
-> AnnotationTypeElementModifier -> Ordering
AnnotationTypeElementModifier
-> AnnotationTypeElementModifier -> AnnotationTypeElementModifier
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: AnnotationTypeElementModifier
-> AnnotationTypeElementModifier -> AnnotationTypeElementModifier
$cmin :: AnnotationTypeElementModifier
-> AnnotationTypeElementModifier -> AnnotationTypeElementModifier
max :: AnnotationTypeElementModifier
-> AnnotationTypeElementModifier -> AnnotationTypeElementModifier
$cmax :: AnnotationTypeElementModifier
-> AnnotationTypeElementModifier -> AnnotationTypeElementModifier
>= :: AnnotationTypeElementModifier
-> AnnotationTypeElementModifier -> Bool
$c>= :: AnnotationTypeElementModifier
-> AnnotationTypeElementModifier -> Bool
> :: AnnotationTypeElementModifier
-> AnnotationTypeElementModifier -> Bool
$c> :: AnnotationTypeElementModifier
-> AnnotationTypeElementModifier -> Bool
<= :: AnnotationTypeElementModifier
-> AnnotationTypeElementModifier -> Bool
$c<= :: AnnotationTypeElementModifier
-> AnnotationTypeElementModifier -> Bool
< :: AnnotationTypeElementModifier
-> AnnotationTypeElementModifier -> Bool
$c< :: AnnotationTypeElementModifier
-> AnnotationTypeElementModifier -> Bool
compare :: AnnotationTypeElementModifier
-> AnnotationTypeElementModifier -> Ordering
$ccompare :: AnnotationTypeElementModifier
-> AnnotationTypeElementModifier -> Ordering
Ord, ReadPrec [AnnotationTypeElementModifier]
ReadPrec AnnotationTypeElementModifier
Int -> ReadS AnnotationTypeElementModifier
ReadS [AnnotationTypeElementModifier]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AnnotationTypeElementModifier]
$creadListPrec :: ReadPrec [AnnotationTypeElementModifier]
readPrec :: ReadPrec AnnotationTypeElementModifier
$creadPrec :: ReadPrec AnnotationTypeElementModifier
readList :: ReadS [AnnotationTypeElementModifier]
$creadList :: ReadS [AnnotationTypeElementModifier]
readsPrec :: Int -> ReadS AnnotationTypeElementModifier
$creadsPrec :: Int -> ReadS AnnotationTypeElementModifier
Read, Int -> AnnotationTypeElementModifier -> String -> String
[AnnotationTypeElementModifier] -> String -> String
AnnotationTypeElementModifier -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [AnnotationTypeElementModifier] -> String -> String
$cshowList :: [AnnotationTypeElementModifier] -> String -> String
show :: AnnotationTypeElementModifier -> String
$cshow :: AnnotationTypeElementModifier -> String
showsPrec :: Int -> AnnotationTypeElementModifier -> String -> String
$cshowsPrec :: Int -> AnnotationTypeElementModifier -> String -> String
Show)

_AnnotationTypeElementModifier :: Name
_AnnotationTypeElementModifier = (String -> Name
Core.Name String
"hydra/ext/java/syntax.AnnotationTypeElementModifier")

_AnnotationTypeElementModifier_public :: FieldName
_AnnotationTypeElementModifier_public = (String -> FieldName
Core.FieldName String
"public")

_AnnotationTypeElementModifier_abstract :: FieldName
_AnnotationTypeElementModifier_abstract = (String -> FieldName
Core.FieldName String
"abstract")

newtype DefaultValue = 
  DefaultValue {
    DefaultValue -> ElementValue
unDefaultValue :: ElementValue}
  deriving (DefaultValue -> DefaultValue -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DefaultValue -> DefaultValue -> Bool
$c/= :: DefaultValue -> DefaultValue -> Bool
== :: DefaultValue -> DefaultValue -> Bool
$c== :: DefaultValue -> DefaultValue -> Bool
Eq, Eq DefaultValue
DefaultValue -> DefaultValue -> Bool
DefaultValue -> DefaultValue -> Ordering
DefaultValue -> DefaultValue -> DefaultValue
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: DefaultValue -> DefaultValue -> DefaultValue
$cmin :: DefaultValue -> DefaultValue -> DefaultValue
max :: DefaultValue -> DefaultValue -> DefaultValue
$cmax :: DefaultValue -> DefaultValue -> DefaultValue
>= :: DefaultValue -> DefaultValue -> Bool
$c>= :: DefaultValue -> DefaultValue -> Bool
> :: DefaultValue -> DefaultValue -> Bool
$c> :: DefaultValue -> DefaultValue -> Bool
<= :: DefaultValue -> DefaultValue -> Bool
$c<= :: DefaultValue -> DefaultValue -> Bool
< :: DefaultValue -> DefaultValue -> Bool
$c< :: DefaultValue -> DefaultValue -> Bool
compare :: DefaultValue -> DefaultValue -> Ordering
$ccompare :: DefaultValue -> DefaultValue -> Ordering
Ord, ReadPrec [DefaultValue]
ReadPrec DefaultValue
Int -> ReadS DefaultValue
ReadS [DefaultValue]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DefaultValue]
$creadListPrec :: ReadPrec [DefaultValue]
readPrec :: ReadPrec DefaultValue
$creadPrec :: ReadPrec DefaultValue
readList :: ReadS [DefaultValue]
$creadList :: ReadS [DefaultValue]
readsPrec :: Int -> ReadS DefaultValue
$creadsPrec :: Int -> ReadS DefaultValue
Read, Int -> DefaultValue -> String -> String
[DefaultValue] -> String -> String
DefaultValue -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [DefaultValue] -> String -> String
$cshowList :: [DefaultValue] -> String -> String
show :: DefaultValue -> String
$cshow :: DefaultValue -> String
showsPrec :: Int -> DefaultValue -> String -> String
$cshowsPrec :: Int -> DefaultValue -> String -> String
Show)

_DefaultValue :: Name
_DefaultValue = (String -> Name
Core.Name String
"hydra/ext/java/syntax.DefaultValue")

data Annotation = 
  AnnotationNormal NormalAnnotation |
  AnnotationMarker MarkerAnnotation |
  AnnotationSingleElement SingleElementAnnotation
  deriving (Annotation -> Annotation -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Annotation -> Annotation -> Bool
$c/= :: Annotation -> Annotation -> Bool
== :: Annotation -> Annotation -> Bool
$c== :: Annotation -> Annotation -> Bool
Eq, Eq Annotation
Annotation -> Annotation -> Bool
Annotation -> Annotation -> Ordering
Annotation -> Annotation -> Annotation
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Annotation -> Annotation -> Annotation
$cmin :: Annotation -> Annotation -> Annotation
max :: Annotation -> Annotation -> Annotation
$cmax :: Annotation -> Annotation -> Annotation
>= :: Annotation -> Annotation -> Bool
$c>= :: Annotation -> Annotation -> Bool
> :: Annotation -> Annotation -> Bool
$c> :: Annotation -> Annotation -> Bool
<= :: Annotation -> Annotation -> Bool
$c<= :: Annotation -> Annotation -> Bool
< :: Annotation -> Annotation -> Bool
$c< :: Annotation -> Annotation -> Bool
compare :: Annotation -> Annotation -> Ordering
$ccompare :: Annotation -> Annotation -> Ordering
Ord, ReadPrec [Annotation]
ReadPrec Annotation
Int -> ReadS Annotation
ReadS [Annotation]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Annotation]
$creadListPrec :: ReadPrec [Annotation]
readPrec :: ReadPrec Annotation
$creadPrec :: ReadPrec Annotation
readList :: ReadS [Annotation]
$creadList :: ReadS [Annotation]
readsPrec :: Int -> ReadS Annotation
$creadsPrec :: Int -> ReadS Annotation
Read, Int -> Annotation -> String -> String
[Annotation] -> String -> String
Annotation -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [Annotation] -> String -> String
$cshowList :: [Annotation] -> String -> String
show :: Annotation -> String
$cshow :: Annotation -> String
showsPrec :: Int -> Annotation -> String -> String
$cshowsPrec :: Int -> Annotation -> String -> String
Show)

_Annotation :: Name
_Annotation = (String -> Name
Core.Name String
"hydra/ext/java/syntax.Annotation")

_Annotation_normal :: FieldName
_Annotation_normal = (String -> FieldName
Core.FieldName String
"normal")

_Annotation_marker :: FieldName
_Annotation_marker = (String -> FieldName
Core.FieldName String
"marker")

_Annotation_singleElement :: FieldName
_Annotation_singleElement = (String -> FieldName
Core.FieldName String
"singleElement")

data NormalAnnotation = 
  NormalAnnotation {
    NormalAnnotation -> TypeName
normalAnnotationTypeName :: TypeName,
    NormalAnnotation -> [ElementValuePair]
normalAnnotationPairs :: [ElementValuePair]}
  deriving (NormalAnnotation -> NormalAnnotation -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NormalAnnotation -> NormalAnnotation -> Bool
$c/= :: NormalAnnotation -> NormalAnnotation -> Bool
== :: NormalAnnotation -> NormalAnnotation -> Bool
$c== :: NormalAnnotation -> NormalAnnotation -> Bool
Eq, Eq NormalAnnotation
NormalAnnotation -> NormalAnnotation -> Bool
NormalAnnotation -> NormalAnnotation -> Ordering
NormalAnnotation -> NormalAnnotation -> NormalAnnotation
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: NormalAnnotation -> NormalAnnotation -> NormalAnnotation
$cmin :: NormalAnnotation -> NormalAnnotation -> NormalAnnotation
max :: NormalAnnotation -> NormalAnnotation -> NormalAnnotation
$cmax :: NormalAnnotation -> NormalAnnotation -> NormalAnnotation
>= :: NormalAnnotation -> NormalAnnotation -> Bool
$c>= :: NormalAnnotation -> NormalAnnotation -> Bool
> :: NormalAnnotation -> NormalAnnotation -> Bool
$c> :: NormalAnnotation -> NormalAnnotation -> Bool
<= :: NormalAnnotation -> NormalAnnotation -> Bool
$c<= :: NormalAnnotation -> NormalAnnotation -> Bool
< :: NormalAnnotation -> NormalAnnotation -> Bool
$c< :: NormalAnnotation -> NormalAnnotation -> Bool
compare :: NormalAnnotation -> NormalAnnotation -> Ordering
$ccompare :: NormalAnnotation -> NormalAnnotation -> Ordering
Ord, ReadPrec [NormalAnnotation]
ReadPrec NormalAnnotation
Int -> ReadS NormalAnnotation
ReadS [NormalAnnotation]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [NormalAnnotation]
$creadListPrec :: ReadPrec [NormalAnnotation]
readPrec :: ReadPrec NormalAnnotation
$creadPrec :: ReadPrec NormalAnnotation
readList :: ReadS [NormalAnnotation]
$creadList :: ReadS [NormalAnnotation]
readsPrec :: Int -> ReadS NormalAnnotation
$creadsPrec :: Int -> ReadS NormalAnnotation
Read, Int -> NormalAnnotation -> String -> String
[NormalAnnotation] -> String -> String
NormalAnnotation -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [NormalAnnotation] -> String -> String
$cshowList :: [NormalAnnotation] -> String -> String
show :: NormalAnnotation -> String
$cshow :: NormalAnnotation -> String
showsPrec :: Int -> NormalAnnotation -> String -> String
$cshowsPrec :: Int -> NormalAnnotation -> String -> String
Show)

_NormalAnnotation :: Name
_NormalAnnotation = (String -> Name
Core.Name String
"hydra/ext/java/syntax.NormalAnnotation")

_NormalAnnotation_typeName :: FieldName
_NormalAnnotation_typeName = (String -> FieldName
Core.FieldName String
"typeName")

_NormalAnnotation_pairs :: FieldName
_NormalAnnotation_pairs = (String -> FieldName
Core.FieldName String
"pairs")

data ElementValuePair = 
  ElementValuePair {
    ElementValuePair -> Identifier
elementValuePairKey :: Identifier,
    ElementValuePair -> ElementValue
elementValuePairValue :: ElementValue}
  deriving (ElementValuePair -> ElementValuePair -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ElementValuePair -> ElementValuePair -> Bool
$c/= :: ElementValuePair -> ElementValuePair -> Bool
== :: ElementValuePair -> ElementValuePair -> Bool
$c== :: ElementValuePair -> ElementValuePair -> Bool
Eq, Eq ElementValuePair
ElementValuePair -> ElementValuePair -> Bool
ElementValuePair -> ElementValuePair -> Ordering
ElementValuePair -> ElementValuePair -> ElementValuePair
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ElementValuePair -> ElementValuePair -> ElementValuePair
$cmin :: ElementValuePair -> ElementValuePair -> ElementValuePair
max :: ElementValuePair -> ElementValuePair -> ElementValuePair
$cmax :: ElementValuePair -> ElementValuePair -> ElementValuePair
>= :: ElementValuePair -> ElementValuePair -> Bool
$c>= :: ElementValuePair -> ElementValuePair -> Bool
> :: ElementValuePair -> ElementValuePair -> Bool
$c> :: ElementValuePair -> ElementValuePair -> Bool
<= :: ElementValuePair -> ElementValuePair -> Bool
$c<= :: ElementValuePair -> ElementValuePair -> Bool
< :: ElementValuePair -> ElementValuePair -> Bool
$c< :: ElementValuePair -> ElementValuePair -> Bool
compare :: ElementValuePair -> ElementValuePair -> Ordering
$ccompare :: ElementValuePair -> ElementValuePair -> Ordering
Ord, ReadPrec [ElementValuePair]
ReadPrec ElementValuePair
Int -> ReadS ElementValuePair
ReadS [ElementValuePair]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ElementValuePair]
$creadListPrec :: ReadPrec [ElementValuePair]
readPrec :: ReadPrec ElementValuePair
$creadPrec :: ReadPrec ElementValuePair
readList :: ReadS [ElementValuePair]
$creadList :: ReadS [ElementValuePair]
readsPrec :: Int -> ReadS ElementValuePair
$creadsPrec :: Int -> ReadS ElementValuePair
Read, Int -> ElementValuePair -> String -> String
[ElementValuePair] -> String -> String
ElementValuePair -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ElementValuePair] -> String -> String
$cshowList :: [ElementValuePair] -> String -> String
show :: ElementValuePair -> String
$cshow :: ElementValuePair -> String
showsPrec :: Int -> ElementValuePair -> String -> String
$cshowsPrec :: Int -> ElementValuePair -> String -> String
Show)

_ElementValuePair :: Name
_ElementValuePair = (String -> Name
Core.Name String
"hydra/ext/java/syntax.ElementValuePair")

_ElementValuePair_key :: FieldName
_ElementValuePair_key = (String -> FieldName
Core.FieldName String
"key")

_ElementValuePair_value :: FieldName
_ElementValuePair_value = (String -> FieldName
Core.FieldName String
"value")

data ElementValue = 
  ElementValueConditionalExpression ConditionalExpression |
  ElementValueElementValueArrayInitializer ElementValueArrayInitializer |
  ElementValueAnnotation Annotation
  deriving (ElementValue -> ElementValue -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ElementValue -> ElementValue -> Bool
$c/= :: ElementValue -> ElementValue -> Bool
== :: ElementValue -> ElementValue -> Bool
$c== :: ElementValue -> ElementValue -> Bool
Eq, Eq ElementValue
ElementValue -> ElementValue -> Bool
ElementValue -> ElementValue -> Ordering
ElementValue -> ElementValue -> ElementValue
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ElementValue -> ElementValue -> ElementValue
$cmin :: ElementValue -> ElementValue -> ElementValue
max :: ElementValue -> ElementValue -> ElementValue
$cmax :: ElementValue -> ElementValue -> ElementValue
>= :: ElementValue -> ElementValue -> Bool
$c>= :: ElementValue -> ElementValue -> Bool
> :: ElementValue -> ElementValue -> Bool
$c> :: ElementValue -> ElementValue -> Bool
<= :: ElementValue -> ElementValue -> Bool
$c<= :: ElementValue -> ElementValue -> Bool
< :: ElementValue -> ElementValue -> Bool
$c< :: ElementValue -> ElementValue -> Bool
compare :: ElementValue -> ElementValue -> Ordering
$ccompare :: ElementValue -> ElementValue -> Ordering
Ord, ReadPrec [ElementValue]
ReadPrec ElementValue
Int -> ReadS ElementValue
ReadS [ElementValue]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ElementValue]
$creadListPrec :: ReadPrec [ElementValue]
readPrec :: ReadPrec ElementValue
$creadPrec :: ReadPrec ElementValue
readList :: ReadS [ElementValue]
$creadList :: ReadS [ElementValue]
readsPrec :: Int -> ReadS ElementValue
$creadsPrec :: Int -> ReadS ElementValue
Read, Int -> ElementValue -> String -> String
[ElementValue] -> String -> String
ElementValue -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ElementValue] -> String -> String
$cshowList :: [ElementValue] -> String -> String
show :: ElementValue -> String
$cshow :: ElementValue -> String
showsPrec :: Int -> ElementValue -> String -> String
$cshowsPrec :: Int -> ElementValue -> String -> String
Show)

_ElementValue :: Name
_ElementValue = (String -> Name
Core.Name String
"hydra/ext/java/syntax.ElementValue")

_ElementValue_conditionalExpression :: FieldName
_ElementValue_conditionalExpression = (String -> FieldName
Core.FieldName String
"conditionalExpression")

_ElementValue_elementValueArrayInitializer :: FieldName
_ElementValue_elementValueArrayInitializer = (String -> FieldName
Core.FieldName String
"elementValueArrayInitializer")

_ElementValue_annotation :: FieldName
_ElementValue_annotation = (String -> FieldName
Core.FieldName String
"annotation")

newtype ElementValueArrayInitializer = 
  ElementValueArrayInitializer {
    ElementValueArrayInitializer -> [ElementValue]
unElementValueArrayInitializer :: [ElementValue]}
  deriving (ElementValueArrayInitializer
-> ElementValueArrayInitializer -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ElementValueArrayInitializer
-> ElementValueArrayInitializer -> Bool
$c/= :: ElementValueArrayInitializer
-> ElementValueArrayInitializer -> Bool
== :: ElementValueArrayInitializer
-> ElementValueArrayInitializer -> Bool
$c== :: ElementValueArrayInitializer
-> ElementValueArrayInitializer -> Bool
Eq, Eq ElementValueArrayInitializer
ElementValueArrayInitializer
-> ElementValueArrayInitializer -> Bool
ElementValueArrayInitializer
-> ElementValueArrayInitializer -> Ordering
ElementValueArrayInitializer
-> ElementValueArrayInitializer -> ElementValueArrayInitializer
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ElementValueArrayInitializer
-> ElementValueArrayInitializer -> ElementValueArrayInitializer
$cmin :: ElementValueArrayInitializer
-> ElementValueArrayInitializer -> ElementValueArrayInitializer
max :: ElementValueArrayInitializer
-> ElementValueArrayInitializer -> ElementValueArrayInitializer
$cmax :: ElementValueArrayInitializer
-> ElementValueArrayInitializer -> ElementValueArrayInitializer
>= :: ElementValueArrayInitializer
-> ElementValueArrayInitializer -> Bool
$c>= :: ElementValueArrayInitializer
-> ElementValueArrayInitializer -> Bool
> :: ElementValueArrayInitializer
-> ElementValueArrayInitializer -> Bool
$c> :: ElementValueArrayInitializer
-> ElementValueArrayInitializer -> Bool
<= :: ElementValueArrayInitializer
-> ElementValueArrayInitializer -> Bool
$c<= :: ElementValueArrayInitializer
-> ElementValueArrayInitializer -> Bool
< :: ElementValueArrayInitializer
-> ElementValueArrayInitializer -> Bool
$c< :: ElementValueArrayInitializer
-> ElementValueArrayInitializer -> Bool
compare :: ElementValueArrayInitializer
-> ElementValueArrayInitializer -> Ordering
$ccompare :: ElementValueArrayInitializer
-> ElementValueArrayInitializer -> Ordering
Ord, ReadPrec [ElementValueArrayInitializer]
ReadPrec ElementValueArrayInitializer
Int -> ReadS ElementValueArrayInitializer
ReadS [ElementValueArrayInitializer]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ElementValueArrayInitializer]
$creadListPrec :: ReadPrec [ElementValueArrayInitializer]
readPrec :: ReadPrec ElementValueArrayInitializer
$creadPrec :: ReadPrec ElementValueArrayInitializer
readList :: ReadS [ElementValueArrayInitializer]
$creadList :: ReadS [ElementValueArrayInitializer]
readsPrec :: Int -> ReadS ElementValueArrayInitializer
$creadsPrec :: Int -> ReadS ElementValueArrayInitializer
Read, Int -> ElementValueArrayInitializer -> String -> String
[ElementValueArrayInitializer] -> String -> String
ElementValueArrayInitializer -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ElementValueArrayInitializer] -> String -> String
$cshowList :: [ElementValueArrayInitializer] -> String -> String
show :: ElementValueArrayInitializer -> String
$cshow :: ElementValueArrayInitializer -> String
showsPrec :: Int -> ElementValueArrayInitializer -> String -> String
$cshowsPrec :: Int -> ElementValueArrayInitializer -> String -> String
Show)

_ElementValueArrayInitializer :: Name
_ElementValueArrayInitializer = (String -> Name
Core.Name String
"hydra/ext/java/syntax.ElementValueArrayInitializer")

newtype MarkerAnnotation = 
  MarkerAnnotation {
    MarkerAnnotation -> TypeName
unMarkerAnnotation :: TypeName}
  deriving (MarkerAnnotation -> MarkerAnnotation -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MarkerAnnotation -> MarkerAnnotation -> Bool
$c/= :: MarkerAnnotation -> MarkerAnnotation -> Bool
== :: MarkerAnnotation -> MarkerAnnotation -> Bool
$c== :: MarkerAnnotation -> MarkerAnnotation -> Bool
Eq, Eq MarkerAnnotation
MarkerAnnotation -> MarkerAnnotation -> Bool
MarkerAnnotation -> MarkerAnnotation -> Ordering
MarkerAnnotation -> MarkerAnnotation -> MarkerAnnotation
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: MarkerAnnotation -> MarkerAnnotation -> MarkerAnnotation
$cmin :: MarkerAnnotation -> MarkerAnnotation -> MarkerAnnotation
max :: MarkerAnnotation -> MarkerAnnotation -> MarkerAnnotation
$cmax :: MarkerAnnotation -> MarkerAnnotation -> MarkerAnnotation
>= :: MarkerAnnotation -> MarkerAnnotation -> Bool
$c>= :: MarkerAnnotation -> MarkerAnnotation -> Bool
> :: MarkerAnnotation -> MarkerAnnotation -> Bool
$c> :: MarkerAnnotation -> MarkerAnnotation -> Bool
<= :: MarkerAnnotation -> MarkerAnnotation -> Bool
$c<= :: MarkerAnnotation -> MarkerAnnotation -> Bool
< :: MarkerAnnotation -> MarkerAnnotation -> Bool
$c< :: MarkerAnnotation -> MarkerAnnotation -> Bool
compare :: MarkerAnnotation -> MarkerAnnotation -> Ordering
$ccompare :: MarkerAnnotation -> MarkerAnnotation -> Ordering
Ord, ReadPrec [MarkerAnnotation]
ReadPrec MarkerAnnotation
Int -> ReadS MarkerAnnotation
ReadS [MarkerAnnotation]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [MarkerAnnotation]
$creadListPrec :: ReadPrec [MarkerAnnotation]
readPrec :: ReadPrec MarkerAnnotation
$creadPrec :: ReadPrec MarkerAnnotation
readList :: ReadS [MarkerAnnotation]
$creadList :: ReadS [MarkerAnnotation]
readsPrec :: Int -> ReadS MarkerAnnotation
$creadsPrec :: Int -> ReadS MarkerAnnotation
Read, Int -> MarkerAnnotation -> String -> String
[MarkerAnnotation] -> String -> String
MarkerAnnotation -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [MarkerAnnotation] -> String -> String
$cshowList :: [MarkerAnnotation] -> String -> String
show :: MarkerAnnotation -> String
$cshow :: MarkerAnnotation -> String
showsPrec :: Int -> MarkerAnnotation -> String -> String
$cshowsPrec :: Int -> MarkerAnnotation -> String -> String
Show)

_MarkerAnnotation :: Name
_MarkerAnnotation = (String -> Name
Core.Name String
"hydra/ext/java/syntax.MarkerAnnotation")

data SingleElementAnnotation = 
  SingleElementAnnotation {
    SingleElementAnnotation -> TypeName
singleElementAnnotationName :: TypeName,
    SingleElementAnnotation -> Maybe ElementValue
singleElementAnnotationValue :: (Maybe ElementValue)}
  deriving (SingleElementAnnotation -> SingleElementAnnotation -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SingleElementAnnotation -> SingleElementAnnotation -> Bool
$c/= :: SingleElementAnnotation -> SingleElementAnnotation -> Bool
== :: SingleElementAnnotation -> SingleElementAnnotation -> Bool
$c== :: SingleElementAnnotation -> SingleElementAnnotation -> Bool
Eq, Eq SingleElementAnnotation
SingleElementAnnotation -> SingleElementAnnotation -> Bool
SingleElementAnnotation -> SingleElementAnnotation -> Ordering
SingleElementAnnotation
-> SingleElementAnnotation -> SingleElementAnnotation
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: SingleElementAnnotation
-> SingleElementAnnotation -> SingleElementAnnotation
$cmin :: SingleElementAnnotation
-> SingleElementAnnotation -> SingleElementAnnotation
max :: SingleElementAnnotation
-> SingleElementAnnotation -> SingleElementAnnotation
$cmax :: SingleElementAnnotation
-> SingleElementAnnotation -> SingleElementAnnotation
>= :: SingleElementAnnotation -> SingleElementAnnotation -> Bool
$c>= :: SingleElementAnnotation -> SingleElementAnnotation -> Bool
> :: SingleElementAnnotation -> SingleElementAnnotation -> Bool
$c> :: SingleElementAnnotation -> SingleElementAnnotation -> Bool
<= :: SingleElementAnnotation -> SingleElementAnnotation -> Bool
$c<= :: SingleElementAnnotation -> SingleElementAnnotation -> Bool
< :: SingleElementAnnotation -> SingleElementAnnotation -> Bool
$c< :: SingleElementAnnotation -> SingleElementAnnotation -> Bool
compare :: SingleElementAnnotation -> SingleElementAnnotation -> Ordering
$ccompare :: SingleElementAnnotation -> SingleElementAnnotation -> Ordering
Ord, ReadPrec [SingleElementAnnotation]
ReadPrec SingleElementAnnotation
Int -> ReadS SingleElementAnnotation
ReadS [SingleElementAnnotation]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SingleElementAnnotation]
$creadListPrec :: ReadPrec [SingleElementAnnotation]
readPrec :: ReadPrec SingleElementAnnotation
$creadPrec :: ReadPrec SingleElementAnnotation
readList :: ReadS [SingleElementAnnotation]
$creadList :: ReadS [SingleElementAnnotation]
readsPrec :: Int -> ReadS SingleElementAnnotation
$creadsPrec :: Int -> ReadS SingleElementAnnotation
Read, Int -> SingleElementAnnotation -> String -> String
[SingleElementAnnotation] -> String -> String
SingleElementAnnotation -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [SingleElementAnnotation] -> String -> String
$cshowList :: [SingleElementAnnotation] -> String -> String
show :: SingleElementAnnotation -> String
$cshow :: SingleElementAnnotation -> String
showsPrec :: Int -> SingleElementAnnotation -> String -> String
$cshowsPrec :: Int -> SingleElementAnnotation -> String -> String
Show)

_SingleElementAnnotation :: Name
_SingleElementAnnotation = (String -> Name
Core.Name String
"hydra/ext/java/syntax.SingleElementAnnotation")

_SingleElementAnnotation_name :: FieldName
_SingleElementAnnotation_name = (String -> FieldName
Core.FieldName String
"name")

_SingleElementAnnotation_value :: FieldName
_SingleElementAnnotation_value = (String -> FieldName
Core.FieldName String
"value")

newtype ArrayInitializer = 
  ArrayInitializer {
    ArrayInitializer -> [[VariableInitializer]]
unArrayInitializer :: [[VariableInitializer]]}
  deriving (ArrayInitializer -> ArrayInitializer -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ArrayInitializer -> ArrayInitializer -> Bool
$c/= :: ArrayInitializer -> ArrayInitializer -> Bool
== :: ArrayInitializer -> ArrayInitializer -> Bool
$c== :: ArrayInitializer -> ArrayInitializer -> Bool
Eq, Eq ArrayInitializer
ArrayInitializer -> ArrayInitializer -> Bool
ArrayInitializer -> ArrayInitializer -> Ordering
ArrayInitializer -> ArrayInitializer -> ArrayInitializer
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ArrayInitializer -> ArrayInitializer -> ArrayInitializer
$cmin :: ArrayInitializer -> ArrayInitializer -> ArrayInitializer
max :: ArrayInitializer -> ArrayInitializer -> ArrayInitializer
$cmax :: ArrayInitializer -> ArrayInitializer -> ArrayInitializer
>= :: ArrayInitializer -> ArrayInitializer -> Bool
$c>= :: ArrayInitializer -> ArrayInitializer -> Bool
> :: ArrayInitializer -> ArrayInitializer -> Bool
$c> :: ArrayInitializer -> ArrayInitializer -> Bool
<= :: ArrayInitializer -> ArrayInitializer -> Bool
$c<= :: ArrayInitializer -> ArrayInitializer -> Bool
< :: ArrayInitializer -> ArrayInitializer -> Bool
$c< :: ArrayInitializer -> ArrayInitializer -> Bool
compare :: ArrayInitializer -> ArrayInitializer -> Ordering
$ccompare :: ArrayInitializer -> ArrayInitializer -> Ordering
Ord, ReadPrec [ArrayInitializer]
ReadPrec ArrayInitializer
Int -> ReadS ArrayInitializer
ReadS [ArrayInitializer]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ArrayInitializer]
$creadListPrec :: ReadPrec [ArrayInitializer]
readPrec :: ReadPrec ArrayInitializer
$creadPrec :: ReadPrec ArrayInitializer
readList :: ReadS [ArrayInitializer]
$creadList :: ReadS [ArrayInitializer]
readsPrec :: Int -> ReadS ArrayInitializer
$creadsPrec :: Int -> ReadS ArrayInitializer
Read, Int -> ArrayInitializer -> String -> String
[ArrayInitializer] -> String -> String
ArrayInitializer -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ArrayInitializer] -> String -> String
$cshowList :: [ArrayInitializer] -> String -> String
show :: ArrayInitializer -> String
$cshow :: ArrayInitializer -> String
showsPrec :: Int -> ArrayInitializer -> String -> String
$cshowsPrec :: Int -> ArrayInitializer -> String -> String
Show)

_ArrayInitializer :: Name
_ArrayInitializer = (String -> Name
Core.Name String
"hydra/ext/java/syntax.ArrayInitializer")

newtype Block = 
  Block {
    Block -> [BlockStatement]
unBlock :: [BlockStatement]}
  deriving (Block -> Block -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Block -> Block -> Bool
$c/= :: Block -> Block -> Bool
== :: Block -> Block -> Bool
$c== :: Block -> Block -> Bool
Eq, Eq Block
Block -> Block -> Bool
Block -> Block -> Ordering
Block -> Block -> Block
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Block -> Block -> Block
$cmin :: Block -> Block -> Block
max :: Block -> Block -> Block
$cmax :: Block -> Block -> Block
>= :: Block -> Block -> Bool
$c>= :: Block -> Block -> Bool
> :: Block -> Block -> Bool
$c> :: Block -> Block -> Bool
<= :: Block -> Block -> Bool
$c<= :: Block -> Block -> Bool
< :: Block -> Block -> Bool
$c< :: Block -> Block -> Bool
compare :: Block -> Block -> Ordering
$ccompare :: Block -> Block -> Ordering
Ord, ReadPrec [Block]
ReadPrec Block
Int -> ReadS Block
ReadS [Block]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Block]
$creadListPrec :: ReadPrec [Block]
readPrec :: ReadPrec Block
$creadPrec :: ReadPrec Block
readList :: ReadS [Block]
$creadList :: ReadS [Block]
readsPrec :: Int -> ReadS Block
$creadsPrec :: Int -> ReadS Block
Read, Int -> Block -> String -> String
[Block] -> String -> String
Block -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [Block] -> String -> String
$cshowList :: [Block] -> String -> String
show :: Block -> String
$cshow :: Block -> String
showsPrec :: Int -> Block -> String -> String
$cshowsPrec :: Int -> Block -> String -> String
Show)

_Block :: Name
_Block = (String -> Name
Core.Name String
"hydra/ext/java/syntax.Block")

data BlockStatement = 
  BlockStatementLocalVariableDeclaration LocalVariableDeclarationStatement |
  BlockStatementClass ClassDeclaration |
  BlockStatementStatement Statement
  deriving (BlockStatement -> BlockStatement -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BlockStatement -> BlockStatement -> Bool
$c/= :: BlockStatement -> BlockStatement -> Bool
== :: BlockStatement -> BlockStatement -> Bool
$c== :: BlockStatement -> BlockStatement -> Bool
Eq, Eq BlockStatement
BlockStatement -> BlockStatement -> Bool
BlockStatement -> BlockStatement -> Ordering
BlockStatement -> BlockStatement -> BlockStatement
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: BlockStatement -> BlockStatement -> BlockStatement
$cmin :: BlockStatement -> BlockStatement -> BlockStatement
max :: BlockStatement -> BlockStatement -> BlockStatement
$cmax :: BlockStatement -> BlockStatement -> BlockStatement
>= :: BlockStatement -> BlockStatement -> Bool
$c>= :: BlockStatement -> BlockStatement -> Bool
> :: BlockStatement -> BlockStatement -> Bool
$c> :: BlockStatement -> BlockStatement -> Bool
<= :: BlockStatement -> BlockStatement -> Bool
$c<= :: BlockStatement -> BlockStatement -> Bool
< :: BlockStatement -> BlockStatement -> Bool
$c< :: BlockStatement -> BlockStatement -> Bool
compare :: BlockStatement -> BlockStatement -> Ordering
$ccompare :: BlockStatement -> BlockStatement -> Ordering
Ord, ReadPrec [BlockStatement]
ReadPrec BlockStatement
Int -> ReadS BlockStatement
ReadS [BlockStatement]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [BlockStatement]
$creadListPrec :: ReadPrec [BlockStatement]
readPrec :: ReadPrec BlockStatement
$creadPrec :: ReadPrec BlockStatement
readList :: ReadS [BlockStatement]
$creadList :: ReadS [BlockStatement]
readsPrec :: Int -> ReadS BlockStatement
$creadsPrec :: Int -> ReadS BlockStatement
Read, Int -> BlockStatement -> String -> String
[BlockStatement] -> String -> String
BlockStatement -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [BlockStatement] -> String -> String
$cshowList :: [BlockStatement] -> String -> String
show :: BlockStatement -> String
$cshow :: BlockStatement -> String
showsPrec :: Int -> BlockStatement -> String -> String
$cshowsPrec :: Int -> BlockStatement -> String -> String
Show)

_BlockStatement :: Name
_BlockStatement = (String -> Name
Core.Name String
"hydra/ext/java/syntax.BlockStatement")

_BlockStatement_localVariableDeclaration :: FieldName
_BlockStatement_localVariableDeclaration = (String -> FieldName
Core.FieldName String
"localVariableDeclaration")

_BlockStatement_class :: FieldName
_BlockStatement_class = (String -> FieldName
Core.FieldName String
"class")

_BlockStatement_statement :: FieldName
_BlockStatement_statement = (String -> FieldName
Core.FieldName String
"statement")

newtype LocalVariableDeclarationStatement = 
  LocalVariableDeclarationStatement {
    LocalVariableDeclarationStatement -> LocalVariableDeclaration
unLocalVariableDeclarationStatement :: LocalVariableDeclaration}
  deriving (LocalVariableDeclarationStatement
-> LocalVariableDeclarationStatement -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LocalVariableDeclarationStatement
-> LocalVariableDeclarationStatement -> Bool
$c/= :: LocalVariableDeclarationStatement
-> LocalVariableDeclarationStatement -> Bool
== :: LocalVariableDeclarationStatement
-> LocalVariableDeclarationStatement -> Bool
$c== :: LocalVariableDeclarationStatement
-> LocalVariableDeclarationStatement -> Bool
Eq, Eq LocalVariableDeclarationStatement
LocalVariableDeclarationStatement
-> LocalVariableDeclarationStatement -> Bool
LocalVariableDeclarationStatement
-> LocalVariableDeclarationStatement -> Ordering
LocalVariableDeclarationStatement
-> LocalVariableDeclarationStatement
-> LocalVariableDeclarationStatement
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: LocalVariableDeclarationStatement
-> LocalVariableDeclarationStatement
-> LocalVariableDeclarationStatement
$cmin :: LocalVariableDeclarationStatement
-> LocalVariableDeclarationStatement
-> LocalVariableDeclarationStatement
max :: LocalVariableDeclarationStatement
-> LocalVariableDeclarationStatement
-> LocalVariableDeclarationStatement
$cmax :: LocalVariableDeclarationStatement
-> LocalVariableDeclarationStatement
-> LocalVariableDeclarationStatement
>= :: LocalVariableDeclarationStatement
-> LocalVariableDeclarationStatement -> Bool
$c>= :: LocalVariableDeclarationStatement
-> LocalVariableDeclarationStatement -> Bool
> :: LocalVariableDeclarationStatement
-> LocalVariableDeclarationStatement -> Bool
$c> :: LocalVariableDeclarationStatement
-> LocalVariableDeclarationStatement -> Bool
<= :: LocalVariableDeclarationStatement
-> LocalVariableDeclarationStatement -> Bool
$c<= :: LocalVariableDeclarationStatement
-> LocalVariableDeclarationStatement -> Bool
< :: LocalVariableDeclarationStatement
-> LocalVariableDeclarationStatement -> Bool
$c< :: LocalVariableDeclarationStatement
-> LocalVariableDeclarationStatement -> Bool
compare :: LocalVariableDeclarationStatement
-> LocalVariableDeclarationStatement -> Ordering
$ccompare :: LocalVariableDeclarationStatement
-> LocalVariableDeclarationStatement -> Ordering
Ord, ReadPrec [LocalVariableDeclarationStatement]
ReadPrec LocalVariableDeclarationStatement
Int -> ReadS LocalVariableDeclarationStatement
ReadS [LocalVariableDeclarationStatement]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [LocalVariableDeclarationStatement]
$creadListPrec :: ReadPrec [LocalVariableDeclarationStatement]
readPrec :: ReadPrec LocalVariableDeclarationStatement
$creadPrec :: ReadPrec LocalVariableDeclarationStatement
readList :: ReadS [LocalVariableDeclarationStatement]
$creadList :: ReadS [LocalVariableDeclarationStatement]
readsPrec :: Int -> ReadS LocalVariableDeclarationStatement
$creadsPrec :: Int -> ReadS LocalVariableDeclarationStatement
Read, Int -> LocalVariableDeclarationStatement -> String -> String
[LocalVariableDeclarationStatement] -> String -> String
LocalVariableDeclarationStatement -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [LocalVariableDeclarationStatement] -> String -> String
$cshowList :: [LocalVariableDeclarationStatement] -> String -> String
show :: LocalVariableDeclarationStatement -> String
$cshow :: LocalVariableDeclarationStatement -> String
showsPrec :: Int -> LocalVariableDeclarationStatement -> String -> String
$cshowsPrec :: Int -> LocalVariableDeclarationStatement -> String -> String
Show)

_LocalVariableDeclarationStatement :: Name
_LocalVariableDeclarationStatement = (String -> Name
Core.Name String
"hydra/ext/java/syntax.LocalVariableDeclarationStatement")

data LocalVariableDeclaration = 
  LocalVariableDeclaration {
    LocalVariableDeclaration -> [VariableModifier]
localVariableDeclarationModifiers :: [VariableModifier],
    LocalVariableDeclaration -> LocalVariableType
localVariableDeclarationType :: LocalVariableType,
    LocalVariableDeclaration -> [VariableDeclarator]
localVariableDeclarationDeclarators :: [VariableDeclarator]}
  deriving (LocalVariableDeclaration -> LocalVariableDeclaration -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LocalVariableDeclaration -> LocalVariableDeclaration -> Bool
$c/= :: LocalVariableDeclaration -> LocalVariableDeclaration -> Bool
== :: LocalVariableDeclaration -> LocalVariableDeclaration -> Bool
$c== :: LocalVariableDeclaration -> LocalVariableDeclaration -> Bool
Eq, Eq LocalVariableDeclaration
LocalVariableDeclaration -> LocalVariableDeclaration -> Bool
LocalVariableDeclaration -> LocalVariableDeclaration -> Ordering
LocalVariableDeclaration
-> LocalVariableDeclaration -> LocalVariableDeclaration
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: LocalVariableDeclaration
-> LocalVariableDeclaration -> LocalVariableDeclaration
$cmin :: LocalVariableDeclaration
-> LocalVariableDeclaration -> LocalVariableDeclaration
max :: LocalVariableDeclaration
-> LocalVariableDeclaration -> LocalVariableDeclaration
$cmax :: LocalVariableDeclaration
-> LocalVariableDeclaration -> LocalVariableDeclaration
>= :: LocalVariableDeclaration -> LocalVariableDeclaration -> Bool
$c>= :: LocalVariableDeclaration -> LocalVariableDeclaration -> Bool
> :: LocalVariableDeclaration -> LocalVariableDeclaration -> Bool
$c> :: LocalVariableDeclaration -> LocalVariableDeclaration -> Bool
<= :: LocalVariableDeclaration -> LocalVariableDeclaration -> Bool
$c<= :: LocalVariableDeclaration -> LocalVariableDeclaration -> Bool
< :: LocalVariableDeclaration -> LocalVariableDeclaration -> Bool
$c< :: LocalVariableDeclaration -> LocalVariableDeclaration -> Bool
compare :: LocalVariableDeclaration -> LocalVariableDeclaration -> Ordering
$ccompare :: LocalVariableDeclaration -> LocalVariableDeclaration -> Ordering
Ord, ReadPrec [LocalVariableDeclaration]
ReadPrec LocalVariableDeclaration
Int -> ReadS LocalVariableDeclaration
ReadS [LocalVariableDeclaration]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [LocalVariableDeclaration]
$creadListPrec :: ReadPrec [LocalVariableDeclaration]
readPrec :: ReadPrec LocalVariableDeclaration
$creadPrec :: ReadPrec LocalVariableDeclaration
readList :: ReadS [LocalVariableDeclaration]
$creadList :: ReadS [LocalVariableDeclaration]
readsPrec :: Int -> ReadS LocalVariableDeclaration
$creadsPrec :: Int -> ReadS LocalVariableDeclaration
Read, Int -> LocalVariableDeclaration -> String -> String
[LocalVariableDeclaration] -> String -> String
LocalVariableDeclaration -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [LocalVariableDeclaration] -> String -> String
$cshowList :: [LocalVariableDeclaration] -> String -> String
show :: LocalVariableDeclaration -> String
$cshow :: LocalVariableDeclaration -> String
showsPrec :: Int -> LocalVariableDeclaration -> String -> String
$cshowsPrec :: Int -> LocalVariableDeclaration -> String -> String
Show)

_LocalVariableDeclaration :: Name
_LocalVariableDeclaration = (String -> Name
Core.Name String
"hydra/ext/java/syntax.LocalVariableDeclaration")

_LocalVariableDeclaration_modifiers :: FieldName
_LocalVariableDeclaration_modifiers = (String -> FieldName
Core.FieldName String
"modifiers")

_LocalVariableDeclaration_type :: FieldName
_LocalVariableDeclaration_type = (String -> FieldName
Core.FieldName String
"type")

_LocalVariableDeclaration_declarators :: FieldName
_LocalVariableDeclaration_declarators = (String -> FieldName
Core.FieldName String
"declarators")

data LocalVariableType = 
  LocalVariableTypeType UnannType |
  LocalVariableTypeVar 
  deriving (LocalVariableType -> LocalVariableType -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LocalVariableType -> LocalVariableType -> Bool
$c/= :: LocalVariableType -> LocalVariableType -> Bool
== :: LocalVariableType -> LocalVariableType -> Bool
$c== :: LocalVariableType -> LocalVariableType -> Bool
Eq, Eq LocalVariableType
LocalVariableType -> LocalVariableType -> Bool
LocalVariableType -> LocalVariableType -> Ordering
LocalVariableType -> LocalVariableType -> LocalVariableType
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: LocalVariableType -> LocalVariableType -> LocalVariableType
$cmin :: LocalVariableType -> LocalVariableType -> LocalVariableType
max :: LocalVariableType -> LocalVariableType -> LocalVariableType
$cmax :: LocalVariableType -> LocalVariableType -> LocalVariableType
>= :: LocalVariableType -> LocalVariableType -> Bool
$c>= :: LocalVariableType -> LocalVariableType -> Bool
> :: LocalVariableType -> LocalVariableType -> Bool
$c> :: LocalVariableType -> LocalVariableType -> Bool
<= :: LocalVariableType -> LocalVariableType -> Bool
$c<= :: LocalVariableType -> LocalVariableType -> Bool
< :: LocalVariableType -> LocalVariableType -> Bool
$c< :: LocalVariableType -> LocalVariableType -> Bool
compare :: LocalVariableType -> LocalVariableType -> Ordering
$ccompare :: LocalVariableType -> LocalVariableType -> Ordering
Ord, ReadPrec [LocalVariableType]
ReadPrec LocalVariableType
Int -> ReadS LocalVariableType
ReadS [LocalVariableType]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [LocalVariableType]
$creadListPrec :: ReadPrec [LocalVariableType]
readPrec :: ReadPrec LocalVariableType
$creadPrec :: ReadPrec LocalVariableType
readList :: ReadS [LocalVariableType]
$creadList :: ReadS [LocalVariableType]
readsPrec :: Int -> ReadS LocalVariableType
$creadsPrec :: Int -> ReadS LocalVariableType
Read, Int -> LocalVariableType -> String -> String
[LocalVariableType] -> String -> String
LocalVariableType -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [LocalVariableType] -> String -> String
$cshowList :: [LocalVariableType] -> String -> String
show :: LocalVariableType -> String
$cshow :: LocalVariableType -> String
showsPrec :: Int -> LocalVariableType -> String -> String
$cshowsPrec :: Int -> LocalVariableType -> String -> String
Show)

_LocalVariableType :: Name
_LocalVariableType = (String -> Name
Core.Name String
"hydra/ext/java/syntax.LocalVariableType")

_LocalVariableType_type :: FieldName
_LocalVariableType_type = (String -> FieldName
Core.FieldName String
"type")

_LocalVariableType_var :: FieldName
_LocalVariableType_var = (String -> FieldName
Core.FieldName String
"var")

data Statement = 
  StatementWithoutTrailing StatementWithoutTrailingSubstatement |
  StatementLabeled LabeledStatement |
  StatementIfThen IfThenStatement |
  StatementIfThenElse IfThenElseStatement |
  StatementWhile WhileStatement |
  StatementFor ForStatement
  deriving (Statement -> Statement -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Statement -> Statement -> Bool
$c/= :: Statement -> Statement -> Bool
== :: Statement -> Statement -> Bool
$c== :: Statement -> Statement -> Bool
Eq, Eq Statement
Statement -> Statement -> Bool
Statement -> Statement -> Ordering
Statement -> Statement -> Statement
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Statement -> Statement -> Statement
$cmin :: Statement -> Statement -> Statement
max :: Statement -> Statement -> Statement
$cmax :: Statement -> Statement -> Statement
>= :: Statement -> Statement -> Bool
$c>= :: Statement -> Statement -> Bool
> :: Statement -> Statement -> Bool
$c> :: Statement -> Statement -> Bool
<= :: Statement -> Statement -> Bool
$c<= :: Statement -> Statement -> Bool
< :: Statement -> Statement -> Bool
$c< :: Statement -> Statement -> Bool
compare :: Statement -> Statement -> Ordering
$ccompare :: Statement -> Statement -> Ordering
Ord, ReadPrec [Statement]
ReadPrec Statement
Int -> ReadS Statement
ReadS [Statement]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Statement]
$creadListPrec :: ReadPrec [Statement]
readPrec :: ReadPrec Statement
$creadPrec :: ReadPrec Statement
readList :: ReadS [Statement]
$creadList :: ReadS [Statement]
readsPrec :: Int -> ReadS Statement
$creadsPrec :: Int -> ReadS Statement
Read, Int -> Statement -> String -> String
[Statement] -> String -> String
Statement -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [Statement] -> String -> String
$cshowList :: [Statement] -> String -> String
show :: Statement -> String
$cshow :: Statement -> String
showsPrec :: Int -> Statement -> String -> String
$cshowsPrec :: Int -> Statement -> String -> String
Show)

_Statement :: Name
_Statement = (String -> Name
Core.Name String
"hydra/ext/java/syntax.Statement")

_Statement_withoutTrailing :: FieldName
_Statement_withoutTrailing = (String -> FieldName
Core.FieldName String
"withoutTrailing")

_Statement_labeled :: FieldName
_Statement_labeled = (String -> FieldName
Core.FieldName String
"labeled")

_Statement_ifThen :: FieldName
_Statement_ifThen = (String -> FieldName
Core.FieldName String
"ifThen")

_Statement_ifThenElse :: FieldName
_Statement_ifThenElse = (String -> FieldName
Core.FieldName String
"ifThenElse")

_Statement_while :: FieldName
_Statement_while = (String -> FieldName
Core.FieldName String
"while")

_Statement_for :: FieldName
_Statement_for = (String -> FieldName
Core.FieldName String
"for")

data StatementNoShortIf = 
  StatementNoShortIfWithoutTrailing StatementWithoutTrailingSubstatement |
  StatementNoShortIfLabeled LabeledStatementNoShortIf |
  StatementNoShortIfIfThenElse IfThenElseStatementNoShortIf |
  StatementNoShortIfWhile WhileStatementNoShortIf |
  StatementNoShortIfFor ForStatementNoShortIf
  deriving (StatementNoShortIf -> StatementNoShortIf -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StatementNoShortIf -> StatementNoShortIf -> Bool
$c/= :: StatementNoShortIf -> StatementNoShortIf -> Bool
== :: StatementNoShortIf -> StatementNoShortIf -> Bool
$c== :: StatementNoShortIf -> StatementNoShortIf -> Bool
Eq, Eq StatementNoShortIf
StatementNoShortIf -> StatementNoShortIf -> Bool
StatementNoShortIf -> StatementNoShortIf -> Ordering
StatementNoShortIf -> StatementNoShortIf -> StatementNoShortIf
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: StatementNoShortIf -> StatementNoShortIf -> StatementNoShortIf
$cmin :: StatementNoShortIf -> StatementNoShortIf -> StatementNoShortIf
max :: StatementNoShortIf -> StatementNoShortIf -> StatementNoShortIf
$cmax :: StatementNoShortIf -> StatementNoShortIf -> StatementNoShortIf
>= :: StatementNoShortIf -> StatementNoShortIf -> Bool
$c>= :: StatementNoShortIf -> StatementNoShortIf -> Bool
> :: StatementNoShortIf -> StatementNoShortIf -> Bool
$c> :: StatementNoShortIf -> StatementNoShortIf -> Bool
<= :: StatementNoShortIf -> StatementNoShortIf -> Bool
$c<= :: StatementNoShortIf -> StatementNoShortIf -> Bool
< :: StatementNoShortIf -> StatementNoShortIf -> Bool
$c< :: StatementNoShortIf -> StatementNoShortIf -> Bool
compare :: StatementNoShortIf -> StatementNoShortIf -> Ordering
$ccompare :: StatementNoShortIf -> StatementNoShortIf -> Ordering
Ord, ReadPrec [StatementNoShortIf]
ReadPrec StatementNoShortIf
Int -> ReadS StatementNoShortIf
ReadS [StatementNoShortIf]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StatementNoShortIf]
$creadListPrec :: ReadPrec [StatementNoShortIf]
readPrec :: ReadPrec StatementNoShortIf
$creadPrec :: ReadPrec StatementNoShortIf
readList :: ReadS [StatementNoShortIf]
$creadList :: ReadS [StatementNoShortIf]
readsPrec :: Int -> ReadS StatementNoShortIf
$creadsPrec :: Int -> ReadS StatementNoShortIf
Read, Int -> StatementNoShortIf -> String -> String
[StatementNoShortIf] -> String -> String
StatementNoShortIf -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [StatementNoShortIf] -> String -> String
$cshowList :: [StatementNoShortIf] -> String -> String
show :: StatementNoShortIf -> String
$cshow :: StatementNoShortIf -> String
showsPrec :: Int -> StatementNoShortIf -> String -> String
$cshowsPrec :: Int -> StatementNoShortIf -> String -> String
Show)

_StatementNoShortIf :: Name
_StatementNoShortIf = (String -> Name
Core.Name String
"hydra/ext/java/syntax.StatementNoShortIf")

_StatementNoShortIf_withoutTrailing :: FieldName
_StatementNoShortIf_withoutTrailing = (String -> FieldName
Core.FieldName String
"withoutTrailing")

_StatementNoShortIf_labeled :: FieldName
_StatementNoShortIf_labeled = (String -> FieldName
Core.FieldName String
"labeled")

_StatementNoShortIf_ifThenElse :: FieldName
_StatementNoShortIf_ifThenElse = (String -> FieldName
Core.FieldName String
"ifThenElse")

_StatementNoShortIf_while :: FieldName
_StatementNoShortIf_while = (String -> FieldName
Core.FieldName String
"while")

_StatementNoShortIf_for :: FieldName
_StatementNoShortIf_for = (String -> FieldName
Core.FieldName String
"for")

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
  deriving (StatementWithoutTrailingSubstatement
-> StatementWithoutTrailingSubstatement -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StatementWithoutTrailingSubstatement
-> StatementWithoutTrailingSubstatement -> Bool
$c/= :: StatementWithoutTrailingSubstatement
-> StatementWithoutTrailingSubstatement -> Bool
== :: StatementWithoutTrailingSubstatement
-> StatementWithoutTrailingSubstatement -> Bool
$c== :: StatementWithoutTrailingSubstatement
-> StatementWithoutTrailingSubstatement -> Bool
Eq, Eq StatementWithoutTrailingSubstatement
StatementWithoutTrailingSubstatement
-> StatementWithoutTrailingSubstatement -> Bool
StatementWithoutTrailingSubstatement
-> StatementWithoutTrailingSubstatement -> Ordering
StatementWithoutTrailingSubstatement
-> StatementWithoutTrailingSubstatement
-> StatementWithoutTrailingSubstatement
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: StatementWithoutTrailingSubstatement
-> StatementWithoutTrailingSubstatement
-> StatementWithoutTrailingSubstatement
$cmin :: StatementWithoutTrailingSubstatement
-> StatementWithoutTrailingSubstatement
-> StatementWithoutTrailingSubstatement
max :: StatementWithoutTrailingSubstatement
-> StatementWithoutTrailingSubstatement
-> StatementWithoutTrailingSubstatement
$cmax :: StatementWithoutTrailingSubstatement
-> StatementWithoutTrailingSubstatement
-> StatementWithoutTrailingSubstatement
>= :: StatementWithoutTrailingSubstatement
-> StatementWithoutTrailingSubstatement -> Bool
$c>= :: StatementWithoutTrailingSubstatement
-> StatementWithoutTrailingSubstatement -> Bool
> :: StatementWithoutTrailingSubstatement
-> StatementWithoutTrailingSubstatement -> Bool
$c> :: StatementWithoutTrailingSubstatement
-> StatementWithoutTrailingSubstatement -> Bool
<= :: StatementWithoutTrailingSubstatement
-> StatementWithoutTrailingSubstatement -> Bool
$c<= :: StatementWithoutTrailingSubstatement
-> StatementWithoutTrailingSubstatement -> Bool
< :: StatementWithoutTrailingSubstatement
-> StatementWithoutTrailingSubstatement -> Bool
$c< :: StatementWithoutTrailingSubstatement
-> StatementWithoutTrailingSubstatement -> Bool
compare :: StatementWithoutTrailingSubstatement
-> StatementWithoutTrailingSubstatement -> Ordering
$ccompare :: StatementWithoutTrailingSubstatement
-> StatementWithoutTrailingSubstatement -> Ordering
Ord, ReadPrec [StatementWithoutTrailingSubstatement]
ReadPrec StatementWithoutTrailingSubstatement
Int -> ReadS StatementWithoutTrailingSubstatement
ReadS [StatementWithoutTrailingSubstatement]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StatementWithoutTrailingSubstatement]
$creadListPrec :: ReadPrec [StatementWithoutTrailingSubstatement]
readPrec :: ReadPrec StatementWithoutTrailingSubstatement
$creadPrec :: ReadPrec StatementWithoutTrailingSubstatement
readList :: ReadS [StatementWithoutTrailingSubstatement]
$creadList :: ReadS [StatementWithoutTrailingSubstatement]
readsPrec :: Int -> ReadS StatementWithoutTrailingSubstatement
$creadsPrec :: Int -> ReadS StatementWithoutTrailingSubstatement
Read, Int -> StatementWithoutTrailingSubstatement -> String -> String
[StatementWithoutTrailingSubstatement] -> String -> String
StatementWithoutTrailingSubstatement -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [StatementWithoutTrailingSubstatement] -> String -> String
$cshowList :: [StatementWithoutTrailingSubstatement] -> String -> String
show :: StatementWithoutTrailingSubstatement -> String
$cshow :: StatementWithoutTrailingSubstatement -> String
showsPrec :: Int -> StatementWithoutTrailingSubstatement -> String -> String
$cshowsPrec :: Int -> StatementWithoutTrailingSubstatement -> String -> String
Show)

_StatementWithoutTrailingSubstatement :: Name
_StatementWithoutTrailingSubstatement = (String -> Name
Core.Name String
"hydra/ext/java/syntax.StatementWithoutTrailingSubstatement")

_StatementWithoutTrailingSubstatement_block :: FieldName
_StatementWithoutTrailingSubstatement_block = (String -> FieldName
Core.FieldName String
"block")

_StatementWithoutTrailingSubstatement_empty :: FieldName
_StatementWithoutTrailingSubstatement_empty = (String -> FieldName
Core.FieldName String
"empty")

_StatementWithoutTrailingSubstatement_expression :: FieldName
_StatementWithoutTrailingSubstatement_expression = (String -> FieldName
Core.FieldName String
"expression")

_StatementWithoutTrailingSubstatement_assert :: FieldName
_StatementWithoutTrailingSubstatement_assert = (String -> FieldName
Core.FieldName String
"assert")

_StatementWithoutTrailingSubstatement_switch :: FieldName
_StatementWithoutTrailingSubstatement_switch = (String -> FieldName
Core.FieldName String
"switch")

_StatementWithoutTrailingSubstatement_do :: FieldName
_StatementWithoutTrailingSubstatement_do = (String -> FieldName
Core.FieldName String
"do")

_StatementWithoutTrailingSubstatement_break :: FieldName
_StatementWithoutTrailingSubstatement_break = (String -> FieldName
Core.FieldName String
"break")

_StatementWithoutTrailingSubstatement_continue :: FieldName
_StatementWithoutTrailingSubstatement_continue = (String -> FieldName
Core.FieldName String
"continue")

_StatementWithoutTrailingSubstatement_return :: FieldName
_StatementWithoutTrailingSubstatement_return = (String -> FieldName
Core.FieldName String
"return")

_StatementWithoutTrailingSubstatement_synchronized :: FieldName
_StatementWithoutTrailingSubstatement_synchronized = (String -> FieldName
Core.FieldName String
"synchronized")

_StatementWithoutTrailingSubstatement_throw :: FieldName
_StatementWithoutTrailingSubstatement_throw = (String -> FieldName
Core.FieldName String
"throw")

_StatementWithoutTrailingSubstatement_try :: FieldName
_StatementWithoutTrailingSubstatement_try = (String -> FieldName
Core.FieldName String
"try")

data EmptyStatement = 
  EmptyStatement {}
  deriving (EmptyStatement -> EmptyStatement -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EmptyStatement -> EmptyStatement -> Bool
$c/= :: EmptyStatement -> EmptyStatement -> Bool
== :: EmptyStatement -> EmptyStatement -> Bool
$c== :: EmptyStatement -> EmptyStatement -> Bool
Eq, Eq EmptyStatement
EmptyStatement -> EmptyStatement -> Bool
EmptyStatement -> EmptyStatement -> Ordering
EmptyStatement -> EmptyStatement -> EmptyStatement
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: EmptyStatement -> EmptyStatement -> EmptyStatement
$cmin :: EmptyStatement -> EmptyStatement -> EmptyStatement
max :: EmptyStatement -> EmptyStatement -> EmptyStatement
$cmax :: EmptyStatement -> EmptyStatement -> EmptyStatement
>= :: EmptyStatement -> EmptyStatement -> Bool
$c>= :: EmptyStatement -> EmptyStatement -> Bool
> :: EmptyStatement -> EmptyStatement -> Bool
$c> :: EmptyStatement -> EmptyStatement -> Bool
<= :: EmptyStatement -> EmptyStatement -> Bool
$c<= :: EmptyStatement -> EmptyStatement -> Bool
< :: EmptyStatement -> EmptyStatement -> Bool
$c< :: EmptyStatement -> EmptyStatement -> Bool
compare :: EmptyStatement -> EmptyStatement -> Ordering
$ccompare :: EmptyStatement -> EmptyStatement -> Ordering
Ord, ReadPrec [EmptyStatement]
ReadPrec EmptyStatement
Int -> ReadS EmptyStatement
ReadS [EmptyStatement]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [EmptyStatement]
$creadListPrec :: ReadPrec [EmptyStatement]
readPrec :: ReadPrec EmptyStatement
$creadPrec :: ReadPrec EmptyStatement
readList :: ReadS [EmptyStatement]
$creadList :: ReadS [EmptyStatement]
readsPrec :: Int -> ReadS EmptyStatement
$creadsPrec :: Int -> ReadS EmptyStatement
Read, Int -> EmptyStatement -> String -> String
[EmptyStatement] -> String -> String
EmptyStatement -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [EmptyStatement] -> String -> String
$cshowList :: [EmptyStatement] -> String -> String
show :: EmptyStatement -> String
$cshow :: EmptyStatement -> String
showsPrec :: Int -> EmptyStatement -> String -> String
$cshowsPrec :: Int -> EmptyStatement -> String -> String
Show)

_EmptyStatement :: Name
_EmptyStatement = (String -> Name
Core.Name String
"hydra/ext/java/syntax.EmptyStatement")

data LabeledStatement = 
  LabeledStatement {
    LabeledStatement -> Identifier
labeledStatementIdentifier :: Identifier,
    LabeledStatement -> Statement
labeledStatementStatement :: Statement}
  deriving (LabeledStatement -> LabeledStatement -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LabeledStatement -> LabeledStatement -> Bool
$c/= :: LabeledStatement -> LabeledStatement -> Bool
== :: LabeledStatement -> LabeledStatement -> Bool
$c== :: LabeledStatement -> LabeledStatement -> Bool
Eq, Eq LabeledStatement
LabeledStatement -> LabeledStatement -> Bool
LabeledStatement -> LabeledStatement -> Ordering
LabeledStatement -> LabeledStatement -> LabeledStatement
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: LabeledStatement -> LabeledStatement -> LabeledStatement
$cmin :: LabeledStatement -> LabeledStatement -> LabeledStatement
max :: LabeledStatement -> LabeledStatement -> LabeledStatement
$cmax :: LabeledStatement -> LabeledStatement -> LabeledStatement
>= :: LabeledStatement -> LabeledStatement -> Bool
$c>= :: LabeledStatement -> LabeledStatement -> Bool
> :: LabeledStatement -> LabeledStatement -> Bool
$c> :: LabeledStatement -> LabeledStatement -> Bool
<= :: LabeledStatement -> LabeledStatement -> Bool
$c<= :: LabeledStatement -> LabeledStatement -> Bool
< :: LabeledStatement -> LabeledStatement -> Bool
$c< :: LabeledStatement -> LabeledStatement -> Bool
compare :: LabeledStatement -> LabeledStatement -> Ordering
$ccompare :: LabeledStatement -> LabeledStatement -> Ordering
Ord, ReadPrec [LabeledStatement]
ReadPrec LabeledStatement
Int -> ReadS LabeledStatement
ReadS [LabeledStatement]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [LabeledStatement]
$creadListPrec :: ReadPrec [LabeledStatement]
readPrec :: ReadPrec LabeledStatement
$creadPrec :: ReadPrec LabeledStatement
readList :: ReadS [LabeledStatement]
$creadList :: ReadS [LabeledStatement]
readsPrec :: Int -> ReadS LabeledStatement
$creadsPrec :: Int -> ReadS LabeledStatement
Read, Int -> LabeledStatement -> String -> String
[LabeledStatement] -> String -> String
LabeledStatement -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [LabeledStatement] -> String -> String
$cshowList :: [LabeledStatement] -> String -> String
show :: LabeledStatement -> String
$cshow :: LabeledStatement -> String
showsPrec :: Int -> LabeledStatement -> String -> String
$cshowsPrec :: Int -> LabeledStatement -> String -> String
Show)

_LabeledStatement :: Name
_LabeledStatement = (String -> Name
Core.Name String
"hydra/ext/java/syntax.LabeledStatement")

_LabeledStatement_identifier :: FieldName
_LabeledStatement_identifier = (String -> FieldName
Core.FieldName String
"identifier")

_LabeledStatement_statement :: FieldName
_LabeledStatement_statement = (String -> FieldName
Core.FieldName String
"statement")

data LabeledStatementNoShortIf = 
  LabeledStatementNoShortIf {
    LabeledStatementNoShortIf -> Identifier
labeledStatementNoShortIfIdentifier :: Identifier,
    LabeledStatementNoShortIf -> StatementNoShortIf
labeledStatementNoShortIfStatement :: StatementNoShortIf}
  deriving (LabeledStatementNoShortIf -> LabeledStatementNoShortIf -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LabeledStatementNoShortIf -> LabeledStatementNoShortIf -> Bool
$c/= :: LabeledStatementNoShortIf -> LabeledStatementNoShortIf -> Bool
== :: LabeledStatementNoShortIf -> LabeledStatementNoShortIf -> Bool
$c== :: LabeledStatementNoShortIf -> LabeledStatementNoShortIf -> Bool
Eq, Eq LabeledStatementNoShortIf
LabeledStatementNoShortIf -> LabeledStatementNoShortIf -> Bool
LabeledStatementNoShortIf -> LabeledStatementNoShortIf -> Ordering
LabeledStatementNoShortIf
-> LabeledStatementNoShortIf -> LabeledStatementNoShortIf
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: LabeledStatementNoShortIf
-> LabeledStatementNoShortIf -> LabeledStatementNoShortIf
$cmin :: LabeledStatementNoShortIf
-> LabeledStatementNoShortIf -> LabeledStatementNoShortIf
max :: LabeledStatementNoShortIf
-> LabeledStatementNoShortIf -> LabeledStatementNoShortIf
$cmax :: LabeledStatementNoShortIf
-> LabeledStatementNoShortIf -> LabeledStatementNoShortIf
>= :: LabeledStatementNoShortIf -> LabeledStatementNoShortIf -> Bool
$c>= :: LabeledStatementNoShortIf -> LabeledStatementNoShortIf -> Bool
> :: LabeledStatementNoShortIf -> LabeledStatementNoShortIf -> Bool
$c> :: LabeledStatementNoShortIf -> LabeledStatementNoShortIf -> Bool
<= :: LabeledStatementNoShortIf -> LabeledStatementNoShortIf -> Bool
$c<= :: LabeledStatementNoShortIf -> LabeledStatementNoShortIf -> Bool
< :: LabeledStatementNoShortIf -> LabeledStatementNoShortIf -> Bool
$c< :: LabeledStatementNoShortIf -> LabeledStatementNoShortIf -> Bool
compare :: LabeledStatementNoShortIf -> LabeledStatementNoShortIf -> Ordering
$ccompare :: LabeledStatementNoShortIf -> LabeledStatementNoShortIf -> Ordering
Ord, ReadPrec [LabeledStatementNoShortIf]
ReadPrec LabeledStatementNoShortIf
Int -> ReadS LabeledStatementNoShortIf
ReadS [LabeledStatementNoShortIf]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [LabeledStatementNoShortIf]
$creadListPrec :: ReadPrec [LabeledStatementNoShortIf]
readPrec :: ReadPrec LabeledStatementNoShortIf
$creadPrec :: ReadPrec LabeledStatementNoShortIf
readList :: ReadS [LabeledStatementNoShortIf]
$creadList :: ReadS [LabeledStatementNoShortIf]
readsPrec :: Int -> ReadS LabeledStatementNoShortIf
$creadsPrec :: Int -> ReadS LabeledStatementNoShortIf
Read, Int -> LabeledStatementNoShortIf -> String -> String
[LabeledStatementNoShortIf] -> String -> String
LabeledStatementNoShortIf -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [LabeledStatementNoShortIf] -> String -> String
$cshowList :: [LabeledStatementNoShortIf] -> String -> String
show :: LabeledStatementNoShortIf -> String
$cshow :: LabeledStatementNoShortIf -> String
showsPrec :: Int -> LabeledStatementNoShortIf -> String -> String
$cshowsPrec :: Int -> LabeledStatementNoShortIf -> String -> String
Show)

_LabeledStatementNoShortIf :: Name
_LabeledStatementNoShortIf = (String -> Name
Core.Name String
"hydra/ext/java/syntax.LabeledStatementNoShortIf")

_LabeledStatementNoShortIf_identifier :: FieldName
_LabeledStatementNoShortIf_identifier = (String -> FieldName
Core.FieldName String
"identifier")

_LabeledStatementNoShortIf_statement :: FieldName
_LabeledStatementNoShortIf_statement = (String -> FieldName
Core.FieldName String
"statement")

newtype ExpressionStatement = 
  ExpressionStatement {
    ExpressionStatement -> StatementExpression
unExpressionStatement :: StatementExpression}
  deriving (ExpressionStatement -> ExpressionStatement -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ExpressionStatement -> ExpressionStatement -> Bool
$c/= :: ExpressionStatement -> ExpressionStatement -> Bool
== :: ExpressionStatement -> ExpressionStatement -> Bool
$c== :: ExpressionStatement -> ExpressionStatement -> Bool
Eq, Eq ExpressionStatement
ExpressionStatement -> ExpressionStatement -> Bool
ExpressionStatement -> ExpressionStatement -> Ordering
ExpressionStatement -> ExpressionStatement -> ExpressionStatement
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ExpressionStatement -> ExpressionStatement -> ExpressionStatement
$cmin :: ExpressionStatement -> ExpressionStatement -> ExpressionStatement
max :: ExpressionStatement -> ExpressionStatement -> ExpressionStatement
$cmax :: ExpressionStatement -> ExpressionStatement -> ExpressionStatement
>= :: ExpressionStatement -> ExpressionStatement -> Bool
$c>= :: ExpressionStatement -> ExpressionStatement -> Bool
> :: ExpressionStatement -> ExpressionStatement -> Bool
$c> :: ExpressionStatement -> ExpressionStatement -> Bool
<= :: ExpressionStatement -> ExpressionStatement -> Bool
$c<= :: ExpressionStatement -> ExpressionStatement -> Bool
< :: ExpressionStatement -> ExpressionStatement -> Bool
$c< :: ExpressionStatement -> ExpressionStatement -> Bool
compare :: ExpressionStatement -> ExpressionStatement -> Ordering
$ccompare :: ExpressionStatement -> ExpressionStatement -> Ordering
Ord, ReadPrec [ExpressionStatement]
ReadPrec ExpressionStatement
Int -> ReadS ExpressionStatement
ReadS [ExpressionStatement]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ExpressionStatement]
$creadListPrec :: ReadPrec [ExpressionStatement]
readPrec :: ReadPrec ExpressionStatement
$creadPrec :: ReadPrec ExpressionStatement
readList :: ReadS [ExpressionStatement]
$creadList :: ReadS [ExpressionStatement]
readsPrec :: Int -> ReadS ExpressionStatement
$creadsPrec :: Int -> ReadS ExpressionStatement
Read, Int -> ExpressionStatement -> String -> String
[ExpressionStatement] -> String -> String
ExpressionStatement -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ExpressionStatement] -> String -> String
$cshowList :: [ExpressionStatement] -> String -> String
show :: ExpressionStatement -> String
$cshow :: ExpressionStatement -> String
showsPrec :: Int -> ExpressionStatement -> String -> String
$cshowsPrec :: Int -> ExpressionStatement -> String -> String
Show)

_ExpressionStatement :: Name
_ExpressionStatement = (String -> Name
Core.Name String
"hydra/ext/java/syntax.ExpressionStatement")

data StatementExpression = 
  StatementExpressionAssignment Assignment |
  StatementExpressionPreIncrement PreIncrementExpression |
  StatementExpressionPreDecrement PreDecrementExpression |
  StatementExpressionPostIncrement PostIncrementExpression |
  StatementExpressionPostDecrement PostDecrementExpression |
  StatementExpressionMethodInvocation MethodInvocation |
  StatementExpressionClassInstanceCreation ClassInstanceCreationExpression
  deriving (StatementExpression -> StatementExpression -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StatementExpression -> StatementExpression -> Bool
$c/= :: StatementExpression -> StatementExpression -> Bool
== :: StatementExpression -> StatementExpression -> Bool
$c== :: StatementExpression -> StatementExpression -> Bool
Eq, Eq StatementExpression
StatementExpression -> StatementExpression -> Bool
StatementExpression -> StatementExpression -> Ordering
StatementExpression -> StatementExpression -> StatementExpression
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: StatementExpression -> StatementExpression -> StatementExpression
$cmin :: StatementExpression -> StatementExpression -> StatementExpression
max :: StatementExpression -> StatementExpression -> StatementExpression
$cmax :: StatementExpression -> StatementExpression -> StatementExpression
>= :: StatementExpression -> StatementExpression -> Bool
$c>= :: StatementExpression -> StatementExpression -> Bool
> :: StatementExpression -> StatementExpression -> Bool
$c> :: StatementExpression -> StatementExpression -> Bool
<= :: StatementExpression -> StatementExpression -> Bool
$c<= :: StatementExpression -> StatementExpression -> Bool
< :: StatementExpression -> StatementExpression -> Bool
$c< :: StatementExpression -> StatementExpression -> Bool
compare :: StatementExpression -> StatementExpression -> Ordering
$ccompare :: StatementExpression -> StatementExpression -> Ordering
Ord, ReadPrec [StatementExpression]
ReadPrec StatementExpression
Int -> ReadS StatementExpression
ReadS [StatementExpression]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StatementExpression]
$creadListPrec :: ReadPrec [StatementExpression]
readPrec :: ReadPrec StatementExpression
$creadPrec :: ReadPrec StatementExpression
readList :: ReadS [StatementExpression]
$creadList :: ReadS [StatementExpression]
readsPrec :: Int -> ReadS StatementExpression
$creadsPrec :: Int -> ReadS StatementExpression
Read, Int -> StatementExpression -> String -> String
[StatementExpression] -> String -> String
StatementExpression -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [StatementExpression] -> String -> String
$cshowList :: [StatementExpression] -> String -> String
show :: StatementExpression -> String
$cshow :: StatementExpression -> String
showsPrec :: Int -> StatementExpression -> String -> String
$cshowsPrec :: Int -> StatementExpression -> String -> String
Show)

_StatementExpression :: Name
_StatementExpression = (String -> Name
Core.Name String
"hydra/ext/java/syntax.StatementExpression")

_StatementExpression_assignment :: FieldName
_StatementExpression_assignment = (String -> FieldName
Core.FieldName String
"assignment")

_StatementExpression_preIncrement :: FieldName
_StatementExpression_preIncrement = (String -> FieldName
Core.FieldName String
"preIncrement")

_StatementExpression_preDecrement :: FieldName
_StatementExpression_preDecrement = (String -> FieldName
Core.FieldName String
"preDecrement")

_StatementExpression_postIncrement :: FieldName
_StatementExpression_postIncrement = (String -> FieldName
Core.FieldName String
"postIncrement")

_StatementExpression_postDecrement :: FieldName
_StatementExpression_postDecrement = (String -> FieldName
Core.FieldName String
"postDecrement")

_StatementExpression_methodInvocation :: FieldName
_StatementExpression_methodInvocation = (String -> FieldName
Core.FieldName String
"methodInvocation")

_StatementExpression_classInstanceCreation :: FieldName
_StatementExpression_classInstanceCreation = (String -> FieldName
Core.FieldName String
"classInstanceCreation")

data IfThenStatement = 
  IfThenStatement {
    IfThenStatement -> Expression
ifThenStatementExpression :: Expression,
    IfThenStatement -> Statement
ifThenStatementStatement :: Statement}
  deriving (IfThenStatement -> IfThenStatement -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IfThenStatement -> IfThenStatement -> Bool
$c/= :: IfThenStatement -> IfThenStatement -> Bool
== :: IfThenStatement -> IfThenStatement -> Bool
$c== :: IfThenStatement -> IfThenStatement -> Bool
Eq, Eq IfThenStatement
IfThenStatement -> IfThenStatement -> Bool
IfThenStatement -> IfThenStatement -> Ordering
IfThenStatement -> IfThenStatement -> IfThenStatement
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: IfThenStatement -> IfThenStatement -> IfThenStatement
$cmin :: IfThenStatement -> IfThenStatement -> IfThenStatement
max :: IfThenStatement -> IfThenStatement -> IfThenStatement
$cmax :: IfThenStatement -> IfThenStatement -> IfThenStatement
>= :: IfThenStatement -> IfThenStatement -> Bool
$c>= :: IfThenStatement -> IfThenStatement -> Bool
> :: IfThenStatement -> IfThenStatement -> Bool
$c> :: IfThenStatement -> IfThenStatement -> Bool
<= :: IfThenStatement -> IfThenStatement -> Bool
$c<= :: IfThenStatement -> IfThenStatement -> Bool
< :: IfThenStatement -> IfThenStatement -> Bool
$c< :: IfThenStatement -> IfThenStatement -> Bool
compare :: IfThenStatement -> IfThenStatement -> Ordering
$ccompare :: IfThenStatement -> IfThenStatement -> Ordering
Ord, ReadPrec [IfThenStatement]
ReadPrec IfThenStatement
Int -> ReadS IfThenStatement
ReadS [IfThenStatement]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [IfThenStatement]
$creadListPrec :: ReadPrec [IfThenStatement]
readPrec :: ReadPrec IfThenStatement
$creadPrec :: ReadPrec IfThenStatement
readList :: ReadS [IfThenStatement]
$creadList :: ReadS [IfThenStatement]
readsPrec :: Int -> ReadS IfThenStatement
$creadsPrec :: Int -> ReadS IfThenStatement
Read, Int -> IfThenStatement -> String -> String
[IfThenStatement] -> String -> String
IfThenStatement -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [IfThenStatement] -> String -> String
$cshowList :: [IfThenStatement] -> String -> String
show :: IfThenStatement -> String
$cshow :: IfThenStatement -> String
showsPrec :: Int -> IfThenStatement -> String -> String
$cshowsPrec :: Int -> IfThenStatement -> String -> String
Show)

_IfThenStatement :: Name
_IfThenStatement = (String -> Name
Core.Name String
"hydra/ext/java/syntax.IfThenStatement")

_IfThenStatement_expression :: FieldName
_IfThenStatement_expression = (String -> FieldName
Core.FieldName String
"expression")

_IfThenStatement_statement :: FieldName
_IfThenStatement_statement = (String -> FieldName
Core.FieldName String
"statement")

data IfThenElseStatement = 
  IfThenElseStatement {
    IfThenElseStatement -> Maybe Expression
ifThenElseStatementCond :: (Maybe Expression),
    IfThenElseStatement -> StatementNoShortIf
ifThenElseStatementThen :: StatementNoShortIf,
    IfThenElseStatement -> Statement
ifThenElseStatementElse :: Statement}
  deriving (IfThenElseStatement -> IfThenElseStatement -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IfThenElseStatement -> IfThenElseStatement -> Bool
$c/= :: IfThenElseStatement -> IfThenElseStatement -> Bool
== :: IfThenElseStatement -> IfThenElseStatement -> Bool
$c== :: IfThenElseStatement -> IfThenElseStatement -> Bool
Eq, Eq IfThenElseStatement
IfThenElseStatement -> IfThenElseStatement -> Bool
IfThenElseStatement -> IfThenElseStatement -> Ordering
IfThenElseStatement -> IfThenElseStatement -> IfThenElseStatement
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: IfThenElseStatement -> IfThenElseStatement -> IfThenElseStatement
$cmin :: IfThenElseStatement -> IfThenElseStatement -> IfThenElseStatement
max :: IfThenElseStatement -> IfThenElseStatement -> IfThenElseStatement
$cmax :: IfThenElseStatement -> IfThenElseStatement -> IfThenElseStatement
>= :: IfThenElseStatement -> IfThenElseStatement -> Bool
$c>= :: IfThenElseStatement -> IfThenElseStatement -> Bool
> :: IfThenElseStatement -> IfThenElseStatement -> Bool
$c> :: IfThenElseStatement -> IfThenElseStatement -> Bool
<= :: IfThenElseStatement -> IfThenElseStatement -> Bool
$c<= :: IfThenElseStatement -> IfThenElseStatement -> Bool
< :: IfThenElseStatement -> IfThenElseStatement -> Bool
$c< :: IfThenElseStatement -> IfThenElseStatement -> Bool
compare :: IfThenElseStatement -> IfThenElseStatement -> Ordering
$ccompare :: IfThenElseStatement -> IfThenElseStatement -> Ordering
Ord, ReadPrec [IfThenElseStatement]
ReadPrec IfThenElseStatement
Int -> ReadS IfThenElseStatement
ReadS [IfThenElseStatement]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [IfThenElseStatement]
$creadListPrec :: ReadPrec [IfThenElseStatement]
readPrec :: ReadPrec IfThenElseStatement
$creadPrec :: ReadPrec IfThenElseStatement
readList :: ReadS [IfThenElseStatement]
$creadList :: ReadS [IfThenElseStatement]
readsPrec :: Int -> ReadS IfThenElseStatement
$creadsPrec :: Int -> ReadS IfThenElseStatement
Read, Int -> IfThenElseStatement -> String -> String
[IfThenElseStatement] -> String -> String
IfThenElseStatement -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [IfThenElseStatement] -> String -> String
$cshowList :: [IfThenElseStatement] -> String -> String
show :: IfThenElseStatement -> String
$cshow :: IfThenElseStatement -> String
showsPrec :: Int -> IfThenElseStatement -> String -> String
$cshowsPrec :: Int -> IfThenElseStatement -> String -> String
Show)

_IfThenElseStatement :: Name
_IfThenElseStatement = (String -> Name
Core.Name String
"hydra/ext/java/syntax.IfThenElseStatement")

_IfThenElseStatement_cond :: FieldName
_IfThenElseStatement_cond = (String -> FieldName
Core.FieldName String
"cond")

_IfThenElseStatement_then :: FieldName
_IfThenElseStatement_then = (String -> FieldName
Core.FieldName String
"then")

_IfThenElseStatement_else :: FieldName
_IfThenElseStatement_else = (String -> FieldName
Core.FieldName String
"else")

data IfThenElseStatementNoShortIf = 
  IfThenElseStatementNoShortIf {
    IfThenElseStatementNoShortIf -> Maybe Expression
ifThenElseStatementNoShortIfCond :: (Maybe Expression),
    IfThenElseStatementNoShortIf -> StatementNoShortIf
ifThenElseStatementNoShortIfThen :: StatementNoShortIf,
    IfThenElseStatementNoShortIf -> StatementNoShortIf
ifThenElseStatementNoShortIfElse :: StatementNoShortIf}
  deriving (IfThenElseStatementNoShortIf
-> IfThenElseStatementNoShortIf -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IfThenElseStatementNoShortIf
-> IfThenElseStatementNoShortIf -> Bool
$c/= :: IfThenElseStatementNoShortIf
-> IfThenElseStatementNoShortIf -> Bool
== :: IfThenElseStatementNoShortIf
-> IfThenElseStatementNoShortIf -> Bool
$c== :: IfThenElseStatementNoShortIf
-> IfThenElseStatementNoShortIf -> Bool
Eq, Eq IfThenElseStatementNoShortIf
IfThenElseStatementNoShortIf
-> IfThenElseStatementNoShortIf -> Bool
IfThenElseStatementNoShortIf
-> IfThenElseStatementNoShortIf -> Ordering
IfThenElseStatementNoShortIf
-> IfThenElseStatementNoShortIf -> IfThenElseStatementNoShortIf
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: IfThenElseStatementNoShortIf
-> IfThenElseStatementNoShortIf -> IfThenElseStatementNoShortIf
$cmin :: IfThenElseStatementNoShortIf
-> IfThenElseStatementNoShortIf -> IfThenElseStatementNoShortIf
max :: IfThenElseStatementNoShortIf
-> IfThenElseStatementNoShortIf -> IfThenElseStatementNoShortIf
$cmax :: IfThenElseStatementNoShortIf
-> IfThenElseStatementNoShortIf -> IfThenElseStatementNoShortIf
>= :: IfThenElseStatementNoShortIf
-> IfThenElseStatementNoShortIf -> Bool
$c>= :: IfThenElseStatementNoShortIf
-> IfThenElseStatementNoShortIf -> Bool
> :: IfThenElseStatementNoShortIf
-> IfThenElseStatementNoShortIf -> Bool
$c> :: IfThenElseStatementNoShortIf
-> IfThenElseStatementNoShortIf -> Bool
<= :: IfThenElseStatementNoShortIf
-> IfThenElseStatementNoShortIf -> Bool
$c<= :: IfThenElseStatementNoShortIf
-> IfThenElseStatementNoShortIf -> Bool
< :: IfThenElseStatementNoShortIf
-> IfThenElseStatementNoShortIf -> Bool
$c< :: IfThenElseStatementNoShortIf
-> IfThenElseStatementNoShortIf -> Bool
compare :: IfThenElseStatementNoShortIf
-> IfThenElseStatementNoShortIf -> Ordering
$ccompare :: IfThenElseStatementNoShortIf
-> IfThenElseStatementNoShortIf -> Ordering
Ord, ReadPrec [IfThenElseStatementNoShortIf]
ReadPrec IfThenElseStatementNoShortIf
Int -> ReadS IfThenElseStatementNoShortIf
ReadS [IfThenElseStatementNoShortIf]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [IfThenElseStatementNoShortIf]
$creadListPrec :: ReadPrec [IfThenElseStatementNoShortIf]
readPrec :: ReadPrec IfThenElseStatementNoShortIf
$creadPrec :: ReadPrec IfThenElseStatementNoShortIf
readList :: ReadS [IfThenElseStatementNoShortIf]
$creadList :: ReadS [IfThenElseStatementNoShortIf]
readsPrec :: Int -> ReadS IfThenElseStatementNoShortIf
$creadsPrec :: Int -> ReadS IfThenElseStatementNoShortIf
Read, Int -> IfThenElseStatementNoShortIf -> String -> String
[IfThenElseStatementNoShortIf] -> String -> String
IfThenElseStatementNoShortIf -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [IfThenElseStatementNoShortIf] -> String -> String
$cshowList :: [IfThenElseStatementNoShortIf] -> String -> String
show :: IfThenElseStatementNoShortIf -> String
$cshow :: IfThenElseStatementNoShortIf -> String
showsPrec :: Int -> IfThenElseStatementNoShortIf -> String -> String
$cshowsPrec :: Int -> IfThenElseStatementNoShortIf -> String -> String
Show)

_IfThenElseStatementNoShortIf :: Name
_IfThenElseStatementNoShortIf = (String -> Name
Core.Name String
"hydra/ext/java/syntax.IfThenElseStatementNoShortIf")

_IfThenElseStatementNoShortIf_cond :: FieldName
_IfThenElseStatementNoShortIf_cond = (String -> FieldName
Core.FieldName String
"cond")

_IfThenElseStatementNoShortIf_then :: FieldName
_IfThenElseStatementNoShortIf_then = (String -> FieldName
Core.FieldName String
"then")

_IfThenElseStatementNoShortIf_else :: FieldName
_IfThenElseStatementNoShortIf_else = (String -> FieldName
Core.FieldName String
"else")

data AssertStatement = 
  AssertStatementSingle Expression |
  AssertStatementPair AssertStatement_Pair
  deriving (AssertStatement -> AssertStatement -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AssertStatement -> AssertStatement -> Bool
$c/= :: AssertStatement -> AssertStatement -> Bool
== :: AssertStatement -> AssertStatement -> Bool
$c== :: AssertStatement -> AssertStatement -> Bool
Eq, Eq AssertStatement
AssertStatement -> AssertStatement -> Bool
AssertStatement -> AssertStatement -> Ordering
AssertStatement -> AssertStatement -> AssertStatement
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: AssertStatement -> AssertStatement -> AssertStatement
$cmin :: AssertStatement -> AssertStatement -> AssertStatement
max :: AssertStatement -> AssertStatement -> AssertStatement
$cmax :: AssertStatement -> AssertStatement -> AssertStatement
>= :: AssertStatement -> AssertStatement -> Bool
$c>= :: AssertStatement -> AssertStatement -> Bool
> :: AssertStatement -> AssertStatement -> Bool
$c> :: AssertStatement -> AssertStatement -> Bool
<= :: AssertStatement -> AssertStatement -> Bool
$c<= :: AssertStatement -> AssertStatement -> Bool
< :: AssertStatement -> AssertStatement -> Bool
$c< :: AssertStatement -> AssertStatement -> Bool
compare :: AssertStatement -> AssertStatement -> Ordering
$ccompare :: AssertStatement -> AssertStatement -> Ordering
Ord, ReadPrec [AssertStatement]
ReadPrec AssertStatement
Int -> ReadS AssertStatement
ReadS [AssertStatement]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AssertStatement]
$creadListPrec :: ReadPrec [AssertStatement]
readPrec :: ReadPrec AssertStatement
$creadPrec :: ReadPrec AssertStatement
readList :: ReadS [AssertStatement]
$creadList :: ReadS [AssertStatement]
readsPrec :: Int -> ReadS AssertStatement
$creadsPrec :: Int -> ReadS AssertStatement
Read, Int -> AssertStatement -> String -> String
[AssertStatement] -> String -> String
AssertStatement -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [AssertStatement] -> String -> String
$cshowList :: [AssertStatement] -> String -> String
show :: AssertStatement -> String
$cshow :: AssertStatement -> String
showsPrec :: Int -> AssertStatement -> String -> String
$cshowsPrec :: Int -> AssertStatement -> String -> String
Show)

_AssertStatement :: Name
_AssertStatement = (String -> Name
Core.Name String
"hydra/ext/java/syntax.AssertStatement")

_AssertStatement_single :: FieldName
_AssertStatement_single = (String -> FieldName
Core.FieldName String
"single")

_AssertStatement_pair :: FieldName
_AssertStatement_pair = (String -> FieldName
Core.FieldName String
"pair")

data AssertStatement_Pair = 
  AssertStatement_Pair {
    AssertStatement_Pair -> Expression
assertStatement_PairFirst :: Expression,
    AssertStatement_Pair -> Expression
assertStatement_PairSecond :: Expression}
  deriving (AssertStatement_Pair -> AssertStatement_Pair -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AssertStatement_Pair -> AssertStatement_Pair -> Bool
$c/= :: AssertStatement_Pair -> AssertStatement_Pair -> Bool
== :: AssertStatement_Pair -> AssertStatement_Pair -> Bool
$c== :: AssertStatement_Pair -> AssertStatement_Pair -> Bool
Eq, Eq AssertStatement_Pair
AssertStatement_Pair -> AssertStatement_Pair -> Bool
AssertStatement_Pair -> AssertStatement_Pair -> Ordering
AssertStatement_Pair
-> AssertStatement_Pair -> AssertStatement_Pair
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: AssertStatement_Pair
-> AssertStatement_Pair -> AssertStatement_Pair
$cmin :: AssertStatement_Pair
-> AssertStatement_Pair -> AssertStatement_Pair
max :: AssertStatement_Pair
-> AssertStatement_Pair -> AssertStatement_Pair
$cmax :: AssertStatement_Pair
-> AssertStatement_Pair -> AssertStatement_Pair
>= :: AssertStatement_Pair -> AssertStatement_Pair -> Bool
$c>= :: AssertStatement_Pair -> AssertStatement_Pair -> Bool
> :: AssertStatement_Pair -> AssertStatement_Pair -> Bool
$c> :: AssertStatement_Pair -> AssertStatement_Pair -> Bool
<= :: AssertStatement_Pair -> AssertStatement_Pair -> Bool
$c<= :: AssertStatement_Pair -> AssertStatement_Pair -> Bool
< :: AssertStatement_Pair -> AssertStatement_Pair -> Bool
$c< :: AssertStatement_Pair -> AssertStatement_Pair -> Bool
compare :: AssertStatement_Pair -> AssertStatement_Pair -> Ordering
$ccompare :: AssertStatement_Pair -> AssertStatement_Pair -> Ordering
Ord, ReadPrec [AssertStatement_Pair]
ReadPrec AssertStatement_Pair
Int -> ReadS AssertStatement_Pair
ReadS [AssertStatement_Pair]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AssertStatement_Pair]
$creadListPrec :: ReadPrec [AssertStatement_Pair]
readPrec :: ReadPrec AssertStatement_Pair
$creadPrec :: ReadPrec AssertStatement_Pair
readList :: ReadS [AssertStatement_Pair]
$creadList :: ReadS [AssertStatement_Pair]
readsPrec :: Int -> ReadS AssertStatement_Pair
$creadsPrec :: Int -> ReadS AssertStatement_Pair
Read, Int -> AssertStatement_Pair -> String -> String
[AssertStatement_Pair] -> String -> String
AssertStatement_Pair -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [AssertStatement_Pair] -> String -> String
$cshowList :: [AssertStatement_Pair] -> String -> String
show :: AssertStatement_Pair -> String
$cshow :: AssertStatement_Pair -> String
showsPrec :: Int -> AssertStatement_Pair -> String -> String
$cshowsPrec :: Int -> AssertStatement_Pair -> String -> String
Show)

_AssertStatement_Pair :: Name
_AssertStatement_Pair = (String -> Name
Core.Name String
"hydra/ext/java/syntax.AssertStatement.Pair")

_AssertStatement_Pair_first :: FieldName
_AssertStatement_Pair_first = (String -> FieldName
Core.FieldName String
"first")

_AssertStatement_Pair_second :: FieldName
_AssertStatement_Pair_second = (String -> FieldName
Core.FieldName String
"second")

data SwitchStatement = 
  SwitchStatement {
    SwitchStatement -> Expression
switchStatementCond :: Expression,
    SwitchStatement -> SwitchBlock
switchStatementBlock :: SwitchBlock}
  deriving (SwitchStatement -> SwitchStatement -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SwitchStatement -> SwitchStatement -> Bool
$c/= :: SwitchStatement -> SwitchStatement -> Bool
== :: SwitchStatement -> SwitchStatement -> Bool
$c== :: SwitchStatement -> SwitchStatement -> Bool
Eq, Eq SwitchStatement
SwitchStatement -> SwitchStatement -> Bool
SwitchStatement -> SwitchStatement -> Ordering
SwitchStatement -> SwitchStatement -> SwitchStatement
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: SwitchStatement -> SwitchStatement -> SwitchStatement
$cmin :: SwitchStatement -> SwitchStatement -> SwitchStatement
max :: SwitchStatement -> SwitchStatement -> SwitchStatement
$cmax :: SwitchStatement -> SwitchStatement -> SwitchStatement
>= :: SwitchStatement -> SwitchStatement -> Bool
$c>= :: SwitchStatement -> SwitchStatement -> Bool
> :: SwitchStatement -> SwitchStatement -> Bool
$c> :: SwitchStatement -> SwitchStatement -> Bool
<= :: SwitchStatement -> SwitchStatement -> Bool
$c<= :: SwitchStatement -> SwitchStatement -> Bool
< :: SwitchStatement -> SwitchStatement -> Bool
$c< :: SwitchStatement -> SwitchStatement -> Bool
compare :: SwitchStatement -> SwitchStatement -> Ordering
$ccompare :: SwitchStatement -> SwitchStatement -> Ordering
Ord, ReadPrec [SwitchStatement]
ReadPrec SwitchStatement
Int -> ReadS SwitchStatement
ReadS [SwitchStatement]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SwitchStatement]
$creadListPrec :: ReadPrec [SwitchStatement]
readPrec :: ReadPrec SwitchStatement
$creadPrec :: ReadPrec SwitchStatement
readList :: ReadS [SwitchStatement]
$creadList :: ReadS [SwitchStatement]
readsPrec :: Int -> ReadS SwitchStatement
$creadsPrec :: Int -> ReadS SwitchStatement
Read, Int -> SwitchStatement -> String -> String
[SwitchStatement] -> String -> String
SwitchStatement -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [SwitchStatement] -> String -> String
$cshowList :: [SwitchStatement] -> String -> String
show :: SwitchStatement -> String
$cshow :: SwitchStatement -> String
showsPrec :: Int -> SwitchStatement -> String -> String
$cshowsPrec :: Int -> SwitchStatement -> String -> String
Show)

_SwitchStatement :: Name
_SwitchStatement = (String -> Name
Core.Name String
"hydra/ext/java/syntax.SwitchStatement")

_SwitchStatement_cond :: FieldName
_SwitchStatement_cond = (String -> FieldName
Core.FieldName String
"cond")

_SwitchStatement_block :: FieldName
_SwitchStatement_block = (String -> FieldName
Core.FieldName String
"block")

newtype SwitchBlock = 
  SwitchBlock {
    SwitchBlock -> [SwitchBlock_Pair]
unSwitchBlock :: [SwitchBlock_Pair]}
  deriving (SwitchBlock -> SwitchBlock -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SwitchBlock -> SwitchBlock -> Bool
$c/= :: SwitchBlock -> SwitchBlock -> Bool
== :: SwitchBlock -> SwitchBlock -> Bool
$c== :: SwitchBlock -> SwitchBlock -> Bool
Eq, Eq SwitchBlock
SwitchBlock -> SwitchBlock -> Bool
SwitchBlock -> SwitchBlock -> Ordering
SwitchBlock -> SwitchBlock -> SwitchBlock
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: SwitchBlock -> SwitchBlock -> SwitchBlock
$cmin :: SwitchBlock -> SwitchBlock -> SwitchBlock
max :: SwitchBlock -> SwitchBlock -> SwitchBlock
$cmax :: SwitchBlock -> SwitchBlock -> SwitchBlock
>= :: SwitchBlock -> SwitchBlock -> Bool
$c>= :: SwitchBlock -> SwitchBlock -> Bool
> :: SwitchBlock -> SwitchBlock -> Bool
$c> :: SwitchBlock -> SwitchBlock -> Bool
<= :: SwitchBlock -> SwitchBlock -> Bool
$c<= :: SwitchBlock -> SwitchBlock -> Bool
< :: SwitchBlock -> SwitchBlock -> Bool
$c< :: SwitchBlock -> SwitchBlock -> Bool
compare :: SwitchBlock -> SwitchBlock -> Ordering
$ccompare :: SwitchBlock -> SwitchBlock -> Ordering
Ord, ReadPrec [SwitchBlock]
ReadPrec SwitchBlock
Int -> ReadS SwitchBlock
ReadS [SwitchBlock]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SwitchBlock]
$creadListPrec :: ReadPrec [SwitchBlock]
readPrec :: ReadPrec SwitchBlock
$creadPrec :: ReadPrec SwitchBlock
readList :: ReadS [SwitchBlock]
$creadList :: ReadS [SwitchBlock]
readsPrec :: Int -> ReadS SwitchBlock
$creadsPrec :: Int -> ReadS SwitchBlock
Read, Int -> SwitchBlock -> String -> String
[SwitchBlock] -> String -> String
SwitchBlock -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [SwitchBlock] -> String -> String
$cshowList :: [SwitchBlock] -> String -> String
show :: SwitchBlock -> String
$cshow :: SwitchBlock -> String
showsPrec :: Int -> SwitchBlock -> String -> String
$cshowsPrec :: Int -> SwitchBlock -> String -> String
Show)

_SwitchBlock :: Name
_SwitchBlock = (String -> Name
Core.Name String
"hydra/ext/java/syntax.SwitchBlock")

data SwitchBlock_Pair = 
  SwitchBlock_Pair {
    SwitchBlock_Pair -> [SwitchBlockStatementGroup]
switchBlock_PairStatements :: [SwitchBlockStatementGroup],
    SwitchBlock_Pair -> [SwitchLabel]
switchBlock_PairLabels :: [SwitchLabel]}
  deriving (SwitchBlock_Pair -> SwitchBlock_Pair -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SwitchBlock_Pair -> SwitchBlock_Pair -> Bool
$c/= :: SwitchBlock_Pair -> SwitchBlock_Pair -> Bool
== :: SwitchBlock_Pair -> SwitchBlock_Pair -> Bool
$c== :: SwitchBlock_Pair -> SwitchBlock_Pair -> Bool
Eq, Eq SwitchBlock_Pair
SwitchBlock_Pair -> SwitchBlock_Pair -> Bool
SwitchBlock_Pair -> SwitchBlock_Pair -> Ordering
SwitchBlock_Pair -> SwitchBlock_Pair -> SwitchBlock_Pair
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: SwitchBlock_Pair -> SwitchBlock_Pair -> SwitchBlock_Pair
$cmin :: SwitchBlock_Pair -> SwitchBlock_Pair -> SwitchBlock_Pair
max :: SwitchBlock_Pair -> SwitchBlock_Pair -> SwitchBlock_Pair
$cmax :: SwitchBlock_Pair -> SwitchBlock_Pair -> SwitchBlock_Pair
>= :: SwitchBlock_Pair -> SwitchBlock_Pair -> Bool
$c>= :: SwitchBlock_Pair -> SwitchBlock_Pair -> Bool
> :: SwitchBlock_Pair -> SwitchBlock_Pair -> Bool
$c> :: SwitchBlock_Pair -> SwitchBlock_Pair -> Bool
<= :: SwitchBlock_Pair -> SwitchBlock_Pair -> Bool
$c<= :: SwitchBlock_Pair -> SwitchBlock_Pair -> Bool
< :: SwitchBlock_Pair -> SwitchBlock_Pair -> Bool
$c< :: SwitchBlock_Pair -> SwitchBlock_Pair -> Bool
compare :: SwitchBlock_Pair -> SwitchBlock_Pair -> Ordering
$ccompare :: SwitchBlock_Pair -> SwitchBlock_Pair -> Ordering
Ord, ReadPrec [SwitchBlock_Pair]
ReadPrec SwitchBlock_Pair
Int -> ReadS SwitchBlock_Pair
ReadS [SwitchBlock_Pair]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SwitchBlock_Pair]
$creadListPrec :: ReadPrec [SwitchBlock_Pair]
readPrec :: ReadPrec SwitchBlock_Pair
$creadPrec :: ReadPrec SwitchBlock_Pair
readList :: ReadS [SwitchBlock_Pair]
$creadList :: ReadS [SwitchBlock_Pair]
readsPrec :: Int -> ReadS SwitchBlock_Pair
$creadsPrec :: Int -> ReadS SwitchBlock_Pair
Read, Int -> SwitchBlock_Pair -> String -> String
[SwitchBlock_Pair] -> String -> String
SwitchBlock_Pair -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [SwitchBlock_Pair] -> String -> String
$cshowList :: [SwitchBlock_Pair] -> String -> String
show :: SwitchBlock_Pair -> String
$cshow :: SwitchBlock_Pair -> String
showsPrec :: Int -> SwitchBlock_Pair -> String -> String
$cshowsPrec :: Int -> SwitchBlock_Pair -> String -> String
Show)

_SwitchBlock_Pair :: Name
_SwitchBlock_Pair = (String -> Name
Core.Name String
"hydra/ext/java/syntax.SwitchBlock.Pair")

_SwitchBlock_Pair_statements :: FieldName
_SwitchBlock_Pair_statements = (String -> FieldName
Core.FieldName String
"statements")

_SwitchBlock_Pair_labels :: FieldName
_SwitchBlock_Pair_labels = (String -> FieldName
Core.FieldName String
"labels")

data SwitchBlockStatementGroup = 
  SwitchBlockStatementGroup {
    SwitchBlockStatementGroup -> [SwitchLabel]
switchBlockStatementGroupLabels :: [SwitchLabel],
    SwitchBlockStatementGroup -> [BlockStatement]
switchBlockStatementGroupStatements :: [BlockStatement]}
  deriving (SwitchBlockStatementGroup -> SwitchBlockStatementGroup -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SwitchBlockStatementGroup -> SwitchBlockStatementGroup -> Bool
$c/= :: SwitchBlockStatementGroup -> SwitchBlockStatementGroup -> Bool
== :: SwitchBlockStatementGroup -> SwitchBlockStatementGroup -> Bool
$c== :: SwitchBlockStatementGroup -> SwitchBlockStatementGroup -> Bool
Eq, Eq SwitchBlockStatementGroup
SwitchBlockStatementGroup -> SwitchBlockStatementGroup -> Bool
SwitchBlockStatementGroup -> SwitchBlockStatementGroup -> Ordering
SwitchBlockStatementGroup
-> SwitchBlockStatementGroup -> SwitchBlockStatementGroup
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: SwitchBlockStatementGroup
-> SwitchBlockStatementGroup -> SwitchBlockStatementGroup
$cmin :: SwitchBlockStatementGroup
-> SwitchBlockStatementGroup -> SwitchBlockStatementGroup
max :: SwitchBlockStatementGroup
-> SwitchBlockStatementGroup -> SwitchBlockStatementGroup
$cmax :: SwitchBlockStatementGroup
-> SwitchBlockStatementGroup -> SwitchBlockStatementGroup
>= :: SwitchBlockStatementGroup -> SwitchBlockStatementGroup -> Bool
$c>= :: SwitchBlockStatementGroup -> SwitchBlockStatementGroup -> Bool
> :: SwitchBlockStatementGroup -> SwitchBlockStatementGroup -> Bool
$c> :: SwitchBlockStatementGroup -> SwitchBlockStatementGroup -> Bool
<= :: SwitchBlockStatementGroup -> SwitchBlockStatementGroup -> Bool
$c<= :: SwitchBlockStatementGroup -> SwitchBlockStatementGroup -> Bool
< :: SwitchBlockStatementGroup -> SwitchBlockStatementGroup -> Bool
$c< :: SwitchBlockStatementGroup -> SwitchBlockStatementGroup -> Bool
compare :: SwitchBlockStatementGroup -> SwitchBlockStatementGroup -> Ordering
$ccompare :: SwitchBlockStatementGroup -> SwitchBlockStatementGroup -> Ordering
Ord, ReadPrec [SwitchBlockStatementGroup]
ReadPrec SwitchBlockStatementGroup
Int -> ReadS SwitchBlockStatementGroup
ReadS [SwitchBlockStatementGroup]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SwitchBlockStatementGroup]
$creadListPrec :: ReadPrec [SwitchBlockStatementGroup]
readPrec :: ReadPrec SwitchBlockStatementGroup
$creadPrec :: ReadPrec SwitchBlockStatementGroup
readList :: ReadS [SwitchBlockStatementGroup]
$creadList :: ReadS [SwitchBlockStatementGroup]
readsPrec :: Int -> ReadS SwitchBlockStatementGroup
$creadsPrec :: Int -> ReadS SwitchBlockStatementGroup
Read, Int -> SwitchBlockStatementGroup -> String -> String
[SwitchBlockStatementGroup] -> String -> String
SwitchBlockStatementGroup -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [SwitchBlockStatementGroup] -> String -> String
$cshowList :: [SwitchBlockStatementGroup] -> String -> String
show :: SwitchBlockStatementGroup -> String
$cshow :: SwitchBlockStatementGroup -> String
showsPrec :: Int -> SwitchBlockStatementGroup -> String -> String
$cshowsPrec :: Int -> SwitchBlockStatementGroup -> String -> String
Show)

_SwitchBlockStatementGroup :: Name
_SwitchBlockStatementGroup = (String -> Name
Core.Name String
"hydra/ext/java/syntax.SwitchBlockStatementGroup")

_SwitchBlockStatementGroup_labels :: FieldName
_SwitchBlockStatementGroup_labels = (String -> FieldName
Core.FieldName String
"labels")

_SwitchBlockStatementGroup_statements :: FieldName
_SwitchBlockStatementGroup_statements = (String -> FieldName
Core.FieldName String
"statements")

data SwitchLabel = 
  SwitchLabelConstant ConstantExpression |
  SwitchLabelEnumConstant EnumConstantName |
  SwitchLabelDefault 
  deriving (SwitchLabel -> SwitchLabel -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SwitchLabel -> SwitchLabel -> Bool
$c/= :: SwitchLabel -> SwitchLabel -> Bool
== :: SwitchLabel -> SwitchLabel -> Bool
$c== :: SwitchLabel -> SwitchLabel -> Bool
Eq, Eq SwitchLabel
SwitchLabel -> SwitchLabel -> Bool
SwitchLabel -> SwitchLabel -> Ordering
SwitchLabel -> SwitchLabel -> SwitchLabel
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: SwitchLabel -> SwitchLabel -> SwitchLabel
$cmin :: SwitchLabel -> SwitchLabel -> SwitchLabel
max :: SwitchLabel -> SwitchLabel -> SwitchLabel
$cmax :: SwitchLabel -> SwitchLabel -> SwitchLabel
>= :: SwitchLabel -> SwitchLabel -> Bool
$c>= :: SwitchLabel -> SwitchLabel -> Bool
> :: SwitchLabel -> SwitchLabel -> Bool
$c> :: SwitchLabel -> SwitchLabel -> Bool
<= :: SwitchLabel -> SwitchLabel -> Bool
$c<= :: SwitchLabel -> SwitchLabel -> Bool
< :: SwitchLabel -> SwitchLabel -> Bool
$c< :: SwitchLabel -> SwitchLabel -> Bool
compare :: SwitchLabel -> SwitchLabel -> Ordering
$ccompare :: SwitchLabel -> SwitchLabel -> Ordering
Ord, ReadPrec [SwitchLabel]
ReadPrec SwitchLabel
Int -> ReadS SwitchLabel
ReadS [SwitchLabel]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SwitchLabel]
$creadListPrec :: ReadPrec [SwitchLabel]
readPrec :: ReadPrec SwitchLabel
$creadPrec :: ReadPrec SwitchLabel
readList :: ReadS [SwitchLabel]
$creadList :: ReadS [SwitchLabel]
readsPrec :: Int -> ReadS SwitchLabel
$creadsPrec :: Int -> ReadS SwitchLabel
Read, Int -> SwitchLabel -> String -> String
[SwitchLabel] -> String -> String
SwitchLabel -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [SwitchLabel] -> String -> String
$cshowList :: [SwitchLabel] -> String -> String
show :: SwitchLabel -> String
$cshow :: SwitchLabel -> String
showsPrec :: Int -> SwitchLabel -> String -> String
$cshowsPrec :: Int -> SwitchLabel -> String -> String
Show)

_SwitchLabel :: Name
_SwitchLabel = (String -> Name
Core.Name String
"hydra/ext/java/syntax.SwitchLabel")

_SwitchLabel_constant :: FieldName
_SwitchLabel_constant = (String -> FieldName
Core.FieldName String
"constant")

_SwitchLabel_enumConstant :: FieldName
_SwitchLabel_enumConstant = (String -> FieldName
Core.FieldName String
"enumConstant")

_SwitchLabel_default :: FieldName
_SwitchLabel_default = (String -> FieldName
Core.FieldName String
"default")

newtype EnumConstantName = 
  EnumConstantName {
    EnumConstantName -> Identifier
unEnumConstantName :: Identifier}
  deriving (EnumConstantName -> EnumConstantName -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EnumConstantName -> EnumConstantName -> Bool
$c/= :: EnumConstantName -> EnumConstantName -> Bool
== :: EnumConstantName -> EnumConstantName -> Bool
$c== :: EnumConstantName -> EnumConstantName -> Bool
Eq, Eq EnumConstantName
EnumConstantName -> EnumConstantName -> Bool
EnumConstantName -> EnumConstantName -> Ordering
EnumConstantName -> EnumConstantName -> EnumConstantName
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: EnumConstantName -> EnumConstantName -> EnumConstantName
$cmin :: EnumConstantName -> EnumConstantName -> EnumConstantName
max :: EnumConstantName -> EnumConstantName -> EnumConstantName
$cmax :: EnumConstantName -> EnumConstantName -> EnumConstantName
>= :: EnumConstantName -> EnumConstantName -> Bool
$c>= :: EnumConstantName -> EnumConstantName -> Bool
> :: EnumConstantName -> EnumConstantName -> Bool
$c> :: EnumConstantName -> EnumConstantName -> Bool
<= :: EnumConstantName -> EnumConstantName -> Bool
$c<= :: EnumConstantName -> EnumConstantName -> Bool
< :: EnumConstantName -> EnumConstantName -> Bool
$c< :: EnumConstantName -> EnumConstantName -> Bool
compare :: EnumConstantName -> EnumConstantName -> Ordering
$ccompare :: EnumConstantName -> EnumConstantName -> Ordering
Ord, ReadPrec [EnumConstantName]
ReadPrec EnumConstantName
Int -> ReadS EnumConstantName
ReadS [EnumConstantName]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [EnumConstantName]
$creadListPrec :: ReadPrec [EnumConstantName]
readPrec :: ReadPrec EnumConstantName
$creadPrec :: ReadPrec EnumConstantName
readList :: ReadS [EnumConstantName]
$creadList :: ReadS [EnumConstantName]
readsPrec :: Int -> ReadS EnumConstantName
$creadsPrec :: Int -> ReadS EnumConstantName
Read, Int -> EnumConstantName -> String -> String
[EnumConstantName] -> String -> String
EnumConstantName -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [EnumConstantName] -> String -> String
$cshowList :: [EnumConstantName] -> String -> String
show :: EnumConstantName -> String
$cshow :: EnumConstantName -> String
showsPrec :: Int -> EnumConstantName -> String -> String
$cshowsPrec :: Int -> EnumConstantName -> String -> String
Show)

_EnumConstantName :: Name
_EnumConstantName = (String -> Name
Core.Name String
"hydra/ext/java/syntax.EnumConstantName")

data WhileStatement = 
  WhileStatement {
    WhileStatement -> Maybe Expression
whileStatementCond :: (Maybe Expression),
    WhileStatement -> Statement
whileStatementBody :: Statement}
  deriving (WhileStatement -> WhileStatement -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WhileStatement -> WhileStatement -> Bool
$c/= :: WhileStatement -> WhileStatement -> Bool
== :: WhileStatement -> WhileStatement -> Bool
$c== :: WhileStatement -> WhileStatement -> Bool
Eq, Eq WhileStatement
WhileStatement -> WhileStatement -> Bool
WhileStatement -> WhileStatement -> Ordering
WhileStatement -> WhileStatement -> WhileStatement
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: WhileStatement -> WhileStatement -> WhileStatement
$cmin :: WhileStatement -> WhileStatement -> WhileStatement
max :: WhileStatement -> WhileStatement -> WhileStatement
$cmax :: WhileStatement -> WhileStatement -> WhileStatement
>= :: WhileStatement -> WhileStatement -> Bool
$c>= :: WhileStatement -> WhileStatement -> Bool
> :: WhileStatement -> WhileStatement -> Bool
$c> :: WhileStatement -> WhileStatement -> Bool
<= :: WhileStatement -> WhileStatement -> Bool
$c<= :: WhileStatement -> WhileStatement -> Bool
< :: WhileStatement -> WhileStatement -> Bool
$c< :: WhileStatement -> WhileStatement -> Bool
compare :: WhileStatement -> WhileStatement -> Ordering
$ccompare :: WhileStatement -> WhileStatement -> Ordering
Ord, ReadPrec [WhileStatement]
ReadPrec WhileStatement
Int -> ReadS WhileStatement
ReadS [WhileStatement]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [WhileStatement]
$creadListPrec :: ReadPrec [WhileStatement]
readPrec :: ReadPrec WhileStatement
$creadPrec :: ReadPrec WhileStatement
readList :: ReadS [WhileStatement]
$creadList :: ReadS [WhileStatement]
readsPrec :: Int -> ReadS WhileStatement
$creadsPrec :: Int -> ReadS WhileStatement
Read, Int -> WhileStatement -> String -> String
[WhileStatement] -> String -> String
WhileStatement -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [WhileStatement] -> String -> String
$cshowList :: [WhileStatement] -> String -> String
show :: WhileStatement -> String
$cshow :: WhileStatement -> String
showsPrec :: Int -> WhileStatement -> String -> String
$cshowsPrec :: Int -> WhileStatement -> String -> String
Show)

_WhileStatement :: Name
_WhileStatement = (String -> Name
Core.Name String
"hydra/ext/java/syntax.WhileStatement")

_WhileStatement_cond :: FieldName
_WhileStatement_cond = (String -> FieldName
Core.FieldName String
"cond")

_WhileStatement_body :: FieldName
_WhileStatement_body = (String -> FieldName
Core.FieldName String
"body")

data WhileStatementNoShortIf = 
  WhileStatementNoShortIf {
    WhileStatementNoShortIf -> Maybe Expression
whileStatementNoShortIfCond :: (Maybe Expression),
    WhileStatementNoShortIf -> StatementNoShortIf
whileStatementNoShortIfBody :: StatementNoShortIf}
  deriving (WhileStatementNoShortIf -> WhileStatementNoShortIf -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WhileStatementNoShortIf -> WhileStatementNoShortIf -> Bool
$c/= :: WhileStatementNoShortIf -> WhileStatementNoShortIf -> Bool
== :: WhileStatementNoShortIf -> WhileStatementNoShortIf -> Bool
$c== :: WhileStatementNoShortIf -> WhileStatementNoShortIf -> Bool
Eq, Eq WhileStatementNoShortIf
WhileStatementNoShortIf -> WhileStatementNoShortIf -> Bool
WhileStatementNoShortIf -> WhileStatementNoShortIf -> Ordering
WhileStatementNoShortIf
-> WhileStatementNoShortIf -> WhileStatementNoShortIf
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: WhileStatementNoShortIf
-> WhileStatementNoShortIf -> WhileStatementNoShortIf
$cmin :: WhileStatementNoShortIf
-> WhileStatementNoShortIf -> WhileStatementNoShortIf
max :: WhileStatementNoShortIf
-> WhileStatementNoShortIf -> WhileStatementNoShortIf
$cmax :: WhileStatementNoShortIf
-> WhileStatementNoShortIf -> WhileStatementNoShortIf
>= :: WhileStatementNoShortIf -> WhileStatementNoShortIf -> Bool
$c>= :: WhileStatementNoShortIf -> WhileStatementNoShortIf -> Bool
> :: WhileStatementNoShortIf -> WhileStatementNoShortIf -> Bool
$c> :: WhileStatementNoShortIf -> WhileStatementNoShortIf -> Bool
<= :: WhileStatementNoShortIf -> WhileStatementNoShortIf -> Bool
$c<= :: WhileStatementNoShortIf -> WhileStatementNoShortIf -> Bool
< :: WhileStatementNoShortIf -> WhileStatementNoShortIf -> Bool
$c< :: WhileStatementNoShortIf -> WhileStatementNoShortIf -> Bool
compare :: WhileStatementNoShortIf -> WhileStatementNoShortIf -> Ordering
$ccompare :: WhileStatementNoShortIf -> WhileStatementNoShortIf -> Ordering
Ord, ReadPrec [WhileStatementNoShortIf]
ReadPrec WhileStatementNoShortIf
Int -> ReadS WhileStatementNoShortIf
ReadS [WhileStatementNoShortIf]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [WhileStatementNoShortIf]
$creadListPrec :: ReadPrec [WhileStatementNoShortIf]
readPrec :: ReadPrec WhileStatementNoShortIf
$creadPrec :: ReadPrec WhileStatementNoShortIf
readList :: ReadS [WhileStatementNoShortIf]
$creadList :: ReadS [WhileStatementNoShortIf]
readsPrec :: Int -> ReadS WhileStatementNoShortIf
$creadsPrec :: Int -> ReadS WhileStatementNoShortIf
Read, Int -> WhileStatementNoShortIf -> String -> String
[WhileStatementNoShortIf] -> String -> String
WhileStatementNoShortIf -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [WhileStatementNoShortIf] -> String -> String
$cshowList :: [WhileStatementNoShortIf] -> String -> String
show :: WhileStatementNoShortIf -> String
$cshow :: WhileStatementNoShortIf -> String
showsPrec :: Int -> WhileStatementNoShortIf -> String -> String
$cshowsPrec :: Int -> WhileStatementNoShortIf -> String -> String
Show)

_WhileStatementNoShortIf :: Name
_WhileStatementNoShortIf = (String -> Name
Core.Name String
"hydra/ext/java/syntax.WhileStatementNoShortIf")

_WhileStatementNoShortIf_cond :: FieldName
_WhileStatementNoShortIf_cond = (String -> FieldName
Core.FieldName String
"cond")

_WhileStatementNoShortIf_body :: FieldName
_WhileStatementNoShortIf_body = (String -> FieldName
Core.FieldName String
"body")

data DoStatement = 
  DoStatement {
    DoStatement -> Statement
doStatementBody :: Statement,
    DoStatement -> Maybe Expression
doStatementConde :: (Maybe Expression)}
  deriving (DoStatement -> DoStatement -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DoStatement -> DoStatement -> Bool
$c/= :: DoStatement -> DoStatement -> Bool
== :: DoStatement -> DoStatement -> Bool
$c== :: DoStatement -> DoStatement -> Bool
Eq, Eq DoStatement
DoStatement -> DoStatement -> Bool
DoStatement -> DoStatement -> Ordering
DoStatement -> DoStatement -> DoStatement
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: DoStatement -> DoStatement -> DoStatement
$cmin :: DoStatement -> DoStatement -> DoStatement
max :: DoStatement -> DoStatement -> DoStatement
$cmax :: DoStatement -> DoStatement -> DoStatement
>= :: DoStatement -> DoStatement -> Bool
$c>= :: DoStatement -> DoStatement -> Bool
> :: DoStatement -> DoStatement -> Bool
$c> :: DoStatement -> DoStatement -> Bool
<= :: DoStatement -> DoStatement -> Bool
$c<= :: DoStatement -> DoStatement -> Bool
< :: DoStatement -> DoStatement -> Bool
$c< :: DoStatement -> DoStatement -> Bool
compare :: DoStatement -> DoStatement -> Ordering
$ccompare :: DoStatement -> DoStatement -> Ordering
Ord, ReadPrec [DoStatement]
ReadPrec DoStatement
Int -> ReadS DoStatement
ReadS [DoStatement]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DoStatement]
$creadListPrec :: ReadPrec [DoStatement]
readPrec :: ReadPrec DoStatement
$creadPrec :: ReadPrec DoStatement
readList :: ReadS [DoStatement]
$creadList :: ReadS [DoStatement]
readsPrec :: Int -> ReadS DoStatement
$creadsPrec :: Int -> ReadS DoStatement
Read, Int -> DoStatement -> String -> String
[DoStatement] -> String -> String
DoStatement -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [DoStatement] -> String -> String
$cshowList :: [DoStatement] -> String -> String
show :: DoStatement -> String
$cshow :: DoStatement -> String
showsPrec :: Int -> DoStatement -> String -> String
$cshowsPrec :: Int -> DoStatement -> String -> String
Show)

_DoStatement :: Name
_DoStatement = (String -> Name
Core.Name String
"hydra/ext/java/syntax.DoStatement")

_DoStatement_body :: FieldName
_DoStatement_body = (String -> FieldName
Core.FieldName String
"body")

_DoStatement_conde :: FieldName
_DoStatement_conde = (String -> FieldName
Core.FieldName String
"conde")

data ForStatement = 
  ForStatementBasic BasicForStatement |
  ForStatementEnhanced EnhancedForStatement
  deriving (ForStatement -> ForStatement -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ForStatement -> ForStatement -> Bool
$c/= :: ForStatement -> ForStatement -> Bool
== :: ForStatement -> ForStatement -> Bool
$c== :: ForStatement -> ForStatement -> Bool
Eq, Eq ForStatement
ForStatement -> ForStatement -> Bool
ForStatement -> ForStatement -> Ordering
ForStatement -> ForStatement -> ForStatement
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ForStatement -> ForStatement -> ForStatement
$cmin :: ForStatement -> ForStatement -> ForStatement
max :: ForStatement -> ForStatement -> ForStatement
$cmax :: ForStatement -> ForStatement -> ForStatement
>= :: ForStatement -> ForStatement -> Bool
$c>= :: ForStatement -> ForStatement -> Bool
> :: ForStatement -> ForStatement -> Bool
$c> :: ForStatement -> ForStatement -> Bool
<= :: ForStatement -> ForStatement -> Bool
$c<= :: ForStatement -> ForStatement -> Bool
< :: ForStatement -> ForStatement -> Bool
$c< :: ForStatement -> ForStatement -> Bool
compare :: ForStatement -> ForStatement -> Ordering
$ccompare :: ForStatement -> ForStatement -> Ordering
Ord, ReadPrec [ForStatement]
ReadPrec ForStatement
Int -> ReadS ForStatement
ReadS [ForStatement]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ForStatement]
$creadListPrec :: ReadPrec [ForStatement]
readPrec :: ReadPrec ForStatement
$creadPrec :: ReadPrec ForStatement
readList :: ReadS [ForStatement]
$creadList :: ReadS [ForStatement]
readsPrec :: Int -> ReadS ForStatement
$creadsPrec :: Int -> ReadS ForStatement
Read, Int -> ForStatement -> String -> String
[ForStatement] -> String -> String
ForStatement -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ForStatement] -> String -> String
$cshowList :: [ForStatement] -> String -> String
show :: ForStatement -> String
$cshow :: ForStatement -> String
showsPrec :: Int -> ForStatement -> String -> String
$cshowsPrec :: Int -> ForStatement -> String -> String
Show)

_ForStatement :: Name
_ForStatement = (String -> Name
Core.Name String
"hydra/ext/java/syntax.ForStatement")

_ForStatement_basic :: FieldName
_ForStatement_basic = (String -> FieldName
Core.FieldName String
"basic")

_ForStatement_enhanced :: FieldName
_ForStatement_enhanced = (String -> FieldName
Core.FieldName String
"enhanced")

data ForStatementNoShortIf = 
  ForStatementNoShortIfBasic BasicForStatementNoShortIf |
  ForStatementNoShortIfEnhanced EnhancedForStatementNoShortIf
  deriving (ForStatementNoShortIf -> ForStatementNoShortIf -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ForStatementNoShortIf -> ForStatementNoShortIf -> Bool
$c/= :: ForStatementNoShortIf -> ForStatementNoShortIf -> Bool
== :: ForStatementNoShortIf -> ForStatementNoShortIf -> Bool
$c== :: ForStatementNoShortIf -> ForStatementNoShortIf -> Bool
Eq, Eq ForStatementNoShortIf
ForStatementNoShortIf -> ForStatementNoShortIf -> Bool
ForStatementNoShortIf -> ForStatementNoShortIf -> Ordering
ForStatementNoShortIf
-> ForStatementNoShortIf -> ForStatementNoShortIf
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ForStatementNoShortIf
-> ForStatementNoShortIf -> ForStatementNoShortIf
$cmin :: ForStatementNoShortIf
-> ForStatementNoShortIf -> ForStatementNoShortIf
max :: ForStatementNoShortIf
-> ForStatementNoShortIf -> ForStatementNoShortIf
$cmax :: ForStatementNoShortIf
-> ForStatementNoShortIf -> ForStatementNoShortIf
>= :: ForStatementNoShortIf -> ForStatementNoShortIf -> Bool
$c>= :: ForStatementNoShortIf -> ForStatementNoShortIf -> Bool
> :: ForStatementNoShortIf -> ForStatementNoShortIf -> Bool
$c> :: ForStatementNoShortIf -> ForStatementNoShortIf -> Bool
<= :: ForStatementNoShortIf -> ForStatementNoShortIf -> Bool
$c<= :: ForStatementNoShortIf -> ForStatementNoShortIf -> Bool
< :: ForStatementNoShortIf -> ForStatementNoShortIf -> Bool
$c< :: ForStatementNoShortIf -> ForStatementNoShortIf -> Bool
compare :: ForStatementNoShortIf -> ForStatementNoShortIf -> Ordering
$ccompare :: ForStatementNoShortIf -> ForStatementNoShortIf -> Ordering
Ord, ReadPrec [ForStatementNoShortIf]
ReadPrec ForStatementNoShortIf
Int -> ReadS ForStatementNoShortIf
ReadS [ForStatementNoShortIf]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ForStatementNoShortIf]
$creadListPrec :: ReadPrec [ForStatementNoShortIf]
readPrec :: ReadPrec ForStatementNoShortIf
$creadPrec :: ReadPrec ForStatementNoShortIf
readList :: ReadS [ForStatementNoShortIf]
$creadList :: ReadS [ForStatementNoShortIf]
readsPrec :: Int -> ReadS ForStatementNoShortIf
$creadsPrec :: Int -> ReadS ForStatementNoShortIf
Read, Int -> ForStatementNoShortIf -> String -> String
[ForStatementNoShortIf] -> String -> String
ForStatementNoShortIf -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ForStatementNoShortIf] -> String -> String
$cshowList :: [ForStatementNoShortIf] -> String -> String
show :: ForStatementNoShortIf -> String
$cshow :: ForStatementNoShortIf -> String
showsPrec :: Int -> ForStatementNoShortIf -> String -> String
$cshowsPrec :: Int -> ForStatementNoShortIf -> String -> String
Show)

_ForStatementNoShortIf :: Name
_ForStatementNoShortIf = (String -> Name
Core.Name String
"hydra/ext/java/syntax.ForStatementNoShortIf")

_ForStatementNoShortIf_basic :: FieldName
_ForStatementNoShortIf_basic = (String -> FieldName
Core.FieldName String
"basic")

_ForStatementNoShortIf_enhanced :: FieldName
_ForStatementNoShortIf_enhanced = (String -> FieldName
Core.FieldName String
"enhanced")

data BasicForStatement = 
  BasicForStatement {
    BasicForStatement -> ForCond
basicForStatementCond :: ForCond,
    BasicForStatement -> Statement
basicForStatementBody :: Statement}
  deriving (BasicForStatement -> BasicForStatement -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BasicForStatement -> BasicForStatement -> Bool
$c/= :: BasicForStatement -> BasicForStatement -> Bool
== :: BasicForStatement -> BasicForStatement -> Bool
$c== :: BasicForStatement -> BasicForStatement -> Bool
Eq, Eq BasicForStatement
BasicForStatement -> BasicForStatement -> Bool
BasicForStatement -> BasicForStatement -> Ordering
BasicForStatement -> BasicForStatement -> BasicForStatement
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: BasicForStatement -> BasicForStatement -> BasicForStatement
$cmin :: BasicForStatement -> BasicForStatement -> BasicForStatement
max :: BasicForStatement -> BasicForStatement -> BasicForStatement
$cmax :: BasicForStatement -> BasicForStatement -> BasicForStatement
>= :: BasicForStatement -> BasicForStatement -> Bool
$c>= :: BasicForStatement -> BasicForStatement -> Bool
> :: BasicForStatement -> BasicForStatement -> Bool
$c> :: BasicForStatement -> BasicForStatement -> Bool
<= :: BasicForStatement -> BasicForStatement -> Bool
$c<= :: BasicForStatement -> BasicForStatement -> Bool
< :: BasicForStatement -> BasicForStatement -> Bool
$c< :: BasicForStatement -> BasicForStatement -> Bool
compare :: BasicForStatement -> BasicForStatement -> Ordering
$ccompare :: BasicForStatement -> BasicForStatement -> Ordering
Ord, ReadPrec [BasicForStatement]
ReadPrec BasicForStatement
Int -> ReadS BasicForStatement
ReadS [BasicForStatement]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [BasicForStatement]
$creadListPrec :: ReadPrec [BasicForStatement]
readPrec :: ReadPrec BasicForStatement
$creadPrec :: ReadPrec BasicForStatement
readList :: ReadS [BasicForStatement]
$creadList :: ReadS [BasicForStatement]
readsPrec :: Int -> ReadS BasicForStatement
$creadsPrec :: Int -> ReadS BasicForStatement
Read, Int -> BasicForStatement -> String -> String
[BasicForStatement] -> String -> String
BasicForStatement -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [BasicForStatement] -> String -> String
$cshowList :: [BasicForStatement] -> String -> String
show :: BasicForStatement -> String
$cshow :: BasicForStatement -> String
showsPrec :: Int -> BasicForStatement -> String -> String
$cshowsPrec :: Int -> BasicForStatement -> String -> String
Show)

_BasicForStatement :: Name
_BasicForStatement = (String -> Name
Core.Name String
"hydra/ext/java/syntax.BasicForStatement")

_BasicForStatement_cond :: FieldName
_BasicForStatement_cond = (String -> FieldName
Core.FieldName String
"cond")

_BasicForStatement_body :: FieldName
_BasicForStatement_body = (String -> FieldName
Core.FieldName String
"body")

data ForCond = 
  ForCond {
    ForCond -> Maybe ForInit
forCondInit :: (Maybe ForInit),
    ForCond -> Maybe Expression
forCondCond :: (Maybe Expression),
    ForCond -> Maybe ForUpdate
forCondUpdate :: (Maybe ForUpdate)}
  deriving (ForCond -> ForCond -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ForCond -> ForCond -> Bool
$c/= :: ForCond -> ForCond -> Bool
== :: ForCond -> ForCond -> Bool
$c== :: ForCond -> ForCond -> Bool
Eq, Eq ForCond
ForCond -> ForCond -> Bool
ForCond -> ForCond -> Ordering
ForCond -> ForCond -> ForCond
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ForCond -> ForCond -> ForCond
$cmin :: ForCond -> ForCond -> ForCond
max :: ForCond -> ForCond -> ForCond
$cmax :: ForCond -> ForCond -> ForCond
>= :: ForCond -> ForCond -> Bool
$c>= :: ForCond -> ForCond -> Bool
> :: ForCond -> ForCond -> Bool
$c> :: ForCond -> ForCond -> Bool
<= :: ForCond -> ForCond -> Bool
$c<= :: ForCond -> ForCond -> Bool
< :: ForCond -> ForCond -> Bool
$c< :: ForCond -> ForCond -> Bool
compare :: ForCond -> ForCond -> Ordering
$ccompare :: ForCond -> ForCond -> Ordering
Ord, ReadPrec [ForCond]
ReadPrec ForCond
Int -> ReadS ForCond
ReadS [ForCond]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ForCond]
$creadListPrec :: ReadPrec [ForCond]
readPrec :: ReadPrec ForCond
$creadPrec :: ReadPrec ForCond
readList :: ReadS [ForCond]
$creadList :: ReadS [ForCond]
readsPrec :: Int -> ReadS ForCond
$creadsPrec :: Int -> ReadS ForCond
Read, Int -> ForCond -> String -> String
[ForCond] -> String -> String
ForCond -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ForCond] -> String -> String
$cshowList :: [ForCond] -> String -> String
show :: ForCond -> String
$cshow :: ForCond -> String
showsPrec :: Int -> ForCond -> String -> String
$cshowsPrec :: Int -> ForCond -> String -> String
Show)

_ForCond :: Name
_ForCond = (String -> Name
Core.Name String
"hydra/ext/java/syntax.ForCond")

_ForCond_init :: FieldName
_ForCond_init = (String -> FieldName
Core.FieldName String
"init")

_ForCond_cond :: FieldName
_ForCond_cond = (String -> FieldName
Core.FieldName String
"cond")

_ForCond_update :: FieldName
_ForCond_update = (String -> FieldName
Core.FieldName String
"update")

data BasicForStatementNoShortIf = 
  BasicForStatementNoShortIf {
    BasicForStatementNoShortIf -> ForCond
basicForStatementNoShortIfCond :: ForCond,
    BasicForStatementNoShortIf -> StatementNoShortIf
basicForStatementNoShortIfBody :: StatementNoShortIf}
  deriving (BasicForStatementNoShortIf -> BasicForStatementNoShortIf -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BasicForStatementNoShortIf -> BasicForStatementNoShortIf -> Bool
$c/= :: BasicForStatementNoShortIf -> BasicForStatementNoShortIf -> Bool
== :: BasicForStatementNoShortIf -> BasicForStatementNoShortIf -> Bool
$c== :: BasicForStatementNoShortIf -> BasicForStatementNoShortIf -> Bool
Eq, Eq BasicForStatementNoShortIf
BasicForStatementNoShortIf -> BasicForStatementNoShortIf -> Bool
BasicForStatementNoShortIf
-> BasicForStatementNoShortIf -> Ordering
BasicForStatementNoShortIf
-> BasicForStatementNoShortIf -> BasicForStatementNoShortIf
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: BasicForStatementNoShortIf
-> BasicForStatementNoShortIf -> BasicForStatementNoShortIf
$cmin :: BasicForStatementNoShortIf
-> BasicForStatementNoShortIf -> BasicForStatementNoShortIf
max :: BasicForStatementNoShortIf
-> BasicForStatementNoShortIf -> BasicForStatementNoShortIf
$cmax :: BasicForStatementNoShortIf
-> BasicForStatementNoShortIf -> BasicForStatementNoShortIf
>= :: BasicForStatementNoShortIf -> BasicForStatementNoShortIf -> Bool
$c>= :: BasicForStatementNoShortIf -> BasicForStatementNoShortIf -> Bool
> :: BasicForStatementNoShortIf -> BasicForStatementNoShortIf -> Bool
$c> :: BasicForStatementNoShortIf -> BasicForStatementNoShortIf -> Bool
<= :: BasicForStatementNoShortIf -> BasicForStatementNoShortIf -> Bool
$c<= :: BasicForStatementNoShortIf -> BasicForStatementNoShortIf -> Bool
< :: BasicForStatementNoShortIf -> BasicForStatementNoShortIf -> Bool
$c< :: BasicForStatementNoShortIf -> BasicForStatementNoShortIf -> Bool
compare :: BasicForStatementNoShortIf
-> BasicForStatementNoShortIf -> Ordering
$ccompare :: BasicForStatementNoShortIf
-> BasicForStatementNoShortIf -> Ordering
Ord, ReadPrec [BasicForStatementNoShortIf]
ReadPrec BasicForStatementNoShortIf
Int -> ReadS BasicForStatementNoShortIf
ReadS [BasicForStatementNoShortIf]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [BasicForStatementNoShortIf]
$creadListPrec :: ReadPrec [BasicForStatementNoShortIf]
readPrec :: ReadPrec BasicForStatementNoShortIf
$creadPrec :: ReadPrec BasicForStatementNoShortIf
readList :: ReadS [BasicForStatementNoShortIf]
$creadList :: ReadS [BasicForStatementNoShortIf]
readsPrec :: Int -> ReadS BasicForStatementNoShortIf
$creadsPrec :: Int -> ReadS BasicForStatementNoShortIf
Read, Int -> BasicForStatementNoShortIf -> String -> String
[BasicForStatementNoShortIf] -> String -> String
BasicForStatementNoShortIf -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [BasicForStatementNoShortIf] -> String -> String
$cshowList :: [BasicForStatementNoShortIf] -> String -> String
show :: BasicForStatementNoShortIf -> String
$cshow :: BasicForStatementNoShortIf -> String
showsPrec :: Int -> BasicForStatementNoShortIf -> String -> String
$cshowsPrec :: Int -> BasicForStatementNoShortIf -> String -> String
Show)

_BasicForStatementNoShortIf :: Name
_BasicForStatementNoShortIf = (String -> Name
Core.Name String
"hydra/ext/java/syntax.BasicForStatementNoShortIf")

_BasicForStatementNoShortIf_cond :: FieldName
_BasicForStatementNoShortIf_cond = (String -> FieldName
Core.FieldName String
"cond")

_BasicForStatementNoShortIf_body :: FieldName
_BasicForStatementNoShortIf_body = (String -> FieldName
Core.FieldName String
"body")

data ForInit = 
  ForInitStatements [StatementExpression] |
  ForInitLocalVariable LocalVariableDeclaration
  deriving (ForInit -> ForInit -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ForInit -> ForInit -> Bool
$c/= :: ForInit -> ForInit -> Bool
== :: ForInit -> ForInit -> Bool
$c== :: ForInit -> ForInit -> Bool
Eq, Eq ForInit
ForInit -> ForInit -> Bool
ForInit -> ForInit -> Ordering
ForInit -> ForInit -> ForInit
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ForInit -> ForInit -> ForInit
$cmin :: ForInit -> ForInit -> ForInit
max :: ForInit -> ForInit -> ForInit
$cmax :: ForInit -> ForInit -> ForInit
>= :: ForInit -> ForInit -> Bool
$c>= :: ForInit -> ForInit -> Bool
> :: ForInit -> ForInit -> Bool
$c> :: ForInit -> ForInit -> Bool
<= :: ForInit -> ForInit -> Bool
$c<= :: ForInit -> ForInit -> Bool
< :: ForInit -> ForInit -> Bool
$c< :: ForInit -> ForInit -> Bool
compare :: ForInit -> ForInit -> Ordering
$ccompare :: ForInit -> ForInit -> Ordering
Ord, ReadPrec [ForInit]
ReadPrec ForInit
Int -> ReadS ForInit
ReadS [ForInit]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ForInit]
$creadListPrec :: ReadPrec [ForInit]
readPrec :: ReadPrec ForInit
$creadPrec :: ReadPrec ForInit
readList :: ReadS [ForInit]
$creadList :: ReadS [ForInit]
readsPrec :: Int -> ReadS ForInit
$creadsPrec :: Int -> ReadS ForInit
Read, Int -> ForInit -> String -> String
[ForInit] -> String -> String
ForInit -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ForInit] -> String -> String
$cshowList :: [ForInit] -> String -> String
show :: ForInit -> String
$cshow :: ForInit -> String
showsPrec :: Int -> ForInit -> String -> String
$cshowsPrec :: Int -> ForInit -> String -> String
Show)

_ForInit :: Name
_ForInit = (String -> Name
Core.Name String
"hydra/ext/java/syntax.ForInit")

_ForInit_statements :: FieldName
_ForInit_statements = (String -> FieldName
Core.FieldName String
"statements")

_ForInit_localVariable :: FieldName
_ForInit_localVariable = (String -> FieldName
Core.FieldName String
"localVariable")

newtype ForUpdate = 
  ForUpdate {
    ForUpdate -> [StatementExpression]
unForUpdate :: [StatementExpression]}
  deriving (ForUpdate -> ForUpdate -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ForUpdate -> ForUpdate -> Bool
$c/= :: ForUpdate -> ForUpdate -> Bool
== :: ForUpdate -> ForUpdate -> Bool
$c== :: ForUpdate -> ForUpdate -> Bool
Eq, Eq ForUpdate
ForUpdate -> ForUpdate -> Bool
ForUpdate -> ForUpdate -> Ordering
ForUpdate -> ForUpdate -> ForUpdate
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ForUpdate -> ForUpdate -> ForUpdate
$cmin :: ForUpdate -> ForUpdate -> ForUpdate
max :: ForUpdate -> ForUpdate -> ForUpdate
$cmax :: ForUpdate -> ForUpdate -> ForUpdate
>= :: ForUpdate -> ForUpdate -> Bool
$c>= :: ForUpdate -> ForUpdate -> Bool
> :: ForUpdate -> ForUpdate -> Bool
$c> :: ForUpdate -> ForUpdate -> Bool
<= :: ForUpdate -> ForUpdate -> Bool
$c<= :: ForUpdate -> ForUpdate -> Bool
< :: ForUpdate -> ForUpdate -> Bool
$c< :: ForUpdate -> ForUpdate -> Bool
compare :: ForUpdate -> ForUpdate -> Ordering
$ccompare :: ForUpdate -> ForUpdate -> Ordering
Ord, ReadPrec [ForUpdate]
ReadPrec ForUpdate
Int -> ReadS ForUpdate
ReadS [ForUpdate]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ForUpdate]
$creadListPrec :: ReadPrec [ForUpdate]
readPrec :: ReadPrec ForUpdate
$creadPrec :: ReadPrec ForUpdate
readList :: ReadS [ForUpdate]
$creadList :: ReadS [ForUpdate]
readsPrec :: Int -> ReadS ForUpdate
$creadsPrec :: Int -> ReadS ForUpdate
Read, Int -> ForUpdate -> String -> String
[ForUpdate] -> String -> String
ForUpdate -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ForUpdate] -> String -> String
$cshowList :: [ForUpdate] -> String -> String
show :: ForUpdate -> String
$cshow :: ForUpdate -> String
showsPrec :: Int -> ForUpdate -> String -> String
$cshowsPrec :: Int -> ForUpdate -> String -> String
Show)

_ForUpdate :: Name
_ForUpdate = (String -> Name
Core.Name String
"hydra/ext/java/syntax.ForUpdate")

data EnhancedForStatement = 
  EnhancedForStatement {
    EnhancedForStatement -> EnhancedForCond
enhancedForStatementCond :: EnhancedForCond,
    EnhancedForStatement -> Statement
enhancedForStatementBody :: Statement}
  deriving (EnhancedForStatement -> EnhancedForStatement -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EnhancedForStatement -> EnhancedForStatement -> Bool
$c/= :: EnhancedForStatement -> EnhancedForStatement -> Bool
== :: EnhancedForStatement -> EnhancedForStatement -> Bool
$c== :: EnhancedForStatement -> EnhancedForStatement -> Bool
Eq, Eq EnhancedForStatement
EnhancedForStatement -> EnhancedForStatement -> Bool
EnhancedForStatement -> EnhancedForStatement -> Ordering
EnhancedForStatement
-> EnhancedForStatement -> EnhancedForStatement
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: EnhancedForStatement
-> EnhancedForStatement -> EnhancedForStatement
$cmin :: EnhancedForStatement
-> EnhancedForStatement -> EnhancedForStatement
max :: EnhancedForStatement
-> EnhancedForStatement -> EnhancedForStatement
$cmax :: EnhancedForStatement
-> EnhancedForStatement -> EnhancedForStatement
>= :: EnhancedForStatement -> EnhancedForStatement -> Bool
$c>= :: EnhancedForStatement -> EnhancedForStatement -> Bool
> :: EnhancedForStatement -> EnhancedForStatement -> Bool
$c> :: EnhancedForStatement -> EnhancedForStatement -> Bool
<= :: EnhancedForStatement -> EnhancedForStatement -> Bool
$c<= :: EnhancedForStatement -> EnhancedForStatement -> Bool
< :: EnhancedForStatement -> EnhancedForStatement -> Bool
$c< :: EnhancedForStatement -> EnhancedForStatement -> Bool
compare :: EnhancedForStatement -> EnhancedForStatement -> Ordering
$ccompare :: EnhancedForStatement -> EnhancedForStatement -> Ordering
Ord, ReadPrec [EnhancedForStatement]
ReadPrec EnhancedForStatement
Int -> ReadS EnhancedForStatement
ReadS [EnhancedForStatement]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [EnhancedForStatement]
$creadListPrec :: ReadPrec [EnhancedForStatement]
readPrec :: ReadPrec EnhancedForStatement
$creadPrec :: ReadPrec EnhancedForStatement
readList :: ReadS [EnhancedForStatement]
$creadList :: ReadS [EnhancedForStatement]
readsPrec :: Int -> ReadS EnhancedForStatement
$creadsPrec :: Int -> ReadS EnhancedForStatement
Read, Int -> EnhancedForStatement -> String -> String
[EnhancedForStatement] -> String -> String
EnhancedForStatement -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [EnhancedForStatement] -> String -> String
$cshowList :: [EnhancedForStatement] -> String -> String
show :: EnhancedForStatement -> String
$cshow :: EnhancedForStatement -> String
showsPrec :: Int -> EnhancedForStatement -> String -> String
$cshowsPrec :: Int -> EnhancedForStatement -> String -> String
Show)

_EnhancedForStatement :: Name
_EnhancedForStatement = (String -> Name
Core.Name String
"hydra/ext/java/syntax.EnhancedForStatement")

_EnhancedForStatement_cond :: FieldName
_EnhancedForStatement_cond = (String -> FieldName
Core.FieldName String
"cond")

_EnhancedForStatement_body :: FieldName
_EnhancedForStatement_body = (String -> FieldName
Core.FieldName String
"body")

data EnhancedForCond = 
  EnhancedForCond {
    EnhancedForCond -> [VariableModifier]
enhancedForCondModifiers :: [VariableModifier],
    EnhancedForCond -> LocalVariableType
enhancedForCondType :: LocalVariableType,
    EnhancedForCond -> VariableDeclaratorId
enhancedForCondId :: VariableDeclaratorId,
    EnhancedForCond -> Expression
enhancedForCondExpression :: Expression}
  deriving (EnhancedForCond -> EnhancedForCond -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EnhancedForCond -> EnhancedForCond -> Bool
$c/= :: EnhancedForCond -> EnhancedForCond -> Bool
== :: EnhancedForCond -> EnhancedForCond -> Bool
$c== :: EnhancedForCond -> EnhancedForCond -> Bool
Eq, Eq EnhancedForCond
EnhancedForCond -> EnhancedForCond -> Bool
EnhancedForCond -> EnhancedForCond -> Ordering
EnhancedForCond -> EnhancedForCond -> EnhancedForCond
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: EnhancedForCond -> EnhancedForCond -> EnhancedForCond
$cmin :: EnhancedForCond -> EnhancedForCond -> EnhancedForCond
max :: EnhancedForCond -> EnhancedForCond -> EnhancedForCond
$cmax :: EnhancedForCond -> EnhancedForCond -> EnhancedForCond
>= :: EnhancedForCond -> EnhancedForCond -> Bool
$c>= :: EnhancedForCond -> EnhancedForCond -> Bool
> :: EnhancedForCond -> EnhancedForCond -> Bool
$c> :: EnhancedForCond -> EnhancedForCond -> Bool
<= :: EnhancedForCond -> EnhancedForCond -> Bool
$c<= :: EnhancedForCond -> EnhancedForCond -> Bool
< :: EnhancedForCond -> EnhancedForCond -> Bool
$c< :: EnhancedForCond -> EnhancedForCond -> Bool
compare :: EnhancedForCond -> EnhancedForCond -> Ordering
$ccompare :: EnhancedForCond -> EnhancedForCond -> Ordering
Ord, ReadPrec [EnhancedForCond]
ReadPrec EnhancedForCond
Int -> ReadS EnhancedForCond
ReadS [EnhancedForCond]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [EnhancedForCond]
$creadListPrec :: ReadPrec [EnhancedForCond]
readPrec :: ReadPrec EnhancedForCond
$creadPrec :: ReadPrec EnhancedForCond
readList :: ReadS [EnhancedForCond]
$creadList :: ReadS [EnhancedForCond]
readsPrec :: Int -> ReadS EnhancedForCond
$creadsPrec :: Int -> ReadS EnhancedForCond
Read, Int -> EnhancedForCond -> String -> String
[EnhancedForCond] -> String -> String
EnhancedForCond -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [EnhancedForCond] -> String -> String
$cshowList :: [EnhancedForCond] -> String -> String
show :: EnhancedForCond -> String
$cshow :: EnhancedForCond -> String
showsPrec :: Int -> EnhancedForCond -> String -> String
$cshowsPrec :: Int -> EnhancedForCond -> String -> String
Show)

_EnhancedForCond :: Name
_EnhancedForCond = (String -> Name
Core.Name String
"hydra/ext/java/syntax.EnhancedForCond")

_EnhancedForCond_modifiers :: FieldName
_EnhancedForCond_modifiers = (String -> FieldName
Core.FieldName String
"modifiers")

_EnhancedForCond_type :: FieldName
_EnhancedForCond_type = (String -> FieldName
Core.FieldName String
"type")

_EnhancedForCond_id :: FieldName
_EnhancedForCond_id = (String -> FieldName
Core.FieldName String
"id")

_EnhancedForCond_expression :: FieldName
_EnhancedForCond_expression = (String -> FieldName
Core.FieldName String
"expression")

data EnhancedForStatementNoShortIf = 
  EnhancedForStatementNoShortIf {
    EnhancedForStatementNoShortIf -> EnhancedForCond
enhancedForStatementNoShortIfCond :: EnhancedForCond,
    EnhancedForStatementNoShortIf -> StatementNoShortIf
enhancedForStatementNoShortIfBody :: StatementNoShortIf}
  deriving (EnhancedForStatementNoShortIf
-> EnhancedForStatementNoShortIf -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EnhancedForStatementNoShortIf
-> EnhancedForStatementNoShortIf -> Bool
$c/= :: EnhancedForStatementNoShortIf
-> EnhancedForStatementNoShortIf -> Bool
== :: EnhancedForStatementNoShortIf
-> EnhancedForStatementNoShortIf -> Bool
$c== :: EnhancedForStatementNoShortIf
-> EnhancedForStatementNoShortIf -> Bool
Eq, Eq EnhancedForStatementNoShortIf
EnhancedForStatementNoShortIf
-> EnhancedForStatementNoShortIf -> Bool
EnhancedForStatementNoShortIf
-> EnhancedForStatementNoShortIf -> Ordering
EnhancedForStatementNoShortIf
-> EnhancedForStatementNoShortIf -> EnhancedForStatementNoShortIf
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: EnhancedForStatementNoShortIf
-> EnhancedForStatementNoShortIf -> EnhancedForStatementNoShortIf
$cmin :: EnhancedForStatementNoShortIf
-> EnhancedForStatementNoShortIf -> EnhancedForStatementNoShortIf
max :: EnhancedForStatementNoShortIf
-> EnhancedForStatementNoShortIf -> EnhancedForStatementNoShortIf
$cmax :: EnhancedForStatementNoShortIf
-> EnhancedForStatementNoShortIf -> EnhancedForStatementNoShortIf
>= :: EnhancedForStatementNoShortIf
-> EnhancedForStatementNoShortIf -> Bool
$c>= :: EnhancedForStatementNoShortIf
-> EnhancedForStatementNoShortIf -> Bool
> :: EnhancedForStatementNoShortIf
-> EnhancedForStatementNoShortIf -> Bool
$c> :: EnhancedForStatementNoShortIf
-> EnhancedForStatementNoShortIf -> Bool
<= :: EnhancedForStatementNoShortIf
-> EnhancedForStatementNoShortIf -> Bool
$c<= :: EnhancedForStatementNoShortIf
-> EnhancedForStatementNoShortIf -> Bool
< :: EnhancedForStatementNoShortIf
-> EnhancedForStatementNoShortIf -> Bool
$c< :: EnhancedForStatementNoShortIf
-> EnhancedForStatementNoShortIf -> Bool
compare :: EnhancedForStatementNoShortIf
-> EnhancedForStatementNoShortIf -> Ordering
$ccompare :: EnhancedForStatementNoShortIf
-> EnhancedForStatementNoShortIf -> Ordering
Ord, ReadPrec [EnhancedForStatementNoShortIf]
ReadPrec EnhancedForStatementNoShortIf
Int -> ReadS EnhancedForStatementNoShortIf
ReadS [EnhancedForStatementNoShortIf]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [EnhancedForStatementNoShortIf]
$creadListPrec :: ReadPrec [EnhancedForStatementNoShortIf]
readPrec :: ReadPrec EnhancedForStatementNoShortIf
$creadPrec :: ReadPrec EnhancedForStatementNoShortIf
readList :: ReadS [EnhancedForStatementNoShortIf]
$creadList :: ReadS [EnhancedForStatementNoShortIf]
readsPrec :: Int -> ReadS EnhancedForStatementNoShortIf
$creadsPrec :: Int -> ReadS EnhancedForStatementNoShortIf
Read, Int -> EnhancedForStatementNoShortIf -> String -> String
[EnhancedForStatementNoShortIf] -> String -> String
EnhancedForStatementNoShortIf -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [EnhancedForStatementNoShortIf] -> String -> String
$cshowList :: [EnhancedForStatementNoShortIf] -> String -> String
show :: EnhancedForStatementNoShortIf -> String
$cshow :: EnhancedForStatementNoShortIf -> String
showsPrec :: Int -> EnhancedForStatementNoShortIf -> String -> String
$cshowsPrec :: Int -> EnhancedForStatementNoShortIf -> String -> String
Show)

_EnhancedForStatementNoShortIf :: Name
_EnhancedForStatementNoShortIf = (String -> Name
Core.Name String
"hydra/ext/java/syntax.EnhancedForStatementNoShortIf")

_EnhancedForStatementNoShortIf_cond :: FieldName
_EnhancedForStatementNoShortIf_cond = (String -> FieldName
Core.FieldName String
"cond")

_EnhancedForStatementNoShortIf_body :: FieldName
_EnhancedForStatementNoShortIf_body = (String -> FieldName
Core.FieldName String
"body")

newtype BreakStatement = 
  BreakStatement {
    BreakStatement -> Maybe Identifier
unBreakStatement :: (Maybe Identifier)}
  deriving (BreakStatement -> BreakStatement -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BreakStatement -> BreakStatement -> Bool
$c/= :: BreakStatement -> BreakStatement -> Bool
== :: BreakStatement -> BreakStatement -> Bool
$c== :: BreakStatement -> BreakStatement -> Bool
Eq, Eq BreakStatement
BreakStatement -> BreakStatement -> Bool
BreakStatement -> BreakStatement -> Ordering
BreakStatement -> BreakStatement -> BreakStatement
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: BreakStatement -> BreakStatement -> BreakStatement
$cmin :: BreakStatement -> BreakStatement -> BreakStatement
max :: BreakStatement -> BreakStatement -> BreakStatement
$cmax :: BreakStatement -> BreakStatement -> BreakStatement
>= :: BreakStatement -> BreakStatement -> Bool
$c>= :: BreakStatement -> BreakStatement -> Bool
> :: BreakStatement -> BreakStatement -> Bool
$c> :: BreakStatement -> BreakStatement -> Bool
<= :: BreakStatement -> BreakStatement -> Bool
$c<= :: BreakStatement -> BreakStatement -> Bool
< :: BreakStatement -> BreakStatement -> Bool
$c< :: BreakStatement -> BreakStatement -> Bool
compare :: BreakStatement -> BreakStatement -> Ordering
$ccompare :: BreakStatement -> BreakStatement -> Ordering
Ord, ReadPrec [BreakStatement]
ReadPrec BreakStatement
Int -> ReadS BreakStatement
ReadS [BreakStatement]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [BreakStatement]
$creadListPrec :: ReadPrec [BreakStatement]
readPrec :: ReadPrec BreakStatement
$creadPrec :: ReadPrec BreakStatement
readList :: ReadS [BreakStatement]
$creadList :: ReadS [BreakStatement]
readsPrec :: Int -> ReadS BreakStatement
$creadsPrec :: Int -> ReadS BreakStatement
Read, Int -> BreakStatement -> String -> String
[BreakStatement] -> String -> String
BreakStatement -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [BreakStatement] -> String -> String
$cshowList :: [BreakStatement] -> String -> String
show :: BreakStatement -> String
$cshow :: BreakStatement -> String
showsPrec :: Int -> BreakStatement -> String -> String
$cshowsPrec :: Int -> BreakStatement -> String -> String
Show)

_BreakStatement :: Name
_BreakStatement = (String -> Name
Core.Name String
"hydra/ext/java/syntax.BreakStatement")

newtype ContinueStatement = 
  ContinueStatement {
    ContinueStatement -> Maybe Identifier
unContinueStatement :: (Maybe Identifier)}
  deriving (ContinueStatement -> ContinueStatement -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ContinueStatement -> ContinueStatement -> Bool
$c/= :: ContinueStatement -> ContinueStatement -> Bool
== :: ContinueStatement -> ContinueStatement -> Bool
$c== :: ContinueStatement -> ContinueStatement -> Bool
Eq, Eq ContinueStatement
ContinueStatement -> ContinueStatement -> Bool
ContinueStatement -> ContinueStatement -> Ordering
ContinueStatement -> ContinueStatement -> ContinueStatement
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ContinueStatement -> ContinueStatement -> ContinueStatement
$cmin :: ContinueStatement -> ContinueStatement -> ContinueStatement
max :: ContinueStatement -> ContinueStatement -> ContinueStatement
$cmax :: ContinueStatement -> ContinueStatement -> ContinueStatement
>= :: ContinueStatement -> ContinueStatement -> Bool
$c>= :: ContinueStatement -> ContinueStatement -> Bool
> :: ContinueStatement -> ContinueStatement -> Bool
$c> :: ContinueStatement -> ContinueStatement -> Bool
<= :: ContinueStatement -> ContinueStatement -> Bool
$c<= :: ContinueStatement -> ContinueStatement -> Bool
< :: ContinueStatement -> ContinueStatement -> Bool
$c< :: ContinueStatement -> ContinueStatement -> Bool
compare :: ContinueStatement -> ContinueStatement -> Ordering
$ccompare :: ContinueStatement -> ContinueStatement -> Ordering
Ord, ReadPrec [ContinueStatement]
ReadPrec ContinueStatement
Int -> ReadS ContinueStatement
ReadS [ContinueStatement]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ContinueStatement]
$creadListPrec :: ReadPrec [ContinueStatement]
readPrec :: ReadPrec ContinueStatement
$creadPrec :: ReadPrec ContinueStatement
readList :: ReadS [ContinueStatement]
$creadList :: ReadS [ContinueStatement]
readsPrec :: Int -> ReadS ContinueStatement
$creadsPrec :: Int -> ReadS ContinueStatement
Read, Int -> ContinueStatement -> String -> String
[ContinueStatement] -> String -> String
ContinueStatement -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ContinueStatement] -> String -> String
$cshowList :: [ContinueStatement] -> String -> String
show :: ContinueStatement -> String
$cshow :: ContinueStatement -> String
showsPrec :: Int -> ContinueStatement -> String -> String
$cshowsPrec :: Int -> ContinueStatement -> String -> String
Show)

_ContinueStatement :: Name
_ContinueStatement = (String -> Name
Core.Name String
"hydra/ext/java/syntax.ContinueStatement")

newtype ReturnStatement = 
  ReturnStatement {
    ReturnStatement -> Maybe Expression
unReturnStatement :: (Maybe Expression)}
  deriving (ReturnStatement -> ReturnStatement -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ReturnStatement -> ReturnStatement -> Bool
$c/= :: ReturnStatement -> ReturnStatement -> Bool
== :: ReturnStatement -> ReturnStatement -> Bool
$c== :: ReturnStatement -> ReturnStatement -> Bool
Eq, Eq ReturnStatement
ReturnStatement -> ReturnStatement -> Bool
ReturnStatement -> ReturnStatement -> Ordering
ReturnStatement -> ReturnStatement -> ReturnStatement
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ReturnStatement -> ReturnStatement -> ReturnStatement
$cmin :: ReturnStatement -> ReturnStatement -> ReturnStatement
max :: ReturnStatement -> ReturnStatement -> ReturnStatement
$cmax :: ReturnStatement -> ReturnStatement -> ReturnStatement
>= :: ReturnStatement -> ReturnStatement -> Bool
$c>= :: ReturnStatement -> ReturnStatement -> Bool
> :: ReturnStatement -> ReturnStatement -> Bool
$c> :: ReturnStatement -> ReturnStatement -> Bool
<= :: ReturnStatement -> ReturnStatement -> Bool
$c<= :: ReturnStatement -> ReturnStatement -> Bool
< :: ReturnStatement -> ReturnStatement -> Bool
$c< :: ReturnStatement -> ReturnStatement -> Bool
compare :: ReturnStatement -> ReturnStatement -> Ordering
$ccompare :: ReturnStatement -> ReturnStatement -> Ordering
Ord, ReadPrec [ReturnStatement]
ReadPrec ReturnStatement
Int -> ReadS ReturnStatement
ReadS [ReturnStatement]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ReturnStatement]
$creadListPrec :: ReadPrec [ReturnStatement]
readPrec :: ReadPrec ReturnStatement
$creadPrec :: ReadPrec ReturnStatement
readList :: ReadS [ReturnStatement]
$creadList :: ReadS [ReturnStatement]
readsPrec :: Int -> ReadS ReturnStatement
$creadsPrec :: Int -> ReadS ReturnStatement
Read, Int -> ReturnStatement -> String -> String
[ReturnStatement] -> String -> String
ReturnStatement -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ReturnStatement] -> String -> String
$cshowList :: [ReturnStatement] -> String -> String
show :: ReturnStatement -> String
$cshow :: ReturnStatement -> String
showsPrec :: Int -> ReturnStatement -> String -> String
$cshowsPrec :: Int -> ReturnStatement -> String -> String
Show)

_ReturnStatement :: Name
_ReturnStatement = (String -> Name
Core.Name String
"hydra/ext/java/syntax.ReturnStatement")

newtype ThrowStatement = 
  ThrowStatement {
    ThrowStatement -> Expression
unThrowStatement :: Expression}
  deriving (ThrowStatement -> ThrowStatement -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ThrowStatement -> ThrowStatement -> Bool
$c/= :: ThrowStatement -> ThrowStatement -> Bool
== :: ThrowStatement -> ThrowStatement -> Bool
$c== :: ThrowStatement -> ThrowStatement -> Bool
Eq, Eq ThrowStatement
ThrowStatement -> ThrowStatement -> Bool
ThrowStatement -> ThrowStatement -> Ordering
ThrowStatement -> ThrowStatement -> ThrowStatement
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ThrowStatement -> ThrowStatement -> ThrowStatement
$cmin :: ThrowStatement -> ThrowStatement -> ThrowStatement
max :: ThrowStatement -> ThrowStatement -> ThrowStatement
$cmax :: ThrowStatement -> ThrowStatement -> ThrowStatement
>= :: ThrowStatement -> ThrowStatement -> Bool
$c>= :: ThrowStatement -> ThrowStatement -> Bool
> :: ThrowStatement -> ThrowStatement -> Bool
$c> :: ThrowStatement -> ThrowStatement -> Bool
<= :: ThrowStatement -> ThrowStatement -> Bool
$c<= :: ThrowStatement -> ThrowStatement -> Bool
< :: ThrowStatement -> ThrowStatement -> Bool
$c< :: ThrowStatement -> ThrowStatement -> Bool
compare :: ThrowStatement -> ThrowStatement -> Ordering
$ccompare :: ThrowStatement -> ThrowStatement -> Ordering
Ord, ReadPrec [ThrowStatement]
ReadPrec ThrowStatement
Int -> ReadS ThrowStatement
ReadS [ThrowStatement]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ThrowStatement]
$creadListPrec :: ReadPrec [ThrowStatement]
readPrec :: ReadPrec ThrowStatement
$creadPrec :: ReadPrec ThrowStatement
readList :: ReadS [ThrowStatement]
$creadList :: ReadS [ThrowStatement]
readsPrec :: Int -> ReadS ThrowStatement
$creadsPrec :: Int -> ReadS ThrowStatement
Read, Int -> ThrowStatement -> String -> String
[ThrowStatement] -> String -> String
ThrowStatement -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ThrowStatement] -> String -> String
$cshowList :: [ThrowStatement] -> String -> String
show :: ThrowStatement -> String
$cshow :: ThrowStatement -> String
showsPrec :: Int -> ThrowStatement -> String -> String
$cshowsPrec :: Int -> ThrowStatement -> String -> String
Show)

_ThrowStatement :: Name
_ThrowStatement = (String -> Name
Core.Name String
"hydra/ext/java/syntax.ThrowStatement")

data SynchronizedStatement = 
  SynchronizedStatement {
    SynchronizedStatement -> Expression
synchronizedStatementExpression :: Expression,
    SynchronizedStatement -> Block
synchronizedStatementBlock :: Block}
  deriving (SynchronizedStatement -> SynchronizedStatement -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SynchronizedStatement -> SynchronizedStatement -> Bool
$c/= :: SynchronizedStatement -> SynchronizedStatement -> Bool
== :: SynchronizedStatement -> SynchronizedStatement -> Bool
$c== :: SynchronizedStatement -> SynchronizedStatement -> Bool
Eq, Eq SynchronizedStatement
SynchronizedStatement -> SynchronizedStatement -> Bool
SynchronizedStatement -> SynchronizedStatement -> Ordering
SynchronizedStatement
-> SynchronizedStatement -> SynchronizedStatement
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: SynchronizedStatement
-> SynchronizedStatement -> SynchronizedStatement
$cmin :: SynchronizedStatement
-> SynchronizedStatement -> SynchronizedStatement
max :: SynchronizedStatement
-> SynchronizedStatement -> SynchronizedStatement
$cmax :: SynchronizedStatement
-> SynchronizedStatement -> SynchronizedStatement
>= :: SynchronizedStatement -> SynchronizedStatement -> Bool
$c>= :: SynchronizedStatement -> SynchronizedStatement -> Bool
> :: SynchronizedStatement -> SynchronizedStatement -> Bool
$c> :: SynchronizedStatement -> SynchronizedStatement -> Bool
<= :: SynchronizedStatement -> SynchronizedStatement -> Bool
$c<= :: SynchronizedStatement -> SynchronizedStatement -> Bool
< :: SynchronizedStatement -> SynchronizedStatement -> Bool
$c< :: SynchronizedStatement -> SynchronizedStatement -> Bool
compare :: SynchronizedStatement -> SynchronizedStatement -> Ordering
$ccompare :: SynchronizedStatement -> SynchronizedStatement -> Ordering
Ord, ReadPrec [SynchronizedStatement]
ReadPrec SynchronizedStatement
Int -> ReadS SynchronizedStatement
ReadS [SynchronizedStatement]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SynchronizedStatement]
$creadListPrec :: ReadPrec [SynchronizedStatement]
readPrec :: ReadPrec SynchronizedStatement
$creadPrec :: ReadPrec SynchronizedStatement
readList :: ReadS [SynchronizedStatement]
$creadList :: ReadS [SynchronizedStatement]
readsPrec :: Int -> ReadS SynchronizedStatement
$creadsPrec :: Int -> ReadS SynchronizedStatement
Read, Int -> SynchronizedStatement -> String -> String
[SynchronizedStatement] -> String -> String
SynchronizedStatement -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [SynchronizedStatement] -> String -> String
$cshowList :: [SynchronizedStatement] -> String -> String
show :: SynchronizedStatement -> String
$cshow :: SynchronizedStatement -> String
showsPrec :: Int -> SynchronizedStatement -> String -> String
$cshowsPrec :: Int -> SynchronizedStatement -> String -> String
Show)

_SynchronizedStatement :: Name
_SynchronizedStatement = (String -> Name
Core.Name String
"hydra/ext/java/syntax.SynchronizedStatement")

_SynchronizedStatement_expression :: FieldName
_SynchronizedStatement_expression = (String -> FieldName
Core.FieldName String
"expression")

_SynchronizedStatement_block :: FieldName
_SynchronizedStatement_block = (String -> FieldName
Core.FieldName String
"block")

data TryStatement = 
  TryStatementSimple TryStatement_Simple |
  TryStatementWithFinally TryStatement_WithFinally |
  TryStatementWithResources TryWithResourcesStatement
  deriving (TryStatement -> TryStatement -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TryStatement -> TryStatement -> Bool
$c/= :: TryStatement -> TryStatement -> Bool
== :: TryStatement -> TryStatement -> Bool
$c== :: TryStatement -> TryStatement -> Bool
Eq, Eq TryStatement
TryStatement -> TryStatement -> Bool
TryStatement -> TryStatement -> Ordering
TryStatement -> TryStatement -> TryStatement
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: TryStatement -> TryStatement -> TryStatement
$cmin :: TryStatement -> TryStatement -> TryStatement
max :: TryStatement -> TryStatement -> TryStatement
$cmax :: TryStatement -> TryStatement -> TryStatement
>= :: TryStatement -> TryStatement -> Bool
$c>= :: TryStatement -> TryStatement -> Bool
> :: TryStatement -> TryStatement -> Bool
$c> :: TryStatement -> TryStatement -> Bool
<= :: TryStatement -> TryStatement -> Bool
$c<= :: TryStatement -> TryStatement -> Bool
< :: TryStatement -> TryStatement -> Bool
$c< :: TryStatement -> TryStatement -> Bool
compare :: TryStatement -> TryStatement -> Ordering
$ccompare :: TryStatement -> TryStatement -> Ordering
Ord, ReadPrec [TryStatement]
ReadPrec TryStatement
Int -> ReadS TryStatement
ReadS [TryStatement]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [TryStatement]
$creadListPrec :: ReadPrec [TryStatement]
readPrec :: ReadPrec TryStatement
$creadPrec :: ReadPrec TryStatement
readList :: ReadS [TryStatement]
$creadList :: ReadS [TryStatement]
readsPrec :: Int -> ReadS TryStatement
$creadsPrec :: Int -> ReadS TryStatement
Read, Int -> TryStatement -> String -> String
[TryStatement] -> String -> String
TryStatement -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [TryStatement] -> String -> String
$cshowList :: [TryStatement] -> String -> String
show :: TryStatement -> String
$cshow :: TryStatement -> String
showsPrec :: Int -> TryStatement -> String -> String
$cshowsPrec :: Int -> TryStatement -> String -> String
Show)

_TryStatement :: Name
_TryStatement = (String -> Name
Core.Name String
"hydra/ext/java/syntax.TryStatement")

_TryStatement_simple :: FieldName
_TryStatement_simple = (String -> FieldName
Core.FieldName String
"simple")

_TryStatement_withFinally :: FieldName
_TryStatement_withFinally = (String -> FieldName
Core.FieldName String
"withFinally")

_TryStatement_withResources :: FieldName
_TryStatement_withResources = (String -> FieldName
Core.FieldName String
"withResources")

data TryStatement_Simple = 
  TryStatement_Simple {
    TryStatement_Simple -> Block
tryStatement_SimpleBlock :: Block,
    TryStatement_Simple -> Catches
tryStatement_SimpleCatches :: Catches}
  deriving (TryStatement_Simple -> TryStatement_Simple -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TryStatement_Simple -> TryStatement_Simple -> Bool
$c/= :: TryStatement_Simple -> TryStatement_Simple -> Bool
== :: TryStatement_Simple -> TryStatement_Simple -> Bool
$c== :: TryStatement_Simple -> TryStatement_Simple -> Bool
Eq, Eq TryStatement_Simple
TryStatement_Simple -> TryStatement_Simple -> Bool
TryStatement_Simple -> TryStatement_Simple -> Ordering
TryStatement_Simple -> TryStatement_Simple -> TryStatement_Simple
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: TryStatement_Simple -> TryStatement_Simple -> TryStatement_Simple
$cmin :: TryStatement_Simple -> TryStatement_Simple -> TryStatement_Simple
max :: TryStatement_Simple -> TryStatement_Simple -> TryStatement_Simple
$cmax :: TryStatement_Simple -> TryStatement_Simple -> TryStatement_Simple
>= :: TryStatement_Simple -> TryStatement_Simple -> Bool
$c>= :: TryStatement_Simple -> TryStatement_Simple -> Bool
> :: TryStatement_Simple -> TryStatement_Simple -> Bool
$c> :: TryStatement_Simple -> TryStatement_Simple -> Bool
<= :: TryStatement_Simple -> TryStatement_Simple -> Bool
$c<= :: TryStatement_Simple -> TryStatement_Simple -> Bool
< :: TryStatement_Simple -> TryStatement_Simple -> Bool
$c< :: TryStatement_Simple -> TryStatement_Simple -> Bool
compare :: TryStatement_Simple -> TryStatement_Simple -> Ordering
$ccompare :: TryStatement_Simple -> TryStatement_Simple -> Ordering
Ord, ReadPrec [TryStatement_Simple]
ReadPrec TryStatement_Simple
Int -> ReadS TryStatement_Simple
ReadS [TryStatement_Simple]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [TryStatement_Simple]
$creadListPrec :: ReadPrec [TryStatement_Simple]
readPrec :: ReadPrec TryStatement_Simple
$creadPrec :: ReadPrec TryStatement_Simple
readList :: ReadS [TryStatement_Simple]
$creadList :: ReadS [TryStatement_Simple]
readsPrec :: Int -> ReadS TryStatement_Simple
$creadsPrec :: Int -> ReadS TryStatement_Simple
Read, Int -> TryStatement_Simple -> String -> String
[TryStatement_Simple] -> String -> String
TryStatement_Simple -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [TryStatement_Simple] -> String -> String
$cshowList :: [TryStatement_Simple] -> String -> String
show :: TryStatement_Simple -> String
$cshow :: TryStatement_Simple -> String
showsPrec :: Int -> TryStatement_Simple -> String -> String
$cshowsPrec :: Int -> TryStatement_Simple -> String -> String
Show)

_TryStatement_Simple :: Name
_TryStatement_Simple = (String -> Name
Core.Name String
"hydra/ext/java/syntax.TryStatement.Simple")

_TryStatement_Simple_block :: FieldName
_TryStatement_Simple_block = (String -> FieldName
Core.FieldName String
"block")

_TryStatement_Simple_catches :: FieldName
_TryStatement_Simple_catches = (String -> FieldName
Core.FieldName String
"catches")

data TryStatement_WithFinally = 
  TryStatement_WithFinally {
    TryStatement_WithFinally -> Block
tryStatement_WithFinallyBlock :: Block,
    TryStatement_WithFinally -> Maybe Catches
tryStatement_WithFinallyCatches :: (Maybe Catches),
    TryStatement_WithFinally -> Finally
tryStatement_WithFinallyFinally :: Finally}
  deriving (TryStatement_WithFinally -> TryStatement_WithFinally -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TryStatement_WithFinally -> TryStatement_WithFinally -> Bool
$c/= :: TryStatement_WithFinally -> TryStatement_WithFinally -> Bool
== :: TryStatement_WithFinally -> TryStatement_WithFinally -> Bool
$c== :: TryStatement_WithFinally -> TryStatement_WithFinally -> Bool
Eq, Eq TryStatement_WithFinally
TryStatement_WithFinally -> TryStatement_WithFinally -> Bool
TryStatement_WithFinally -> TryStatement_WithFinally -> Ordering
TryStatement_WithFinally
-> TryStatement_WithFinally -> TryStatement_WithFinally
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: TryStatement_WithFinally
-> TryStatement_WithFinally -> TryStatement_WithFinally
$cmin :: TryStatement_WithFinally
-> TryStatement_WithFinally -> TryStatement_WithFinally
max :: TryStatement_WithFinally
-> TryStatement_WithFinally -> TryStatement_WithFinally
$cmax :: TryStatement_WithFinally
-> TryStatement_WithFinally -> TryStatement_WithFinally
>= :: TryStatement_WithFinally -> TryStatement_WithFinally -> Bool
$c>= :: TryStatement_WithFinally -> TryStatement_WithFinally -> Bool
> :: TryStatement_WithFinally -> TryStatement_WithFinally -> Bool
$c> :: TryStatement_WithFinally -> TryStatement_WithFinally -> Bool
<= :: TryStatement_WithFinally -> TryStatement_WithFinally -> Bool
$c<= :: TryStatement_WithFinally -> TryStatement_WithFinally -> Bool
< :: TryStatement_WithFinally -> TryStatement_WithFinally -> Bool
$c< :: TryStatement_WithFinally -> TryStatement_WithFinally -> Bool
compare :: TryStatement_WithFinally -> TryStatement_WithFinally -> Ordering
$ccompare :: TryStatement_WithFinally -> TryStatement_WithFinally -> Ordering
Ord, ReadPrec [TryStatement_WithFinally]
ReadPrec TryStatement_WithFinally
Int -> ReadS TryStatement_WithFinally
ReadS [TryStatement_WithFinally]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [TryStatement_WithFinally]
$creadListPrec :: ReadPrec [TryStatement_WithFinally]
readPrec :: ReadPrec TryStatement_WithFinally
$creadPrec :: ReadPrec TryStatement_WithFinally
readList :: ReadS [TryStatement_WithFinally]
$creadList :: ReadS [TryStatement_WithFinally]
readsPrec :: Int -> ReadS TryStatement_WithFinally
$creadsPrec :: Int -> ReadS TryStatement_WithFinally
Read, Int -> TryStatement_WithFinally -> String -> String
[TryStatement_WithFinally] -> String -> String
TryStatement_WithFinally -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [TryStatement_WithFinally] -> String -> String
$cshowList :: [TryStatement_WithFinally] -> String -> String
show :: TryStatement_WithFinally -> String
$cshow :: TryStatement_WithFinally -> String
showsPrec :: Int -> TryStatement_WithFinally -> String -> String
$cshowsPrec :: Int -> TryStatement_WithFinally -> String -> String
Show)

_TryStatement_WithFinally :: Name
_TryStatement_WithFinally = (String -> Name
Core.Name String
"hydra/ext/java/syntax.TryStatement.WithFinally")

_TryStatement_WithFinally_block :: FieldName
_TryStatement_WithFinally_block = (String -> FieldName
Core.FieldName String
"block")

_TryStatement_WithFinally_catches :: FieldName
_TryStatement_WithFinally_catches = (String -> FieldName
Core.FieldName String
"catches")

_TryStatement_WithFinally_finally :: FieldName
_TryStatement_WithFinally_finally = (String -> FieldName
Core.FieldName String
"finally")

newtype Catches = 
  Catches {
    Catches -> [CatchClause]
unCatches :: [CatchClause]}
  deriving (Catches -> Catches -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Catches -> Catches -> Bool
$c/= :: Catches -> Catches -> Bool
== :: Catches -> Catches -> Bool
$c== :: Catches -> Catches -> Bool
Eq, Eq Catches
Catches -> Catches -> Bool
Catches -> Catches -> Ordering
Catches -> Catches -> Catches
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Catches -> Catches -> Catches
$cmin :: Catches -> Catches -> Catches
max :: Catches -> Catches -> Catches
$cmax :: Catches -> Catches -> Catches
>= :: Catches -> Catches -> Bool
$c>= :: Catches -> Catches -> Bool
> :: Catches -> Catches -> Bool
$c> :: Catches -> Catches -> Bool
<= :: Catches -> Catches -> Bool
$c<= :: Catches -> Catches -> Bool
< :: Catches -> Catches -> Bool
$c< :: Catches -> Catches -> Bool
compare :: Catches -> Catches -> Ordering
$ccompare :: Catches -> Catches -> Ordering
Ord, ReadPrec [Catches]
ReadPrec Catches
Int -> ReadS Catches
ReadS [Catches]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Catches]
$creadListPrec :: ReadPrec [Catches]
readPrec :: ReadPrec Catches
$creadPrec :: ReadPrec Catches
readList :: ReadS [Catches]
$creadList :: ReadS [Catches]
readsPrec :: Int -> ReadS Catches
$creadsPrec :: Int -> ReadS Catches
Read, Int -> Catches -> String -> String
[Catches] -> String -> String
Catches -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [Catches] -> String -> String
$cshowList :: [Catches] -> String -> String
show :: Catches -> String
$cshow :: Catches -> String
showsPrec :: Int -> Catches -> String -> String
$cshowsPrec :: Int -> Catches -> String -> String
Show)

_Catches :: Name
_Catches = (String -> Name
Core.Name String
"hydra/ext/java/syntax.Catches")

data CatchClause = 
  CatchClause {
    CatchClause -> Maybe CatchFormalParameter
catchClauseParameter :: (Maybe CatchFormalParameter),
    CatchClause -> Block
catchClauseBlock :: Block}
  deriving (CatchClause -> CatchClause -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CatchClause -> CatchClause -> Bool
$c/= :: CatchClause -> CatchClause -> Bool
== :: CatchClause -> CatchClause -> Bool
$c== :: CatchClause -> CatchClause -> Bool
Eq, Eq CatchClause
CatchClause -> CatchClause -> Bool
CatchClause -> CatchClause -> Ordering
CatchClause -> CatchClause -> CatchClause
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CatchClause -> CatchClause -> CatchClause
$cmin :: CatchClause -> CatchClause -> CatchClause
max :: CatchClause -> CatchClause -> CatchClause
$cmax :: CatchClause -> CatchClause -> CatchClause
>= :: CatchClause -> CatchClause -> Bool
$c>= :: CatchClause -> CatchClause -> Bool
> :: CatchClause -> CatchClause -> Bool
$c> :: CatchClause -> CatchClause -> Bool
<= :: CatchClause -> CatchClause -> Bool
$c<= :: CatchClause -> CatchClause -> Bool
< :: CatchClause -> CatchClause -> Bool
$c< :: CatchClause -> CatchClause -> Bool
compare :: CatchClause -> CatchClause -> Ordering
$ccompare :: CatchClause -> CatchClause -> Ordering
Ord, ReadPrec [CatchClause]
ReadPrec CatchClause
Int -> ReadS CatchClause
ReadS [CatchClause]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CatchClause]
$creadListPrec :: ReadPrec [CatchClause]
readPrec :: ReadPrec CatchClause
$creadPrec :: ReadPrec CatchClause
readList :: ReadS [CatchClause]
$creadList :: ReadS [CatchClause]
readsPrec :: Int -> ReadS CatchClause
$creadsPrec :: Int -> ReadS CatchClause
Read, Int -> CatchClause -> String -> String
[CatchClause] -> String -> String
CatchClause -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [CatchClause] -> String -> String
$cshowList :: [CatchClause] -> String -> String
show :: CatchClause -> String
$cshow :: CatchClause -> String
showsPrec :: Int -> CatchClause -> String -> String
$cshowsPrec :: Int -> CatchClause -> String -> String
Show)

_CatchClause :: Name
_CatchClause = (String -> Name
Core.Name String
"hydra/ext/java/syntax.CatchClause")

_CatchClause_parameter :: FieldName
_CatchClause_parameter = (String -> FieldName
Core.FieldName String
"parameter")

_CatchClause_block :: FieldName
_CatchClause_block = (String -> FieldName
Core.FieldName String
"block")

data CatchFormalParameter = 
  CatchFormalParameter {
    CatchFormalParameter -> [VariableModifier]
catchFormalParameterModifiers :: [VariableModifier],
    CatchFormalParameter -> CatchType
catchFormalParameterType :: CatchType,
    CatchFormalParameter -> VariableDeclaratorId
catchFormalParameterId :: VariableDeclaratorId}
  deriving (CatchFormalParameter -> CatchFormalParameter -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CatchFormalParameter -> CatchFormalParameter -> Bool
$c/= :: CatchFormalParameter -> CatchFormalParameter -> Bool
== :: CatchFormalParameter -> CatchFormalParameter -> Bool
$c== :: CatchFormalParameter -> CatchFormalParameter -> Bool
Eq, Eq CatchFormalParameter
CatchFormalParameter -> CatchFormalParameter -> Bool
CatchFormalParameter -> CatchFormalParameter -> Ordering
CatchFormalParameter
-> CatchFormalParameter -> CatchFormalParameter
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CatchFormalParameter
-> CatchFormalParameter -> CatchFormalParameter
$cmin :: CatchFormalParameter
-> CatchFormalParameter -> CatchFormalParameter
max :: CatchFormalParameter
-> CatchFormalParameter -> CatchFormalParameter
$cmax :: CatchFormalParameter
-> CatchFormalParameter -> CatchFormalParameter
>= :: CatchFormalParameter -> CatchFormalParameter -> Bool
$c>= :: CatchFormalParameter -> CatchFormalParameter -> Bool
> :: CatchFormalParameter -> CatchFormalParameter -> Bool
$c> :: CatchFormalParameter -> CatchFormalParameter -> Bool
<= :: CatchFormalParameter -> CatchFormalParameter -> Bool
$c<= :: CatchFormalParameter -> CatchFormalParameter -> Bool
< :: CatchFormalParameter -> CatchFormalParameter -> Bool
$c< :: CatchFormalParameter -> CatchFormalParameter -> Bool
compare :: CatchFormalParameter -> CatchFormalParameter -> Ordering
$ccompare :: CatchFormalParameter -> CatchFormalParameter -> Ordering
Ord, ReadPrec [CatchFormalParameter]
ReadPrec CatchFormalParameter
Int -> ReadS CatchFormalParameter
ReadS [CatchFormalParameter]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CatchFormalParameter]
$creadListPrec :: ReadPrec [CatchFormalParameter]
readPrec :: ReadPrec CatchFormalParameter
$creadPrec :: ReadPrec CatchFormalParameter
readList :: ReadS [CatchFormalParameter]
$creadList :: ReadS [CatchFormalParameter]
readsPrec :: Int -> ReadS CatchFormalParameter
$creadsPrec :: Int -> ReadS CatchFormalParameter
Read, Int -> CatchFormalParameter -> String -> String
[CatchFormalParameter] -> String -> String
CatchFormalParameter -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [CatchFormalParameter] -> String -> String
$cshowList :: [CatchFormalParameter] -> String -> String
show :: CatchFormalParameter -> String
$cshow :: CatchFormalParameter -> String
showsPrec :: Int -> CatchFormalParameter -> String -> String
$cshowsPrec :: Int -> CatchFormalParameter -> String -> String
Show)

_CatchFormalParameter :: Name
_CatchFormalParameter = (String -> Name
Core.Name String
"hydra/ext/java/syntax.CatchFormalParameter")

_CatchFormalParameter_modifiers :: FieldName
_CatchFormalParameter_modifiers = (String -> FieldName
Core.FieldName String
"modifiers")

_CatchFormalParameter_type :: FieldName
_CatchFormalParameter_type = (String -> FieldName
Core.FieldName String
"type")

_CatchFormalParameter_id :: FieldName
_CatchFormalParameter_id = (String -> FieldName
Core.FieldName String
"id")

data CatchType = 
  CatchType {
    CatchType -> UnannClassType
catchTypeType :: UnannClassType,
    CatchType -> [ClassType]
catchTypeTypes :: [ClassType]}
  deriving (CatchType -> CatchType -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CatchType -> CatchType -> Bool
$c/= :: CatchType -> CatchType -> Bool
== :: CatchType -> CatchType -> Bool
$c== :: CatchType -> CatchType -> Bool
Eq, Eq CatchType
CatchType -> CatchType -> Bool
CatchType -> CatchType -> Ordering
CatchType -> CatchType -> CatchType
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CatchType -> CatchType -> CatchType
$cmin :: CatchType -> CatchType -> CatchType
max :: CatchType -> CatchType -> CatchType
$cmax :: CatchType -> CatchType -> CatchType
>= :: CatchType -> CatchType -> Bool
$c>= :: CatchType -> CatchType -> Bool
> :: CatchType -> CatchType -> Bool
$c> :: CatchType -> CatchType -> Bool
<= :: CatchType -> CatchType -> Bool
$c<= :: CatchType -> CatchType -> Bool
< :: CatchType -> CatchType -> Bool
$c< :: CatchType -> CatchType -> Bool
compare :: CatchType -> CatchType -> Ordering
$ccompare :: CatchType -> CatchType -> Ordering
Ord, ReadPrec [CatchType]
ReadPrec CatchType
Int -> ReadS CatchType
ReadS [CatchType]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CatchType]
$creadListPrec :: ReadPrec [CatchType]
readPrec :: ReadPrec CatchType
$creadPrec :: ReadPrec CatchType
readList :: ReadS [CatchType]
$creadList :: ReadS [CatchType]
readsPrec :: Int -> ReadS CatchType
$creadsPrec :: Int -> ReadS CatchType
Read, Int -> CatchType -> String -> String
[CatchType] -> String -> String
CatchType -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [CatchType] -> String -> String
$cshowList :: [CatchType] -> String -> String
show :: CatchType -> String
$cshow :: CatchType -> String
showsPrec :: Int -> CatchType -> String -> String
$cshowsPrec :: Int -> CatchType -> String -> String
Show)

_CatchType :: Name
_CatchType = (String -> Name
Core.Name String
"hydra/ext/java/syntax.CatchType")

_CatchType_type :: FieldName
_CatchType_type = (String -> FieldName
Core.FieldName String
"type")

_CatchType_types :: FieldName
_CatchType_types = (String -> FieldName
Core.FieldName String
"types")

newtype Finally = 
  Finally {
    Finally -> Block
unFinally :: Block}
  deriving (Finally -> Finally -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Finally -> Finally -> Bool
$c/= :: Finally -> Finally -> Bool
== :: Finally -> Finally -> Bool
$c== :: Finally -> Finally -> Bool
Eq, Eq Finally
Finally -> Finally -> Bool
Finally -> Finally -> Ordering
Finally -> Finally -> Finally
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Finally -> Finally -> Finally
$cmin :: Finally -> Finally -> Finally
max :: Finally -> Finally -> Finally
$cmax :: Finally -> Finally -> Finally
>= :: Finally -> Finally -> Bool
$c>= :: Finally -> Finally -> Bool
> :: Finally -> Finally -> Bool
$c> :: Finally -> Finally -> Bool
<= :: Finally -> Finally -> Bool
$c<= :: Finally -> Finally -> Bool
< :: Finally -> Finally -> Bool
$c< :: Finally -> Finally -> Bool
compare :: Finally -> Finally -> Ordering
$ccompare :: Finally -> Finally -> Ordering
Ord, ReadPrec [Finally]
ReadPrec Finally
Int -> ReadS Finally
ReadS [Finally]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Finally]
$creadListPrec :: ReadPrec [Finally]
readPrec :: ReadPrec Finally
$creadPrec :: ReadPrec Finally
readList :: ReadS [Finally]
$creadList :: ReadS [Finally]
readsPrec :: Int -> ReadS Finally
$creadsPrec :: Int -> ReadS Finally
Read, Int -> Finally -> String -> String
[Finally] -> String -> String
Finally -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [Finally] -> String -> String
$cshowList :: [Finally] -> String -> String
show :: Finally -> String
$cshow :: Finally -> String
showsPrec :: Int -> Finally -> String -> String
$cshowsPrec :: Int -> Finally -> String -> String
Show)

_Finally :: Name
_Finally = (String -> Name
Core.Name String
"hydra/ext/java/syntax.Finally")

data TryWithResourcesStatement = 
  TryWithResourcesStatement {
    TryWithResourcesStatement -> ResourceSpecification
tryWithResourcesStatementResourceSpecification :: ResourceSpecification,
    TryWithResourcesStatement -> Block
tryWithResourcesStatementBlock :: Block,
    TryWithResourcesStatement -> Maybe Catches
tryWithResourcesStatementCatches :: (Maybe Catches),
    TryWithResourcesStatement -> Maybe Finally
tryWithResourcesStatementFinally :: (Maybe Finally)}
  deriving (TryWithResourcesStatement -> TryWithResourcesStatement -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TryWithResourcesStatement -> TryWithResourcesStatement -> Bool
$c/= :: TryWithResourcesStatement -> TryWithResourcesStatement -> Bool
== :: TryWithResourcesStatement -> TryWithResourcesStatement -> Bool
$c== :: TryWithResourcesStatement -> TryWithResourcesStatement -> Bool
Eq, Eq TryWithResourcesStatement
TryWithResourcesStatement -> TryWithResourcesStatement -> Bool
TryWithResourcesStatement -> TryWithResourcesStatement -> Ordering
TryWithResourcesStatement
-> TryWithResourcesStatement -> TryWithResourcesStatement
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: TryWithResourcesStatement
-> TryWithResourcesStatement -> TryWithResourcesStatement
$cmin :: TryWithResourcesStatement
-> TryWithResourcesStatement -> TryWithResourcesStatement
max :: TryWithResourcesStatement
-> TryWithResourcesStatement -> TryWithResourcesStatement
$cmax :: TryWithResourcesStatement
-> TryWithResourcesStatement -> TryWithResourcesStatement
>= :: TryWithResourcesStatement -> TryWithResourcesStatement -> Bool
$c>= :: TryWithResourcesStatement -> TryWithResourcesStatement -> Bool
> :: TryWithResourcesStatement -> TryWithResourcesStatement -> Bool
$c> :: TryWithResourcesStatement -> TryWithResourcesStatement -> Bool
<= :: TryWithResourcesStatement -> TryWithResourcesStatement -> Bool
$c<= :: TryWithResourcesStatement -> TryWithResourcesStatement -> Bool
< :: TryWithResourcesStatement -> TryWithResourcesStatement -> Bool
$c< :: TryWithResourcesStatement -> TryWithResourcesStatement -> Bool
compare :: TryWithResourcesStatement -> TryWithResourcesStatement -> Ordering
$ccompare :: TryWithResourcesStatement -> TryWithResourcesStatement -> Ordering
Ord, ReadPrec [TryWithResourcesStatement]
ReadPrec TryWithResourcesStatement
Int -> ReadS TryWithResourcesStatement
ReadS [TryWithResourcesStatement]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [TryWithResourcesStatement]
$creadListPrec :: ReadPrec [TryWithResourcesStatement]
readPrec :: ReadPrec TryWithResourcesStatement
$creadPrec :: ReadPrec TryWithResourcesStatement
readList :: ReadS [TryWithResourcesStatement]
$creadList :: ReadS [TryWithResourcesStatement]
readsPrec :: Int -> ReadS TryWithResourcesStatement
$creadsPrec :: Int -> ReadS TryWithResourcesStatement
Read, Int -> TryWithResourcesStatement -> String -> String
[TryWithResourcesStatement] -> String -> String
TryWithResourcesStatement -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [TryWithResourcesStatement] -> String -> String
$cshowList :: [TryWithResourcesStatement] -> String -> String
show :: TryWithResourcesStatement -> String
$cshow :: TryWithResourcesStatement -> String
showsPrec :: Int -> TryWithResourcesStatement -> String -> String
$cshowsPrec :: Int -> TryWithResourcesStatement -> String -> String
Show)

_TryWithResourcesStatement :: Name
_TryWithResourcesStatement = (String -> Name
Core.Name String
"hydra/ext/java/syntax.TryWithResourcesStatement")

_TryWithResourcesStatement_resourceSpecification :: FieldName
_TryWithResourcesStatement_resourceSpecification = (String -> FieldName
Core.FieldName String
"resourceSpecification")

_TryWithResourcesStatement_block :: FieldName
_TryWithResourcesStatement_block = (String -> FieldName
Core.FieldName String
"block")

_TryWithResourcesStatement_catches :: FieldName
_TryWithResourcesStatement_catches = (String -> FieldName
Core.FieldName String
"catches")

_TryWithResourcesStatement_finally :: FieldName
_TryWithResourcesStatement_finally = (String -> FieldName
Core.FieldName String
"finally")

newtype ResourceSpecification = 
  ResourceSpecification {
    ResourceSpecification -> [Resource]
unResourceSpecification :: [Resource]}
  deriving (ResourceSpecification -> ResourceSpecification -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ResourceSpecification -> ResourceSpecification -> Bool
$c/= :: ResourceSpecification -> ResourceSpecification -> Bool
== :: ResourceSpecification -> ResourceSpecification -> Bool
$c== :: ResourceSpecification -> ResourceSpecification -> Bool
Eq, Eq ResourceSpecification
ResourceSpecification -> ResourceSpecification -> Bool
ResourceSpecification -> ResourceSpecification -> Ordering
ResourceSpecification
-> ResourceSpecification -> ResourceSpecification
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ResourceSpecification
-> ResourceSpecification -> ResourceSpecification
$cmin :: ResourceSpecification
-> ResourceSpecification -> ResourceSpecification
max :: ResourceSpecification
-> ResourceSpecification -> ResourceSpecification
$cmax :: ResourceSpecification
-> ResourceSpecification -> ResourceSpecification
>= :: ResourceSpecification -> ResourceSpecification -> Bool
$c>= :: ResourceSpecification -> ResourceSpecification -> Bool
> :: ResourceSpecification -> ResourceSpecification -> Bool
$c> :: ResourceSpecification -> ResourceSpecification -> Bool
<= :: ResourceSpecification -> ResourceSpecification -> Bool
$c<= :: ResourceSpecification -> ResourceSpecification -> Bool
< :: ResourceSpecification -> ResourceSpecification -> Bool
$c< :: ResourceSpecification -> ResourceSpecification -> Bool
compare :: ResourceSpecification -> ResourceSpecification -> Ordering
$ccompare :: ResourceSpecification -> ResourceSpecification -> Ordering
Ord, ReadPrec [ResourceSpecification]
ReadPrec ResourceSpecification
Int -> ReadS ResourceSpecification
ReadS [ResourceSpecification]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ResourceSpecification]
$creadListPrec :: ReadPrec [ResourceSpecification]
readPrec :: ReadPrec ResourceSpecification
$creadPrec :: ReadPrec ResourceSpecification
readList :: ReadS [ResourceSpecification]
$creadList :: ReadS [ResourceSpecification]
readsPrec :: Int -> ReadS ResourceSpecification
$creadsPrec :: Int -> ReadS ResourceSpecification
Read, Int -> ResourceSpecification -> String -> String
[ResourceSpecification] -> String -> String
ResourceSpecification -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ResourceSpecification] -> String -> String
$cshowList :: [ResourceSpecification] -> String -> String
show :: ResourceSpecification -> String
$cshow :: ResourceSpecification -> String
showsPrec :: Int -> ResourceSpecification -> String -> String
$cshowsPrec :: Int -> ResourceSpecification -> String -> String
Show)

_ResourceSpecification :: Name
_ResourceSpecification = (String -> Name
Core.Name String
"hydra/ext/java/syntax.ResourceSpecification")

data Resource = 
  ResourceLocal Resource_Local |
  ResourceVariable VariableAccess
  deriving (Resource -> Resource -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Resource -> Resource -> Bool
$c/= :: Resource -> Resource -> Bool
== :: Resource -> Resource -> Bool
$c== :: Resource -> Resource -> Bool
Eq, Eq Resource
Resource -> Resource -> Bool
Resource -> Resource -> Ordering
Resource -> Resource -> Resource
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Resource -> Resource -> Resource
$cmin :: Resource -> Resource -> Resource
max :: Resource -> Resource -> Resource
$cmax :: Resource -> Resource -> Resource
>= :: Resource -> Resource -> Bool
$c>= :: Resource -> Resource -> Bool
> :: Resource -> Resource -> Bool
$c> :: Resource -> Resource -> Bool
<= :: Resource -> Resource -> Bool
$c<= :: Resource -> Resource -> Bool
< :: Resource -> Resource -> Bool
$c< :: Resource -> Resource -> Bool
compare :: Resource -> Resource -> Ordering
$ccompare :: Resource -> Resource -> Ordering
Ord, ReadPrec [Resource]
ReadPrec Resource
Int -> ReadS Resource
ReadS [Resource]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Resource]
$creadListPrec :: ReadPrec [Resource]
readPrec :: ReadPrec Resource
$creadPrec :: ReadPrec Resource
readList :: ReadS [Resource]
$creadList :: ReadS [Resource]
readsPrec :: Int -> ReadS Resource
$creadsPrec :: Int -> ReadS Resource
Read, Int -> Resource -> String -> String
[Resource] -> String -> String
Resource -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [Resource] -> String -> String
$cshowList :: [Resource] -> String -> String
show :: Resource -> String
$cshow :: Resource -> String
showsPrec :: Int -> Resource -> String -> String
$cshowsPrec :: Int -> Resource -> String -> String
Show)

_Resource :: Name
_Resource = (String -> Name
Core.Name String
"hydra/ext/java/syntax.Resource")

_Resource_local :: FieldName
_Resource_local = (String -> FieldName
Core.FieldName String
"local")

_Resource_variable :: FieldName
_Resource_variable = (String -> FieldName
Core.FieldName String
"variable")

data Resource_Local = 
  Resource_Local {
    Resource_Local -> [VariableModifier]
resource_LocalModifiers :: [VariableModifier],
    Resource_Local -> LocalVariableType
resource_LocalType :: LocalVariableType,
    Resource_Local -> Identifier
resource_LocalIdentifier :: Identifier,
    Resource_Local -> Expression
resource_LocalExpression :: Expression}
  deriving (Resource_Local -> Resource_Local -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Resource_Local -> Resource_Local -> Bool
$c/= :: Resource_Local -> Resource_Local -> Bool
== :: Resource_Local -> Resource_Local -> Bool
$c== :: Resource_Local -> Resource_Local -> Bool
Eq, Eq Resource_Local
Resource_Local -> Resource_Local -> Bool
Resource_Local -> Resource_Local -> Ordering
Resource_Local -> Resource_Local -> Resource_Local
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Resource_Local -> Resource_Local -> Resource_Local
$cmin :: Resource_Local -> Resource_Local -> Resource_Local
max :: Resource_Local -> Resource_Local -> Resource_Local
$cmax :: Resource_Local -> Resource_Local -> Resource_Local
>= :: Resource_Local -> Resource_Local -> Bool
$c>= :: Resource_Local -> Resource_Local -> Bool
> :: Resource_Local -> Resource_Local -> Bool
$c> :: Resource_Local -> Resource_Local -> Bool
<= :: Resource_Local -> Resource_Local -> Bool
$c<= :: Resource_Local -> Resource_Local -> Bool
< :: Resource_Local -> Resource_Local -> Bool
$c< :: Resource_Local -> Resource_Local -> Bool
compare :: Resource_Local -> Resource_Local -> Ordering
$ccompare :: Resource_Local -> Resource_Local -> Ordering
Ord, ReadPrec [Resource_Local]
ReadPrec Resource_Local
Int -> ReadS Resource_Local
ReadS [Resource_Local]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Resource_Local]
$creadListPrec :: ReadPrec [Resource_Local]
readPrec :: ReadPrec Resource_Local
$creadPrec :: ReadPrec Resource_Local
readList :: ReadS [Resource_Local]
$creadList :: ReadS [Resource_Local]
readsPrec :: Int -> ReadS Resource_Local
$creadsPrec :: Int -> ReadS Resource_Local
Read, Int -> Resource_Local -> String -> String
[Resource_Local] -> String -> String
Resource_Local -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [Resource_Local] -> String -> String
$cshowList :: [Resource_Local] -> String -> String
show :: Resource_Local -> String
$cshow :: Resource_Local -> String
showsPrec :: Int -> Resource_Local -> String -> String
$cshowsPrec :: Int -> Resource_Local -> String -> String
Show)

_Resource_Local :: Name
_Resource_Local = (String -> Name
Core.Name String
"hydra/ext/java/syntax.Resource.Local")

_Resource_Local_modifiers :: FieldName
_Resource_Local_modifiers = (String -> FieldName
Core.FieldName String
"modifiers")

_Resource_Local_type :: FieldName
_Resource_Local_type = (String -> FieldName
Core.FieldName String
"type")

_Resource_Local_identifier :: FieldName
_Resource_Local_identifier = (String -> FieldName
Core.FieldName String
"identifier")

_Resource_Local_expression :: FieldName
_Resource_Local_expression = (String -> FieldName
Core.FieldName String
"expression")

data VariableAccess = 
  VariableAccessExpressionName ExpressionName |
  VariableAccessFieldAccess FieldAccess
  deriving (VariableAccess -> VariableAccess -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VariableAccess -> VariableAccess -> Bool
$c/= :: VariableAccess -> VariableAccess -> Bool
== :: VariableAccess -> VariableAccess -> Bool
$c== :: VariableAccess -> VariableAccess -> Bool
Eq, Eq VariableAccess
VariableAccess -> VariableAccess -> Bool
VariableAccess -> VariableAccess -> Ordering
VariableAccess -> VariableAccess -> VariableAccess
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: VariableAccess -> VariableAccess -> VariableAccess
$cmin :: VariableAccess -> VariableAccess -> VariableAccess
max :: VariableAccess -> VariableAccess -> VariableAccess
$cmax :: VariableAccess -> VariableAccess -> VariableAccess
>= :: VariableAccess -> VariableAccess -> Bool
$c>= :: VariableAccess -> VariableAccess -> Bool
> :: VariableAccess -> VariableAccess -> Bool
$c> :: VariableAccess -> VariableAccess -> Bool
<= :: VariableAccess -> VariableAccess -> Bool
$c<= :: VariableAccess -> VariableAccess -> Bool
< :: VariableAccess -> VariableAccess -> Bool
$c< :: VariableAccess -> VariableAccess -> Bool
compare :: VariableAccess -> VariableAccess -> Ordering
$ccompare :: VariableAccess -> VariableAccess -> Ordering
Ord, ReadPrec [VariableAccess]
ReadPrec VariableAccess
Int -> ReadS VariableAccess
ReadS [VariableAccess]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [VariableAccess]
$creadListPrec :: ReadPrec [VariableAccess]
readPrec :: ReadPrec VariableAccess
$creadPrec :: ReadPrec VariableAccess
readList :: ReadS [VariableAccess]
$creadList :: ReadS [VariableAccess]
readsPrec :: Int -> ReadS VariableAccess
$creadsPrec :: Int -> ReadS VariableAccess
Read, Int -> VariableAccess -> String -> String
[VariableAccess] -> String -> String
VariableAccess -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [VariableAccess] -> String -> String
$cshowList :: [VariableAccess] -> String -> String
show :: VariableAccess -> String
$cshow :: VariableAccess -> String
showsPrec :: Int -> VariableAccess -> String -> String
$cshowsPrec :: Int -> VariableAccess -> String -> String
Show)

_VariableAccess :: Name
_VariableAccess = (String -> Name
Core.Name String
"hydra/ext/java/syntax.VariableAccess")

_VariableAccess_expressionName :: FieldName
_VariableAccess_expressionName = (String -> FieldName
Core.FieldName String
"expressionName")

_VariableAccess_fieldAccess :: FieldName
_VariableAccess_fieldAccess = (String -> FieldName
Core.FieldName String
"fieldAccess")

data Primary = 
  PrimaryNoNewArray PrimaryNoNewArray |
  PrimaryArrayCreation ArrayCreationExpression
  deriving (Primary -> Primary -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Primary -> Primary -> Bool
$c/= :: Primary -> Primary -> Bool
== :: Primary -> Primary -> Bool
$c== :: Primary -> Primary -> Bool
Eq, Eq Primary
Primary -> Primary -> Bool
Primary -> Primary -> Ordering
Primary -> Primary -> Primary
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Primary -> Primary -> Primary
$cmin :: Primary -> Primary -> Primary
max :: Primary -> Primary -> Primary
$cmax :: Primary -> Primary -> Primary
>= :: Primary -> Primary -> Bool
$c>= :: Primary -> Primary -> Bool
> :: Primary -> Primary -> Bool
$c> :: Primary -> Primary -> Bool
<= :: Primary -> Primary -> Bool
$c<= :: Primary -> Primary -> Bool
< :: Primary -> Primary -> Bool
$c< :: Primary -> Primary -> Bool
compare :: Primary -> Primary -> Ordering
$ccompare :: Primary -> Primary -> Ordering
Ord, ReadPrec [Primary]
ReadPrec Primary
Int -> ReadS Primary
ReadS [Primary]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Primary]
$creadListPrec :: ReadPrec [Primary]
readPrec :: ReadPrec Primary
$creadPrec :: ReadPrec Primary
readList :: ReadS [Primary]
$creadList :: ReadS [Primary]
readsPrec :: Int -> ReadS Primary
$creadsPrec :: Int -> ReadS Primary
Read, Int -> Primary -> String -> String
[Primary] -> String -> String
Primary -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [Primary] -> String -> String
$cshowList :: [Primary] -> String -> String
show :: Primary -> String
$cshow :: Primary -> String
showsPrec :: Int -> Primary -> String -> String
$cshowsPrec :: Int -> Primary -> String -> String
Show)

_Primary :: Name
_Primary = (String -> Name
Core.Name String
"hydra/ext/java/syntax.Primary")

_Primary_noNewArray :: FieldName
_Primary_noNewArray = (String -> FieldName
Core.FieldName String
"noNewArray")

_Primary_arrayCreation :: FieldName
_Primary_arrayCreation = (String -> FieldName
Core.FieldName String
"arrayCreation")

data PrimaryNoNewArray = 
  PrimaryNoNewArrayLiteral Literal |
  PrimaryNoNewArrayClassLiteral ClassLiteral |
  PrimaryNoNewArrayThis  |
  PrimaryNoNewArrayDotThis TypeName |
  PrimaryNoNewArrayParens Expression |
  PrimaryNoNewArrayClassInstance ClassInstanceCreationExpression |
  PrimaryNoNewArrayFieldAccess FieldAccess |
  PrimaryNoNewArrayArrayAccess ArrayAccess |
  PrimaryNoNewArrayMethodInvocation MethodInvocation |
  PrimaryNoNewArrayMethodReference MethodReference
  deriving (PrimaryNoNewArray -> PrimaryNoNewArray -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PrimaryNoNewArray -> PrimaryNoNewArray -> Bool
$c/= :: PrimaryNoNewArray -> PrimaryNoNewArray -> Bool
== :: PrimaryNoNewArray -> PrimaryNoNewArray -> Bool
$c== :: PrimaryNoNewArray -> PrimaryNoNewArray -> Bool
Eq, Eq PrimaryNoNewArray
PrimaryNoNewArray -> PrimaryNoNewArray -> Bool
PrimaryNoNewArray -> PrimaryNoNewArray -> Ordering
PrimaryNoNewArray -> PrimaryNoNewArray -> PrimaryNoNewArray
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: PrimaryNoNewArray -> PrimaryNoNewArray -> PrimaryNoNewArray
$cmin :: PrimaryNoNewArray -> PrimaryNoNewArray -> PrimaryNoNewArray
max :: PrimaryNoNewArray -> PrimaryNoNewArray -> PrimaryNoNewArray
$cmax :: PrimaryNoNewArray -> PrimaryNoNewArray -> PrimaryNoNewArray
>= :: PrimaryNoNewArray -> PrimaryNoNewArray -> Bool
$c>= :: PrimaryNoNewArray -> PrimaryNoNewArray -> Bool
> :: PrimaryNoNewArray -> PrimaryNoNewArray -> Bool
$c> :: PrimaryNoNewArray -> PrimaryNoNewArray -> Bool
<= :: PrimaryNoNewArray -> PrimaryNoNewArray -> Bool
$c<= :: PrimaryNoNewArray -> PrimaryNoNewArray -> Bool
< :: PrimaryNoNewArray -> PrimaryNoNewArray -> Bool
$c< :: PrimaryNoNewArray -> PrimaryNoNewArray -> Bool
compare :: PrimaryNoNewArray -> PrimaryNoNewArray -> Ordering
$ccompare :: PrimaryNoNewArray -> PrimaryNoNewArray -> Ordering
Ord, ReadPrec [PrimaryNoNewArray]
ReadPrec PrimaryNoNewArray
Int -> ReadS PrimaryNoNewArray
ReadS [PrimaryNoNewArray]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [PrimaryNoNewArray]
$creadListPrec :: ReadPrec [PrimaryNoNewArray]
readPrec :: ReadPrec PrimaryNoNewArray
$creadPrec :: ReadPrec PrimaryNoNewArray
readList :: ReadS [PrimaryNoNewArray]
$creadList :: ReadS [PrimaryNoNewArray]
readsPrec :: Int -> ReadS PrimaryNoNewArray
$creadsPrec :: Int -> ReadS PrimaryNoNewArray
Read, Int -> PrimaryNoNewArray -> String -> String
[PrimaryNoNewArray] -> String -> String
PrimaryNoNewArray -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [PrimaryNoNewArray] -> String -> String
$cshowList :: [PrimaryNoNewArray] -> String -> String
show :: PrimaryNoNewArray -> String
$cshow :: PrimaryNoNewArray -> String
showsPrec :: Int -> PrimaryNoNewArray -> String -> String
$cshowsPrec :: Int -> PrimaryNoNewArray -> String -> String
Show)

_PrimaryNoNewArray :: Name
_PrimaryNoNewArray = (String -> Name
Core.Name String
"hydra/ext/java/syntax.PrimaryNoNewArray")

_PrimaryNoNewArray_literal :: FieldName
_PrimaryNoNewArray_literal = (String -> FieldName
Core.FieldName String
"literal")

_PrimaryNoNewArray_classLiteral :: FieldName
_PrimaryNoNewArray_classLiteral = (String -> FieldName
Core.FieldName String
"classLiteral")

_PrimaryNoNewArray_this :: FieldName
_PrimaryNoNewArray_this = (String -> FieldName
Core.FieldName String
"this")

_PrimaryNoNewArray_dotThis :: FieldName
_PrimaryNoNewArray_dotThis = (String -> FieldName
Core.FieldName String
"dotThis")

_PrimaryNoNewArray_parens :: FieldName
_PrimaryNoNewArray_parens = (String -> FieldName
Core.FieldName String
"parens")

_PrimaryNoNewArray_classInstance :: FieldName
_PrimaryNoNewArray_classInstance = (String -> FieldName
Core.FieldName String
"classInstance")

_PrimaryNoNewArray_fieldAccess :: FieldName
_PrimaryNoNewArray_fieldAccess = (String -> FieldName
Core.FieldName String
"fieldAccess")

_PrimaryNoNewArray_arrayAccess :: FieldName
_PrimaryNoNewArray_arrayAccess = (String -> FieldName
Core.FieldName String
"arrayAccess")

_PrimaryNoNewArray_methodInvocation :: FieldName
_PrimaryNoNewArray_methodInvocation = (String -> FieldName
Core.FieldName String
"methodInvocation")

_PrimaryNoNewArray_methodReference :: FieldName
_PrimaryNoNewArray_methodReference = (String -> FieldName
Core.FieldName String
"methodReference")

data ClassLiteral = 
  ClassLiteralType TypeNameArray |
  ClassLiteralNumericType NumericTypeArray |
  ClassLiteralBoolean BooleanArray |
  ClassLiteralVoid 
  deriving (ClassLiteral -> ClassLiteral -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ClassLiteral -> ClassLiteral -> Bool
$c/= :: ClassLiteral -> ClassLiteral -> Bool
== :: ClassLiteral -> ClassLiteral -> Bool
$c== :: ClassLiteral -> ClassLiteral -> Bool
Eq, Eq ClassLiteral
ClassLiteral -> ClassLiteral -> Bool
ClassLiteral -> ClassLiteral -> Ordering
ClassLiteral -> ClassLiteral -> ClassLiteral
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ClassLiteral -> ClassLiteral -> ClassLiteral
$cmin :: ClassLiteral -> ClassLiteral -> ClassLiteral
max :: ClassLiteral -> ClassLiteral -> ClassLiteral
$cmax :: ClassLiteral -> ClassLiteral -> ClassLiteral
>= :: ClassLiteral -> ClassLiteral -> Bool
$c>= :: ClassLiteral -> ClassLiteral -> Bool
> :: ClassLiteral -> ClassLiteral -> Bool
$c> :: ClassLiteral -> ClassLiteral -> Bool
<= :: ClassLiteral -> ClassLiteral -> Bool
$c<= :: ClassLiteral -> ClassLiteral -> Bool
< :: ClassLiteral -> ClassLiteral -> Bool
$c< :: ClassLiteral -> ClassLiteral -> Bool
compare :: ClassLiteral -> ClassLiteral -> Ordering
$ccompare :: ClassLiteral -> ClassLiteral -> Ordering
Ord, ReadPrec [ClassLiteral]
ReadPrec ClassLiteral
Int -> ReadS ClassLiteral
ReadS [ClassLiteral]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ClassLiteral]
$creadListPrec :: ReadPrec [ClassLiteral]
readPrec :: ReadPrec ClassLiteral
$creadPrec :: ReadPrec ClassLiteral
readList :: ReadS [ClassLiteral]
$creadList :: ReadS [ClassLiteral]
readsPrec :: Int -> ReadS ClassLiteral
$creadsPrec :: Int -> ReadS ClassLiteral
Read, Int -> ClassLiteral -> String -> String
[ClassLiteral] -> String -> String
ClassLiteral -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ClassLiteral] -> String -> String
$cshowList :: [ClassLiteral] -> String -> String
show :: ClassLiteral -> String
$cshow :: ClassLiteral -> String
showsPrec :: Int -> ClassLiteral -> String -> String
$cshowsPrec :: Int -> ClassLiteral -> String -> String
Show)

_ClassLiteral :: Name
_ClassLiteral = (String -> Name
Core.Name String
"hydra/ext/java/syntax.ClassLiteral")

_ClassLiteral_type :: FieldName
_ClassLiteral_type = (String -> FieldName
Core.FieldName String
"type")

_ClassLiteral_numericType :: FieldName
_ClassLiteral_numericType = (String -> FieldName
Core.FieldName String
"numericType")

_ClassLiteral_boolean :: FieldName
_ClassLiteral_boolean = (String -> FieldName
Core.FieldName String
"boolean")

_ClassLiteral_void :: FieldName
_ClassLiteral_void = (String -> FieldName
Core.FieldName String
"void")

data TypeNameArray = 
  TypeNameArraySimple TypeName |
  TypeNameArrayArray TypeNameArray
  deriving (TypeNameArray -> TypeNameArray -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TypeNameArray -> TypeNameArray -> Bool
$c/= :: TypeNameArray -> TypeNameArray -> Bool
== :: TypeNameArray -> TypeNameArray -> Bool
$c== :: TypeNameArray -> TypeNameArray -> Bool
Eq, Eq TypeNameArray
TypeNameArray -> TypeNameArray -> Bool
TypeNameArray -> TypeNameArray -> Ordering
TypeNameArray -> TypeNameArray -> TypeNameArray
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: TypeNameArray -> TypeNameArray -> TypeNameArray
$cmin :: TypeNameArray -> TypeNameArray -> TypeNameArray
max :: TypeNameArray -> TypeNameArray -> TypeNameArray
$cmax :: TypeNameArray -> TypeNameArray -> TypeNameArray
>= :: TypeNameArray -> TypeNameArray -> Bool
$c>= :: TypeNameArray -> TypeNameArray -> Bool
> :: TypeNameArray -> TypeNameArray -> Bool
$c> :: TypeNameArray -> TypeNameArray -> Bool
<= :: TypeNameArray -> TypeNameArray -> Bool
$c<= :: TypeNameArray -> TypeNameArray -> Bool
< :: TypeNameArray -> TypeNameArray -> Bool
$c< :: TypeNameArray -> TypeNameArray -> Bool
compare :: TypeNameArray -> TypeNameArray -> Ordering
$ccompare :: TypeNameArray -> TypeNameArray -> Ordering
Ord, ReadPrec [TypeNameArray]
ReadPrec TypeNameArray
Int -> ReadS TypeNameArray
ReadS [TypeNameArray]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [TypeNameArray]
$creadListPrec :: ReadPrec [TypeNameArray]
readPrec :: ReadPrec TypeNameArray
$creadPrec :: ReadPrec TypeNameArray
readList :: ReadS [TypeNameArray]
$creadList :: ReadS [TypeNameArray]
readsPrec :: Int -> ReadS TypeNameArray
$creadsPrec :: Int -> ReadS TypeNameArray
Read, Int -> TypeNameArray -> String -> String
[TypeNameArray] -> String -> String
TypeNameArray -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [TypeNameArray] -> String -> String
$cshowList :: [TypeNameArray] -> String -> String
show :: TypeNameArray -> String
$cshow :: TypeNameArray -> String
showsPrec :: Int -> TypeNameArray -> String -> String
$cshowsPrec :: Int -> TypeNameArray -> String -> String
Show)

_TypeNameArray :: Name
_TypeNameArray = (String -> Name
Core.Name String
"hydra/ext/java/syntax.TypeNameArray")

_TypeNameArray_simple :: FieldName
_TypeNameArray_simple = (String -> FieldName
Core.FieldName String
"simple")

_TypeNameArray_array :: FieldName
_TypeNameArray_array = (String -> FieldName
Core.FieldName String
"array")

data NumericTypeArray = 
  NumericTypeArraySimple NumericType |
  NumericTypeArrayArray NumericTypeArray
  deriving (NumericTypeArray -> NumericTypeArray -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NumericTypeArray -> NumericTypeArray -> Bool
$c/= :: NumericTypeArray -> NumericTypeArray -> Bool
== :: NumericTypeArray -> NumericTypeArray -> Bool
$c== :: NumericTypeArray -> NumericTypeArray -> Bool
Eq, Eq NumericTypeArray
NumericTypeArray -> NumericTypeArray -> Bool
NumericTypeArray -> NumericTypeArray -> Ordering
NumericTypeArray -> NumericTypeArray -> NumericTypeArray
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: NumericTypeArray -> NumericTypeArray -> NumericTypeArray
$cmin :: NumericTypeArray -> NumericTypeArray -> NumericTypeArray
max :: NumericTypeArray -> NumericTypeArray -> NumericTypeArray
$cmax :: NumericTypeArray -> NumericTypeArray -> NumericTypeArray
>= :: NumericTypeArray -> NumericTypeArray -> Bool
$c>= :: NumericTypeArray -> NumericTypeArray -> Bool
> :: NumericTypeArray -> NumericTypeArray -> Bool
$c> :: NumericTypeArray -> NumericTypeArray -> Bool
<= :: NumericTypeArray -> NumericTypeArray -> Bool
$c<= :: NumericTypeArray -> NumericTypeArray -> Bool
< :: NumericTypeArray -> NumericTypeArray -> Bool
$c< :: NumericTypeArray -> NumericTypeArray -> Bool
compare :: NumericTypeArray -> NumericTypeArray -> Ordering
$ccompare :: NumericTypeArray -> NumericTypeArray -> Ordering
Ord, ReadPrec [NumericTypeArray]
ReadPrec NumericTypeArray
Int -> ReadS NumericTypeArray
ReadS [NumericTypeArray]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [NumericTypeArray]
$creadListPrec :: ReadPrec [NumericTypeArray]
readPrec :: ReadPrec NumericTypeArray
$creadPrec :: ReadPrec NumericTypeArray
readList :: ReadS [NumericTypeArray]
$creadList :: ReadS [NumericTypeArray]
readsPrec :: Int -> ReadS NumericTypeArray
$creadsPrec :: Int -> ReadS NumericTypeArray
Read, Int -> NumericTypeArray -> String -> String
[NumericTypeArray] -> String -> String
NumericTypeArray -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [NumericTypeArray] -> String -> String
$cshowList :: [NumericTypeArray] -> String -> String
show :: NumericTypeArray -> String
$cshow :: NumericTypeArray -> String
showsPrec :: Int -> NumericTypeArray -> String -> String
$cshowsPrec :: Int -> NumericTypeArray -> String -> String
Show)

_NumericTypeArray :: Name
_NumericTypeArray = (String -> Name
Core.Name String
"hydra/ext/java/syntax.NumericTypeArray")

_NumericTypeArray_simple :: FieldName
_NumericTypeArray_simple = (String -> FieldName
Core.FieldName String
"simple")

_NumericTypeArray_array :: FieldName
_NumericTypeArray_array = (String -> FieldName
Core.FieldName String
"array")

data BooleanArray = 
  BooleanArraySimple  |
  BooleanArrayArray BooleanArray
  deriving (BooleanArray -> BooleanArray -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BooleanArray -> BooleanArray -> Bool
$c/= :: BooleanArray -> BooleanArray -> Bool
== :: BooleanArray -> BooleanArray -> Bool
$c== :: BooleanArray -> BooleanArray -> Bool
Eq, Eq BooleanArray
BooleanArray -> BooleanArray -> Bool
BooleanArray -> BooleanArray -> Ordering
BooleanArray -> BooleanArray -> BooleanArray
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: BooleanArray -> BooleanArray -> BooleanArray
$cmin :: BooleanArray -> BooleanArray -> BooleanArray
max :: BooleanArray -> BooleanArray -> BooleanArray
$cmax :: BooleanArray -> BooleanArray -> BooleanArray
>= :: BooleanArray -> BooleanArray -> Bool
$c>= :: BooleanArray -> BooleanArray -> Bool
> :: BooleanArray -> BooleanArray -> Bool
$c> :: BooleanArray -> BooleanArray -> Bool
<= :: BooleanArray -> BooleanArray -> Bool
$c<= :: BooleanArray -> BooleanArray -> Bool
< :: BooleanArray -> BooleanArray -> Bool
$c< :: BooleanArray -> BooleanArray -> Bool
compare :: BooleanArray -> BooleanArray -> Ordering
$ccompare :: BooleanArray -> BooleanArray -> Ordering
Ord, ReadPrec [BooleanArray]
ReadPrec BooleanArray
Int -> ReadS BooleanArray
ReadS [BooleanArray]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [BooleanArray]
$creadListPrec :: ReadPrec [BooleanArray]
readPrec :: ReadPrec BooleanArray
$creadPrec :: ReadPrec BooleanArray
readList :: ReadS [BooleanArray]
$creadList :: ReadS [BooleanArray]
readsPrec :: Int -> ReadS BooleanArray
$creadsPrec :: Int -> ReadS BooleanArray
Read, Int -> BooleanArray -> String -> String
[BooleanArray] -> String -> String
BooleanArray -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [BooleanArray] -> String -> String
$cshowList :: [BooleanArray] -> String -> String
show :: BooleanArray -> String
$cshow :: BooleanArray -> String
showsPrec :: Int -> BooleanArray -> String -> String
$cshowsPrec :: Int -> BooleanArray -> String -> String
Show)

_BooleanArray :: Name
_BooleanArray = (String -> Name
Core.Name String
"hydra/ext/java/syntax.BooleanArray")

_BooleanArray_simple :: FieldName
_BooleanArray_simple = (String -> FieldName
Core.FieldName String
"simple")

_BooleanArray_array :: FieldName
_BooleanArray_array = (String -> FieldName
Core.FieldName String
"array")

data ClassInstanceCreationExpression = 
  ClassInstanceCreationExpression {
    ClassInstanceCreationExpression
-> Maybe ClassInstanceCreationExpression_Qualifier
classInstanceCreationExpressionQualifier :: (Maybe ClassInstanceCreationExpression_Qualifier),
    ClassInstanceCreationExpression
-> UnqualifiedClassInstanceCreationExpression
classInstanceCreationExpressionExpression :: UnqualifiedClassInstanceCreationExpression}
  deriving (ClassInstanceCreationExpression
-> ClassInstanceCreationExpression -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ClassInstanceCreationExpression
-> ClassInstanceCreationExpression -> Bool
$c/= :: ClassInstanceCreationExpression
-> ClassInstanceCreationExpression -> Bool
== :: ClassInstanceCreationExpression
-> ClassInstanceCreationExpression -> Bool
$c== :: ClassInstanceCreationExpression
-> ClassInstanceCreationExpression -> Bool
Eq, Eq ClassInstanceCreationExpression
ClassInstanceCreationExpression
-> ClassInstanceCreationExpression -> Bool
ClassInstanceCreationExpression
-> ClassInstanceCreationExpression -> Ordering
ClassInstanceCreationExpression
-> ClassInstanceCreationExpression
-> ClassInstanceCreationExpression
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ClassInstanceCreationExpression
-> ClassInstanceCreationExpression
-> ClassInstanceCreationExpression
$cmin :: ClassInstanceCreationExpression
-> ClassInstanceCreationExpression
-> ClassInstanceCreationExpression
max :: ClassInstanceCreationExpression
-> ClassInstanceCreationExpression
-> ClassInstanceCreationExpression
$cmax :: ClassInstanceCreationExpression
-> ClassInstanceCreationExpression
-> ClassInstanceCreationExpression
>= :: ClassInstanceCreationExpression
-> ClassInstanceCreationExpression -> Bool
$c>= :: ClassInstanceCreationExpression
-> ClassInstanceCreationExpression -> Bool
> :: ClassInstanceCreationExpression
-> ClassInstanceCreationExpression -> Bool
$c> :: ClassInstanceCreationExpression
-> ClassInstanceCreationExpression -> Bool
<= :: ClassInstanceCreationExpression
-> ClassInstanceCreationExpression -> Bool
$c<= :: ClassInstanceCreationExpression
-> ClassInstanceCreationExpression -> Bool
< :: ClassInstanceCreationExpression
-> ClassInstanceCreationExpression -> Bool
$c< :: ClassInstanceCreationExpression
-> ClassInstanceCreationExpression -> Bool
compare :: ClassInstanceCreationExpression
-> ClassInstanceCreationExpression -> Ordering
$ccompare :: ClassInstanceCreationExpression
-> ClassInstanceCreationExpression -> Ordering
Ord, ReadPrec [ClassInstanceCreationExpression]
ReadPrec ClassInstanceCreationExpression
Int -> ReadS ClassInstanceCreationExpression
ReadS [ClassInstanceCreationExpression]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ClassInstanceCreationExpression]
$creadListPrec :: ReadPrec [ClassInstanceCreationExpression]
readPrec :: ReadPrec ClassInstanceCreationExpression
$creadPrec :: ReadPrec ClassInstanceCreationExpression
readList :: ReadS [ClassInstanceCreationExpression]
$creadList :: ReadS [ClassInstanceCreationExpression]
readsPrec :: Int -> ReadS ClassInstanceCreationExpression
$creadsPrec :: Int -> ReadS ClassInstanceCreationExpression
Read, Int -> ClassInstanceCreationExpression -> String -> String
[ClassInstanceCreationExpression] -> String -> String
ClassInstanceCreationExpression -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ClassInstanceCreationExpression] -> String -> String
$cshowList :: [ClassInstanceCreationExpression] -> String -> String
show :: ClassInstanceCreationExpression -> String
$cshow :: ClassInstanceCreationExpression -> String
showsPrec :: Int -> ClassInstanceCreationExpression -> String -> String
$cshowsPrec :: Int -> ClassInstanceCreationExpression -> String -> String
Show)

_ClassInstanceCreationExpression :: Name
_ClassInstanceCreationExpression = (String -> Name
Core.Name String
"hydra/ext/java/syntax.ClassInstanceCreationExpression")

_ClassInstanceCreationExpression_qualifier :: FieldName
_ClassInstanceCreationExpression_qualifier = (String -> FieldName
Core.FieldName String
"qualifier")

_ClassInstanceCreationExpression_expression :: FieldName
_ClassInstanceCreationExpression_expression = (String -> FieldName
Core.FieldName String
"expression")

data ClassInstanceCreationExpression_Qualifier = 
  ClassInstanceCreationExpression_QualifierExpression ExpressionName |
  ClassInstanceCreationExpression_QualifierPrimary Primary
  deriving (ClassInstanceCreationExpression_Qualifier
-> ClassInstanceCreationExpression_Qualifier -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ClassInstanceCreationExpression_Qualifier
-> ClassInstanceCreationExpression_Qualifier -> Bool
$c/= :: ClassInstanceCreationExpression_Qualifier
-> ClassInstanceCreationExpression_Qualifier -> Bool
== :: ClassInstanceCreationExpression_Qualifier
-> ClassInstanceCreationExpression_Qualifier -> Bool
$c== :: ClassInstanceCreationExpression_Qualifier
-> ClassInstanceCreationExpression_Qualifier -> Bool
Eq, Eq ClassInstanceCreationExpression_Qualifier
ClassInstanceCreationExpression_Qualifier
-> ClassInstanceCreationExpression_Qualifier -> Bool
ClassInstanceCreationExpression_Qualifier
-> ClassInstanceCreationExpression_Qualifier -> Ordering
ClassInstanceCreationExpression_Qualifier
-> ClassInstanceCreationExpression_Qualifier
-> ClassInstanceCreationExpression_Qualifier
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ClassInstanceCreationExpression_Qualifier
-> ClassInstanceCreationExpression_Qualifier
-> ClassInstanceCreationExpression_Qualifier
$cmin :: ClassInstanceCreationExpression_Qualifier
-> ClassInstanceCreationExpression_Qualifier
-> ClassInstanceCreationExpression_Qualifier
max :: ClassInstanceCreationExpression_Qualifier
-> ClassInstanceCreationExpression_Qualifier
-> ClassInstanceCreationExpression_Qualifier
$cmax :: ClassInstanceCreationExpression_Qualifier
-> ClassInstanceCreationExpression_Qualifier
-> ClassInstanceCreationExpression_Qualifier
>= :: ClassInstanceCreationExpression_Qualifier
-> ClassInstanceCreationExpression_Qualifier -> Bool
$c>= :: ClassInstanceCreationExpression_Qualifier
-> ClassInstanceCreationExpression_Qualifier -> Bool
> :: ClassInstanceCreationExpression_Qualifier
-> ClassInstanceCreationExpression_Qualifier -> Bool
$c> :: ClassInstanceCreationExpression_Qualifier
-> ClassInstanceCreationExpression_Qualifier -> Bool
<= :: ClassInstanceCreationExpression_Qualifier
-> ClassInstanceCreationExpression_Qualifier -> Bool
$c<= :: ClassInstanceCreationExpression_Qualifier
-> ClassInstanceCreationExpression_Qualifier -> Bool
< :: ClassInstanceCreationExpression_Qualifier
-> ClassInstanceCreationExpression_Qualifier -> Bool
$c< :: ClassInstanceCreationExpression_Qualifier
-> ClassInstanceCreationExpression_Qualifier -> Bool
compare :: ClassInstanceCreationExpression_Qualifier
-> ClassInstanceCreationExpression_Qualifier -> Ordering
$ccompare :: ClassInstanceCreationExpression_Qualifier
-> ClassInstanceCreationExpression_Qualifier -> Ordering
Ord, ReadPrec [ClassInstanceCreationExpression_Qualifier]
ReadPrec ClassInstanceCreationExpression_Qualifier
Int -> ReadS ClassInstanceCreationExpression_Qualifier
ReadS [ClassInstanceCreationExpression_Qualifier]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ClassInstanceCreationExpression_Qualifier]
$creadListPrec :: ReadPrec [ClassInstanceCreationExpression_Qualifier]
readPrec :: ReadPrec ClassInstanceCreationExpression_Qualifier
$creadPrec :: ReadPrec ClassInstanceCreationExpression_Qualifier
readList :: ReadS [ClassInstanceCreationExpression_Qualifier]
$creadList :: ReadS [ClassInstanceCreationExpression_Qualifier]
readsPrec :: Int -> ReadS ClassInstanceCreationExpression_Qualifier
$creadsPrec :: Int -> ReadS ClassInstanceCreationExpression_Qualifier
Read, Int
-> ClassInstanceCreationExpression_Qualifier -> String -> String
[ClassInstanceCreationExpression_Qualifier] -> String -> String
ClassInstanceCreationExpression_Qualifier -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ClassInstanceCreationExpression_Qualifier] -> String -> String
$cshowList :: [ClassInstanceCreationExpression_Qualifier] -> String -> String
show :: ClassInstanceCreationExpression_Qualifier -> String
$cshow :: ClassInstanceCreationExpression_Qualifier -> String
showsPrec :: Int
-> ClassInstanceCreationExpression_Qualifier -> String -> String
$cshowsPrec :: Int
-> ClassInstanceCreationExpression_Qualifier -> String -> String
Show)

_ClassInstanceCreationExpression_Qualifier :: Name
_ClassInstanceCreationExpression_Qualifier = (String -> Name
Core.Name String
"hydra/ext/java/syntax.ClassInstanceCreationExpression.Qualifier")

_ClassInstanceCreationExpression_Qualifier_expression :: FieldName
_ClassInstanceCreationExpression_Qualifier_expression = (String -> FieldName
Core.FieldName String
"expression")

_ClassInstanceCreationExpression_Qualifier_primary :: FieldName
_ClassInstanceCreationExpression_Qualifier_primary = (String -> FieldName
Core.FieldName String
"primary")

data UnqualifiedClassInstanceCreationExpression = 
  UnqualifiedClassInstanceCreationExpression {
    UnqualifiedClassInstanceCreationExpression -> [TypeArgument]
unqualifiedClassInstanceCreationExpressionTypeArguments :: [TypeArgument],
    UnqualifiedClassInstanceCreationExpression
-> ClassOrInterfaceTypeToInstantiate
unqualifiedClassInstanceCreationExpressionClassOrInterface :: ClassOrInterfaceTypeToInstantiate,
    UnqualifiedClassInstanceCreationExpression -> [Expression]
unqualifiedClassInstanceCreationExpressionArguments :: [Expression],
    UnqualifiedClassInstanceCreationExpression -> Maybe ClassBody
unqualifiedClassInstanceCreationExpressionBody :: (Maybe ClassBody)}
  deriving (UnqualifiedClassInstanceCreationExpression
-> UnqualifiedClassInstanceCreationExpression -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UnqualifiedClassInstanceCreationExpression
-> UnqualifiedClassInstanceCreationExpression -> Bool
$c/= :: UnqualifiedClassInstanceCreationExpression
-> UnqualifiedClassInstanceCreationExpression -> Bool
== :: UnqualifiedClassInstanceCreationExpression
-> UnqualifiedClassInstanceCreationExpression -> Bool
$c== :: UnqualifiedClassInstanceCreationExpression
-> UnqualifiedClassInstanceCreationExpression -> Bool
Eq, Eq UnqualifiedClassInstanceCreationExpression
UnqualifiedClassInstanceCreationExpression
-> UnqualifiedClassInstanceCreationExpression -> Bool
UnqualifiedClassInstanceCreationExpression
-> UnqualifiedClassInstanceCreationExpression -> Ordering
UnqualifiedClassInstanceCreationExpression
-> UnqualifiedClassInstanceCreationExpression
-> UnqualifiedClassInstanceCreationExpression
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: UnqualifiedClassInstanceCreationExpression
-> UnqualifiedClassInstanceCreationExpression
-> UnqualifiedClassInstanceCreationExpression
$cmin :: UnqualifiedClassInstanceCreationExpression
-> UnqualifiedClassInstanceCreationExpression
-> UnqualifiedClassInstanceCreationExpression
max :: UnqualifiedClassInstanceCreationExpression
-> UnqualifiedClassInstanceCreationExpression
-> UnqualifiedClassInstanceCreationExpression
$cmax :: UnqualifiedClassInstanceCreationExpression
-> UnqualifiedClassInstanceCreationExpression
-> UnqualifiedClassInstanceCreationExpression
>= :: UnqualifiedClassInstanceCreationExpression
-> UnqualifiedClassInstanceCreationExpression -> Bool
$c>= :: UnqualifiedClassInstanceCreationExpression
-> UnqualifiedClassInstanceCreationExpression -> Bool
> :: UnqualifiedClassInstanceCreationExpression
-> UnqualifiedClassInstanceCreationExpression -> Bool
$c> :: UnqualifiedClassInstanceCreationExpression
-> UnqualifiedClassInstanceCreationExpression -> Bool
<= :: UnqualifiedClassInstanceCreationExpression
-> UnqualifiedClassInstanceCreationExpression -> Bool
$c<= :: UnqualifiedClassInstanceCreationExpression
-> UnqualifiedClassInstanceCreationExpression -> Bool
< :: UnqualifiedClassInstanceCreationExpression
-> UnqualifiedClassInstanceCreationExpression -> Bool
$c< :: UnqualifiedClassInstanceCreationExpression
-> UnqualifiedClassInstanceCreationExpression -> Bool
compare :: UnqualifiedClassInstanceCreationExpression
-> UnqualifiedClassInstanceCreationExpression -> Ordering
$ccompare :: UnqualifiedClassInstanceCreationExpression
-> UnqualifiedClassInstanceCreationExpression -> Ordering
Ord, ReadPrec [UnqualifiedClassInstanceCreationExpression]
ReadPrec UnqualifiedClassInstanceCreationExpression
Int -> ReadS UnqualifiedClassInstanceCreationExpression
ReadS [UnqualifiedClassInstanceCreationExpression]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UnqualifiedClassInstanceCreationExpression]
$creadListPrec :: ReadPrec [UnqualifiedClassInstanceCreationExpression]
readPrec :: ReadPrec UnqualifiedClassInstanceCreationExpression
$creadPrec :: ReadPrec UnqualifiedClassInstanceCreationExpression
readList :: ReadS [UnqualifiedClassInstanceCreationExpression]
$creadList :: ReadS [UnqualifiedClassInstanceCreationExpression]
readsPrec :: Int -> ReadS UnqualifiedClassInstanceCreationExpression
$creadsPrec :: Int -> ReadS UnqualifiedClassInstanceCreationExpression
Read, Int
-> UnqualifiedClassInstanceCreationExpression -> String -> String
[UnqualifiedClassInstanceCreationExpression] -> String -> String
UnqualifiedClassInstanceCreationExpression -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [UnqualifiedClassInstanceCreationExpression] -> String -> String
$cshowList :: [UnqualifiedClassInstanceCreationExpression] -> String -> String
show :: UnqualifiedClassInstanceCreationExpression -> String
$cshow :: UnqualifiedClassInstanceCreationExpression -> String
showsPrec :: Int
-> UnqualifiedClassInstanceCreationExpression -> String -> String
$cshowsPrec :: Int
-> UnqualifiedClassInstanceCreationExpression -> String -> String
Show)

_UnqualifiedClassInstanceCreationExpression :: Name
_UnqualifiedClassInstanceCreationExpression = (String -> Name
Core.Name String
"hydra/ext/java/syntax.UnqualifiedClassInstanceCreationExpression")

_UnqualifiedClassInstanceCreationExpression_typeArguments :: FieldName
_UnqualifiedClassInstanceCreationExpression_typeArguments = (String -> FieldName
Core.FieldName String
"typeArguments")

_UnqualifiedClassInstanceCreationExpression_classOrInterface :: FieldName
_UnqualifiedClassInstanceCreationExpression_classOrInterface = (String -> FieldName
Core.FieldName String
"classOrInterface")

_UnqualifiedClassInstanceCreationExpression_arguments :: FieldName
_UnqualifiedClassInstanceCreationExpression_arguments = (String -> FieldName
Core.FieldName String
"arguments")

_UnqualifiedClassInstanceCreationExpression_body :: FieldName
_UnqualifiedClassInstanceCreationExpression_body = (String -> FieldName
Core.FieldName String
"body")

data ClassOrInterfaceTypeToInstantiate = 
  ClassOrInterfaceTypeToInstantiate {
    ClassOrInterfaceTypeToInstantiate -> [AnnotatedIdentifier]
classOrInterfaceTypeToInstantiateIdentifiers :: [AnnotatedIdentifier],
    ClassOrInterfaceTypeToInstantiate -> Maybe TypeArgumentsOrDiamond
classOrInterfaceTypeToInstantiateTypeArguments :: (Maybe TypeArgumentsOrDiamond)}
  deriving (ClassOrInterfaceTypeToInstantiate
-> ClassOrInterfaceTypeToInstantiate -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ClassOrInterfaceTypeToInstantiate
-> ClassOrInterfaceTypeToInstantiate -> Bool
$c/= :: ClassOrInterfaceTypeToInstantiate
-> ClassOrInterfaceTypeToInstantiate -> Bool
== :: ClassOrInterfaceTypeToInstantiate
-> ClassOrInterfaceTypeToInstantiate -> Bool
$c== :: ClassOrInterfaceTypeToInstantiate
-> ClassOrInterfaceTypeToInstantiate -> Bool
Eq, Eq ClassOrInterfaceTypeToInstantiate
ClassOrInterfaceTypeToInstantiate
-> ClassOrInterfaceTypeToInstantiate -> Bool
ClassOrInterfaceTypeToInstantiate
-> ClassOrInterfaceTypeToInstantiate -> Ordering
ClassOrInterfaceTypeToInstantiate
-> ClassOrInterfaceTypeToInstantiate
-> ClassOrInterfaceTypeToInstantiate
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ClassOrInterfaceTypeToInstantiate
-> ClassOrInterfaceTypeToInstantiate
-> ClassOrInterfaceTypeToInstantiate
$cmin :: ClassOrInterfaceTypeToInstantiate
-> ClassOrInterfaceTypeToInstantiate
-> ClassOrInterfaceTypeToInstantiate
max :: ClassOrInterfaceTypeToInstantiate
-> ClassOrInterfaceTypeToInstantiate
-> ClassOrInterfaceTypeToInstantiate
$cmax :: ClassOrInterfaceTypeToInstantiate
-> ClassOrInterfaceTypeToInstantiate
-> ClassOrInterfaceTypeToInstantiate
>= :: ClassOrInterfaceTypeToInstantiate
-> ClassOrInterfaceTypeToInstantiate -> Bool
$c>= :: ClassOrInterfaceTypeToInstantiate
-> ClassOrInterfaceTypeToInstantiate -> Bool
> :: ClassOrInterfaceTypeToInstantiate
-> ClassOrInterfaceTypeToInstantiate -> Bool
$c> :: ClassOrInterfaceTypeToInstantiate
-> ClassOrInterfaceTypeToInstantiate -> Bool
<= :: ClassOrInterfaceTypeToInstantiate
-> ClassOrInterfaceTypeToInstantiate -> Bool
$c<= :: ClassOrInterfaceTypeToInstantiate
-> ClassOrInterfaceTypeToInstantiate -> Bool
< :: ClassOrInterfaceTypeToInstantiate
-> ClassOrInterfaceTypeToInstantiate -> Bool
$c< :: ClassOrInterfaceTypeToInstantiate
-> ClassOrInterfaceTypeToInstantiate -> Bool
compare :: ClassOrInterfaceTypeToInstantiate
-> ClassOrInterfaceTypeToInstantiate -> Ordering
$ccompare :: ClassOrInterfaceTypeToInstantiate
-> ClassOrInterfaceTypeToInstantiate -> Ordering
Ord, ReadPrec [ClassOrInterfaceTypeToInstantiate]
ReadPrec ClassOrInterfaceTypeToInstantiate
Int -> ReadS ClassOrInterfaceTypeToInstantiate
ReadS [ClassOrInterfaceTypeToInstantiate]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ClassOrInterfaceTypeToInstantiate]
$creadListPrec :: ReadPrec [ClassOrInterfaceTypeToInstantiate]
readPrec :: ReadPrec ClassOrInterfaceTypeToInstantiate
$creadPrec :: ReadPrec ClassOrInterfaceTypeToInstantiate
readList :: ReadS [ClassOrInterfaceTypeToInstantiate]
$creadList :: ReadS [ClassOrInterfaceTypeToInstantiate]
readsPrec :: Int -> ReadS ClassOrInterfaceTypeToInstantiate
$creadsPrec :: Int -> ReadS ClassOrInterfaceTypeToInstantiate
Read, Int -> ClassOrInterfaceTypeToInstantiate -> String -> String
[ClassOrInterfaceTypeToInstantiate] -> String -> String
ClassOrInterfaceTypeToInstantiate -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ClassOrInterfaceTypeToInstantiate] -> String -> String
$cshowList :: [ClassOrInterfaceTypeToInstantiate] -> String -> String
show :: ClassOrInterfaceTypeToInstantiate -> String
$cshow :: ClassOrInterfaceTypeToInstantiate -> String
showsPrec :: Int -> ClassOrInterfaceTypeToInstantiate -> String -> String
$cshowsPrec :: Int -> ClassOrInterfaceTypeToInstantiate -> String -> String
Show)

_ClassOrInterfaceTypeToInstantiate :: Name
_ClassOrInterfaceTypeToInstantiate = (String -> Name
Core.Name String
"hydra/ext/java/syntax.ClassOrInterfaceTypeToInstantiate")

_ClassOrInterfaceTypeToInstantiate_identifiers :: FieldName
_ClassOrInterfaceTypeToInstantiate_identifiers = (String -> FieldName
Core.FieldName String
"identifiers")

_ClassOrInterfaceTypeToInstantiate_typeArguments :: FieldName
_ClassOrInterfaceTypeToInstantiate_typeArguments = (String -> FieldName
Core.FieldName String
"typeArguments")

data AnnotatedIdentifier = 
  AnnotatedIdentifier {
    AnnotatedIdentifier -> [Annotation]
annotatedIdentifierAnnotations :: [Annotation],
    AnnotatedIdentifier -> Identifier
annotatedIdentifierIdentifier :: Identifier}
  deriving (AnnotatedIdentifier -> AnnotatedIdentifier -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AnnotatedIdentifier -> AnnotatedIdentifier -> Bool
$c/= :: AnnotatedIdentifier -> AnnotatedIdentifier -> Bool
== :: AnnotatedIdentifier -> AnnotatedIdentifier -> Bool
$c== :: AnnotatedIdentifier -> AnnotatedIdentifier -> Bool
Eq, Eq AnnotatedIdentifier
AnnotatedIdentifier -> AnnotatedIdentifier -> Bool
AnnotatedIdentifier -> AnnotatedIdentifier -> Ordering
AnnotatedIdentifier -> AnnotatedIdentifier -> AnnotatedIdentifier
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: AnnotatedIdentifier -> AnnotatedIdentifier -> AnnotatedIdentifier
$cmin :: AnnotatedIdentifier -> AnnotatedIdentifier -> AnnotatedIdentifier
max :: AnnotatedIdentifier -> AnnotatedIdentifier -> AnnotatedIdentifier
$cmax :: AnnotatedIdentifier -> AnnotatedIdentifier -> AnnotatedIdentifier
>= :: AnnotatedIdentifier -> AnnotatedIdentifier -> Bool
$c>= :: AnnotatedIdentifier -> AnnotatedIdentifier -> Bool
> :: AnnotatedIdentifier -> AnnotatedIdentifier -> Bool
$c> :: AnnotatedIdentifier -> AnnotatedIdentifier -> Bool
<= :: AnnotatedIdentifier -> AnnotatedIdentifier -> Bool
$c<= :: AnnotatedIdentifier -> AnnotatedIdentifier -> Bool
< :: AnnotatedIdentifier -> AnnotatedIdentifier -> Bool
$c< :: AnnotatedIdentifier -> AnnotatedIdentifier -> Bool
compare :: AnnotatedIdentifier -> AnnotatedIdentifier -> Ordering
$ccompare :: AnnotatedIdentifier -> AnnotatedIdentifier -> Ordering
Ord, ReadPrec [AnnotatedIdentifier]
ReadPrec AnnotatedIdentifier
Int -> ReadS AnnotatedIdentifier
ReadS [AnnotatedIdentifier]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AnnotatedIdentifier]
$creadListPrec :: ReadPrec [AnnotatedIdentifier]
readPrec :: ReadPrec AnnotatedIdentifier
$creadPrec :: ReadPrec AnnotatedIdentifier
readList :: ReadS [AnnotatedIdentifier]
$creadList :: ReadS [AnnotatedIdentifier]
readsPrec :: Int -> ReadS AnnotatedIdentifier
$creadsPrec :: Int -> ReadS AnnotatedIdentifier
Read, Int -> AnnotatedIdentifier -> String -> String
[AnnotatedIdentifier] -> String -> String
AnnotatedIdentifier -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [AnnotatedIdentifier] -> String -> String
$cshowList :: [AnnotatedIdentifier] -> String -> String
show :: AnnotatedIdentifier -> String
$cshow :: AnnotatedIdentifier -> String
showsPrec :: Int -> AnnotatedIdentifier -> String -> String
$cshowsPrec :: Int -> AnnotatedIdentifier -> String -> String
Show)

_AnnotatedIdentifier :: Name
_AnnotatedIdentifier = (String -> Name
Core.Name String
"hydra/ext/java/syntax.AnnotatedIdentifier")

_AnnotatedIdentifier_annotations :: FieldName
_AnnotatedIdentifier_annotations = (String -> FieldName
Core.FieldName String
"annotations")

_AnnotatedIdentifier_identifier :: FieldName
_AnnotatedIdentifier_identifier = (String -> FieldName
Core.FieldName String
"identifier")

data TypeArgumentsOrDiamond = 
  TypeArgumentsOrDiamondArguments [TypeArgument] |
  TypeArgumentsOrDiamondDiamond 
  deriving (TypeArgumentsOrDiamond -> TypeArgumentsOrDiamond -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TypeArgumentsOrDiamond -> TypeArgumentsOrDiamond -> Bool
$c/= :: TypeArgumentsOrDiamond -> TypeArgumentsOrDiamond -> Bool
== :: TypeArgumentsOrDiamond -> TypeArgumentsOrDiamond -> Bool
$c== :: TypeArgumentsOrDiamond -> TypeArgumentsOrDiamond -> Bool
Eq, Eq TypeArgumentsOrDiamond
TypeArgumentsOrDiamond -> TypeArgumentsOrDiamond -> Bool
TypeArgumentsOrDiamond -> TypeArgumentsOrDiamond -> Ordering
TypeArgumentsOrDiamond
-> TypeArgumentsOrDiamond -> TypeArgumentsOrDiamond
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: TypeArgumentsOrDiamond
-> TypeArgumentsOrDiamond -> TypeArgumentsOrDiamond
$cmin :: TypeArgumentsOrDiamond
-> TypeArgumentsOrDiamond -> TypeArgumentsOrDiamond
max :: TypeArgumentsOrDiamond
-> TypeArgumentsOrDiamond -> TypeArgumentsOrDiamond
$cmax :: TypeArgumentsOrDiamond
-> TypeArgumentsOrDiamond -> TypeArgumentsOrDiamond
>= :: TypeArgumentsOrDiamond -> TypeArgumentsOrDiamond -> Bool
$c>= :: TypeArgumentsOrDiamond -> TypeArgumentsOrDiamond -> Bool
> :: TypeArgumentsOrDiamond -> TypeArgumentsOrDiamond -> Bool
$c> :: TypeArgumentsOrDiamond -> TypeArgumentsOrDiamond -> Bool
<= :: TypeArgumentsOrDiamond -> TypeArgumentsOrDiamond -> Bool
$c<= :: TypeArgumentsOrDiamond -> TypeArgumentsOrDiamond -> Bool
< :: TypeArgumentsOrDiamond -> TypeArgumentsOrDiamond -> Bool
$c< :: TypeArgumentsOrDiamond -> TypeArgumentsOrDiamond -> Bool
compare :: TypeArgumentsOrDiamond -> TypeArgumentsOrDiamond -> Ordering
$ccompare :: TypeArgumentsOrDiamond -> TypeArgumentsOrDiamond -> Ordering
Ord, ReadPrec [TypeArgumentsOrDiamond]
ReadPrec TypeArgumentsOrDiamond
Int -> ReadS TypeArgumentsOrDiamond
ReadS [TypeArgumentsOrDiamond]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [TypeArgumentsOrDiamond]
$creadListPrec :: ReadPrec [TypeArgumentsOrDiamond]
readPrec :: ReadPrec TypeArgumentsOrDiamond
$creadPrec :: ReadPrec TypeArgumentsOrDiamond
readList :: ReadS [TypeArgumentsOrDiamond]
$creadList :: ReadS [TypeArgumentsOrDiamond]
readsPrec :: Int -> ReadS TypeArgumentsOrDiamond
$creadsPrec :: Int -> ReadS TypeArgumentsOrDiamond
Read, Int -> TypeArgumentsOrDiamond -> String -> String
[TypeArgumentsOrDiamond] -> String -> String
TypeArgumentsOrDiamond -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [TypeArgumentsOrDiamond] -> String -> String
$cshowList :: [TypeArgumentsOrDiamond] -> String -> String
show :: TypeArgumentsOrDiamond -> String
$cshow :: TypeArgumentsOrDiamond -> String
showsPrec :: Int -> TypeArgumentsOrDiamond -> String -> String
$cshowsPrec :: Int -> TypeArgumentsOrDiamond -> String -> String
Show)

_TypeArgumentsOrDiamond :: Name
_TypeArgumentsOrDiamond = (String -> Name
Core.Name String
"hydra/ext/java/syntax.TypeArgumentsOrDiamond")

_TypeArgumentsOrDiamond_arguments :: FieldName
_TypeArgumentsOrDiamond_arguments = (String -> FieldName
Core.FieldName String
"arguments")

_TypeArgumentsOrDiamond_diamond :: FieldName
_TypeArgumentsOrDiamond_diamond = (String -> FieldName
Core.FieldName String
"diamond")

data FieldAccess = 
  FieldAccess {
    FieldAccess -> FieldAccess_Qualifier
fieldAccessQualifier :: FieldAccess_Qualifier,
    FieldAccess -> Identifier
fieldAccessIdentifier :: Identifier}
  deriving (FieldAccess -> FieldAccess -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FieldAccess -> FieldAccess -> Bool
$c/= :: FieldAccess -> FieldAccess -> Bool
== :: FieldAccess -> FieldAccess -> Bool
$c== :: FieldAccess -> FieldAccess -> Bool
Eq, Eq FieldAccess
FieldAccess -> FieldAccess -> Bool
FieldAccess -> FieldAccess -> Ordering
FieldAccess -> FieldAccess -> FieldAccess
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: FieldAccess -> FieldAccess -> FieldAccess
$cmin :: FieldAccess -> FieldAccess -> FieldAccess
max :: FieldAccess -> FieldAccess -> FieldAccess
$cmax :: FieldAccess -> FieldAccess -> FieldAccess
>= :: FieldAccess -> FieldAccess -> Bool
$c>= :: FieldAccess -> FieldAccess -> Bool
> :: FieldAccess -> FieldAccess -> Bool
$c> :: FieldAccess -> FieldAccess -> Bool
<= :: FieldAccess -> FieldAccess -> Bool
$c<= :: FieldAccess -> FieldAccess -> Bool
< :: FieldAccess -> FieldAccess -> Bool
$c< :: FieldAccess -> FieldAccess -> Bool
compare :: FieldAccess -> FieldAccess -> Ordering
$ccompare :: FieldAccess -> FieldAccess -> Ordering
Ord, ReadPrec [FieldAccess]
ReadPrec FieldAccess
Int -> ReadS FieldAccess
ReadS [FieldAccess]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [FieldAccess]
$creadListPrec :: ReadPrec [FieldAccess]
readPrec :: ReadPrec FieldAccess
$creadPrec :: ReadPrec FieldAccess
readList :: ReadS [FieldAccess]
$creadList :: ReadS [FieldAccess]
readsPrec :: Int -> ReadS FieldAccess
$creadsPrec :: Int -> ReadS FieldAccess
Read, Int -> FieldAccess -> String -> String
[FieldAccess] -> String -> String
FieldAccess -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [FieldAccess] -> String -> String
$cshowList :: [FieldAccess] -> String -> String
show :: FieldAccess -> String
$cshow :: FieldAccess -> String
showsPrec :: Int -> FieldAccess -> String -> String
$cshowsPrec :: Int -> FieldAccess -> String -> String
Show)

_FieldAccess :: Name
_FieldAccess = (String -> Name
Core.Name String
"hydra/ext/java/syntax.FieldAccess")

_FieldAccess_qualifier :: FieldName
_FieldAccess_qualifier = (String -> FieldName
Core.FieldName String
"qualifier")

_FieldAccess_identifier :: FieldName
_FieldAccess_identifier = (String -> FieldName
Core.FieldName String
"identifier")

data FieldAccess_Qualifier = 
  FieldAccess_QualifierPrimary Primary |
  FieldAccess_QualifierSuper  |
  FieldAccess_QualifierTyped TypeName
  deriving (FieldAccess_Qualifier -> FieldAccess_Qualifier -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FieldAccess_Qualifier -> FieldAccess_Qualifier -> Bool
$c/= :: FieldAccess_Qualifier -> FieldAccess_Qualifier -> Bool
== :: FieldAccess_Qualifier -> FieldAccess_Qualifier -> Bool
$c== :: FieldAccess_Qualifier -> FieldAccess_Qualifier -> Bool
Eq, Eq FieldAccess_Qualifier
FieldAccess_Qualifier -> FieldAccess_Qualifier -> Bool
FieldAccess_Qualifier -> FieldAccess_Qualifier -> Ordering
FieldAccess_Qualifier
-> FieldAccess_Qualifier -> FieldAccess_Qualifier
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: FieldAccess_Qualifier
-> FieldAccess_Qualifier -> FieldAccess_Qualifier
$cmin :: FieldAccess_Qualifier
-> FieldAccess_Qualifier -> FieldAccess_Qualifier
max :: FieldAccess_Qualifier
-> FieldAccess_Qualifier -> FieldAccess_Qualifier
$cmax :: FieldAccess_Qualifier
-> FieldAccess_Qualifier -> FieldAccess_Qualifier
>= :: FieldAccess_Qualifier -> FieldAccess_Qualifier -> Bool
$c>= :: FieldAccess_Qualifier -> FieldAccess_Qualifier -> Bool
> :: FieldAccess_Qualifier -> FieldAccess_Qualifier -> Bool
$c> :: FieldAccess_Qualifier -> FieldAccess_Qualifier -> Bool
<= :: FieldAccess_Qualifier -> FieldAccess_Qualifier -> Bool
$c<= :: FieldAccess_Qualifier -> FieldAccess_Qualifier -> Bool
< :: FieldAccess_Qualifier -> FieldAccess_Qualifier -> Bool
$c< :: FieldAccess_Qualifier -> FieldAccess_Qualifier -> Bool
compare :: FieldAccess_Qualifier -> FieldAccess_Qualifier -> Ordering
$ccompare :: FieldAccess_Qualifier -> FieldAccess_Qualifier -> Ordering
Ord, ReadPrec [FieldAccess_Qualifier]
ReadPrec FieldAccess_Qualifier
Int -> ReadS FieldAccess_Qualifier
ReadS [FieldAccess_Qualifier]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [FieldAccess_Qualifier]
$creadListPrec :: ReadPrec [FieldAccess_Qualifier]
readPrec :: ReadPrec FieldAccess_Qualifier
$creadPrec :: ReadPrec FieldAccess_Qualifier
readList :: ReadS [FieldAccess_Qualifier]
$creadList :: ReadS [FieldAccess_Qualifier]
readsPrec :: Int -> ReadS FieldAccess_Qualifier
$creadsPrec :: Int -> ReadS FieldAccess_Qualifier
Read, Int -> FieldAccess_Qualifier -> String -> String
[FieldAccess_Qualifier] -> String -> String
FieldAccess_Qualifier -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [FieldAccess_Qualifier] -> String -> String
$cshowList :: [FieldAccess_Qualifier] -> String -> String
show :: FieldAccess_Qualifier -> String
$cshow :: FieldAccess_Qualifier -> String
showsPrec :: Int -> FieldAccess_Qualifier -> String -> String
$cshowsPrec :: Int -> FieldAccess_Qualifier -> String -> String
Show)

_FieldAccess_Qualifier :: Name
_FieldAccess_Qualifier = (String -> Name
Core.Name String
"hydra/ext/java/syntax.FieldAccess.Qualifier")

_FieldAccess_Qualifier_primary :: FieldName
_FieldAccess_Qualifier_primary = (String -> FieldName
Core.FieldName String
"primary")

_FieldAccess_Qualifier_super :: FieldName
_FieldAccess_Qualifier_super = (String -> FieldName
Core.FieldName String
"super")

_FieldAccess_Qualifier_typed :: FieldName
_FieldAccess_Qualifier_typed = (String -> FieldName
Core.FieldName String
"typed")

data ArrayAccess = 
  ArrayAccess {
    ArrayAccess -> Maybe Expression
arrayAccessExpression :: (Maybe Expression),
    ArrayAccess -> ArrayAccess_Variant
arrayAccessVariant :: ArrayAccess_Variant}
  deriving (ArrayAccess -> ArrayAccess -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ArrayAccess -> ArrayAccess -> Bool
$c/= :: ArrayAccess -> ArrayAccess -> Bool
== :: ArrayAccess -> ArrayAccess -> Bool
$c== :: ArrayAccess -> ArrayAccess -> Bool
Eq, Eq ArrayAccess
ArrayAccess -> ArrayAccess -> Bool
ArrayAccess -> ArrayAccess -> Ordering
ArrayAccess -> ArrayAccess -> ArrayAccess
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ArrayAccess -> ArrayAccess -> ArrayAccess
$cmin :: ArrayAccess -> ArrayAccess -> ArrayAccess
max :: ArrayAccess -> ArrayAccess -> ArrayAccess
$cmax :: ArrayAccess -> ArrayAccess -> ArrayAccess
>= :: ArrayAccess -> ArrayAccess -> Bool
$c>= :: ArrayAccess -> ArrayAccess -> Bool
> :: ArrayAccess -> ArrayAccess -> Bool
$c> :: ArrayAccess -> ArrayAccess -> Bool
<= :: ArrayAccess -> ArrayAccess -> Bool
$c<= :: ArrayAccess -> ArrayAccess -> Bool
< :: ArrayAccess -> ArrayAccess -> Bool
$c< :: ArrayAccess -> ArrayAccess -> Bool
compare :: ArrayAccess -> ArrayAccess -> Ordering
$ccompare :: ArrayAccess -> ArrayAccess -> Ordering
Ord, ReadPrec [ArrayAccess]
ReadPrec ArrayAccess
Int -> ReadS ArrayAccess
ReadS [ArrayAccess]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ArrayAccess]
$creadListPrec :: ReadPrec [ArrayAccess]
readPrec :: ReadPrec ArrayAccess
$creadPrec :: ReadPrec ArrayAccess
readList :: ReadS [ArrayAccess]
$creadList :: ReadS [ArrayAccess]
readsPrec :: Int -> ReadS ArrayAccess
$creadsPrec :: Int -> ReadS ArrayAccess
Read, Int -> ArrayAccess -> String -> String
[ArrayAccess] -> String -> String
ArrayAccess -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ArrayAccess] -> String -> String
$cshowList :: [ArrayAccess] -> String -> String
show :: ArrayAccess -> String
$cshow :: ArrayAccess -> String
showsPrec :: Int -> ArrayAccess -> String -> String
$cshowsPrec :: Int -> ArrayAccess -> String -> String
Show)

_ArrayAccess :: Name
_ArrayAccess = (String -> Name
Core.Name String
"hydra/ext/java/syntax.ArrayAccess")

_ArrayAccess_expression :: FieldName
_ArrayAccess_expression = (String -> FieldName
Core.FieldName String
"expression")

_ArrayAccess_variant :: FieldName
_ArrayAccess_variant = (String -> FieldName
Core.FieldName String
"variant")

data ArrayAccess_Variant = 
  ArrayAccess_VariantName ExpressionName |
  ArrayAccess_VariantPrimary PrimaryNoNewArray
  deriving (ArrayAccess_Variant -> ArrayAccess_Variant -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ArrayAccess_Variant -> ArrayAccess_Variant -> Bool
$c/= :: ArrayAccess_Variant -> ArrayAccess_Variant -> Bool
== :: ArrayAccess_Variant -> ArrayAccess_Variant -> Bool
$c== :: ArrayAccess_Variant -> ArrayAccess_Variant -> Bool
Eq, Eq ArrayAccess_Variant
ArrayAccess_Variant -> ArrayAccess_Variant -> Bool
ArrayAccess_Variant -> ArrayAccess_Variant -> Ordering
ArrayAccess_Variant -> ArrayAccess_Variant -> ArrayAccess_Variant
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ArrayAccess_Variant -> ArrayAccess_Variant -> ArrayAccess_Variant
$cmin :: ArrayAccess_Variant -> ArrayAccess_Variant -> ArrayAccess_Variant
max :: ArrayAccess_Variant -> ArrayAccess_Variant -> ArrayAccess_Variant
$cmax :: ArrayAccess_Variant -> ArrayAccess_Variant -> ArrayAccess_Variant
>= :: ArrayAccess_Variant -> ArrayAccess_Variant -> Bool
$c>= :: ArrayAccess_Variant -> ArrayAccess_Variant -> Bool
> :: ArrayAccess_Variant -> ArrayAccess_Variant -> Bool
$c> :: ArrayAccess_Variant -> ArrayAccess_Variant -> Bool
<= :: ArrayAccess_Variant -> ArrayAccess_Variant -> Bool
$c<= :: ArrayAccess_Variant -> ArrayAccess_Variant -> Bool
< :: ArrayAccess_Variant -> ArrayAccess_Variant -> Bool
$c< :: ArrayAccess_Variant -> ArrayAccess_Variant -> Bool
compare :: ArrayAccess_Variant -> ArrayAccess_Variant -> Ordering
$ccompare :: ArrayAccess_Variant -> ArrayAccess_Variant -> Ordering
Ord, ReadPrec [ArrayAccess_Variant]
ReadPrec ArrayAccess_Variant
Int -> ReadS ArrayAccess_Variant
ReadS [ArrayAccess_Variant]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ArrayAccess_Variant]
$creadListPrec :: ReadPrec [ArrayAccess_Variant]
readPrec :: ReadPrec ArrayAccess_Variant
$creadPrec :: ReadPrec ArrayAccess_Variant
readList :: ReadS [ArrayAccess_Variant]
$creadList :: ReadS [ArrayAccess_Variant]
readsPrec :: Int -> ReadS ArrayAccess_Variant
$creadsPrec :: Int -> ReadS ArrayAccess_Variant
Read, Int -> ArrayAccess_Variant -> String -> String
[ArrayAccess_Variant] -> String -> String
ArrayAccess_Variant -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ArrayAccess_Variant] -> String -> String
$cshowList :: [ArrayAccess_Variant] -> String -> String
show :: ArrayAccess_Variant -> String
$cshow :: ArrayAccess_Variant -> String
showsPrec :: Int -> ArrayAccess_Variant -> String -> String
$cshowsPrec :: Int -> ArrayAccess_Variant -> String -> String
Show)

_ArrayAccess_Variant :: Name
_ArrayAccess_Variant = (String -> Name
Core.Name String
"hydra/ext/java/syntax.ArrayAccess.Variant")

_ArrayAccess_Variant_name :: FieldName
_ArrayAccess_Variant_name = (String -> FieldName
Core.FieldName String
"name")

_ArrayAccess_Variant_primary :: FieldName
_ArrayAccess_Variant_primary = (String -> FieldName
Core.FieldName String
"primary")

data MethodInvocation = 
  MethodInvocation {
    MethodInvocation -> MethodInvocation_Header
methodInvocationHeader :: MethodInvocation_Header,
    MethodInvocation -> [Expression]
methodInvocationArguments :: [Expression]}
  deriving (MethodInvocation -> MethodInvocation -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MethodInvocation -> MethodInvocation -> Bool
$c/= :: MethodInvocation -> MethodInvocation -> Bool
== :: MethodInvocation -> MethodInvocation -> Bool
$c== :: MethodInvocation -> MethodInvocation -> Bool
Eq, Eq MethodInvocation
MethodInvocation -> MethodInvocation -> Bool
MethodInvocation -> MethodInvocation -> Ordering
MethodInvocation -> MethodInvocation -> MethodInvocation
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: MethodInvocation -> MethodInvocation -> MethodInvocation
$cmin :: MethodInvocation -> MethodInvocation -> MethodInvocation
max :: MethodInvocation -> MethodInvocation -> MethodInvocation
$cmax :: MethodInvocation -> MethodInvocation -> MethodInvocation
>= :: MethodInvocation -> MethodInvocation -> Bool
$c>= :: MethodInvocation -> MethodInvocation -> Bool
> :: MethodInvocation -> MethodInvocation -> Bool
$c> :: MethodInvocation -> MethodInvocation -> Bool
<= :: MethodInvocation -> MethodInvocation -> Bool
$c<= :: MethodInvocation -> MethodInvocation -> Bool
< :: MethodInvocation -> MethodInvocation -> Bool
$c< :: MethodInvocation -> MethodInvocation -> Bool
compare :: MethodInvocation -> MethodInvocation -> Ordering
$ccompare :: MethodInvocation -> MethodInvocation -> Ordering
Ord, ReadPrec [MethodInvocation]
ReadPrec MethodInvocation
Int -> ReadS MethodInvocation
ReadS [MethodInvocation]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [MethodInvocation]
$creadListPrec :: ReadPrec [MethodInvocation]
readPrec :: ReadPrec MethodInvocation
$creadPrec :: ReadPrec MethodInvocation
readList :: ReadS [MethodInvocation]
$creadList :: ReadS [MethodInvocation]
readsPrec :: Int -> ReadS MethodInvocation
$creadsPrec :: Int -> ReadS MethodInvocation
Read, Int -> MethodInvocation -> String -> String
[MethodInvocation] -> String -> String
MethodInvocation -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [MethodInvocation] -> String -> String
$cshowList :: [MethodInvocation] -> String -> String
show :: MethodInvocation -> String
$cshow :: MethodInvocation -> String
showsPrec :: Int -> MethodInvocation -> String -> String
$cshowsPrec :: Int -> MethodInvocation -> String -> String
Show)

_MethodInvocation :: Name
_MethodInvocation = (String -> Name
Core.Name String
"hydra/ext/java/syntax.MethodInvocation")

_MethodInvocation_header :: FieldName
_MethodInvocation_header = (String -> FieldName
Core.FieldName String
"header")

_MethodInvocation_arguments :: FieldName
_MethodInvocation_arguments = (String -> FieldName
Core.FieldName String
"arguments")

data MethodInvocation_Header = 
  MethodInvocation_HeaderSimple MethodName |
  MethodInvocation_HeaderComplex MethodInvocation_Complex
  deriving (MethodInvocation_Header -> MethodInvocation_Header -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MethodInvocation_Header -> MethodInvocation_Header -> Bool
$c/= :: MethodInvocation_Header -> MethodInvocation_Header -> Bool
== :: MethodInvocation_Header -> MethodInvocation_Header -> Bool
$c== :: MethodInvocation_Header -> MethodInvocation_Header -> Bool
Eq, Eq MethodInvocation_Header
MethodInvocation_Header -> MethodInvocation_Header -> Bool
MethodInvocation_Header -> MethodInvocation_Header -> Ordering
MethodInvocation_Header
-> MethodInvocation_Header -> MethodInvocation_Header
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: MethodInvocation_Header
-> MethodInvocation_Header -> MethodInvocation_Header
$cmin :: MethodInvocation_Header
-> MethodInvocation_Header -> MethodInvocation_Header
max :: MethodInvocation_Header
-> MethodInvocation_Header -> MethodInvocation_Header
$cmax :: MethodInvocation_Header
-> MethodInvocation_Header -> MethodInvocation_Header
>= :: MethodInvocation_Header -> MethodInvocation_Header -> Bool
$c>= :: MethodInvocation_Header -> MethodInvocation_Header -> Bool
> :: MethodInvocation_Header -> MethodInvocation_Header -> Bool
$c> :: MethodInvocation_Header -> MethodInvocation_Header -> Bool
<= :: MethodInvocation_Header -> MethodInvocation_Header -> Bool
$c<= :: MethodInvocation_Header -> MethodInvocation_Header -> Bool
< :: MethodInvocation_Header -> MethodInvocation_Header -> Bool
$c< :: MethodInvocation_Header -> MethodInvocation_Header -> Bool
compare :: MethodInvocation_Header -> MethodInvocation_Header -> Ordering
$ccompare :: MethodInvocation_Header -> MethodInvocation_Header -> Ordering
Ord, ReadPrec [MethodInvocation_Header]
ReadPrec MethodInvocation_Header
Int -> ReadS MethodInvocation_Header
ReadS [MethodInvocation_Header]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [MethodInvocation_Header]
$creadListPrec :: ReadPrec [MethodInvocation_Header]
readPrec :: ReadPrec MethodInvocation_Header
$creadPrec :: ReadPrec MethodInvocation_Header
readList :: ReadS [MethodInvocation_Header]
$creadList :: ReadS [MethodInvocation_Header]
readsPrec :: Int -> ReadS MethodInvocation_Header
$creadsPrec :: Int -> ReadS MethodInvocation_Header
Read, Int -> MethodInvocation_Header -> String -> String
[MethodInvocation_Header] -> String -> String
MethodInvocation_Header -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [MethodInvocation_Header] -> String -> String
$cshowList :: [MethodInvocation_Header] -> String -> String
show :: MethodInvocation_Header -> String
$cshow :: MethodInvocation_Header -> String
showsPrec :: Int -> MethodInvocation_Header -> String -> String
$cshowsPrec :: Int -> MethodInvocation_Header -> String -> String
Show)

_MethodInvocation_Header :: Name
_MethodInvocation_Header = (String -> Name
Core.Name String
"hydra/ext/java/syntax.MethodInvocation.Header")

_MethodInvocation_Header_simple :: FieldName
_MethodInvocation_Header_simple = (String -> FieldName
Core.FieldName String
"simple")

_MethodInvocation_Header_complex :: FieldName
_MethodInvocation_Header_complex = (String -> FieldName
Core.FieldName String
"complex")

data MethodInvocation_Complex = 
  MethodInvocation_Complex {
    MethodInvocation_Complex -> MethodInvocation_Variant
methodInvocation_ComplexVariant :: MethodInvocation_Variant,
    MethodInvocation_Complex -> [TypeArgument]
methodInvocation_ComplexTypeArguments :: [TypeArgument],
    MethodInvocation_Complex -> Identifier
methodInvocation_ComplexIdentifier :: Identifier}
  deriving (MethodInvocation_Complex -> MethodInvocation_Complex -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MethodInvocation_Complex -> MethodInvocation_Complex -> Bool
$c/= :: MethodInvocation_Complex -> MethodInvocation_Complex -> Bool
== :: MethodInvocation_Complex -> MethodInvocation_Complex -> Bool
$c== :: MethodInvocation_Complex -> MethodInvocation_Complex -> Bool
Eq, Eq MethodInvocation_Complex
MethodInvocation_Complex -> MethodInvocation_Complex -> Bool
MethodInvocation_Complex -> MethodInvocation_Complex -> Ordering
MethodInvocation_Complex
-> MethodInvocation_Complex -> MethodInvocation_Complex
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: MethodInvocation_Complex
-> MethodInvocation_Complex -> MethodInvocation_Complex
$cmin :: MethodInvocation_Complex
-> MethodInvocation_Complex -> MethodInvocation_Complex
max :: MethodInvocation_Complex
-> MethodInvocation_Complex -> MethodInvocation_Complex
$cmax :: MethodInvocation_Complex
-> MethodInvocation_Complex -> MethodInvocation_Complex
>= :: MethodInvocation_Complex -> MethodInvocation_Complex -> Bool
$c>= :: MethodInvocation_Complex -> MethodInvocation_Complex -> Bool
> :: MethodInvocation_Complex -> MethodInvocation_Complex -> Bool
$c> :: MethodInvocation_Complex -> MethodInvocation_Complex -> Bool
<= :: MethodInvocation_Complex -> MethodInvocation_Complex -> Bool
$c<= :: MethodInvocation_Complex -> MethodInvocation_Complex -> Bool
< :: MethodInvocation_Complex -> MethodInvocation_Complex -> Bool
$c< :: MethodInvocation_Complex -> MethodInvocation_Complex -> Bool
compare :: MethodInvocation_Complex -> MethodInvocation_Complex -> Ordering
$ccompare :: MethodInvocation_Complex -> MethodInvocation_Complex -> Ordering
Ord, ReadPrec [MethodInvocation_Complex]
ReadPrec MethodInvocation_Complex
Int -> ReadS MethodInvocation_Complex
ReadS [MethodInvocation_Complex]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [MethodInvocation_Complex]
$creadListPrec :: ReadPrec [MethodInvocation_Complex]
readPrec :: ReadPrec MethodInvocation_Complex
$creadPrec :: ReadPrec MethodInvocation_Complex
readList :: ReadS [MethodInvocation_Complex]
$creadList :: ReadS [MethodInvocation_Complex]
readsPrec :: Int -> ReadS MethodInvocation_Complex
$creadsPrec :: Int -> ReadS MethodInvocation_Complex
Read, Int -> MethodInvocation_Complex -> String -> String
[MethodInvocation_Complex] -> String -> String
MethodInvocation_Complex -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [MethodInvocation_Complex] -> String -> String
$cshowList :: [MethodInvocation_Complex] -> String -> String
show :: MethodInvocation_Complex -> String
$cshow :: MethodInvocation_Complex -> String
showsPrec :: Int -> MethodInvocation_Complex -> String -> String
$cshowsPrec :: Int -> MethodInvocation_Complex -> String -> String
Show)

_MethodInvocation_Complex :: Name
_MethodInvocation_Complex = (String -> Name
Core.Name String
"hydra/ext/java/syntax.MethodInvocation.Complex")

_MethodInvocation_Complex_variant :: FieldName
_MethodInvocation_Complex_variant = (String -> FieldName
Core.FieldName String
"variant")

_MethodInvocation_Complex_typeArguments :: FieldName
_MethodInvocation_Complex_typeArguments = (String -> FieldName
Core.FieldName String
"typeArguments")

_MethodInvocation_Complex_identifier :: FieldName
_MethodInvocation_Complex_identifier = (String -> FieldName
Core.FieldName String
"identifier")

data MethodInvocation_Variant = 
  MethodInvocation_VariantType TypeName |
  MethodInvocation_VariantExpression ExpressionName |
  MethodInvocation_VariantPrimary Primary |
  MethodInvocation_VariantSuper  |
  MethodInvocation_VariantTypeSuper TypeName
  deriving (MethodInvocation_Variant -> MethodInvocation_Variant -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MethodInvocation_Variant -> MethodInvocation_Variant -> Bool
$c/= :: MethodInvocation_Variant -> MethodInvocation_Variant -> Bool
== :: MethodInvocation_Variant -> MethodInvocation_Variant -> Bool
$c== :: MethodInvocation_Variant -> MethodInvocation_Variant -> Bool
Eq, Eq MethodInvocation_Variant
MethodInvocation_Variant -> MethodInvocation_Variant -> Bool
MethodInvocation_Variant -> MethodInvocation_Variant -> Ordering
MethodInvocation_Variant
-> MethodInvocation_Variant -> MethodInvocation_Variant
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: MethodInvocation_Variant
-> MethodInvocation_Variant -> MethodInvocation_Variant
$cmin :: MethodInvocation_Variant
-> MethodInvocation_Variant -> MethodInvocation_Variant
max :: MethodInvocation_Variant
-> MethodInvocation_Variant -> MethodInvocation_Variant
$cmax :: MethodInvocation_Variant
-> MethodInvocation_Variant -> MethodInvocation_Variant
>= :: MethodInvocation_Variant -> MethodInvocation_Variant -> Bool
$c>= :: MethodInvocation_Variant -> MethodInvocation_Variant -> Bool
> :: MethodInvocation_Variant -> MethodInvocation_Variant -> Bool
$c> :: MethodInvocation_Variant -> MethodInvocation_Variant -> Bool
<= :: MethodInvocation_Variant -> MethodInvocation_Variant -> Bool
$c<= :: MethodInvocation_Variant -> MethodInvocation_Variant -> Bool
< :: MethodInvocation_Variant -> MethodInvocation_Variant -> Bool
$c< :: MethodInvocation_Variant -> MethodInvocation_Variant -> Bool
compare :: MethodInvocation_Variant -> MethodInvocation_Variant -> Ordering
$ccompare :: MethodInvocation_Variant -> MethodInvocation_Variant -> Ordering
Ord, ReadPrec [MethodInvocation_Variant]
ReadPrec MethodInvocation_Variant
Int -> ReadS MethodInvocation_Variant
ReadS [MethodInvocation_Variant]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [MethodInvocation_Variant]
$creadListPrec :: ReadPrec [MethodInvocation_Variant]
readPrec :: ReadPrec MethodInvocation_Variant
$creadPrec :: ReadPrec MethodInvocation_Variant
readList :: ReadS [MethodInvocation_Variant]
$creadList :: ReadS [MethodInvocation_Variant]
readsPrec :: Int -> ReadS MethodInvocation_Variant
$creadsPrec :: Int -> ReadS MethodInvocation_Variant
Read, Int -> MethodInvocation_Variant -> String -> String
[MethodInvocation_Variant] -> String -> String
MethodInvocation_Variant -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [MethodInvocation_Variant] -> String -> String
$cshowList :: [MethodInvocation_Variant] -> String -> String
show :: MethodInvocation_Variant -> String
$cshow :: MethodInvocation_Variant -> String
showsPrec :: Int -> MethodInvocation_Variant -> String -> String
$cshowsPrec :: Int -> MethodInvocation_Variant -> String -> String
Show)

_MethodInvocation_Variant :: Name
_MethodInvocation_Variant = (String -> Name
Core.Name String
"hydra/ext/java/syntax.MethodInvocation.Variant")

_MethodInvocation_Variant_type :: FieldName
_MethodInvocation_Variant_type = (String -> FieldName
Core.FieldName String
"type")

_MethodInvocation_Variant_expression :: FieldName
_MethodInvocation_Variant_expression = (String -> FieldName
Core.FieldName String
"expression")

_MethodInvocation_Variant_primary :: FieldName
_MethodInvocation_Variant_primary = (String -> FieldName
Core.FieldName String
"primary")

_MethodInvocation_Variant_super :: FieldName
_MethodInvocation_Variant_super = (String -> FieldName
Core.FieldName String
"super")

_MethodInvocation_Variant_typeSuper :: FieldName
_MethodInvocation_Variant_typeSuper = (String -> FieldName
Core.FieldName String
"typeSuper")

data MethodReference = 
  MethodReferenceExpression MethodReference_Expression |
  MethodReferencePrimary MethodReference_Primary |
  MethodReferenceReferenceType MethodReference_ReferenceType |
  MethodReferenceSuper MethodReference_Super |
  MethodReferenceNew MethodReference_New |
  MethodReferenceArray MethodReference_Array
  deriving (MethodReference -> MethodReference -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MethodReference -> MethodReference -> Bool
$c/= :: MethodReference -> MethodReference -> Bool
== :: MethodReference -> MethodReference -> Bool
$c== :: MethodReference -> MethodReference -> Bool
Eq, Eq MethodReference
MethodReference -> MethodReference -> Bool
MethodReference -> MethodReference -> Ordering
MethodReference -> MethodReference -> MethodReference
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: MethodReference -> MethodReference -> MethodReference
$cmin :: MethodReference -> MethodReference -> MethodReference
max :: MethodReference -> MethodReference -> MethodReference
$cmax :: MethodReference -> MethodReference -> MethodReference
>= :: MethodReference -> MethodReference -> Bool
$c>= :: MethodReference -> MethodReference -> Bool
> :: MethodReference -> MethodReference -> Bool
$c> :: MethodReference -> MethodReference -> Bool
<= :: MethodReference -> MethodReference -> Bool
$c<= :: MethodReference -> MethodReference -> Bool
< :: MethodReference -> MethodReference -> Bool
$c< :: MethodReference -> MethodReference -> Bool
compare :: MethodReference -> MethodReference -> Ordering
$ccompare :: MethodReference -> MethodReference -> Ordering
Ord, ReadPrec [MethodReference]
ReadPrec MethodReference
Int -> ReadS MethodReference
ReadS [MethodReference]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [MethodReference]
$creadListPrec :: ReadPrec [MethodReference]
readPrec :: ReadPrec MethodReference
$creadPrec :: ReadPrec MethodReference
readList :: ReadS [MethodReference]
$creadList :: ReadS [MethodReference]
readsPrec :: Int -> ReadS MethodReference
$creadsPrec :: Int -> ReadS MethodReference
Read, Int -> MethodReference -> String -> String
[MethodReference] -> String -> String
MethodReference -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [MethodReference] -> String -> String
$cshowList :: [MethodReference] -> String -> String
show :: MethodReference -> String
$cshow :: MethodReference -> String
showsPrec :: Int -> MethodReference -> String -> String
$cshowsPrec :: Int -> MethodReference -> String -> String
Show)

_MethodReference :: Name
_MethodReference = (String -> Name
Core.Name String
"hydra/ext/java/syntax.MethodReference")

_MethodReference_expression :: FieldName
_MethodReference_expression = (String -> FieldName
Core.FieldName String
"expression")

_MethodReference_primary :: FieldName
_MethodReference_primary = (String -> FieldName
Core.FieldName String
"primary")

_MethodReference_referenceType :: FieldName
_MethodReference_referenceType = (String -> FieldName
Core.FieldName String
"referenceType")

_MethodReference_super :: FieldName
_MethodReference_super = (String -> FieldName
Core.FieldName String
"super")

_MethodReference_new :: FieldName
_MethodReference_new = (String -> FieldName
Core.FieldName String
"new")

_MethodReference_array :: FieldName
_MethodReference_array = (String -> FieldName
Core.FieldName String
"array")

data MethodReference_Expression = 
  MethodReference_Expression {
    MethodReference_Expression -> ExpressionName
methodReference_ExpressionName :: ExpressionName,
    MethodReference_Expression -> [TypeArgument]
methodReference_ExpressionTypeArguments :: [TypeArgument],
    MethodReference_Expression -> Identifier
methodReference_ExpressionIdentifier :: Identifier}
  deriving (MethodReference_Expression -> MethodReference_Expression -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MethodReference_Expression -> MethodReference_Expression -> Bool
$c/= :: MethodReference_Expression -> MethodReference_Expression -> Bool
== :: MethodReference_Expression -> MethodReference_Expression -> Bool
$c== :: MethodReference_Expression -> MethodReference_Expression -> Bool
Eq, Eq MethodReference_Expression
MethodReference_Expression -> MethodReference_Expression -> Bool
MethodReference_Expression
-> MethodReference_Expression -> Ordering
MethodReference_Expression
-> MethodReference_Expression -> MethodReference_Expression
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: MethodReference_Expression
-> MethodReference_Expression -> MethodReference_Expression
$cmin :: MethodReference_Expression
-> MethodReference_Expression -> MethodReference_Expression
max :: MethodReference_Expression
-> MethodReference_Expression -> MethodReference_Expression
$cmax :: MethodReference_Expression
-> MethodReference_Expression -> MethodReference_Expression
>= :: MethodReference_Expression -> MethodReference_Expression -> Bool
$c>= :: MethodReference_Expression -> MethodReference_Expression -> Bool
> :: MethodReference_Expression -> MethodReference_Expression -> Bool
$c> :: MethodReference_Expression -> MethodReference_Expression -> Bool
<= :: MethodReference_Expression -> MethodReference_Expression -> Bool
$c<= :: MethodReference_Expression -> MethodReference_Expression -> Bool
< :: MethodReference_Expression -> MethodReference_Expression -> Bool
$c< :: MethodReference_Expression -> MethodReference_Expression -> Bool
compare :: MethodReference_Expression
-> MethodReference_Expression -> Ordering
$ccompare :: MethodReference_Expression
-> MethodReference_Expression -> Ordering
Ord, ReadPrec [MethodReference_Expression]
ReadPrec MethodReference_Expression
Int -> ReadS MethodReference_Expression
ReadS [MethodReference_Expression]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [MethodReference_Expression]
$creadListPrec :: ReadPrec [MethodReference_Expression]
readPrec :: ReadPrec MethodReference_Expression
$creadPrec :: ReadPrec MethodReference_Expression
readList :: ReadS [MethodReference_Expression]
$creadList :: ReadS [MethodReference_Expression]
readsPrec :: Int -> ReadS MethodReference_Expression
$creadsPrec :: Int -> ReadS MethodReference_Expression
Read, Int -> MethodReference_Expression -> String -> String
[MethodReference_Expression] -> String -> String
MethodReference_Expression -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [MethodReference_Expression] -> String -> String
$cshowList :: [MethodReference_Expression] -> String -> String
show :: MethodReference_Expression -> String
$cshow :: MethodReference_Expression -> String
showsPrec :: Int -> MethodReference_Expression -> String -> String
$cshowsPrec :: Int -> MethodReference_Expression -> String -> String
Show)

_MethodReference_Expression :: Name
_MethodReference_Expression = (String -> Name
Core.Name String
"hydra/ext/java/syntax.MethodReference.Expression")

_MethodReference_Expression_name :: FieldName
_MethodReference_Expression_name = (String -> FieldName
Core.FieldName String
"name")

_MethodReference_Expression_typeArguments :: FieldName
_MethodReference_Expression_typeArguments = (String -> FieldName
Core.FieldName String
"typeArguments")

_MethodReference_Expression_identifier :: FieldName
_MethodReference_Expression_identifier = (String -> FieldName
Core.FieldName String
"identifier")

data MethodReference_Primary = 
  MethodReference_Primary {
    MethodReference_Primary -> Primary
methodReference_PrimaryPrimary :: Primary,
    MethodReference_Primary -> [TypeArgument]
methodReference_PrimaryTypeArguments :: [TypeArgument],
    MethodReference_Primary -> Identifier
methodReference_PrimaryIdentifier :: Identifier}
  deriving (MethodReference_Primary -> MethodReference_Primary -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MethodReference_Primary -> MethodReference_Primary -> Bool
$c/= :: MethodReference_Primary -> MethodReference_Primary -> Bool
== :: MethodReference_Primary -> MethodReference_Primary -> Bool
$c== :: MethodReference_Primary -> MethodReference_Primary -> Bool
Eq, Eq MethodReference_Primary
MethodReference_Primary -> MethodReference_Primary -> Bool
MethodReference_Primary -> MethodReference_Primary -> Ordering
MethodReference_Primary
-> MethodReference_Primary -> MethodReference_Primary
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: MethodReference_Primary
-> MethodReference_Primary -> MethodReference_Primary
$cmin :: MethodReference_Primary
-> MethodReference_Primary -> MethodReference_Primary
max :: MethodReference_Primary
-> MethodReference_Primary -> MethodReference_Primary
$cmax :: MethodReference_Primary
-> MethodReference_Primary -> MethodReference_Primary
>= :: MethodReference_Primary -> MethodReference_Primary -> Bool
$c>= :: MethodReference_Primary -> MethodReference_Primary -> Bool
> :: MethodReference_Primary -> MethodReference_Primary -> Bool
$c> :: MethodReference_Primary -> MethodReference_Primary -> Bool
<= :: MethodReference_Primary -> MethodReference_Primary -> Bool
$c<= :: MethodReference_Primary -> MethodReference_Primary -> Bool
< :: MethodReference_Primary -> MethodReference_Primary -> Bool
$c< :: MethodReference_Primary -> MethodReference_Primary -> Bool
compare :: MethodReference_Primary -> MethodReference_Primary -> Ordering
$ccompare :: MethodReference_Primary -> MethodReference_Primary -> Ordering
Ord, ReadPrec [MethodReference_Primary]
ReadPrec MethodReference_Primary
Int -> ReadS MethodReference_Primary
ReadS [MethodReference_Primary]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [MethodReference_Primary]
$creadListPrec :: ReadPrec [MethodReference_Primary]
readPrec :: ReadPrec MethodReference_Primary
$creadPrec :: ReadPrec MethodReference_Primary
readList :: ReadS [MethodReference_Primary]
$creadList :: ReadS [MethodReference_Primary]
readsPrec :: Int -> ReadS MethodReference_Primary
$creadsPrec :: Int -> ReadS MethodReference_Primary
Read, Int -> MethodReference_Primary -> String -> String
[MethodReference_Primary] -> String -> String
MethodReference_Primary -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [MethodReference_Primary] -> String -> String
$cshowList :: [MethodReference_Primary] -> String -> String
show :: MethodReference_Primary -> String
$cshow :: MethodReference_Primary -> String
showsPrec :: Int -> MethodReference_Primary -> String -> String
$cshowsPrec :: Int -> MethodReference_Primary -> String -> String
Show)

_MethodReference_Primary :: Name
_MethodReference_Primary = (String -> Name
Core.Name String
"hydra/ext/java/syntax.MethodReference.Primary")

_MethodReference_Primary_primary :: FieldName
_MethodReference_Primary_primary = (String -> FieldName
Core.FieldName String
"primary")

_MethodReference_Primary_typeArguments :: FieldName
_MethodReference_Primary_typeArguments = (String -> FieldName
Core.FieldName String
"typeArguments")

_MethodReference_Primary_identifier :: FieldName
_MethodReference_Primary_identifier = (String -> FieldName
Core.FieldName String
"identifier")

data MethodReference_ReferenceType = 
  MethodReference_ReferenceType {
    MethodReference_ReferenceType -> ReferenceType
methodReference_ReferenceTypeReferenceType :: ReferenceType,
    MethodReference_ReferenceType -> [TypeArgument]
methodReference_ReferenceTypeTypeArguments :: [TypeArgument],
    MethodReference_ReferenceType -> Identifier
methodReference_ReferenceTypeIdentifier :: Identifier}
  deriving (MethodReference_ReferenceType
-> MethodReference_ReferenceType -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MethodReference_ReferenceType
-> MethodReference_ReferenceType -> Bool
$c/= :: MethodReference_ReferenceType
-> MethodReference_ReferenceType -> Bool
== :: MethodReference_ReferenceType
-> MethodReference_ReferenceType -> Bool
$c== :: MethodReference_ReferenceType
-> MethodReference_ReferenceType -> Bool
Eq, Eq MethodReference_ReferenceType
MethodReference_ReferenceType
-> MethodReference_ReferenceType -> Bool
MethodReference_ReferenceType
-> MethodReference_ReferenceType -> Ordering
MethodReference_ReferenceType
-> MethodReference_ReferenceType -> MethodReference_ReferenceType
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: MethodReference_ReferenceType
-> MethodReference_ReferenceType -> MethodReference_ReferenceType
$cmin :: MethodReference_ReferenceType
-> MethodReference_ReferenceType -> MethodReference_ReferenceType
max :: MethodReference_ReferenceType
-> MethodReference_ReferenceType -> MethodReference_ReferenceType
$cmax :: MethodReference_ReferenceType
-> MethodReference_ReferenceType -> MethodReference_ReferenceType
>= :: MethodReference_ReferenceType
-> MethodReference_ReferenceType -> Bool
$c>= :: MethodReference_ReferenceType
-> MethodReference_ReferenceType -> Bool
> :: MethodReference_ReferenceType
-> MethodReference_ReferenceType -> Bool
$c> :: MethodReference_ReferenceType
-> MethodReference_ReferenceType -> Bool
<= :: MethodReference_ReferenceType
-> MethodReference_ReferenceType -> Bool
$c<= :: MethodReference_ReferenceType
-> MethodReference_ReferenceType -> Bool
< :: MethodReference_ReferenceType
-> MethodReference_ReferenceType -> Bool
$c< :: MethodReference_ReferenceType
-> MethodReference_ReferenceType -> Bool
compare :: MethodReference_ReferenceType
-> MethodReference_ReferenceType -> Ordering
$ccompare :: MethodReference_ReferenceType
-> MethodReference_ReferenceType -> Ordering
Ord, ReadPrec [MethodReference_ReferenceType]
ReadPrec MethodReference_ReferenceType
Int -> ReadS MethodReference_ReferenceType
ReadS [MethodReference_ReferenceType]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [MethodReference_ReferenceType]
$creadListPrec :: ReadPrec [MethodReference_ReferenceType]
readPrec :: ReadPrec MethodReference_ReferenceType
$creadPrec :: ReadPrec MethodReference_ReferenceType
readList :: ReadS [MethodReference_ReferenceType]
$creadList :: ReadS [MethodReference_ReferenceType]
readsPrec :: Int -> ReadS MethodReference_ReferenceType
$creadsPrec :: Int -> ReadS MethodReference_ReferenceType
Read, Int -> MethodReference_ReferenceType -> String -> String
[MethodReference_ReferenceType] -> String -> String
MethodReference_ReferenceType -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [MethodReference_ReferenceType] -> String -> String
$cshowList :: [MethodReference_ReferenceType] -> String -> String
show :: MethodReference_ReferenceType -> String
$cshow :: MethodReference_ReferenceType -> String
showsPrec :: Int -> MethodReference_ReferenceType -> String -> String
$cshowsPrec :: Int -> MethodReference_ReferenceType -> String -> String
Show)

_MethodReference_ReferenceType :: Name
_MethodReference_ReferenceType = (String -> Name
Core.Name String
"hydra/ext/java/syntax.MethodReference.ReferenceType")

_MethodReference_ReferenceType_referenceType :: FieldName
_MethodReference_ReferenceType_referenceType = (String -> FieldName
Core.FieldName String
"referenceType")

_MethodReference_ReferenceType_typeArguments :: FieldName
_MethodReference_ReferenceType_typeArguments = (String -> FieldName
Core.FieldName String
"typeArguments")

_MethodReference_ReferenceType_identifier :: FieldName
_MethodReference_ReferenceType_identifier = (String -> FieldName
Core.FieldName String
"identifier")

data MethodReference_Super = 
  MethodReference_Super {
    MethodReference_Super -> [TypeArgument]
methodReference_SuperTypeArguments :: [TypeArgument],
    MethodReference_Super -> Identifier
methodReference_SuperIdentifier :: Identifier,
    MethodReference_Super -> Bool
methodReference_SuperSuper :: Bool}
  deriving (MethodReference_Super -> MethodReference_Super -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MethodReference_Super -> MethodReference_Super -> Bool
$c/= :: MethodReference_Super -> MethodReference_Super -> Bool
== :: MethodReference_Super -> MethodReference_Super -> Bool
$c== :: MethodReference_Super -> MethodReference_Super -> Bool
Eq, Eq MethodReference_Super
MethodReference_Super -> MethodReference_Super -> Bool
MethodReference_Super -> MethodReference_Super -> Ordering
MethodReference_Super
-> MethodReference_Super -> MethodReference_Super
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: MethodReference_Super
-> MethodReference_Super -> MethodReference_Super
$cmin :: MethodReference_Super
-> MethodReference_Super -> MethodReference_Super
max :: MethodReference_Super
-> MethodReference_Super -> MethodReference_Super
$cmax :: MethodReference_Super
-> MethodReference_Super -> MethodReference_Super
>= :: MethodReference_Super -> MethodReference_Super -> Bool
$c>= :: MethodReference_Super -> MethodReference_Super -> Bool
> :: MethodReference_Super -> MethodReference_Super -> Bool
$c> :: MethodReference_Super -> MethodReference_Super -> Bool
<= :: MethodReference_Super -> MethodReference_Super -> Bool
$c<= :: MethodReference_Super -> MethodReference_Super -> Bool
< :: MethodReference_Super -> MethodReference_Super -> Bool
$c< :: MethodReference_Super -> MethodReference_Super -> Bool
compare :: MethodReference_Super -> MethodReference_Super -> Ordering
$ccompare :: MethodReference_Super -> MethodReference_Super -> Ordering
Ord, ReadPrec [MethodReference_Super]
ReadPrec MethodReference_Super
Int -> ReadS MethodReference_Super
ReadS [MethodReference_Super]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [MethodReference_Super]
$creadListPrec :: ReadPrec [MethodReference_Super]
readPrec :: ReadPrec MethodReference_Super
$creadPrec :: ReadPrec MethodReference_Super
readList :: ReadS [MethodReference_Super]
$creadList :: ReadS [MethodReference_Super]
readsPrec :: Int -> ReadS MethodReference_Super
$creadsPrec :: Int -> ReadS MethodReference_Super
Read, Int -> MethodReference_Super -> String -> String
[MethodReference_Super] -> String -> String
MethodReference_Super -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [MethodReference_Super] -> String -> String
$cshowList :: [MethodReference_Super] -> String -> String
show :: MethodReference_Super -> String
$cshow :: MethodReference_Super -> String
showsPrec :: Int -> MethodReference_Super -> String -> String
$cshowsPrec :: Int -> MethodReference_Super -> String -> String
Show)

_MethodReference_Super :: Name
_MethodReference_Super = (String -> Name
Core.Name String
"hydra/ext/java/syntax.MethodReference.Super")

_MethodReference_Super_typeArguments :: FieldName
_MethodReference_Super_typeArguments = (String -> FieldName
Core.FieldName String
"typeArguments")

_MethodReference_Super_identifier :: FieldName
_MethodReference_Super_identifier = (String -> FieldName
Core.FieldName String
"identifier")

_MethodReference_Super_super :: FieldName
_MethodReference_Super_super = (String -> FieldName
Core.FieldName String
"super")

data MethodReference_New = 
  MethodReference_New {
    MethodReference_New -> ClassType
methodReference_NewClassType :: ClassType,
    MethodReference_New -> [TypeArgument]
methodReference_NewTypeArguments :: [TypeArgument]}
  deriving (MethodReference_New -> MethodReference_New -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MethodReference_New -> MethodReference_New -> Bool
$c/= :: MethodReference_New -> MethodReference_New -> Bool
== :: MethodReference_New -> MethodReference_New -> Bool
$c== :: MethodReference_New -> MethodReference_New -> Bool
Eq, Eq MethodReference_New
MethodReference_New -> MethodReference_New -> Bool
MethodReference_New -> MethodReference_New -> Ordering
MethodReference_New -> MethodReference_New -> MethodReference_New
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: MethodReference_New -> MethodReference_New -> MethodReference_New
$cmin :: MethodReference_New -> MethodReference_New -> MethodReference_New
max :: MethodReference_New -> MethodReference_New -> MethodReference_New
$cmax :: MethodReference_New -> MethodReference_New -> MethodReference_New
>= :: MethodReference_New -> MethodReference_New -> Bool
$c>= :: MethodReference_New -> MethodReference_New -> Bool
> :: MethodReference_New -> MethodReference_New -> Bool
$c> :: MethodReference_New -> MethodReference_New -> Bool
<= :: MethodReference_New -> MethodReference_New -> Bool
$c<= :: MethodReference_New -> MethodReference_New -> Bool
< :: MethodReference_New -> MethodReference_New -> Bool
$c< :: MethodReference_New -> MethodReference_New -> Bool
compare :: MethodReference_New -> MethodReference_New -> Ordering
$ccompare :: MethodReference_New -> MethodReference_New -> Ordering
Ord, ReadPrec [MethodReference_New]
ReadPrec MethodReference_New
Int -> ReadS MethodReference_New
ReadS [MethodReference_New]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [MethodReference_New]
$creadListPrec :: ReadPrec [MethodReference_New]
readPrec :: ReadPrec MethodReference_New
$creadPrec :: ReadPrec MethodReference_New
readList :: ReadS [MethodReference_New]
$creadList :: ReadS [MethodReference_New]
readsPrec :: Int -> ReadS MethodReference_New
$creadsPrec :: Int -> ReadS MethodReference_New
Read, Int -> MethodReference_New -> String -> String
[MethodReference_New] -> String -> String
MethodReference_New -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [MethodReference_New] -> String -> String
$cshowList :: [MethodReference_New] -> String -> String
show :: MethodReference_New -> String
$cshow :: MethodReference_New -> String
showsPrec :: Int -> MethodReference_New -> String -> String
$cshowsPrec :: Int -> MethodReference_New -> String -> String
Show)

_MethodReference_New :: Name
_MethodReference_New = (String -> Name
Core.Name String
"hydra/ext/java/syntax.MethodReference.New")

_MethodReference_New_classType :: FieldName
_MethodReference_New_classType = (String -> FieldName
Core.FieldName String
"classType")

_MethodReference_New_typeArguments :: FieldName
_MethodReference_New_typeArguments = (String -> FieldName
Core.FieldName String
"typeArguments")

newtype MethodReference_Array = 
  MethodReference_Array {
    MethodReference_Array -> ArrayType
unMethodReference_Array :: ArrayType}
  deriving (MethodReference_Array -> MethodReference_Array -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MethodReference_Array -> MethodReference_Array -> Bool
$c/= :: MethodReference_Array -> MethodReference_Array -> Bool
== :: MethodReference_Array -> MethodReference_Array -> Bool
$c== :: MethodReference_Array -> MethodReference_Array -> Bool
Eq, Eq MethodReference_Array
MethodReference_Array -> MethodReference_Array -> Bool
MethodReference_Array -> MethodReference_Array -> Ordering
MethodReference_Array
-> MethodReference_Array -> MethodReference_Array
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: MethodReference_Array
-> MethodReference_Array -> MethodReference_Array
$cmin :: MethodReference_Array
-> MethodReference_Array -> MethodReference_Array
max :: MethodReference_Array
-> MethodReference_Array -> MethodReference_Array
$cmax :: MethodReference_Array
-> MethodReference_Array -> MethodReference_Array
>= :: MethodReference_Array -> MethodReference_Array -> Bool
$c>= :: MethodReference_Array -> MethodReference_Array -> Bool
> :: MethodReference_Array -> MethodReference_Array -> Bool
$c> :: MethodReference_Array -> MethodReference_Array -> Bool
<= :: MethodReference_Array -> MethodReference_Array -> Bool
$c<= :: MethodReference_Array -> MethodReference_Array -> Bool
< :: MethodReference_Array -> MethodReference_Array -> Bool
$c< :: MethodReference_Array -> MethodReference_Array -> Bool
compare :: MethodReference_Array -> MethodReference_Array -> Ordering
$ccompare :: MethodReference_Array -> MethodReference_Array -> Ordering
Ord, ReadPrec [MethodReference_Array]
ReadPrec MethodReference_Array
Int -> ReadS MethodReference_Array
ReadS [MethodReference_Array]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [MethodReference_Array]
$creadListPrec :: ReadPrec [MethodReference_Array]
readPrec :: ReadPrec MethodReference_Array
$creadPrec :: ReadPrec MethodReference_Array
readList :: ReadS [MethodReference_Array]
$creadList :: ReadS [MethodReference_Array]
readsPrec :: Int -> ReadS MethodReference_Array
$creadsPrec :: Int -> ReadS MethodReference_Array
Read, Int -> MethodReference_Array -> String -> String
[MethodReference_Array] -> String -> String
MethodReference_Array -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [MethodReference_Array] -> String -> String
$cshowList :: [MethodReference_Array] -> String -> String
show :: MethodReference_Array -> String
$cshow :: MethodReference_Array -> String
showsPrec :: Int -> MethodReference_Array -> String -> String
$cshowsPrec :: Int -> MethodReference_Array -> String -> String
Show)

_MethodReference_Array :: Name
_MethodReference_Array = (String -> Name
Core.Name String
"hydra/ext/java/syntax.MethodReference.Array")

data ArrayCreationExpression = 
  ArrayCreationExpressionPrimitive ArrayCreationExpression_Primitive |
  ArrayCreationExpressionClassOrInterface ArrayCreationExpression_ClassOrInterface |
  ArrayCreationExpressionPrimitiveArray ArrayCreationExpression_PrimitiveArray |
  ArrayCreationExpressionClassOrInterfaceArray ArrayCreationExpression_ClassOrInterfaceArray
  deriving (ArrayCreationExpression -> ArrayCreationExpression -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ArrayCreationExpression -> ArrayCreationExpression -> Bool
$c/= :: ArrayCreationExpression -> ArrayCreationExpression -> Bool
== :: ArrayCreationExpression -> ArrayCreationExpression -> Bool
$c== :: ArrayCreationExpression -> ArrayCreationExpression -> Bool
Eq, Eq ArrayCreationExpression
ArrayCreationExpression -> ArrayCreationExpression -> Bool
ArrayCreationExpression -> ArrayCreationExpression -> Ordering
ArrayCreationExpression
-> ArrayCreationExpression -> ArrayCreationExpression
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ArrayCreationExpression
-> ArrayCreationExpression -> ArrayCreationExpression
$cmin :: ArrayCreationExpression
-> ArrayCreationExpression -> ArrayCreationExpression
max :: ArrayCreationExpression
-> ArrayCreationExpression -> ArrayCreationExpression
$cmax :: ArrayCreationExpression
-> ArrayCreationExpression -> ArrayCreationExpression
>= :: ArrayCreationExpression -> ArrayCreationExpression -> Bool
$c>= :: ArrayCreationExpression -> ArrayCreationExpression -> Bool
> :: ArrayCreationExpression -> ArrayCreationExpression -> Bool
$c> :: ArrayCreationExpression -> ArrayCreationExpression -> Bool
<= :: ArrayCreationExpression -> ArrayCreationExpression -> Bool
$c<= :: ArrayCreationExpression -> ArrayCreationExpression -> Bool
< :: ArrayCreationExpression -> ArrayCreationExpression -> Bool
$c< :: ArrayCreationExpression -> ArrayCreationExpression -> Bool
compare :: ArrayCreationExpression -> ArrayCreationExpression -> Ordering
$ccompare :: ArrayCreationExpression -> ArrayCreationExpression -> Ordering
Ord, ReadPrec [ArrayCreationExpression]
ReadPrec ArrayCreationExpression
Int -> ReadS ArrayCreationExpression
ReadS [ArrayCreationExpression]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ArrayCreationExpression]
$creadListPrec :: ReadPrec [ArrayCreationExpression]
readPrec :: ReadPrec ArrayCreationExpression
$creadPrec :: ReadPrec ArrayCreationExpression
readList :: ReadS [ArrayCreationExpression]
$creadList :: ReadS [ArrayCreationExpression]
readsPrec :: Int -> ReadS ArrayCreationExpression
$creadsPrec :: Int -> ReadS ArrayCreationExpression
Read, Int -> ArrayCreationExpression -> String -> String
[ArrayCreationExpression] -> String -> String
ArrayCreationExpression -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ArrayCreationExpression] -> String -> String
$cshowList :: [ArrayCreationExpression] -> String -> String
show :: ArrayCreationExpression -> String
$cshow :: ArrayCreationExpression -> String
showsPrec :: Int -> ArrayCreationExpression -> String -> String
$cshowsPrec :: Int -> ArrayCreationExpression -> String -> String
Show)

_ArrayCreationExpression :: Name
_ArrayCreationExpression = (String -> Name
Core.Name String
"hydra/ext/java/syntax.ArrayCreationExpression")

_ArrayCreationExpression_primitive :: FieldName
_ArrayCreationExpression_primitive = (String -> FieldName
Core.FieldName String
"primitive")

_ArrayCreationExpression_classOrInterface :: FieldName
_ArrayCreationExpression_classOrInterface = (String -> FieldName
Core.FieldName String
"classOrInterface")

_ArrayCreationExpression_primitiveArray :: FieldName
_ArrayCreationExpression_primitiveArray = (String -> FieldName
Core.FieldName String
"primitiveArray")

_ArrayCreationExpression_classOrInterfaceArray :: FieldName
_ArrayCreationExpression_classOrInterfaceArray = (String -> FieldName
Core.FieldName String
"classOrInterfaceArray")

data ArrayCreationExpression_Primitive = 
  ArrayCreationExpression_Primitive {
    ArrayCreationExpression_Primitive -> PrimitiveTypeWithAnnotations
arrayCreationExpression_PrimitiveType :: PrimitiveTypeWithAnnotations,
    ArrayCreationExpression_Primitive -> [DimExpr]
arrayCreationExpression_PrimitiveDimExprs :: [DimExpr],
    ArrayCreationExpression_Primitive -> Maybe Dims
arrayCreationExpression_PrimitiveDims :: (Maybe Dims)}
  deriving (ArrayCreationExpression_Primitive
-> ArrayCreationExpression_Primitive -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ArrayCreationExpression_Primitive
-> ArrayCreationExpression_Primitive -> Bool
$c/= :: ArrayCreationExpression_Primitive
-> ArrayCreationExpression_Primitive -> Bool
== :: ArrayCreationExpression_Primitive
-> ArrayCreationExpression_Primitive -> Bool
$c== :: ArrayCreationExpression_Primitive
-> ArrayCreationExpression_Primitive -> Bool
Eq, Eq ArrayCreationExpression_Primitive
ArrayCreationExpression_Primitive
-> ArrayCreationExpression_Primitive -> Bool
ArrayCreationExpression_Primitive
-> ArrayCreationExpression_Primitive -> Ordering
ArrayCreationExpression_Primitive
-> ArrayCreationExpression_Primitive
-> ArrayCreationExpression_Primitive
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ArrayCreationExpression_Primitive
-> ArrayCreationExpression_Primitive
-> ArrayCreationExpression_Primitive
$cmin :: ArrayCreationExpression_Primitive
-> ArrayCreationExpression_Primitive
-> ArrayCreationExpression_Primitive
max :: ArrayCreationExpression_Primitive
-> ArrayCreationExpression_Primitive
-> ArrayCreationExpression_Primitive
$cmax :: ArrayCreationExpression_Primitive
-> ArrayCreationExpression_Primitive
-> ArrayCreationExpression_Primitive
>= :: ArrayCreationExpression_Primitive
-> ArrayCreationExpression_Primitive -> Bool
$c>= :: ArrayCreationExpression_Primitive
-> ArrayCreationExpression_Primitive -> Bool
> :: ArrayCreationExpression_Primitive
-> ArrayCreationExpression_Primitive -> Bool
$c> :: ArrayCreationExpression_Primitive
-> ArrayCreationExpression_Primitive -> Bool
<= :: ArrayCreationExpression_Primitive
-> ArrayCreationExpression_Primitive -> Bool
$c<= :: ArrayCreationExpression_Primitive
-> ArrayCreationExpression_Primitive -> Bool
< :: ArrayCreationExpression_Primitive
-> ArrayCreationExpression_Primitive -> Bool
$c< :: ArrayCreationExpression_Primitive
-> ArrayCreationExpression_Primitive -> Bool
compare :: ArrayCreationExpression_Primitive
-> ArrayCreationExpression_Primitive -> Ordering
$ccompare :: ArrayCreationExpression_Primitive
-> ArrayCreationExpression_Primitive -> Ordering
Ord, ReadPrec [ArrayCreationExpression_Primitive]
ReadPrec ArrayCreationExpression_Primitive
Int -> ReadS ArrayCreationExpression_Primitive
ReadS [ArrayCreationExpression_Primitive]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ArrayCreationExpression_Primitive]
$creadListPrec :: ReadPrec [ArrayCreationExpression_Primitive]
readPrec :: ReadPrec ArrayCreationExpression_Primitive
$creadPrec :: ReadPrec ArrayCreationExpression_Primitive
readList :: ReadS [ArrayCreationExpression_Primitive]
$creadList :: ReadS [ArrayCreationExpression_Primitive]
readsPrec :: Int -> ReadS ArrayCreationExpression_Primitive
$creadsPrec :: Int -> ReadS ArrayCreationExpression_Primitive
Read, Int -> ArrayCreationExpression_Primitive -> String -> String
[ArrayCreationExpression_Primitive] -> String -> String
ArrayCreationExpression_Primitive -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ArrayCreationExpression_Primitive] -> String -> String
$cshowList :: [ArrayCreationExpression_Primitive] -> String -> String
show :: ArrayCreationExpression_Primitive -> String
$cshow :: ArrayCreationExpression_Primitive -> String
showsPrec :: Int -> ArrayCreationExpression_Primitive -> String -> String
$cshowsPrec :: Int -> ArrayCreationExpression_Primitive -> String -> String
Show)

_ArrayCreationExpression_Primitive :: Name
_ArrayCreationExpression_Primitive = (String -> Name
Core.Name String
"hydra/ext/java/syntax.ArrayCreationExpression.Primitive")

_ArrayCreationExpression_Primitive_type :: FieldName
_ArrayCreationExpression_Primitive_type = (String -> FieldName
Core.FieldName String
"type")

_ArrayCreationExpression_Primitive_dimExprs :: FieldName
_ArrayCreationExpression_Primitive_dimExprs = (String -> FieldName
Core.FieldName String
"dimExprs")

_ArrayCreationExpression_Primitive_dims :: FieldName
_ArrayCreationExpression_Primitive_dims = (String -> FieldName
Core.FieldName String
"dims")

data ArrayCreationExpression_ClassOrInterface = 
  ArrayCreationExpression_ClassOrInterface {
    ArrayCreationExpression_ClassOrInterface -> ClassOrInterfaceType
arrayCreationExpression_ClassOrInterfaceType :: ClassOrInterfaceType,
    ArrayCreationExpression_ClassOrInterface -> [DimExpr]
arrayCreationExpression_ClassOrInterfaceDimExprs :: [DimExpr],
    ArrayCreationExpression_ClassOrInterface -> Maybe Dims
arrayCreationExpression_ClassOrInterfaceDims :: (Maybe Dims)}
  deriving (ArrayCreationExpression_ClassOrInterface
-> ArrayCreationExpression_ClassOrInterface -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ArrayCreationExpression_ClassOrInterface
-> ArrayCreationExpression_ClassOrInterface -> Bool
$c/= :: ArrayCreationExpression_ClassOrInterface
-> ArrayCreationExpression_ClassOrInterface -> Bool
== :: ArrayCreationExpression_ClassOrInterface
-> ArrayCreationExpression_ClassOrInterface -> Bool
$c== :: ArrayCreationExpression_ClassOrInterface
-> ArrayCreationExpression_ClassOrInterface -> Bool
Eq, Eq ArrayCreationExpression_ClassOrInterface
ArrayCreationExpression_ClassOrInterface
-> ArrayCreationExpression_ClassOrInterface -> Bool
ArrayCreationExpression_ClassOrInterface
-> ArrayCreationExpression_ClassOrInterface -> Ordering
ArrayCreationExpression_ClassOrInterface
-> ArrayCreationExpression_ClassOrInterface
-> ArrayCreationExpression_ClassOrInterface
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ArrayCreationExpression_ClassOrInterface
-> ArrayCreationExpression_ClassOrInterface
-> ArrayCreationExpression_ClassOrInterface
$cmin :: ArrayCreationExpression_ClassOrInterface
-> ArrayCreationExpression_ClassOrInterface
-> ArrayCreationExpression_ClassOrInterface
max :: ArrayCreationExpression_ClassOrInterface
-> ArrayCreationExpression_ClassOrInterface
-> ArrayCreationExpression_ClassOrInterface
$cmax :: ArrayCreationExpression_ClassOrInterface
-> ArrayCreationExpression_ClassOrInterface
-> ArrayCreationExpression_ClassOrInterface
>= :: ArrayCreationExpression_ClassOrInterface
-> ArrayCreationExpression_ClassOrInterface -> Bool
$c>= :: ArrayCreationExpression_ClassOrInterface
-> ArrayCreationExpression_ClassOrInterface -> Bool
> :: ArrayCreationExpression_ClassOrInterface
-> ArrayCreationExpression_ClassOrInterface -> Bool
$c> :: ArrayCreationExpression_ClassOrInterface
-> ArrayCreationExpression_ClassOrInterface -> Bool
<= :: ArrayCreationExpression_ClassOrInterface
-> ArrayCreationExpression_ClassOrInterface -> Bool
$c<= :: ArrayCreationExpression_ClassOrInterface
-> ArrayCreationExpression_ClassOrInterface -> Bool
< :: ArrayCreationExpression_ClassOrInterface
-> ArrayCreationExpression_ClassOrInterface -> Bool
$c< :: ArrayCreationExpression_ClassOrInterface
-> ArrayCreationExpression_ClassOrInterface -> Bool
compare :: ArrayCreationExpression_ClassOrInterface
-> ArrayCreationExpression_ClassOrInterface -> Ordering
$ccompare :: ArrayCreationExpression_ClassOrInterface
-> ArrayCreationExpression_ClassOrInterface -> Ordering
Ord, ReadPrec [ArrayCreationExpression_ClassOrInterface]
ReadPrec ArrayCreationExpression_ClassOrInterface
Int -> ReadS ArrayCreationExpression_ClassOrInterface
ReadS [ArrayCreationExpression_ClassOrInterface]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ArrayCreationExpression_ClassOrInterface]
$creadListPrec :: ReadPrec [ArrayCreationExpression_ClassOrInterface]
readPrec :: ReadPrec ArrayCreationExpression_ClassOrInterface
$creadPrec :: ReadPrec ArrayCreationExpression_ClassOrInterface
readList :: ReadS [ArrayCreationExpression_ClassOrInterface]
$creadList :: ReadS [ArrayCreationExpression_ClassOrInterface]
readsPrec :: Int -> ReadS ArrayCreationExpression_ClassOrInterface
$creadsPrec :: Int -> ReadS ArrayCreationExpression_ClassOrInterface
Read, Int -> ArrayCreationExpression_ClassOrInterface -> String -> String
[ArrayCreationExpression_ClassOrInterface] -> String -> String
ArrayCreationExpression_ClassOrInterface -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ArrayCreationExpression_ClassOrInterface] -> String -> String
$cshowList :: [ArrayCreationExpression_ClassOrInterface] -> String -> String
show :: ArrayCreationExpression_ClassOrInterface -> String
$cshow :: ArrayCreationExpression_ClassOrInterface -> String
showsPrec :: Int -> ArrayCreationExpression_ClassOrInterface -> String -> String
$cshowsPrec :: Int -> ArrayCreationExpression_ClassOrInterface -> String -> String
Show)

_ArrayCreationExpression_ClassOrInterface :: Name
_ArrayCreationExpression_ClassOrInterface = (String -> Name
Core.Name String
"hydra/ext/java/syntax.ArrayCreationExpression.ClassOrInterface")

_ArrayCreationExpression_ClassOrInterface_type :: FieldName
_ArrayCreationExpression_ClassOrInterface_type = (String -> FieldName
Core.FieldName String
"type")

_ArrayCreationExpression_ClassOrInterface_dimExprs :: FieldName
_ArrayCreationExpression_ClassOrInterface_dimExprs = (String -> FieldName
Core.FieldName String
"dimExprs")

_ArrayCreationExpression_ClassOrInterface_dims :: FieldName
_ArrayCreationExpression_ClassOrInterface_dims = (String -> FieldName
Core.FieldName String
"dims")

data ArrayCreationExpression_PrimitiveArray = 
  ArrayCreationExpression_PrimitiveArray {
    ArrayCreationExpression_PrimitiveArray
-> PrimitiveTypeWithAnnotations
arrayCreationExpression_PrimitiveArrayType :: PrimitiveTypeWithAnnotations,
    ArrayCreationExpression_PrimitiveArray -> [Dims]
arrayCreationExpression_PrimitiveArrayDims :: [Dims],
    ArrayCreationExpression_PrimitiveArray -> ArrayInitializer
arrayCreationExpression_PrimitiveArrayArray :: ArrayInitializer}
  deriving (ArrayCreationExpression_PrimitiveArray
-> ArrayCreationExpression_PrimitiveArray -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ArrayCreationExpression_PrimitiveArray
-> ArrayCreationExpression_PrimitiveArray -> Bool
$c/= :: ArrayCreationExpression_PrimitiveArray
-> ArrayCreationExpression_PrimitiveArray -> Bool
== :: ArrayCreationExpression_PrimitiveArray
-> ArrayCreationExpression_PrimitiveArray -> Bool
$c== :: ArrayCreationExpression_PrimitiveArray
-> ArrayCreationExpression_PrimitiveArray -> Bool
Eq, Eq ArrayCreationExpression_PrimitiveArray
ArrayCreationExpression_PrimitiveArray
-> ArrayCreationExpression_PrimitiveArray -> Bool
ArrayCreationExpression_PrimitiveArray
-> ArrayCreationExpression_PrimitiveArray -> Ordering
ArrayCreationExpression_PrimitiveArray
-> ArrayCreationExpression_PrimitiveArray
-> ArrayCreationExpression_PrimitiveArray
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ArrayCreationExpression_PrimitiveArray
-> ArrayCreationExpression_PrimitiveArray
-> ArrayCreationExpression_PrimitiveArray
$cmin :: ArrayCreationExpression_PrimitiveArray
-> ArrayCreationExpression_PrimitiveArray
-> ArrayCreationExpression_PrimitiveArray
max :: ArrayCreationExpression_PrimitiveArray
-> ArrayCreationExpression_PrimitiveArray
-> ArrayCreationExpression_PrimitiveArray
$cmax :: ArrayCreationExpression_PrimitiveArray
-> ArrayCreationExpression_PrimitiveArray
-> ArrayCreationExpression_PrimitiveArray
>= :: ArrayCreationExpression_PrimitiveArray
-> ArrayCreationExpression_PrimitiveArray -> Bool
$c>= :: ArrayCreationExpression_PrimitiveArray
-> ArrayCreationExpression_PrimitiveArray -> Bool
> :: ArrayCreationExpression_PrimitiveArray
-> ArrayCreationExpression_PrimitiveArray -> Bool
$c> :: ArrayCreationExpression_PrimitiveArray
-> ArrayCreationExpression_PrimitiveArray -> Bool
<= :: ArrayCreationExpression_PrimitiveArray
-> ArrayCreationExpression_PrimitiveArray -> Bool
$c<= :: ArrayCreationExpression_PrimitiveArray
-> ArrayCreationExpression_PrimitiveArray -> Bool
< :: ArrayCreationExpression_PrimitiveArray
-> ArrayCreationExpression_PrimitiveArray -> Bool
$c< :: ArrayCreationExpression_PrimitiveArray
-> ArrayCreationExpression_PrimitiveArray -> Bool
compare :: ArrayCreationExpression_PrimitiveArray
-> ArrayCreationExpression_PrimitiveArray -> Ordering
$ccompare :: ArrayCreationExpression_PrimitiveArray
-> ArrayCreationExpression_PrimitiveArray -> Ordering
Ord, ReadPrec [ArrayCreationExpression_PrimitiveArray]
ReadPrec ArrayCreationExpression_PrimitiveArray
Int -> ReadS ArrayCreationExpression_PrimitiveArray
ReadS [ArrayCreationExpression_PrimitiveArray]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ArrayCreationExpression_PrimitiveArray]
$creadListPrec :: ReadPrec [ArrayCreationExpression_PrimitiveArray]
readPrec :: ReadPrec ArrayCreationExpression_PrimitiveArray
$creadPrec :: ReadPrec ArrayCreationExpression_PrimitiveArray
readList :: ReadS [ArrayCreationExpression_PrimitiveArray]
$creadList :: ReadS [ArrayCreationExpression_PrimitiveArray]
readsPrec :: Int -> ReadS ArrayCreationExpression_PrimitiveArray
$creadsPrec :: Int -> ReadS ArrayCreationExpression_PrimitiveArray
Read, Int -> ArrayCreationExpression_PrimitiveArray -> String -> String
[ArrayCreationExpression_PrimitiveArray] -> String -> String
ArrayCreationExpression_PrimitiveArray -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ArrayCreationExpression_PrimitiveArray] -> String -> String
$cshowList :: [ArrayCreationExpression_PrimitiveArray] -> String -> String
show :: ArrayCreationExpression_PrimitiveArray -> String
$cshow :: ArrayCreationExpression_PrimitiveArray -> String
showsPrec :: Int -> ArrayCreationExpression_PrimitiveArray -> String -> String
$cshowsPrec :: Int -> ArrayCreationExpression_PrimitiveArray -> String -> String
Show)

_ArrayCreationExpression_PrimitiveArray :: Name
_ArrayCreationExpression_PrimitiveArray = (String -> Name
Core.Name String
"hydra/ext/java/syntax.ArrayCreationExpression.PrimitiveArray")

_ArrayCreationExpression_PrimitiveArray_type :: FieldName
_ArrayCreationExpression_PrimitiveArray_type = (String -> FieldName
Core.FieldName String
"type")

_ArrayCreationExpression_PrimitiveArray_dims :: FieldName
_ArrayCreationExpression_PrimitiveArray_dims = (String -> FieldName
Core.FieldName String
"dims")

_ArrayCreationExpression_PrimitiveArray_array :: FieldName
_ArrayCreationExpression_PrimitiveArray_array = (String -> FieldName
Core.FieldName String
"array")

data ArrayCreationExpression_ClassOrInterfaceArray = 
  ArrayCreationExpression_ClassOrInterfaceArray {
    ArrayCreationExpression_ClassOrInterfaceArray
-> ClassOrInterfaceType
arrayCreationExpression_ClassOrInterfaceArrayType :: ClassOrInterfaceType,
    ArrayCreationExpression_ClassOrInterfaceArray -> [Dims]
arrayCreationExpression_ClassOrInterfaceArrayDims :: [Dims],
    ArrayCreationExpression_ClassOrInterfaceArray -> ArrayInitializer
arrayCreationExpression_ClassOrInterfaceArrayArray :: ArrayInitializer}
  deriving (ArrayCreationExpression_ClassOrInterfaceArray
-> ArrayCreationExpression_ClassOrInterfaceArray -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ArrayCreationExpression_ClassOrInterfaceArray
-> ArrayCreationExpression_ClassOrInterfaceArray -> Bool
$c/= :: ArrayCreationExpression_ClassOrInterfaceArray
-> ArrayCreationExpression_ClassOrInterfaceArray -> Bool
== :: ArrayCreationExpression_ClassOrInterfaceArray
-> ArrayCreationExpression_ClassOrInterfaceArray -> Bool
$c== :: ArrayCreationExpression_ClassOrInterfaceArray
-> ArrayCreationExpression_ClassOrInterfaceArray -> Bool
Eq, Eq ArrayCreationExpression_ClassOrInterfaceArray
ArrayCreationExpression_ClassOrInterfaceArray
-> ArrayCreationExpression_ClassOrInterfaceArray -> Bool
ArrayCreationExpression_ClassOrInterfaceArray
-> ArrayCreationExpression_ClassOrInterfaceArray -> Ordering
ArrayCreationExpression_ClassOrInterfaceArray
-> ArrayCreationExpression_ClassOrInterfaceArray
-> ArrayCreationExpression_ClassOrInterfaceArray
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ArrayCreationExpression_ClassOrInterfaceArray
-> ArrayCreationExpression_ClassOrInterfaceArray
-> ArrayCreationExpression_ClassOrInterfaceArray
$cmin :: ArrayCreationExpression_ClassOrInterfaceArray
-> ArrayCreationExpression_ClassOrInterfaceArray
-> ArrayCreationExpression_ClassOrInterfaceArray
max :: ArrayCreationExpression_ClassOrInterfaceArray
-> ArrayCreationExpression_ClassOrInterfaceArray
-> ArrayCreationExpression_ClassOrInterfaceArray
$cmax :: ArrayCreationExpression_ClassOrInterfaceArray
-> ArrayCreationExpression_ClassOrInterfaceArray
-> ArrayCreationExpression_ClassOrInterfaceArray
>= :: ArrayCreationExpression_ClassOrInterfaceArray
-> ArrayCreationExpression_ClassOrInterfaceArray -> Bool
$c>= :: ArrayCreationExpression_ClassOrInterfaceArray
-> ArrayCreationExpression_ClassOrInterfaceArray -> Bool
> :: ArrayCreationExpression_ClassOrInterfaceArray
-> ArrayCreationExpression_ClassOrInterfaceArray -> Bool
$c> :: ArrayCreationExpression_ClassOrInterfaceArray
-> ArrayCreationExpression_ClassOrInterfaceArray -> Bool
<= :: ArrayCreationExpression_ClassOrInterfaceArray
-> ArrayCreationExpression_ClassOrInterfaceArray -> Bool
$c<= :: ArrayCreationExpression_ClassOrInterfaceArray
-> ArrayCreationExpression_ClassOrInterfaceArray -> Bool
< :: ArrayCreationExpression_ClassOrInterfaceArray
-> ArrayCreationExpression_ClassOrInterfaceArray -> Bool
$c< :: ArrayCreationExpression_ClassOrInterfaceArray
-> ArrayCreationExpression_ClassOrInterfaceArray -> Bool
compare :: ArrayCreationExpression_ClassOrInterfaceArray
-> ArrayCreationExpression_ClassOrInterfaceArray -> Ordering
$ccompare :: ArrayCreationExpression_ClassOrInterfaceArray
-> ArrayCreationExpression_ClassOrInterfaceArray -> Ordering
Ord, ReadPrec [ArrayCreationExpression_ClassOrInterfaceArray]
ReadPrec ArrayCreationExpression_ClassOrInterfaceArray
Int -> ReadS ArrayCreationExpression_ClassOrInterfaceArray
ReadS [ArrayCreationExpression_ClassOrInterfaceArray]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ArrayCreationExpression_ClassOrInterfaceArray]
$creadListPrec :: ReadPrec [ArrayCreationExpression_ClassOrInterfaceArray]
readPrec :: ReadPrec ArrayCreationExpression_ClassOrInterfaceArray
$creadPrec :: ReadPrec ArrayCreationExpression_ClassOrInterfaceArray
readList :: ReadS [ArrayCreationExpression_ClassOrInterfaceArray]
$creadList :: ReadS [ArrayCreationExpression_ClassOrInterfaceArray]
readsPrec :: Int -> ReadS ArrayCreationExpression_ClassOrInterfaceArray
$creadsPrec :: Int -> ReadS ArrayCreationExpression_ClassOrInterfaceArray
Read, Int
-> ArrayCreationExpression_ClassOrInterfaceArray
-> String
-> String
[ArrayCreationExpression_ClassOrInterfaceArray] -> String -> String
ArrayCreationExpression_ClassOrInterfaceArray -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ArrayCreationExpression_ClassOrInterfaceArray] -> String -> String
$cshowList :: [ArrayCreationExpression_ClassOrInterfaceArray] -> String -> String
show :: ArrayCreationExpression_ClassOrInterfaceArray -> String
$cshow :: ArrayCreationExpression_ClassOrInterfaceArray -> String
showsPrec :: Int
-> ArrayCreationExpression_ClassOrInterfaceArray
-> String
-> String
$cshowsPrec :: Int
-> ArrayCreationExpression_ClassOrInterfaceArray
-> String
-> String
Show)

_ArrayCreationExpression_ClassOrInterfaceArray :: Name
_ArrayCreationExpression_ClassOrInterfaceArray = (String -> Name
Core.Name String
"hydra/ext/java/syntax.ArrayCreationExpression.ClassOrInterfaceArray")

_ArrayCreationExpression_ClassOrInterfaceArray_type :: FieldName
_ArrayCreationExpression_ClassOrInterfaceArray_type = (String -> FieldName
Core.FieldName String
"type")

_ArrayCreationExpression_ClassOrInterfaceArray_dims :: FieldName
_ArrayCreationExpression_ClassOrInterfaceArray_dims = (String -> FieldName
Core.FieldName String
"dims")

_ArrayCreationExpression_ClassOrInterfaceArray_array :: FieldName
_ArrayCreationExpression_ClassOrInterfaceArray_array = (String -> FieldName
Core.FieldName String
"array")

data DimExpr = 
  DimExpr {
    DimExpr -> [Annotation]
dimExprAnnotations :: [Annotation],
    DimExpr -> Maybe Expression
dimExprExpression :: (Maybe Expression)}
  deriving (DimExpr -> DimExpr -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DimExpr -> DimExpr -> Bool
$c/= :: DimExpr -> DimExpr -> Bool
== :: DimExpr -> DimExpr -> Bool
$c== :: DimExpr -> DimExpr -> Bool
Eq, Eq DimExpr
DimExpr -> DimExpr -> Bool
DimExpr -> DimExpr -> Ordering
DimExpr -> DimExpr -> DimExpr
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: DimExpr -> DimExpr -> DimExpr
$cmin :: DimExpr -> DimExpr -> DimExpr
max :: DimExpr -> DimExpr -> DimExpr
$cmax :: DimExpr -> DimExpr -> DimExpr
>= :: DimExpr -> DimExpr -> Bool
$c>= :: DimExpr -> DimExpr -> Bool
> :: DimExpr -> DimExpr -> Bool
$c> :: DimExpr -> DimExpr -> Bool
<= :: DimExpr -> DimExpr -> Bool
$c<= :: DimExpr -> DimExpr -> Bool
< :: DimExpr -> DimExpr -> Bool
$c< :: DimExpr -> DimExpr -> Bool
compare :: DimExpr -> DimExpr -> Ordering
$ccompare :: DimExpr -> DimExpr -> Ordering
Ord, ReadPrec [DimExpr]
ReadPrec DimExpr
Int -> ReadS DimExpr
ReadS [DimExpr]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DimExpr]
$creadListPrec :: ReadPrec [DimExpr]
readPrec :: ReadPrec DimExpr
$creadPrec :: ReadPrec DimExpr
readList :: ReadS [DimExpr]
$creadList :: ReadS [DimExpr]
readsPrec :: Int -> ReadS DimExpr
$creadsPrec :: Int -> ReadS DimExpr
Read, Int -> DimExpr -> String -> String
[DimExpr] -> String -> String
DimExpr -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [DimExpr] -> String -> String
$cshowList :: [DimExpr] -> String -> String
show :: DimExpr -> String
$cshow :: DimExpr -> String
showsPrec :: Int -> DimExpr -> String -> String
$cshowsPrec :: Int -> DimExpr -> String -> String
Show)

_DimExpr :: Name
_DimExpr = (String -> Name
Core.Name String
"hydra/ext/java/syntax.DimExpr")

_DimExpr_annotations :: FieldName
_DimExpr_annotations = (String -> FieldName
Core.FieldName String
"annotations")

_DimExpr_expression :: FieldName
_DimExpr_expression = (String -> FieldName
Core.FieldName String
"expression")

data Expression = 
  ExpressionLambda LambdaExpression |
  ExpressionAssignment AssignmentExpression
  deriving (Expression -> Expression -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Expression -> Expression -> Bool
$c/= :: Expression -> Expression -> Bool
== :: Expression -> Expression -> Bool
$c== :: Expression -> Expression -> Bool
Eq, Eq Expression
Expression -> Expression -> Bool
Expression -> Expression -> Ordering
Expression -> Expression -> Expression
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Expression -> Expression -> Expression
$cmin :: Expression -> Expression -> Expression
max :: Expression -> Expression -> Expression
$cmax :: Expression -> Expression -> Expression
>= :: Expression -> Expression -> Bool
$c>= :: Expression -> Expression -> Bool
> :: Expression -> Expression -> Bool
$c> :: Expression -> Expression -> Bool
<= :: Expression -> Expression -> Bool
$c<= :: Expression -> Expression -> Bool
< :: Expression -> Expression -> Bool
$c< :: Expression -> Expression -> Bool
compare :: Expression -> Expression -> Ordering
$ccompare :: Expression -> Expression -> Ordering
Ord, ReadPrec [Expression]
ReadPrec Expression
Int -> ReadS Expression
ReadS [Expression]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Expression]
$creadListPrec :: ReadPrec [Expression]
readPrec :: ReadPrec Expression
$creadPrec :: ReadPrec Expression
readList :: ReadS [Expression]
$creadList :: ReadS [Expression]
readsPrec :: Int -> ReadS Expression
$creadsPrec :: Int -> ReadS Expression
Read, Int -> Expression -> String -> String
[Expression] -> String -> String
Expression -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [Expression] -> String -> String
$cshowList :: [Expression] -> String -> String
show :: Expression -> String
$cshow :: Expression -> String
showsPrec :: Int -> Expression -> String -> String
$cshowsPrec :: Int -> Expression -> String -> String
Show)

_Expression :: Name
_Expression = (String -> Name
Core.Name String
"hydra/ext/java/syntax.Expression")

_Expression_lambda :: FieldName
_Expression_lambda = (String -> FieldName
Core.FieldName String
"lambda")

_Expression_assignment :: FieldName
_Expression_assignment = (String -> FieldName
Core.FieldName String
"assignment")

data LambdaExpression = 
  LambdaExpression {
    LambdaExpression -> LambdaParameters
lambdaExpressionParameters :: LambdaParameters,
    LambdaExpression -> LambdaBody
lambdaExpressionBody :: LambdaBody}
  deriving (LambdaExpression -> LambdaExpression -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LambdaExpression -> LambdaExpression -> Bool
$c/= :: LambdaExpression -> LambdaExpression -> Bool
== :: LambdaExpression -> LambdaExpression -> Bool
$c== :: LambdaExpression -> LambdaExpression -> Bool
Eq, Eq LambdaExpression
LambdaExpression -> LambdaExpression -> Bool
LambdaExpression -> LambdaExpression -> Ordering
LambdaExpression -> LambdaExpression -> LambdaExpression
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: LambdaExpression -> LambdaExpression -> LambdaExpression
$cmin :: LambdaExpression -> LambdaExpression -> LambdaExpression
max :: LambdaExpression -> LambdaExpression -> LambdaExpression
$cmax :: LambdaExpression -> LambdaExpression -> LambdaExpression
>= :: LambdaExpression -> LambdaExpression -> Bool
$c>= :: LambdaExpression -> LambdaExpression -> Bool
> :: LambdaExpression -> LambdaExpression -> Bool
$c> :: LambdaExpression -> LambdaExpression -> Bool
<= :: LambdaExpression -> LambdaExpression -> Bool
$c<= :: LambdaExpression -> LambdaExpression -> Bool
< :: LambdaExpression -> LambdaExpression -> Bool
$c< :: LambdaExpression -> LambdaExpression -> Bool
compare :: LambdaExpression -> LambdaExpression -> Ordering
$ccompare :: LambdaExpression -> LambdaExpression -> Ordering
Ord, ReadPrec [LambdaExpression]
ReadPrec LambdaExpression
Int -> ReadS LambdaExpression
ReadS [LambdaExpression]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [LambdaExpression]
$creadListPrec :: ReadPrec [LambdaExpression]
readPrec :: ReadPrec LambdaExpression
$creadPrec :: ReadPrec LambdaExpression
readList :: ReadS [LambdaExpression]
$creadList :: ReadS [LambdaExpression]
readsPrec :: Int -> ReadS LambdaExpression
$creadsPrec :: Int -> ReadS LambdaExpression
Read, Int -> LambdaExpression -> String -> String
[LambdaExpression] -> String -> String
LambdaExpression -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [LambdaExpression] -> String -> String
$cshowList :: [LambdaExpression] -> String -> String
show :: LambdaExpression -> String
$cshow :: LambdaExpression -> String
showsPrec :: Int -> LambdaExpression -> String -> String
$cshowsPrec :: Int -> LambdaExpression -> String -> String
Show)

_LambdaExpression :: Name
_LambdaExpression = (String -> Name
Core.Name String
"hydra/ext/java/syntax.LambdaExpression")

_LambdaExpression_parameters :: FieldName
_LambdaExpression_parameters = (String -> FieldName
Core.FieldName String
"parameters")

_LambdaExpression_body :: FieldName
_LambdaExpression_body = (String -> FieldName
Core.FieldName String
"body")

data LambdaParameters = 
  LambdaParametersTuple [LambdaParameters] |
  LambdaParametersSingle Identifier
  deriving (LambdaParameters -> LambdaParameters -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LambdaParameters -> LambdaParameters -> Bool
$c/= :: LambdaParameters -> LambdaParameters -> Bool
== :: LambdaParameters -> LambdaParameters -> Bool
$c== :: LambdaParameters -> LambdaParameters -> Bool
Eq, Eq LambdaParameters
LambdaParameters -> LambdaParameters -> Bool
LambdaParameters -> LambdaParameters -> Ordering
LambdaParameters -> LambdaParameters -> LambdaParameters
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: LambdaParameters -> LambdaParameters -> LambdaParameters
$cmin :: LambdaParameters -> LambdaParameters -> LambdaParameters
max :: LambdaParameters -> LambdaParameters -> LambdaParameters
$cmax :: LambdaParameters -> LambdaParameters -> LambdaParameters
>= :: LambdaParameters -> LambdaParameters -> Bool
$c>= :: LambdaParameters -> LambdaParameters -> Bool
> :: LambdaParameters -> LambdaParameters -> Bool
$c> :: LambdaParameters -> LambdaParameters -> Bool
<= :: LambdaParameters -> LambdaParameters -> Bool
$c<= :: LambdaParameters -> LambdaParameters -> Bool
< :: LambdaParameters -> LambdaParameters -> Bool
$c< :: LambdaParameters -> LambdaParameters -> Bool
compare :: LambdaParameters -> LambdaParameters -> Ordering
$ccompare :: LambdaParameters -> LambdaParameters -> Ordering
Ord, ReadPrec [LambdaParameters]
ReadPrec LambdaParameters
Int -> ReadS LambdaParameters
ReadS [LambdaParameters]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [LambdaParameters]
$creadListPrec :: ReadPrec [LambdaParameters]
readPrec :: ReadPrec LambdaParameters
$creadPrec :: ReadPrec LambdaParameters
readList :: ReadS [LambdaParameters]
$creadList :: ReadS [LambdaParameters]
readsPrec :: Int -> ReadS LambdaParameters
$creadsPrec :: Int -> ReadS LambdaParameters
Read, Int -> LambdaParameters -> String -> String
[LambdaParameters] -> String -> String
LambdaParameters -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [LambdaParameters] -> String -> String
$cshowList :: [LambdaParameters] -> String -> String
show :: LambdaParameters -> String
$cshow :: LambdaParameters -> String
showsPrec :: Int -> LambdaParameters -> String -> String
$cshowsPrec :: Int -> LambdaParameters -> String -> String
Show)

_LambdaParameters :: Name
_LambdaParameters = (String -> Name
Core.Name String
"hydra/ext/java/syntax.LambdaParameters")

_LambdaParameters_tuple :: FieldName
_LambdaParameters_tuple = (String -> FieldName
Core.FieldName String
"tuple")

_LambdaParameters_single :: FieldName
_LambdaParameters_single = (String -> FieldName
Core.FieldName String
"single")

data LambdaParameter = 
  LambdaParameterNormal LambdaParameter_Normal |
  LambdaParameterVariableArity VariableArityParameter
  deriving (LambdaParameter -> LambdaParameter -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LambdaParameter -> LambdaParameter -> Bool
$c/= :: LambdaParameter -> LambdaParameter -> Bool
== :: LambdaParameter -> LambdaParameter -> Bool
$c== :: LambdaParameter -> LambdaParameter -> Bool
Eq, Eq LambdaParameter
LambdaParameter -> LambdaParameter -> Bool
LambdaParameter -> LambdaParameter -> Ordering
LambdaParameter -> LambdaParameter -> LambdaParameter
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: LambdaParameter -> LambdaParameter -> LambdaParameter
$cmin :: LambdaParameter -> LambdaParameter -> LambdaParameter
max :: LambdaParameter -> LambdaParameter -> LambdaParameter
$cmax :: LambdaParameter -> LambdaParameter -> LambdaParameter
>= :: LambdaParameter -> LambdaParameter -> Bool
$c>= :: LambdaParameter -> LambdaParameter -> Bool
> :: LambdaParameter -> LambdaParameter -> Bool
$c> :: LambdaParameter -> LambdaParameter -> Bool
<= :: LambdaParameter -> LambdaParameter -> Bool
$c<= :: LambdaParameter -> LambdaParameter -> Bool
< :: LambdaParameter -> LambdaParameter -> Bool
$c< :: LambdaParameter -> LambdaParameter -> Bool
compare :: LambdaParameter -> LambdaParameter -> Ordering
$ccompare :: LambdaParameter -> LambdaParameter -> Ordering
Ord, ReadPrec [LambdaParameter]
ReadPrec LambdaParameter
Int -> ReadS LambdaParameter
ReadS [LambdaParameter]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [LambdaParameter]
$creadListPrec :: ReadPrec [LambdaParameter]
readPrec :: ReadPrec LambdaParameter
$creadPrec :: ReadPrec LambdaParameter
readList :: ReadS [LambdaParameter]
$creadList :: ReadS [LambdaParameter]
readsPrec :: Int -> ReadS LambdaParameter
$creadsPrec :: Int -> ReadS LambdaParameter
Read, Int -> LambdaParameter -> String -> String
[LambdaParameter] -> String -> String
LambdaParameter -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [LambdaParameter] -> String -> String
$cshowList :: [LambdaParameter] -> String -> String
show :: LambdaParameter -> String
$cshow :: LambdaParameter -> String
showsPrec :: Int -> LambdaParameter -> String -> String
$cshowsPrec :: Int -> LambdaParameter -> String -> String
Show)

_LambdaParameter :: Name
_LambdaParameter = (String -> Name
Core.Name String
"hydra/ext/java/syntax.LambdaParameter")

_LambdaParameter_normal :: FieldName
_LambdaParameter_normal = (String -> FieldName
Core.FieldName String
"normal")

_LambdaParameter_variableArity :: FieldName
_LambdaParameter_variableArity = (String -> FieldName
Core.FieldName String
"variableArity")

data LambdaParameter_Normal = 
  LambdaParameter_Normal {
    LambdaParameter_Normal -> [VariableModifier]
lambdaParameter_NormalModifiers :: [VariableModifier],
    LambdaParameter_Normal -> LambdaParameterType
lambdaParameter_NormalType :: LambdaParameterType,
    LambdaParameter_Normal -> VariableDeclaratorId
lambdaParameter_NormalId :: VariableDeclaratorId}
  deriving (LambdaParameter_Normal -> LambdaParameter_Normal -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LambdaParameter_Normal -> LambdaParameter_Normal -> Bool
$c/= :: LambdaParameter_Normal -> LambdaParameter_Normal -> Bool
== :: LambdaParameter_Normal -> LambdaParameter_Normal -> Bool
$c== :: LambdaParameter_Normal -> LambdaParameter_Normal -> Bool
Eq, Eq LambdaParameter_Normal
LambdaParameter_Normal -> LambdaParameter_Normal -> Bool
LambdaParameter_Normal -> LambdaParameter_Normal -> Ordering
LambdaParameter_Normal
-> LambdaParameter_Normal -> LambdaParameter_Normal
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: LambdaParameter_Normal
-> LambdaParameter_Normal -> LambdaParameter_Normal
$cmin :: LambdaParameter_Normal
-> LambdaParameter_Normal -> LambdaParameter_Normal
max :: LambdaParameter_Normal
-> LambdaParameter_Normal -> LambdaParameter_Normal
$cmax :: LambdaParameter_Normal
-> LambdaParameter_Normal -> LambdaParameter_Normal
>= :: LambdaParameter_Normal -> LambdaParameter_Normal -> Bool
$c>= :: LambdaParameter_Normal -> LambdaParameter_Normal -> Bool
> :: LambdaParameter_Normal -> LambdaParameter_Normal -> Bool
$c> :: LambdaParameter_Normal -> LambdaParameter_Normal -> Bool
<= :: LambdaParameter_Normal -> LambdaParameter_Normal -> Bool
$c<= :: LambdaParameter_Normal -> LambdaParameter_Normal -> Bool
< :: LambdaParameter_Normal -> LambdaParameter_Normal -> Bool
$c< :: LambdaParameter_Normal -> LambdaParameter_Normal -> Bool
compare :: LambdaParameter_Normal -> LambdaParameter_Normal -> Ordering
$ccompare :: LambdaParameter_Normal -> LambdaParameter_Normal -> Ordering
Ord, ReadPrec [LambdaParameter_Normal]
ReadPrec LambdaParameter_Normal
Int -> ReadS LambdaParameter_Normal
ReadS [LambdaParameter_Normal]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [LambdaParameter_Normal]
$creadListPrec :: ReadPrec [LambdaParameter_Normal]
readPrec :: ReadPrec LambdaParameter_Normal
$creadPrec :: ReadPrec LambdaParameter_Normal
readList :: ReadS [LambdaParameter_Normal]
$creadList :: ReadS [LambdaParameter_Normal]
readsPrec :: Int -> ReadS LambdaParameter_Normal
$creadsPrec :: Int -> ReadS LambdaParameter_Normal
Read, Int -> LambdaParameter_Normal -> String -> String
[LambdaParameter_Normal] -> String -> String
LambdaParameter_Normal -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [LambdaParameter_Normal] -> String -> String
$cshowList :: [LambdaParameter_Normal] -> String -> String
show :: LambdaParameter_Normal -> String
$cshow :: LambdaParameter_Normal -> String
showsPrec :: Int -> LambdaParameter_Normal -> String -> String
$cshowsPrec :: Int -> LambdaParameter_Normal -> String -> String
Show)

_LambdaParameter_Normal :: Name
_LambdaParameter_Normal = (String -> Name
Core.Name String
"hydra/ext/java/syntax.LambdaParameter.Normal")

_LambdaParameter_Normal_modifiers :: FieldName
_LambdaParameter_Normal_modifiers = (String -> FieldName
Core.FieldName String
"modifiers")

_LambdaParameter_Normal_type :: FieldName
_LambdaParameter_Normal_type = (String -> FieldName
Core.FieldName String
"type")

_LambdaParameter_Normal_id :: FieldName
_LambdaParameter_Normal_id = (String -> FieldName
Core.FieldName String
"id")

data LambdaParameterType = 
  LambdaParameterTypeType UnannType |
  LambdaParameterTypeVar 
  deriving (LambdaParameterType -> LambdaParameterType -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LambdaParameterType -> LambdaParameterType -> Bool
$c/= :: LambdaParameterType -> LambdaParameterType -> Bool
== :: LambdaParameterType -> LambdaParameterType -> Bool
$c== :: LambdaParameterType -> LambdaParameterType -> Bool
Eq, Eq LambdaParameterType
LambdaParameterType -> LambdaParameterType -> Bool
LambdaParameterType -> LambdaParameterType -> Ordering
LambdaParameterType -> LambdaParameterType -> LambdaParameterType
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: LambdaParameterType -> LambdaParameterType -> LambdaParameterType
$cmin :: LambdaParameterType -> LambdaParameterType -> LambdaParameterType
max :: LambdaParameterType -> LambdaParameterType -> LambdaParameterType
$cmax :: LambdaParameterType -> LambdaParameterType -> LambdaParameterType
>= :: LambdaParameterType -> LambdaParameterType -> Bool
$c>= :: LambdaParameterType -> LambdaParameterType -> Bool
> :: LambdaParameterType -> LambdaParameterType -> Bool
$c> :: LambdaParameterType -> LambdaParameterType -> Bool
<= :: LambdaParameterType -> LambdaParameterType -> Bool
$c<= :: LambdaParameterType -> LambdaParameterType -> Bool
< :: LambdaParameterType -> LambdaParameterType -> Bool
$c< :: LambdaParameterType -> LambdaParameterType -> Bool
compare :: LambdaParameterType -> LambdaParameterType -> Ordering
$ccompare :: LambdaParameterType -> LambdaParameterType -> Ordering
Ord, ReadPrec [LambdaParameterType]
ReadPrec LambdaParameterType
Int -> ReadS LambdaParameterType
ReadS [LambdaParameterType]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [LambdaParameterType]
$creadListPrec :: ReadPrec [LambdaParameterType]
readPrec :: ReadPrec LambdaParameterType
$creadPrec :: ReadPrec LambdaParameterType
readList :: ReadS [LambdaParameterType]
$creadList :: ReadS [LambdaParameterType]
readsPrec :: Int -> ReadS LambdaParameterType
$creadsPrec :: Int -> ReadS LambdaParameterType
Read, Int -> LambdaParameterType -> String -> String
[LambdaParameterType] -> String -> String
LambdaParameterType -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [LambdaParameterType] -> String -> String
$cshowList :: [LambdaParameterType] -> String -> String
show :: LambdaParameterType -> String
$cshow :: LambdaParameterType -> String
showsPrec :: Int -> LambdaParameterType -> String -> String
$cshowsPrec :: Int -> LambdaParameterType -> String -> String
Show)

_LambdaParameterType :: Name
_LambdaParameterType = (String -> Name
Core.Name String
"hydra/ext/java/syntax.LambdaParameterType")

_LambdaParameterType_type :: FieldName
_LambdaParameterType_type = (String -> FieldName
Core.FieldName String
"type")

_LambdaParameterType_var :: FieldName
_LambdaParameterType_var = (String -> FieldName
Core.FieldName String
"var")

data LambdaBody = 
  LambdaBodyExpression Expression |
  LambdaBodyBlock Block
  deriving (LambdaBody -> LambdaBody -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LambdaBody -> LambdaBody -> Bool
$c/= :: LambdaBody -> LambdaBody -> Bool
== :: LambdaBody -> LambdaBody -> Bool
$c== :: LambdaBody -> LambdaBody -> Bool
Eq, Eq LambdaBody
LambdaBody -> LambdaBody -> Bool
LambdaBody -> LambdaBody -> Ordering
LambdaBody -> LambdaBody -> LambdaBody
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: LambdaBody -> LambdaBody -> LambdaBody
$cmin :: LambdaBody -> LambdaBody -> LambdaBody
max :: LambdaBody -> LambdaBody -> LambdaBody
$cmax :: LambdaBody -> LambdaBody -> LambdaBody
>= :: LambdaBody -> LambdaBody -> Bool
$c>= :: LambdaBody -> LambdaBody -> Bool
> :: LambdaBody -> LambdaBody -> Bool
$c> :: LambdaBody -> LambdaBody -> Bool
<= :: LambdaBody -> LambdaBody -> Bool
$c<= :: LambdaBody -> LambdaBody -> Bool
< :: LambdaBody -> LambdaBody -> Bool
$c< :: LambdaBody -> LambdaBody -> Bool
compare :: LambdaBody -> LambdaBody -> Ordering
$ccompare :: LambdaBody -> LambdaBody -> Ordering
Ord, ReadPrec [LambdaBody]
ReadPrec LambdaBody
Int -> ReadS LambdaBody
ReadS [LambdaBody]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [LambdaBody]
$creadListPrec :: ReadPrec [LambdaBody]
readPrec :: ReadPrec LambdaBody
$creadPrec :: ReadPrec LambdaBody
readList :: ReadS [LambdaBody]
$creadList :: ReadS [LambdaBody]
readsPrec :: Int -> ReadS LambdaBody
$creadsPrec :: Int -> ReadS LambdaBody
Read, Int -> LambdaBody -> String -> String
[LambdaBody] -> String -> String
LambdaBody -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [LambdaBody] -> String -> String
$cshowList :: [LambdaBody] -> String -> String
show :: LambdaBody -> String
$cshow :: LambdaBody -> String
showsPrec :: Int -> LambdaBody -> String -> String
$cshowsPrec :: Int -> LambdaBody -> String -> String
Show)

_LambdaBody :: Name
_LambdaBody = (String -> Name
Core.Name String
"hydra/ext/java/syntax.LambdaBody")

_LambdaBody_expression :: FieldName
_LambdaBody_expression = (String -> FieldName
Core.FieldName String
"expression")

_LambdaBody_block :: FieldName
_LambdaBody_block = (String -> FieldName
Core.FieldName String
"block")

data AssignmentExpression = 
  AssignmentExpressionConditional ConditionalExpression |
  AssignmentExpressionAssignment Assignment
  deriving (AssignmentExpression -> AssignmentExpression -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AssignmentExpression -> AssignmentExpression -> Bool
$c/= :: AssignmentExpression -> AssignmentExpression -> Bool
== :: AssignmentExpression -> AssignmentExpression -> Bool
$c== :: AssignmentExpression -> AssignmentExpression -> Bool
Eq, Eq AssignmentExpression
AssignmentExpression -> AssignmentExpression -> Bool
AssignmentExpression -> AssignmentExpression -> Ordering
AssignmentExpression
-> AssignmentExpression -> AssignmentExpression
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: AssignmentExpression
-> AssignmentExpression -> AssignmentExpression
$cmin :: AssignmentExpression
-> AssignmentExpression -> AssignmentExpression
max :: AssignmentExpression
-> AssignmentExpression -> AssignmentExpression
$cmax :: AssignmentExpression
-> AssignmentExpression -> AssignmentExpression
>= :: AssignmentExpression -> AssignmentExpression -> Bool
$c>= :: AssignmentExpression -> AssignmentExpression -> Bool
> :: AssignmentExpression -> AssignmentExpression -> Bool
$c> :: AssignmentExpression -> AssignmentExpression -> Bool
<= :: AssignmentExpression -> AssignmentExpression -> Bool
$c<= :: AssignmentExpression -> AssignmentExpression -> Bool
< :: AssignmentExpression -> AssignmentExpression -> Bool
$c< :: AssignmentExpression -> AssignmentExpression -> Bool
compare :: AssignmentExpression -> AssignmentExpression -> Ordering
$ccompare :: AssignmentExpression -> AssignmentExpression -> Ordering
Ord, ReadPrec [AssignmentExpression]
ReadPrec AssignmentExpression
Int -> ReadS AssignmentExpression
ReadS [AssignmentExpression]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AssignmentExpression]
$creadListPrec :: ReadPrec [AssignmentExpression]
readPrec :: ReadPrec AssignmentExpression
$creadPrec :: ReadPrec AssignmentExpression
readList :: ReadS [AssignmentExpression]
$creadList :: ReadS [AssignmentExpression]
readsPrec :: Int -> ReadS AssignmentExpression
$creadsPrec :: Int -> ReadS AssignmentExpression
Read, Int -> AssignmentExpression -> String -> String
[AssignmentExpression] -> String -> String
AssignmentExpression -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [AssignmentExpression] -> String -> String
$cshowList :: [AssignmentExpression] -> String -> String
show :: AssignmentExpression -> String
$cshow :: AssignmentExpression -> String
showsPrec :: Int -> AssignmentExpression -> String -> String
$cshowsPrec :: Int -> AssignmentExpression -> String -> String
Show)

_AssignmentExpression :: Name
_AssignmentExpression = (String -> Name
Core.Name String
"hydra/ext/java/syntax.AssignmentExpression")

_AssignmentExpression_conditional :: FieldName
_AssignmentExpression_conditional = (String -> FieldName
Core.FieldName String
"conditional")

_AssignmentExpression_assignment :: FieldName
_AssignmentExpression_assignment = (String -> FieldName
Core.FieldName String
"assignment")

data Assignment = 
  Assignment {
    Assignment -> LeftHandSide
assignmentLhs :: LeftHandSide,
    Assignment -> AssignmentOperator
assignmentOp :: AssignmentOperator,
    Assignment -> Expression
assignmentExpression :: Expression}
  deriving (Assignment -> Assignment -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Assignment -> Assignment -> Bool
$c/= :: Assignment -> Assignment -> Bool
== :: Assignment -> Assignment -> Bool
$c== :: Assignment -> Assignment -> Bool
Eq, Eq Assignment
Assignment -> Assignment -> Bool
Assignment -> Assignment -> Ordering
Assignment -> Assignment -> Assignment
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Assignment -> Assignment -> Assignment
$cmin :: Assignment -> Assignment -> Assignment
max :: Assignment -> Assignment -> Assignment
$cmax :: Assignment -> Assignment -> Assignment
>= :: Assignment -> Assignment -> Bool
$c>= :: Assignment -> Assignment -> Bool
> :: Assignment -> Assignment -> Bool
$c> :: Assignment -> Assignment -> Bool
<= :: Assignment -> Assignment -> Bool
$c<= :: Assignment -> Assignment -> Bool
< :: Assignment -> Assignment -> Bool
$c< :: Assignment -> Assignment -> Bool
compare :: Assignment -> Assignment -> Ordering
$ccompare :: Assignment -> Assignment -> Ordering
Ord, ReadPrec [Assignment]
ReadPrec Assignment
Int -> ReadS Assignment
ReadS [Assignment]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Assignment]
$creadListPrec :: ReadPrec [Assignment]
readPrec :: ReadPrec Assignment
$creadPrec :: ReadPrec Assignment
readList :: ReadS [Assignment]
$creadList :: ReadS [Assignment]
readsPrec :: Int -> ReadS Assignment
$creadsPrec :: Int -> ReadS Assignment
Read, Int -> Assignment -> String -> String
[Assignment] -> String -> String
Assignment -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [Assignment] -> String -> String
$cshowList :: [Assignment] -> String -> String
show :: Assignment -> String
$cshow :: Assignment -> String
showsPrec :: Int -> Assignment -> String -> String
$cshowsPrec :: Int -> Assignment -> String -> String
Show)

_Assignment :: Name
_Assignment = (String -> Name
Core.Name String
"hydra/ext/java/syntax.Assignment")

_Assignment_lhs :: FieldName
_Assignment_lhs = (String -> FieldName
Core.FieldName String
"lhs")

_Assignment_op :: FieldName
_Assignment_op = (String -> FieldName
Core.FieldName String
"op")

_Assignment_expression :: FieldName
_Assignment_expression = (String -> FieldName
Core.FieldName String
"expression")

data LeftHandSide = 
  LeftHandSideExpressionName ExpressionName |
  LeftHandSideFieldAccess FieldAccess |
  LeftHandSideArrayAccess ArrayAccess
  deriving (LeftHandSide -> LeftHandSide -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LeftHandSide -> LeftHandSide -> Bool
$c/= :: LeftHandSide -> LeftHandSide -> Bool
== :: LeftHandSide -> LeftHandSide -> Bool
$c== :: LeftHandSide -> LeftHandSide -> Bool
Eq, Eq LeftHandSide
LeftHandSide -> LeftHandSide -> Bool
LeftHandSide -> LeftHandSide -> Ordering
LeftHandSide -> LeftHandSide -> LeftHandSide
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: LeftHandSide -> LeftHandSide -> LeftHandSide
$cmin :: LeftHandSide -> LeftHandSide -> LeftHandSide
max :: LeftHandSide -> LeftHandSide -> LeftHandSide
$cmax :: LeftHandSide -> LeftHandSide -> LeftHandSide
>= :: LeftHandSide -> LeftHandSide -> Bool
$c>= :: LeftHandSide -> LeftHandSide -> Bool
> :: LeftHandSide -> LeftHandSide -> Bool
$c> :: LeftHandSide -> LeftHandSide -> Bool
<= :: LeftHandSide -> LeftHandSide -> Bool
$c<= :: LeftHandSide -> LeftHandSide -> Bool
< :: LeftHandSide -> LeftHandSide -> Bool
$c< :: LeftHandSide -> LeftHandSide -> Bool
compare :: LeftHandSide -> LeftHandSide -> Ordering
$ccompare :: LeftHandSide -> LeftHandSide -> Ordering
Ord, ReadPrec [LeftHandSide]
ReadPrec LeftHandSide
Int -> ReadS LeftHandSide
ReadS [LeftHandSide]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [LeftHandSide]
$creadListPrec :: ReadPrec [LeftHandSide]
readPrec :: ReadPrec LeftHandSide
$creadPrec :: ReadPrec LeftHandSide
readList :: ReadS [LeftHandSide]
$creadList :: ReadS [LeftHandSide]
readsPrec :: Int -> ReadS LeftHandSide
$creadsPrec :: Int -> ReadS LeftHandSide
Read, Int -> LeftHandSide -> String -> String
[LeftHandSide] -> String -> String
LeftHandSide -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [LeftHandSide] -> String -> String
$cshowList :: [LeftHandSide] -> String -> String
show :: LeftHandSide -> String
$cshow :: LeftHandSide -> String
showsPrec :: Int -> LeftHandSide -> String -> String
$cshowsPrec :: Int -> LeftHandSide -> String -> String
Show)

_LeftHandSide :: Name
_LeftHandSide = (String -> Name
Core.Name String
"hydra/ext/java/syntax.LeftHandSide")

_LeftHandSide_expressionName :: FieldName
_LeftHandSide_expressionName = (String -> FieldName
Core.FieldName String
"expressionName")

_LeftHandSide_fieldAccess :: FieldName
_LeftHandSide_fieldAccess = (String -> FieldName
Core.FieldName String
"fieldAccess")

_LeftHandSide_arrayAccess :: FieldName
_LeftHandSide_arrayAccess = (String -> FieldName
Core.FieldName String
"arrayAccess")

data AssignmentOperator = 
  AssignmentOperatorSimple  |
  AssignmentOperatorTimes  |
  AssignmentOperatorDiv  |
  AssignmentOperatorMod  |
  AssignmentOperatorPlus  |
  AssignmentOperatorMinus  |
  AssignmentOperatorShiftLeft  |
  AssignmentOperatorShiftRight  |
  AssignmentOperatorShiftRightZeroFill  |
  AssignmentOperatorAnd  |
  AssignmentOperatorXor  |
  AssignmentOperatorOr 
  deriving (AssignmentOperator -> AssignmentOperator -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AssignmentOperator -> AssignmentOperator -> Bool
$c/= :: AssignmentOperator -> AssignmentOperator -> Bool
== :: AssignmentOperator -> AssignmentOperator -> Bool
$c== :: AssignmentOperator -> AssignmentOperator -> Bool
Eq, Eq AssignmentOperator
AssignmentOperator -> AssignmentOperator -> Bool
AssignmentOperator -> AssignmentOperator -> Ordering
AssignmentOperator -> AssignmentOperator -> AssignmentOperator
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: AssignmentOperator -> AssignmentOperator -> AssignmentOperator
$cmin :: AssignmentOperator -> AssignmentOperator -> AssignmentOperator
max :: AssignmentOperator -> AssignmentOperator -> AssignmentOperator
$cmax :: AssignmentOperator -> AssignmentOperator -> AssignmentOperator
>= :: AssignmentOperator -> AssignmentOperator -> Bool
$c>= :: AssignmentOperator -> AssignmentOperator -> Bool
> :: AssignmentOperator -> AssignmentOperator -> Bool
$c> :: AssignmentOperator -> AssignmentOperator -> Bool
<= :: AssignmentOperator -> AssignmentOperator -> Bool
$c<= :: AssignmentOperator -> AssignmentOperator -> Bool
< :: AssignmentOperator -> AssignmentOperator -> Bool
$c< :: AssignmentOperator -> AssignmentOperator -> Bool
compare :: AssignmentOperator -> AssignmentOperator -> Ordering
$ccompare :: AssignmentOperator -> AssignmentOperator -> Ordering
Ord, ReadPrec [AssignmentOperator]
ReadPrec AssignmentOperator
Int -> ReadS AssignmentOperator
ReadS [AssignmentOperator]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AssignmentOperator]
$creadListPrec :: ReadPrec [AssignmentOperator]
readPrec :: ReadPrec AssignmentOperator
$creadPrec :: ReadPrec AssignmentOperator
readList :: ReadS [AssignmentOperator]
$creadList :: ReadS [AssignmentOperator]
readsPrec :: Int -> ReadS AssignmentOperator
$creadsPrec :: Int -> ReadS AssignmentOperator
Read, Int -> AssignmentOperator -> String -> String
[AssignmentOperator] -> String -> String
AssignmentOperator -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [AssignmentOperator] -> String -> String
$cshowList :: [AssignmentOperator] -> String -> String
show :: AssignmentOperator -> String
$cshow :: AssignmentOperator -> String
showsPrec :: Int -> AssignmentOperator -> String -> String
$cshowsPrec :: Int -> AssignmentOperator -> String -> String
Show)

_AssignmentOperator :: Name
_AssignmentOperator = (String -> Name
Core.Name String
"hydra/ext/java/syntax.AssignmentOperator")

_AssignmentOperator_simple :: FieldName
_AssignmentOperator_simple = (String -> FieldName
Core.FieldName String
"simple")

_AssignmentOperator_times :: FieldName
_AssignmentOperator_times = (String -> FieldName
Core.FieldName String
"times")

_AssignmentOperator_div :: FieldName
_AssignmentOperator_div = (String -> FieldName
Core.FieldName String
"div")

_AssignmentOperator_mod :: FieldName
_AssignmentOperator_mod = (String -> FieldName
Core.FieldName String
"mod")

_AssignmentOperator_plus :: FieldName
_AssignmentOperator_plus = (String -> FieldName
Core.FieldName String
"plus")

_AssignmentOperator_minus :: FieldName
_AssignmentOperator_minus = (String -> FieldName
Core.FieldName String
"minus")

_AssignmentOperator_shiftLeft :: FieldName
_AssignmentOperator_shiftLeft = (String -> FieldName
Core.FieldName String
"shiftLeft")

_AssignmentOperator_shiftRight :: FieldName
_AssignmentOperator_shiftRight = (String -> FieldName
Core.FieldName String
"shiftRight")

_AssignmentOperator_shiftRightZeroFill :: FieldName
_AssignmentOperator_shiftRightZeroFill = (String -> FieldName
Core.FieldName String
"shiftRightZeroFill")

_AssignmentOperator_and :: FieldName
_AssignmentOperator_and = (String -> FieldName
Core.FieldName String
"and")

_AssignmentOperator_xor :: FieldName
_AssignmentOperator_xor = (String -> FieldName
Core.FieldName String
"xor")

_AssignmentOperator_or :: FieldName
_AssignmentOperator_or = (String -> FieldName
Core.FieldName String
"or")

data ConditionalExpression = 
  ConditionalExpressionSimple ConditionalOrExpression |
  ConditionalExpressionTernaryCond ConditionalExpression_TernaryCond |
  ConditionalExpressionTernaryLambda ConditionalExpression_TernaryLambda
  deriving (ConditionalExpression -> ConditionalExpression -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ConditionalExpression -> ConditionalExpression -> Bool
$c/= :: ConditionalExpression -> ConditionalExpression -> Bool
== :: ConditionalExpression -> ConditionalExpression -> Bool
$c== :: ConditionalExpression -> ConditionalExpression -> Bool
Eq, Eq ConditionalExpression
ConditionalExpression -> ConditionalExpression -> Bool
ConditionalExpression -> ConditionalExpression -> Ordering
ConditionalExpression
-> ConditionalExpression -> ConditionalExpression
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ConditionalExpression
-> ConditionalExpression -> ConditionalExpression
$cmin :: ConditionalExpression
-> ConditionalExpression -> ConditionalExpression
max :: ConditionalExpression
-> ConditionalExpression -> ConditionalExpression
$cmax :: ConditionalExpression
-> ConditionalExpression -> ConditionalExpression
>= :: ConditionalExpression -> ConditionalExpression -> Bool
$c>= :: ConditionalExpression -> ConditionalExpression -> Bool
> :: ConditionalExpression -> ConditionalExpression -> Bool
$c> :: ConditionalExpression -> ConditionalExpression -> Bool
<= :: ConditionalExpression -> ConditionalExpression -> Bool
$c<= :: ConditionalExpression -> ConditionalExpression -> Bool
< :: ConditionalExpression -> ConditionalExpression -> Bool
$c< :: ConditionalExpression -> ConditionalExpression -> Bool
compare :: ConditionalExpression -> ConditionalExpression -> Ordering
$ccompare :: ConditionalExpression -> ConditionalExpression -> Ordering
Ord, ReadPrec [ConditionalExpression]
ReadPrec ConditionalExpression
Int -> ReadS ConditionalExpression
ReadS [ConditionalExpression]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ConditionalExpression]
$creadListPrec :: ReadPrec [ConditionalExpression]
readPrec :: ReadPrec ConditionalExpression
$creadPrec :: ReadPrec ConditionalExpression
readList :: ReadS [ConditionalExpression]
$creadList :: ReadS [ConditionalExpression]
readsPrec :: Int -> ReadS ConditionalExpression
$creadsPrec :: Int -> ReadS ConditionalExpression
Read, Int -> ConditionalExpression -> String -> String
[ConditionalExpression] -> String -> String
ConditionalExpression -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ConditionalExpression] -> String -> String
$cshowList :: [ConditionalExpression] -> String -> String
show :: ConditionalExpression -> String
$cshow :: ConditionalExpression -> String
showsPrec :: Int -> ConditionalExpression -> String -> String
$cshowsPrec :: Int -> ConditionalExpression -> String -> String
Show)

_ConditionalExpression :: Name
_ConditionalExpression = (String -> Name
Core.Name String
"hydra/ext/java/syntax.ConditionalExpression")

_ConditionalExpression_simple :: FieldName
_ConditionalExpression_simple = (String -> FieldName
Core.FieldName String
"simple")

_ConditionalExpression_ternaryCond :: FieldName
_ConditionalExpression_ternaryCond = (String -> FieldName
Core.FieldName String
"ternaryCond")

_ConditionalExpression_ternaryLambda :: FieldName
_ConditionalExpression_ternaryLambda = (String -> FieldName
Core.FieldName String
"ternaryLambda")

data ConditionalExpression_TernaryCond = 
  ConditionalExpression_TernaryCond {
    ConditionalExpression_TernaryCond -> ConditionalOrExpression
conditionalExpression_TernaryCondCond :: ConditionalOrExpression,
    ConditionalExpression_TernaryCond -> Expression
conditionalExpression_TernaryCondIfTrue :: Expression,
    ConditionalExpression_TernaryCond -> ConditionalExpression
conditionalExpression_TernaryCondIfFalse :: ConditionalExpression}
  deriving (ConditionalExpression_TernaryCond
-> ConditionalExpression_TernaryCond -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ConditionalExpression_TernaryCond
-> ConditionalExpression_TernaryCond -> Bool
$c/= :: ConditionalExpression_TernaryCond
-> ConditionalExpression_TernaryCond -> Bool
== :: ConditionalExpression_TernaryCond
-> ConditionalExpression_TernaryCond -> Bool
$c== :: ConditionalExpression_TernaryCond
-> ConditionalExpression_TernaryCond -> Bool
Eq, Eq ConditionalExpression_TernaryCond
ConditionalExpression_TernaryCond
-> ConditionalExpression_TernaryCond -> Bool
ConditionalExpression_TernaryCond
-> ConditionalExpression_TernaryCond -> Ordering
ConditionalExpression_TernaryCond
-> ConditionalExpression_TernaryCond
-> ConditionalExpression_TernaryCond
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ConditionalExpression_TernaryCond
-> ConditionalExpression_TernaryCond
-> ConditionalExpression_TernaryCond
$cmin :: ConditionalExpression_TernaryCond
-> ConditionalExpression_TernaryCond
-> ConditionalExpression_TernaryCond
max :: ConditionalExpression_TernaryCond
-> ConditionalExpression_TernaryCond
-> ConditionalExpression_TernaryCond
$cmax :: ConditionalExpression_TernaryCond
-> ConditionalExpression_TernaryCond
-> ConditionalExpression_TernaryCond
>= :: ConditionalExpression_TernaryCond
-> ConditionalExpression_TernaryCond -> Bool
$c>= :: ConditionalExpression_TernaryCond
-> ConditionalExpression_TernaryCond -> Bool
> :: ConditionalExpression_TernaryCond
-> ConditionalExpression_TernaryCond -> Bool
$c> :: ConditionalExpression_TernaryCond
-> ConditionalExpression_TernaryCond -> Bool
<= :: ConditionalExpression_TernaryCond
-> ConditionalExpression_TernaryCond -> Bool
$c<= :: ConditionalExpression_TernaryCond
-> ConditionalExpression_TernaryCond -> Bool
< :: ConditionalExpression_TernaryCond
-> ConditionalExpression_TernaryCond -> Bool
$c< :: ConditionalExpression_TernaryCond
-> ConditionalExpression_TernaryCond -> Bool
compare :: ConditionalExpression_TernaryCond
-> ConditionalExpression_TernaryCond -> Ordering
$ccompare :: ConditionalExpression_TernaryCond
-> ConditionalExpression_TernaryCond -> Ordering
Ord, ReadPrec [ConditionalExpression_TernaryCond]
ReadPrec ConditionalExpression_TernaryCond
Int -> ReadS ConditionalExpression_TernaryCond
ReadS [ConditionalExpression_TernaryCond]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ConditionalExpression_TernaryCond]
$creadListPrec :: ReadPrec [ConditionalExpression_TernaryCond]
readPrec :: ReadPrec ConditionalExpression_TernaryCond
$creadPrec :: ReadPrec ConditionalExpression_TernaryCond
readList :: ReadS [ConditionalExpression_TernaryCond]
$creadList :: ReadS [ConditionalExpression_TernaryCond]
readsPrec :: Int -> ReadS ConditionalExpression_TernaryCond
$creadsPrec :: Int -> ReadS ConditionalExpression_TernaryCond
Read, Int -> ConditionalExpression_TernaryCond -> String -> String
[ConditionalExpression_TernaryCond] -> String -> String
ConditionalExpression_TernaryCond -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ConditionalExpression_TernaryCond] -> String -> String
$cshowList :: [ConditionalExpression_TernaryCond] -> String -> String
show :: ConditionalExpression_TernaryCond -> String
$cshow :: ConditionalExpression_TernaryCond -> String
showsPrec :: Int -> ConditionalExpression_TernaryCond -> String -> String
$cshowsPrec :: Int -> ConditionalExpression_TernaryCond -> String -> String
Show)

_ConditionalExpression_TernaryCond :: Name
_ConditionalExpression_TernaryCond = (String -> Name
Core.Name String
"hydra/ext/java/syntax.ConditionalExpression.TernaryCond")

_ConditionalExpression_TernaryCond_cond :: FieldName
_ConditionalExpression_TernaryCond_cond = (String -> FieldName
Core.FieldName String
"cond")

_ConditionalExpression_TernaryCond_ifTrue :: FieldName
_ConditionalExpression_TernaryCond_ifTrue = (String -> FieldName
Core.FieldName String
"ifTrue")

_ConditionalExpression_TernaryCond_ifFalse :: FieldName
_ConditionalExpression_TernaryCond_ifFalse = (String -> FieldName
Core.FieldName String
"ifFalse")

data ConditionalExpression_TernaryLambda = 
  ConditionalExpression_TernaryLambda {
    ConditionalExpression_TernaryLambda -> ConditionalOrExpression
conditionalExpression_TernaryLambdaCond :: ConditionalOrExpression,
    ConditionalExpression_TernaryLambda -> Expression
conditionalExpression_TernaryLambdaIfTrue :: Expression,
    ConditionalExpression_TernaryLambda -> LambdaExpression
conditionalExpression_TernaryLambdaIfFalse :: LambdaExpression}
  deriving (ConditionalExpression_TernaryLambda
-> ConditionalExpression_TernaryLambda -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ConditionalExpression_TernaryLambda
-> ConditionalExpression_TernaryLambda -> Bool
$c/= :: ConditionalExpression_TernaryLambda
-> ConditionalExpression_TernaryLambda -> Bool
== :: ConditionalExpression_TernaryLambda
-> ConditionalExpression_TernaryLambda -> Bool
$c== :: ConditionalExpression_TernaryLambda
-> ConditionalExpression_TernaryLambda -> Bool
Eq, Eq ConditionalExpression_TernaryLambda
ConditionalExpression_TernaryLambda
-> ConditionalExpression_TernaryLambda -> Bool
ConditionalExpression_TernaryLambda
-> ConditionalExpression_TernaryLambda -> Ordering
ConditionalExpression_TernaryLambda
-> ConditionalExpression_TernaryLambda
-> ConditionalExpression_TernaryLambda
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ConditionalExpression_TernaryLambda
-> ConditionalExpression_TernaryLambda
-> ConditionalExpression_TernaryLambda
$cmin :: ConditionalExpression_TernaryLambda
-> ConditionalExpression_TernaryLambda
-> ConditionalExpression_TernaryLambda
max :: ConditionalExpression_TernaryLambda
-> ConditionalExpression_TernaryLambda
-> ConditionalExpression_TernaryLambda
$cmax :: ConditionalExpression_TernaryLambda
-> ConditionalExpression_TernaryLambda
-> ConditionalExpression_TernaryLambda
>= :: ConditionalExpression_TernaryLambda
-> ConditionalExpression_TernaryLambda -> Bool
$c>= :: ConditionalExpression_TernaryLambda
-> ConditionalExpression_TernaryLambda -> Bool
> :: ConditionalExpression_TernaryLambda
-> ConditionalExpression_TernaryLambda -> Bool
$c> :: ConditionalExpression_TernaryLambda
-> ConditionalExpression_TernaryLambda -> Bool
<= :: ConditionalExpression_TernaryLambda
-> ConditionalExpression_TernaryLambda -> Bool
$c<= :: ConditionalExpression_TernaryLambda
-> ConditionalExpression_TernaryLambda -> Bool
< :: ConditionalExpression_TernaryLambda
-> ConditionalExpression_TernaryLambda -> Bool
$c< :: ConditionalExpression_TernaryLambda
-> ConditionalExpression_TernaryLambda -> Bool
compare :: ConditionalExpression_TernaryLambda
-> ConditionalExpression_TernaryLambda -> Ordering
$ccompare :: ConditionalExpression_TernaryLambda
-> ConditionalExpression_TernaryLambda -> Ordering
Ord, ReadPrec [ConditionalExpression_TernaryLambda]
ReadPrec ConditionalExpression_TernaryLambda
Int -> ReadS ConditionalExpression_TernaryLambda
ReadS [ConditionalExpression_TernaryLambda]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ConditionalExpression_TernaryLambda]
$creadListPrec :: ReadPrec [ConditionalExpression_TernaryLambda]
readPrec :: ReadPrec ConditionalExpression_TernaryLambda
$creadPrec :: ReadPrec ConditionalExpression_TernaryLambda
readList :: ReadS [ConditionalExpression_TernaryLambda]
$creadList :: ReadS [ConditionalExpression_TernaryLambda]
readsPrec :: Int -> ReadS ConditionalExpression_TernaryLambda
$creadsPrec :: Int -> ReadS ConditionalExpression_TernaryLambda
Read, Int -> ConditionalExpression_TernaryLambda -> String -> String
[ConditionalExpression_TernaryLambda] -> String -> String
ConditionalExpression_TernaryLambda -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ConditionalExpression_TernaryLambda] -> String -> String
$cshowList :: [ConditionalExpression_TernaryLambda] -> String -> String
show :: ConditionalExpression_TernaryLambda -> String
$cshow :: ConditionalExpression_TernaryLambda -> String
showsPrec :: Int -> ConditionalExpression_TernaryLambda -> String -> String
$cshowsPrec :: Int -> ConditionalExpression_TernaryLambda -> String -> String
Show)

_ConditionalExpression_TernaryLambda :: Name
_ConditionalExpression_TernaryLambda = (String -> Name
Core.Name String
"hydra/ext/java/syntax.ConditionalExpression.TernaryLambda")

_ConditionalExpression_TernaryLambda_cond :: FieldName
_ConditionalExpression_TernaryLambda_cond = (String -> FieldName
Core.FieldName String
"cond")

_ConditionalExpression_TernaryLambda_ifTrue :: FieldName
_ConditionalExpression_TernaryLambda_ifTrue = (String -> FieldName
Core.FieldName String
"ifTrue")

_ConditionalExpression_TernaryLambda_ifFalse :: FieldName
_ConditionalExpression_TernaryLambda_ifFalse = (String -> FieldName
Core.FieldName String
"ifFalse")

newtype ConditionalOrExpression = 
  ConditionalOrExpression {
    ConditionalOrExpression -> [ConditionalAndExpression]
unConditionalOrExpression :: [ConditionalAndExpression]}
  deriving (ConditionalOrExpression -> ConditionalOrExpression -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ConditionalOrExpression -> ConditionalOrExpression -> Bool
$c/= :: ConditionalOrExpression -> ConditionalOrExpression -> Bool
== :: ConditionalOrExpression -> ConditionalOrExpression -> Bool
$c== :: ConditionalOrExpression -> ConditionalOrExpression -> Bool
Eq, Eq ConditionalOrExpression
ConditionalOrExpression -> ConditionalOrExpression -> Bool
ConditionalOrExpression -> ConditionalOrExpression -> Ordering
ConditionalOrExpression
-> ConditionalOrExpression -> ConditionalOrExpression
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ConditionalOrExpression
-> ConditionalOrExpression -> ConditionalOrExpression
$cmin :: ConditionalOrExpression
-> ConditionalOrExpression -> ConditionalOrExpression
max :: ConditionalOrExpression
-> ConditionalOrExpression -> ConditionalOrExpression
$cmax :: ConditionalOrExpression
-> ConditionalOrExpression -> ConditionalOrExpression
>= :: ConditionalOrExpression -> ConditionalOrExpression -> Bool
$c>= :: ConditionalOrExpression -> ConditionalOrExpression -> Bool
> :: ConditionalOrExpression -> ConditionalOrExpression -> Bool
$c> :: ConditionalOrExpression -> ConditionalOrExpression -> Bool
<= :: ConditionalOrExpression -> ConditionalOrExpression -> Bool
$c<= :: ConditionalOrExpression -> ConditionalOrExpression -> Bool
< :: ConditionalOrExpression -> ConditionalOrExpression -> Bool
$c< :: ConditionalOrExpression -> ConditionalOrExpression -> Bool
compare :: ConditionalOrExpression -> ConditionalOrExpression -> Ordering
$ccompare :: ConditionalOrExpression -> ConditionalOrExpression -> Ordering
Ord, ReadPrec [ConditionalOrExpression]
ReadPrec ConditionalOrExpression
Int -> ReadS ConditionalOrExpression
ReadS [ConditionalOrExpression]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ConditionalOrExpression]
$creadListPrec :: ReadPrec [ConditionalOrExpression]
readPrec :: ReadPrec ConditionalOrExpression
$creadPrec :: ReadPrec ConditionalOrExpression
readList :: ReadS [ConditionalOrExpression]
$creadList :: ReadS [ConditionalOrExpression]
readsPrec :: Int -> ReadS ConditionalOrExpression
$creadsPrec :: Int -> ReadS ConditionalOrExpression
Read, Int -> ConditionalOrExpression -> String -> String
[ConditionalOrExpression] -> String -> String
ConditionalOrExpression -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ConditionalOrExpression] -> String -> String
$cshowList :: [ConditionalOrExpression] -> String -> String
show :: ConditionalOrExpression -> String
$cshow :: ConditionalOrExpression -> String
showsPrec :: Int -> ConditionalOrExpression -> String -> String
$cshowsPrec :: Int -> ConditionalOrExpression -> String -> String
Show)

_ConditionalOrExpression :: Name
_ConditionalOrExpression = (String -> Name
Core.Name String
"hydra/ext/java/syntax.ConditionalOrExpression")

newtype ConditionalAndExpression = 
  ConditionalAndExpression {
    ConditionalAndExpression -> [InclusiveOrExpression]
unConditionalAndExpression :: [InclusiveOrExpression]}
  deriving (ConditionalAndExpression -> ConditionalAndExpression -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ConditionalAndExpression -> ConditionalAndExpression -> Bool
$c/= :: ConditionalAndExpression -> ConditionalAndExpression -> Bool
== :: ConditionalAndExpression -> ConditionalAndExpression -> Bool
$c== :: ConditionalAndExpression -> ConditionalAndExpression -> Bool
Eq, Eq ConditionalAndExpression
ConditionalAndExpression -> ConditionalAndExpression -> Bool
ConditionalAndExpression -> ConditionalAndExpression -> Ordering
ConditionalAndExpression
-> ConditionalAndExpression -> ConditionalAndExpression
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ConditionalAndExpression
-> ConditionalAndExpression -> ConditionalAndExpression
$cmin :: ConditionalAndExpression
-> ConditionalAndExpression -> ConditionalAndExpression
max :: ConditionalAndExpression
-> ConditionalAndExpression -> ConditionalAndExpression
$cmax :: ConditionalAndExpression
-> ConditionalAndExpression -> ConditionalAndExpression
>= :: ConditionalAndExpression -> ConditionalAndExpression -> Bool
$c>= :: ConditionalAndExpression -> ConditionalAndExpression -> Bool
> :: ConditionalAndExpression -> ConditionalAndExpression -> Bool
$c> :: ConditionalAndExpression -> ConditionalAndExpression -> Bool
<= :: ConditionalAndExpression -> ConditionalAndExpression -> Bool
$c<= :: ConditionalAndExpression -> ConditionalAndExpression -> Bool
< :: ConditionalAndExpression -> ConditionalAndExpression -> Bool
$c< :: ConditionalAndExpression -> ConditionalAndExpression -> Bool
compare :: ConditionalAndExpression -> ConditionalAndExpression -> Ordering
$ccompare :: ConditionalAndExpression -> ConditionalAndExpression -> Ordering
Ord, ReadPrec [ConditionalAndExpression]
ReadPrec ConditionalAndExpression
Int -> ReadS ConditionalAndExpression
ReadS [ConditionalAndExpression]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ConditionalAndExpression]
$creadListPrec :: ReadPrec [ConditionalAndExpression]
readPrec :: ReadPrec ConditionalAndExpression
$creadPrec :: ReadPrec ConditionalAndExpression
readList :: ReadS [ConditionalAndExpression]
$creadList :: ReadS [ConditionalAndExpression]
readsPrec :: Int -> ReadS ConditionalAndExpression
$creadsPrec :: Int -> ReadS ConditionalAndExpression
Read, Int -> ConditionalAndExpression -> String -> String
[ConditionalAndExpression] -> String -> String
ConditionalAndExpression -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ConditionalAndExpression] -> String -> String
$cshowList :: [ConditionalAndExpression] -> String -> String
show :: ConditionalAndExpression -> String
$cshow :: ConditionalAndExpression -> String
showsPrec :: Int -> ConditionalAndExpression -> String -> String
$cshowsPrec :: Int -> ConditionalAndExpression -> String -> String
Show)

_ConditionalAndExpression :: Name
_ConditionalAndExpression = (String -> Name
Core.Name String
"hydra/ext/java/syntax.ConditionalAndExpression")

newtype InclusiveOrExpression = 
  InclusiveOrExpression {
    InclusiveOrExpression -> [ExclusiveOrExpression]
unInclusiveOrExpression :: [ExclusiveOrExpression]}
  deriving (InclusiveOrExpression -> InclusiveOrExpression -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InclusiveOrExpression -> InclusiveOrExpression -> Bool
$c/= :: InclusiveOrExpression -> InclusiveOrExpression -> Bool
== :: InclusiveOrExpression -> InclusiveOrExpression -> Bool
$c== :: InclusiveOrExpression -> InclusiveOrExpression -> Bool
Eq, Eq InclusiveOrExpression
InclusiveOrExpression -> InclusiveOrExpression -> Bool
InclusiveOrExpression -> InclusiveOrExpression -> Ordering
InclusiveOrExpression
-> InclusiveOrExpression -> InclusiveOrExpression
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: InclusiveOrExpression
-> InclusiveOrExpression -> InclusiveOrExpression
$cmin :: InclusiveOrExpression
-> InclusiveOrExpression -> InclusiveOrExpression
max :: InclusiveOrExpression
-> InclusiveOrExpression -> InclusiveOrExpression
$cmax :: InclusiveOrExpression
-> InclusiveOrExpression -> InclusiveOrExpression
>= :: InclusiveOrExpression -> InclusiveOrExpression -> Bool
$c>= :: InclusiveOrExpression -> InclusiveOrExpression -> Bool
> :: InclusiveOrExpression -> InclusiveOrExpression -> Bool
$c> :: InclusiveOrExpression -> InclusiveOrExpression -> Bool
<= :: InclusiveOrExpression -> InclusiveOrExpression -> Bool
$c<= :: InclusiveOrExpression -> InclusiveOrExpression -> Bool
< :: InclusiveOrExpression -> InclusiveOrExpression -> Bool
$c< :: InclusiveOrExpression -> InclusiveOrExpression -> Bool
compare :: InclusiveOrExpression -> InclusiveOrExpression -> Ordering
$ccompare :: InclusiveOrExpression -> InclusiveOrExpression -> Ordering
Ord, ReadPrec [InclusiveOrExpression]
ReadPrec InclusiveOrExpression
Int -> ReadS InclusiveOrExpression
ReadS [InclusiveOrExpression]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [InclusiveOrExpression]
$creadListPrec :: ReadPrec [InclusiveOrExpression]
readPrec :: ReadPrec InclusiveOrExpression
$creadPrec :: ReadPrec InclusiveOrExpression
readList :: ReadS [InclusiveOrExpression]
$creadList :: ReadS [InclusiveOrExpression]
readsPrec :: Int -> ReadS InclusiveOrExpression
$creadsPrec :: Int -> ReadS InclusiveOrExpression
Read, Int -> InclusiveOrExpression -> String -> String
[InclusiveOrExpression] -> String -> String
InclusiveOrExpression -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [InclusiveOrExpression] -> String -> String
$cshowList :: [InclusiveOrExpression] -> String -> String
show :: InclusiveOrExpression -> String
$cshow :: InclusiveOrExpression -> String
showsPrec :: Int -> InclusiveOrExpression -> String -> String
$cshowsPrec :: Int -> InclusiveOrExpression -> String -> String
Show)

_InclusiveOrExpression :: Name
_InclusiveOrExpression = (String -> Name
Core.Name String
"hydra/ext/java/syntax.InclusiveOrExpression")

newtype ExclusiveOrExpression = 
  ExclusiveOrExpression {
    ExclusiveOrExpression -> [AndExpression]
unExclusiveOrExpression :: [AndExpression]}
  deriving (ExclusiveOrExpression -> ExclusiveOrExpression -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ExclusiveOrExpression -> ExclusiveOrExpression -> Bool
$c/= :: ExclusiveOrExpression -> ExclusiveOrExpression -> Bool
== :: ExclusiveOrExpression -> ExclusiveOrExpression -> Bool
$c== :: ExclusiveOrExpression -> ExclusiveOrExpression -> Bool
Eq, Eq ExclusiveOrExpression
ExclusiveOrExpression -> ExclusiveOrExpression -> Bool
ExclusiveOrExpression -> ExclusiveOrExpression -> Ordering
ExclusiveOrExpression
-> ExclusiveOrExpression -> ExclusiveOrExpression
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ExclusiveOrExpression
-> ExclusiveOrExpression -> ExclusiveOrExpression
$cmin :: ExclusiveOrExpression
-> ExclusiveOrExpression -> ExclusiveOrExpression
max :: ExclusiveOrExpression
-> ExclusiveOrExpression -> ExclusiveOrExpression
$cmax :: ExclusiveOrExpression
-> ExclusiveOrExpression -> ExclusiveOrExpression
>= :: ExclusiveOrExpression -> ExclusiveOrExpression -> Bool
$c>= :: ExclusiveOrExpression -> ExclusiveOrExpression -> Bool
> :: ExclusiveOrExpression -> ExclusiveOrExpression -> Bool
$c> :: ExclusiveOrExpression -> ExclusiveOrExpression -> Bool
<= :: ExclusiveOrExpression -> ExclusiveOrExpression -> Bool
$c<= :: ExclusiveOrExpression -> ExclusiveOrExpression -> Bool
< :: ExclusiveOrExpression -> ExclusiveOrExpression -> Bool
$c< :: ExclusiveOrExpression -> ExclusiveOrExpression -> Bool
compare :: ExclusiveOrExpression -> ExclusiveOrExpression -> Ordering
$ccompare :: ExclusiveOrExpression -> ExclusiveOrExpression -> Ordering
Ord, ReadPrec [ExclusiveOrExpression]
ReadPrec ExclusiveOrExpression
Int -> ReadS ExclusiveOrExpression
ReadS [ExclusiveOrExpression]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ExclusiveOrExpression]
$creadListPrec :: ReadPrec [ExclusiveOrExpression]
readPrec :: ReadPrec ExclusiveOrExpression
$creadPrec :: ReadPrec ExclusiveOrExpression
readList :: ReadS [ExclusiveOrExpression]
$creadList :: ReadS [ExclusiveOrExpression]
readsPrec :: Int -> ReadS ExclusiveOrExpression
$creadsPrec :: Int -> ReadS ExclusiveOrExpression
Read, Int -> ExclusiveOrExpression -> String -> String
[ExclusiveOrExpression] -> String -> String
ExclusiveOrExpression -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ExclusiveOrExpression] -> String -> String
$cshowList :: [ExclusiveOrExpression] -> String -> String
show :: ExclusiveOrExpression -> String
$cshow :: ExclusiveOrExpression -> String
showsPrec :: Int -> ExclusiveOrExpression -> String -> String
$cshowsPrec :: Int -> ExclusiveOrExpression -> String -> String
Show)

_ExclusiveOrExpression :: Name
_ExclusiveOrExpression = (String -> Name
Core.Name String
"hydra/ext/java/syntax.ExclusiveOrExpression")

newtype AndExpression = 
  AndExpression {
    AndExpression -> [EqualityExpression]
unAndExpression :: [EqualityExpression]}
  deriving (AndExpression -> AndExpression -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AndExpression -> AndExpression -> Bool
$c/= :: AndExpression -> AndExpression -> Bool
== :: AndExpression -> AndExpression -> Bool
$c== :: AndExpression -> AndExpression -> Bool
Eq, Eq AndExpression
AndExpression -> AndExpression -> Bool
AndExpression -> AndExpression -> Ordering
AndExpression -> AndExpression -> AndExpression
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: AndExpression -> AndExpression -> AndExpression
$cmin :: AndExpression -> AndExpression -> AndExpression
max :: AndExpression -> AndExpression -> AndExpression
$cmax :: AndExpression -> AndExpression -> AndExpression
>= :: AndExpression -> AndExpression -> Bool
$c>= :: AndExpression -> AndExpression -> Bool
> :: AndExpression -> AndExpression -> Bool
$c> :: AndExpression -> AndExpression -> Bool
<= :: AndExpression -> AndExpression -> Bool
$c<= :: AndExpression -> AndExpression -> Bool
< :: AndExpression -> AndExpression -> Bool
$c< :: AndExpression -> AndExpression -> Bool
compare :: AndExpression -> AndExpression -> Ordering
$ccompare :: AndExpression -> AndExpression -> Ordering
Ord, ReadPrec [AndExpression]
ReadPrec AndExpression
Int -> ReadS AndExpression
ReadS [AndExpression]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AndExpression]
$creadListPrec :: ReadPrec [AndExpression]
readPrec :: ReadPrec AndExpression
$creadPrec :: ReadPrec AndExpression
readList :: ReadS [AndExpression]
$creadList :: ReadS [AndExpression]
readsPrec :: Int -> ReadS AndExpression
$creadsPrec :: Int -> ReadS AndExpression
Read, Int -> AndExpression -> String -> String
[AndExpression] -> String -> String
AndExpression -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [AndExpression] -> String -> String
$cshowList :: [AndExpression] -> String -> String
show :: AndExpression -> String
$cshow :: AndExpression -> String
showsPrec :: Int -> AndExpression -> String -> String
$cshowsPrec :: Int -> AndExpression -> String -> String
Show)

_AndExpression :: Name
_AndExpression = (String -> Name
Core.Name String
"hydra/ext/java/syntax.AndExpression")

data EqualityExpression = 
  EqualityExpressionUnary RelationalExpression |
  EqualityExpressionEqual EqualityExpression_Binary |
  EqualityExpressionNotEqual EqualityExpression_Binary
  deriving (EqualityExpression -> EqualityExpression -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EqualityExpression -> EqualityExpression -> Bool
$c/= :: EqualityExpression -> EqualityExpression -> Bool
== :: EqualityExpression -> EqualityExpression -> Bool
$c== :: EqualityExpression -> EqualityExpression -> Bool
Eq, Eq EqualityExpression
EqualityExpression -> EqualityExpression -> Bool
EqualityExpression -> EqualityExpression -> Ordering
EqualityExpression -> EqualityExpression -> EqualityExpression
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: EqualityExpression -> EqualityExpression -> EqualityExpression
$cmin :: EqualityExpression -> EqualityExpression -> EqualityExpression
max :: EqualityExpression -> EqualityExpression -> EqualityExpression
$cmax :: EqualityExpression -> EqualityExpression -> EqualityExpression
>= :: EqualityExpression -> EqualityExpression -> Bool
$c>= :: EqualityExpression -> EqualityExpression -> Bool
> :: EqualityExpression -> EqualityExpression -> Bool
$c> :: EqualityExpression -> EqualityExpression -> Bool
<= :: EqualityExpression -> EqualityExpression -> Bool
$c<= :: EqualityExpression -> EqualityExpression -> Bool
< :: EqualityExpression -> EqualityExpression -> Bool
$c< :: EqualityExpression -> EqualityExpression -> Bool
compare :: EqualityExpression -> EqualityExpression -> Ordering
$ccompare :: EqualityExpression -> EqualityExpression -> Ordering
Ord, ReadPrec [EqualityExpression]
ReadPrec EqualityExpression
Int -> ReadS EqualityExpression
ReadS [EqualityExpression]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [EqualityExpression]
$creadListPrec :: ReadPrec [EqualityExpression]
readPrec :: ReadPrec EqualityExpression
$creadPrec :: ReadPrec EqualityExpression
readList :: ReadS [EqualityExpression]
$creadList :: ReadS [EqualityExpression]
readsPrec :: Int -> ReadS EqualityExpression
$creadsPrec :: Int -> ReadS EqualityExpression
Read, Int -> EqualityExpression -> String -> String
[EqualityExpression] -> String -> String
EqualityExpression -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [EqualityExpression] -> String -> String
$cshowList :: [EqualityExpression] -> String -> String
show :: EqualityExpression -> String
$cshow :: EqualityExpression -> String
showsPrec :: Int -> EqualityExpression -> String -> String
$cshowsPrec :: Int -> EqualityExpression -> String -> String
Show)

_EqualityExpression :: Name
_EqualityExpression = (String -> Name
Core.Name String
"hydra/ext/java/syntax.EqualityExpression")

_EqualityExpression_unary :: FieldName
_EqualityExpression_unary = (String -> FieldName
Core.FieldName String
"unary")

_EqualityExpression_equal :: FieldName
_EqualityExpression_equal = (String -> FieldName
Core.FieldName String
"equal")

_EqualityExpression_notEqual :: FieldName
_EqualityExpression_notEqual = (String -> FieldName
Core.FieldName String
"notEqual")

data EqualityExpression_Binary = 
  EqualityExpression_Binary {
    EqualityExpression_Binary -> EqualityExpression
equalityExpression_BinaryLhs :: EqualityExpression,
    EqualityExpression_Binary -> RelationalExpression
equalityExpression_BinaryRhs :: RelationalExpression}
  deriving (EqualityExpression_Binary -> EqualityExpression_Binary -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EqualityExpression_Binary -> EqualityExpression_Binary -> Bool
$c/= :: EqualityExpression_Binary -> EqualityExpression_Binary -> Bool
== :: EqualityExpression_Binary -> EqualityExpression_Binary -> Bool
$c== :: EqualityExpression_Binary -> EqualityExpression_Binary -> Bool
Eq, Eq EqualityExpression_Binary
EqualityExpression_Binary -> EqualityExpression_Binary -> Bool
EqualityExpression_Binary -> EqualityExpression_Binary -> Ordering
EqualityExpression_Binary
-> EqualityExpression_Binary -> EqualityExpression_Binary
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: EqualityExpression_Binary
-> EqualityExpression_Binary -> EqualityExpression_Binary
$cmin :: EqualityExpression_Binary
-> EqualityExpression_Binary -> EqualityExpression_Binary
max :: EqualityExpression_Binary
-> EqualityExpression_Binary -> EqualityExpression_Binary
$cmax :: EqualityExpression_Binary
-> EqualityExpression_Binary -> EqualityExpression_Binary
>= :: EqualityExpression_Binary -> EqualityExpression_Binary -> Bool
$c>= :: EqualityExpression_Binary -> EqualityExpression_Binary -> Bool
> :: EqualityExpression_Binary -> EqualityExpression_Binary -> Bool
$c> :: EqualityExpression_Binary -> EqualityExpression_Binary -> Bool
<= :: EqualityExpression_Binary -> EqualityExpression_Binary -> Bool
$c<= :: EqualityExpression_Binary -> EqualityExpression_Binary -> Bool
< :: EqualityExpression_Binary -> EqualityExpression_Binary -> Bool
$c< :: EqualityExpression_Binary -> EqualityExpression_Binary -> Bool
compare :: EqualityExpression_Binary -> EqualityExpression_Binary -> Ordering
$ccompare :: EqualityExpression_Binary -> EqualityExpression_Binary -> Ordering
Ord, ReadPrec [EqualityExpression_Binary]
ReadPrec EqualityExpression_Binary
Int -> ReadS EqualityExpression_Binary
ReadS [EqualityExpression_Binary]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [EqualityExpression_Binary]
$creadListPrec :: ReadPrec [EqualityExpression_Binary]
readPrec :: ReadPrec EqualityExpression_Binary
$creadPrec :: ReadPrec EqualityExpression_Binary
readList :: ReadS [EqualityExpression_Binary]
$creadList :: ReadS [EqualityExpression_Binary]
readsPrec :: Int -> ReadS EqualityExpression_Binary
$creadsPrec :: Int -> ReadS EqualityExpression_Binary
Read, Int -> EqualityExpression_Binary -> String -> String
[EqualityExpression_Binary] -> String -> String
EqualityExpression_Binary -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [EqualityExpression_Binary] -> String -> String
$cshowList :: [EqualityExpression_Binary] -> String -> String
show :: EqualityExpression_Binary -> String
$cshow :: EqualityExpression_Binary -> String
showsPrec :: Int -> EqualityExpression_Binary -> String -> String
$cshowsPrec :: Int -> EqualityExpression_Binary -> String -> String
Show)

_EqualityExpression_Binary :: Name
_EqualityExpression_Binary = (String -> Name
Core.Name String
"hydra/ext/java/syntax.EqualityExpression.Binary")

_EqualityExpression_Binary_lhs :: FieldName
_EqualityExpression_Binary_lhs = (String -> FieldName
Core.FieldName String
"lhs")

_EqualityExpression_Binary_rhs :: FieldName
_EqualityExpression_Binary_rhs = (String -> FieldName
Core.FieldName String
"rhs")

data RelationalExpression = 
  RelationalExpressionSimple ShiftExpression |
  RelationalExpressionLessThan RelationalExpression_LessThan |
  RelationalExpressionGreaterThan RelationalExpression_GreaterThan |
  RelationalExpressionLessThanEqual RelationalExpression_LessThanEqual |
  RelationalExpressionGreaterThanEqual RelationalExpression_GreaterThanEqual |
  RelationalExpressionInstanceof RelationalExpression_InstanceOf
  deriving (RelationalExpression -> RelationalExpression -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RelationalExpression -> RelationalExpression -> Bool
$c/= :: RelationalExpression -> RelationalExpression -> Bool
== :: RelationalExpression -> RelationalExpression -> Bool
$c== :: RelationalExpression -> RelationalExpression -> Bool
Eq, Eq RelationalExpression
RelationalExpression -> RelationalExpression -> Bool
RelationalExpression -> RelationalExpression -> Ordering
RelationalExpression
-> RelationalExpression -> RelationalExpression
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: RelationalExpression
-> RelationalExpression -> RelationalExpression
$cmin :: RelationalExpression
-> RelationalExpression -> RelationalExpression
max :: RelationalExpression
-> RelationalExpression -> RelationalExpression
$cmax :: RelationalExpression
-> RelationalExpression -> RelationalExpression
>= :: RelationalExpression -> RelationalExpression -> Bool
$c>= :: RelationalExpression -> RelationalExpression -> Bool
> :: RelationalExpression -> RelationalExpression -> Bool
$c> :: RelationalExpression -> RelationalExpression -> Bool
<= :: RelationalExpression -> RelationalExpression -> Bool
$c<= :: RelationalExpression -> RelationalExpression -> Bool
< :: RelationalExpression -> RelationalExpression -> Bool
$c< :: RelationalExpression -> RelationalExpression -> Bool
compare :: RelationalExpression -> RelationalExpression -> Ordering
$ccompare :: RelationalExpression -> RelationalExpression -> Ordering
Ord, ReadPrec [RelationalExpression]
ReadPrec RelationalExpression
Int -> ReadS RelationalExpression
ReadS [RelationalExpression]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RelationalExpression]
$creadListPrec :: ReadPrec [RelationalExpression]
readPrec :: ReadPrec RelationalExpression
$creadPrec :: ReadPrec RelationalExpression
readList :: ReadS [RelationalExpression]
$creadList :: ReadS [RelationalExpression]
readsPrec :: Int -> ReadS RelationalExpression
$creadsPrec :: Int -> ReadS RelationalExpression
Read, Int -> RelationalExpression -> String -> String
[RelationalExpression] -> String -> String
RelationalExpression -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [RelationalExpression] -> String -> String
$cshowList :: [RelationalExpression] -> String -> String
show :: RelationalExpression -> String
$cshow :: RelationalExpression -> String
showsPrec :: Int -> RelationalExpression -> String -> String
$cshowsPrec :: Int -> RelationalExpression -> String -> String
Show)

_RelationalExpression :: Name
_RelationalExpression = (String -> Name
Core.Name String
"hydra/ext/java/syntax.RelationalExpression")

_RelationalExpression_simple :: FieldName
_RelationalExpression_simple = (String -> FieldName
Core.FieldName String
"simple")

_RelationalExpression_lessThan :: FieldName
_RelationalExpression_lessThan = (String -> FieldName
Core.FieldName String
"lessThan")

_RelationalExpression_greaterThan :: FieldName
_RelationalExpression_greaterThan = (String -> FieldName
Core.FieldName String
"greaterThan")

_RelationalExpression_lessThanEqual :: FieldName
_RelationalExpression_lessThanEqual = (String -> FieldName
Core.FieldName String
"lessThanEqual")

_RelationalExpression_greaterThanEqual :: FieldName
_RelationalExpression_greaterThanEqual = (String -> FieldName
Core.FieldName String
"greaterThanEqual")

_RelationalExpression_instanceof :: FieldName
_RelationalExpression_instanceof = (String -> FieldName
Core.FieldName String
"instanceof")

data RelationalExpression_LessThan = 
  RelationalExpression_LessThan {
    RelationalExpression_LessThan -> RelationalExpression
relationalExpression_LessThanLhs :: RelationalExpression,
    RelationalExpression_LessThan -> ShiftExpression
relationalExpression_LessThanRhs :: ShiftExpression}
  deriving (RelationalExpression_LessThan
-> RelationalExpression_LessThan -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RelationalExpression_LessThan
-> RelationalExpression_LessThan -> Bool
$c/= :: RelationalExpression_LessThan
-> RelationalExpression_LessThan -> Bool
== :: RelationalExpression_LessThan
-> RelationalExpression_LessThan -> Bool
$c== :: RelationalExpression_LessThan
-> RelationalExpression_LessThan -> Bool
Eq, Eq RelationalExpression_LessThan
RelationalExpression_LessThan
-> RelationalExpression_LessThan -> Bool
RelationalExpression_LessThan
-> RelationalExpression_LessThan -> Ordering
RelationalExpression_LessThan
-> RelationalExpression_LessThan -> RelationalExpression_LessThan
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: RelationalExpression_LessThan
-> RelationalExpression_LessThan -> RelationalExpression_LessThan
$cmin :: RelationalExpression_LessThan
-> RelationalExpression_LessThan -> RelationalExpression_LessThan
max :: RelationalExpression_LessThan
-> RelationalExpression_LessThan -> RelationalExpression_LessThan
$cmax :: RelationalExpression_LessThan
-> RelationalExpression_LessThan -> RelationalExpression_LessThan
>= :: RelationalExpression_LessThan
-> RelationalExpression_LessThan -> Bool
$c>= :: RelationalExpression_LessThan
-> RelationalExpression_LessThan -> Bool
> :: RelationalExpression_LessThan
-> RelationalExpression_LessThan -> Bool
$c> :: RelationalExpression_LessThan
-> RelationalExpression_LessThan -> Bool
<= :: RelationalExpression_LessThan
-> RelationalExpression_LessThan -> Bool
$c<= :: RelationalExpression_LessThan
-> RelationalExpression_LessThan -> Bool
< :: RelationalExpression_LessThan
-> RelationalExpression_LessThan -> Bool
$c< :: RelationalExpression_LessThan
-> RelationalExpression_LessThan -> Bool
compare :: RelationalExpression_LessThan
-> RelationalExpression_LessThan -> Ordering
$ccompare :: RelationalExpression_LessThan
-> RelationalExpression_LessThan -> Ordering
Ord, ReadPrec [RelationalExpression_LessThan]
ReadPrec RelationalExpression_LessThan
Int -> ReadS RelationalExpression_LessThan
ReadS [RelationalExpression_LessThan]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RelationalExpression_LessThan]
$creadListPrec :: ReadPrec [RelationalExpression_LessThan]
readPrec :: ReadPrec RelationalExpression_LessThan
$creadPrec :: ReadPrec RelationalExpression_LessThan
readList :: ReadS [RelationalExpression_LessThan]
$creadList :: ReadS [RelationalExpression_LessThan]
readsPrec :: Int -> ReadS RelationalExpression_LessThan
$creadsPrec :: Int -> ReadS RelationalExpression_LessThan
Read, Int -> RelationalExpression_LessThan -> String -> String
[RelationalExpression_LessThan] -> String -> String
RelationalExpression_LessThan -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [RelationalExpression_LessThan] -> String -> String
$cshowList :: [RelationalExpression_LessThan] -> String -> String
show :: RelationalExpression_LessThan -> String
$cshow :: RelationalExpression_LessThan -> String
showsPrec :: Int -> RelationalExpression_LessThan -> String -> String
$cshowsPrec :: Int -> RelationalExpression_LessThan -> String -> String
Show)

_RelationalExpression_LessThan :: Name
_RelationalExpression_LessThan = (String -> Name
Core.Name String
"hydra/ext/java/syntax.RelationalExpression.LessThan")

_RelationalExpression_LessThan_lhs :: FieldName
_RelationalExpression_LessThan_lhs = (String -> FieldName
Core.FieldName String
"lhs")

_RelationalExpression_LessThan_rhs :: FieldName
_RelationalExpression_LessThan_rhs = (String -> FieldName
Core.FieldName String
"rhs")

data RelationalExpression_GreaterThan = 
  RelationalExpression_GreaterThan {
    RelationalExpression_GreaterThan -> RelationalExpression
relationalExpression_GreaterThanLhs :: RelationalExpression,
    RelationalExpression_GreaterThan -> ShiftExpression
relationalExpression_GreaterThanRhs :: ShiftExpression}
  deriving (RelationalExpression_GreaterThan
-> RelationalExpression_GreaterThan -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RelationalExpression_GreaterThan
-> RelationalExpression_GreaterThan -> Bool
$c/= :: RelationalExpression_GreaterThan
-> RelationalExpression_GreaterThan -> Bool
== :: RelationalExpression_GreaterThan
-> RelationalExpression_GreaterThan -> Bool
$c== :: RelationalExpression_GreaterThan
-> RelationalExpression_GreaterThan -> Bool
Eq, Eq RelationalExpression_GreaterThan
RelationalExpression_GreaterThan
-> RelationalExpression_GreaterThan -> Bool
RelationalExpression_GreaterThan
-> RelationalExpression_GreaterThan -> Ordering
RelationalExpression_GreaterThan
-> RelationalExpression_GreaterThan
-> RelationalExpression_GreaterThan
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: RelationalExpression_GreaterThan
-> RelationalExpression_GreaterThan
-> RelationalExpression_GreaterThan
$cmin :: RelationalExpression_GreaterThan
-> RelationalExpression_GreaterThan
-> RelationalExpression_GreaterThan
max :: RelationalExpression_GreaterThan
-> RelationalExpression_GreaterThan
-> RelationalExpression_GreaterThan
$cmax :: RelationalExpression_GreaterThan
-> RelationalExpression_GreaterThan
-> RelationalExpression_GreaterThan
>= :: RelationalExpression_GreaterThan
-> RelationalExpression_GreaterThan -> Bool
$c>= :: RelationalExpression_GreaterThan
-> RelationalExpression_GreaterThan -> Bool
> :: RelationalExpression_GreaterThan
-> RelationalExpression_GreaterThan -> Bool
$c> :: RelationalExpression_GreaterThan
-> RelationalExpression_GreaterThan -> Bool
<= :: RelationalExpression_GreaterThan
-> RelationalExpression_GreaterThan -> Bool
$c<= :: RelationalExpression_GreaterThan
-> RelationalExpression_GreaterThan -> Bool
< :: RelationalExpression_GreaterThan
-> RelationalExpression_GreaterThan -> Bool
$c< :: RelationalExpression_GreaterThan
-> RelationalExpression_GreaterThan -> Bool
compare :: RelationalExpression_GreaterThan
-> RelationalExpression_GreaterThan -> Ordering
$ccompare :: RelationalExpression_GreaterThan
-> RelationalExpression_GreaterThan -> Ordering
Ord, ReadPrec [RelationalExpression_GreaterThan]
ReadPrec RelationalExpression_GreaterThan
Int -> ReadS RelationalExpression_GreaterThan
ReadS [RelationalExpression_GreaterThan]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RelationalExpression_GreaterThan]
$creadListPrec :: ReadPrec [RelationalExpression_GreaterThan]
readPrec :: ReadPrec RelationalExpression_GreaterThan
$creadPrec :: ReadPrec RelationalExpression_GreaterThan
readList :: ReadS [RelationalExpression_GreaterThan]
$creadList :: ReadS [RelationalExpression_GreaterThan]
readsPrec :: Int -> ReadS RelationalExpression_GreaterThan
$creadsPrec :: Int -> ReadS RelationalExpression_GreaterThan
Read, Int -> RelationalExpression_GreaterThan -> String -> String
[RelationalExpression_GreaterThan] -> String -> String
RelationalExpression_GreaterThan -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [RelationalExpression_GreaterThan] -> String -> String
$cshowList :: [RelationalExpression_GreaterThan] -> String -> String
show :: RelationalExpression_GreaterThan -> String
$cshow :: RelationalExpression_GreaterThan -> String
showsPrec :: Int -> RelationalExpression_GreaterThan -> String -> String
$cshowsPrec :: Int -> RelationalExpression_GreaterThan -> String -> String
Show)

_RelationalExpression_GreaterThan :: Name
_RelationalExpression_GreaterThan = (String -> Name
Core.Name String
"hydra/ext/java/syntax.RelationalExpression.GreaterThan")

_RelationalExpression_GreaterThan_lhs :: FieldName
_RelationalExpression_GreaterThan_lhs = (String -> FieldName
Core.FieldName String
"lhs")

_RelationalExpression_GreaterThan_rhs :: FieldName
_RelationalExpression_GreaterThan_rhs = (String -> FieldName
Core.FieldName String
"rhs")

data RelationalExpression_LessThanEqual = 
  RelationalExpression_LessThanEqual {
    RelationalExpression_LessThanEqual -> RelationalExpression
relationalExpression_LessThanEqualLhs :: RelationalExpression,
    RelationalExpression_LessThanEqual -> ShiftExpression
relationalExpression_LessThanEqualRhs :: ShiftExpression}
  deriving (RelationalExpression_LessThanEqual
-> RelationalExpression_LessThanEqual -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RelationalExpression_LessThanEqual
-> RelationalExpression_LessThanEqual -> Bool
$c/= :: RelationalExpression_LessThanEqual
-> RelationalExpression_LessThanEqual -> Bool
== :: RelationalExpression_LessThanEqual
-> RelationalExpression_LessThanEqual -> Bool
$c== :: RelationalExpression_LessThanEqual
-> RelationalExpression_LessThanEqual -> Bool
Eq, Eq RelationalExpression_LessThanEqual
RelationalExpression_LessThanEqual
-> RelationalExpression_LessThanEqual -> Bool
RelationalExpression_LessThanEqual
-> RelationalExpression_LessThanEqual -> Ordering
RelationalExpression_LessThanEqual
-> RelationalExpression_LessThanEqual
-> RelationalExpression_LessThanEqual
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: RelationalExpression_LessThanEqual
-> RelationalExpression_LessThanEqual
-> RelationalExpression_LessThanEqual
$cmin :: RelationalExpression_LessThanEqual
-> RelationalExpression_LessThanEqual
-> RelationalExpression_LessThanEqual
max :: RelationalExpression_LessThanEqual
-> RelationalExpression_LessThanEqual
-> RelationalExpression_LessThanEqual
$cmax :: RelationalExpression_LessThanEqual
-> RelationalExpression_LessThanEqual
-> RelationalExpression_LessThanEqual
>= :: RelationalExpression_LessThanEqual
-> RelationalExpression_LessThanEqual -> Bool
$c>= :: RelationalExpression_LessThanEqual
-> RelationalExpression_LessThanEqual -> Bool
> :: RelationalExpression_LessThanEqual
-> RelationalExpression_LessThanEqual -> Bool
$c> :: RelationalExpression_LessThanEqual
-> RelationalExpression_LessThanEqual -> Bool
<= :: RelationalExpression_LessThanEqual
-> RelationalExpression_LessThanEqual -> Bool
$c<= :: RelationalExpression_LessThanEqual
-> RelationalExpression_LessThanEqual -> Bool
< :: RelationalExpression_LessThanEqual
-> RelationalExpression_LessThanEqual -> Bool
$c< :: RelationalExpression_LessThanEqual
-> RelationalExpression_LessThanEqual -> Bool
compare :: RelationalExpression_LessThanEqual
-> RelationalExpression_LessThanEqual -> Ordering
$ccompare :: RelationalExpression_LessThanEqual
-> RelationalExpression_LessThanEqual -> Ordering
Ord, ReadPrec [RelationalExpression_LessThanEqual]
ReadPrec RelationalExpression_LessThanEqual
Int -> ReadS RelationalExpression_LessThanEqual
ReadS [RelationalExpression_LessThanEqual]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RelationalExpression_LessThanEqual]
$creadListPrec :: ReadPrec [RelationalExpression_LessThanEqual]
readPrec :: ReadPrec RelationalExpression_LessThanEqual
$creadPrec :: ReadPrec RelationalExpression_LessThanEqual
readList :: ReadS [RelationalExpression_LessThanEqual]
$creadList :: ReadS [RelationalExpression_LessThanEqual]
readsPrec :: Int -> ReadS RelationalExpression_LessThanEqual
$creadsPrec :: Int -> ReadS RelationalExpression_LessThanEqual
Read, Int -> RelationalExpression_LessThanEqual -> String -> String
[RelationalExpression_LessThanEqual] -> String -> String
RelationalExpression_LessThanEqual -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [RelationalExpression_LessThanEqual] -> String -> String
$cshowList :: [RelationalExpression_LessThanEqual] -> String -> String
show :: RelationalExpression_LessThanEqual -> String
$cshow :: RelationalExpression_LessThanEqual -> String
showsPrec :: Int -> RelationalExpression_LessThanEqual -> String -> String
$cshowsPrec :: Int -> RelationalExpression_LessThanEqual -> String -> String
Show)

_RelationalExpression_LessThanEqual :: Name
_RelationalExpression_LessThanEqual = (String -> Name
Core.Name String
"hydra/ext/java/syntax.RelationalExpression.LessThanEqual")

_RelationalExpression_LessThanEqual_lhs :: FieldName
_RelationalExpression_LessThanEqual_lhs = (String -> FieldName
Core.FieldName String
"lhs")

_RelationalExpression_LessThanEqual_rhs :: FieldName
_RelationalExpression_LessThanEqual_rhs = (String -> FieldName
Core.FieldName String
"rhs")

data RelationalExpression_GreaterThanEqual = 
  RelationalExpression_GreaterThanEqual {
    RelationalExpression_GreaterThanEqual -> RelationalExpression
relationalExpression_GreaterThanEqualLhs :: RelationalExpression,
    RelationalExpression_GreaterThanEqual -> ShiftExpression
relationalExpression_GreaterThanEqualRhs :: ShiftExpression}
  deriving (RelationalExpression_GreaterThanEqual
-> RelationalExpression_GreaterThanEqual -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RelationalExpression_GreaterThanEqual
-> RelationalExpression_GreaterThanEqual -> Bool
$c/= :: RelationalExpression_GreaterThanEqual
-> RelationalExpression_GreaterThanEqual -> Bool
== :: RelationalExpression_GreaterThanEqual
-> RelationalExpression_GreaterThanEqual -> Bool
$c== :: RelationalExpression_GreaterThanEqual
-> RelationalExpression_GreaterThanEqual -> Bool
Eq, Eq RelationalExpression_GreaterThanEqual
RelationalExpression_GreaterThanEqual
-> RelationalExpression_GreaterThanEqual -> Bool
RelationalExpression_GreaterThanEqual
-> RelationalExpression_GreaterThanEqual -> Ordering
RelationalExpression_GreaterThanEqual
-> RelationalExpression_GreaterThanEqual
-> RelationalExpression_GreaterThanEqual
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: RelationalExpression_GreaterThanEqual
-> RelationalExpression_GreaterThanEqual
-> RelationalExpression_GreaterThanEqual
$cmin :: RelationalExpression_GreaterThanEqual
-> RelationalExpression_GreaterThanEqual
-> RelationalExpression_GreaterThanEqual
max :: RelationalExpression_GreaterThanEqual
-> RelationalExpression_GreaterThanEqual
-> RelationalExpression_GreaterThanEqual
$cmax :: RelationalExpression_GreaterThanEqual
-> RelationalExpression_GreaterThanEqual
-> RelationalExpression_GreaterThanEqual
>= :: RelationalExpression_GreaterThanEqual
-> RelationalExpression_GreaterThanEqual -> Bool
$c>= :: RelationalExpression_GreaterThanEqual
-> RelationalExpression_GreaterThanEqual -> Bool
> :: RelationalExpression_GreaterThanEqual
-> RelationalExpression_GreaterThanEqual -> Bool
$c> :: RelationalExpression_GreaterThanEqual
-> RelationalExpression_GreaterThanEqual -> Bool
<= :: RelationalExpression_GreaterThanEqual
-> RelationalExpression_GreaterThanEqual -> Bool
$c<= :: RelationalExpression_GreaterThanEqual
-> RelationalExpression_GreaterThanEqual -> Bool
< :: RelationalExpression_GreaterThanEqual
-> RelationalExpression_GreaterThanEqual -> Bool
$c< :: RelationalExpression_GreaterThanEqual
-> RelationalExpression_GreaterThanEqual -> Bool
compare :: RelationalExpression_GreaterThanEqual
-> RelationalExpression_GreaterThanEqual -> Ordering
$ccompare :: RelationalExpression_GreaterThanEqual
-> RelationalExpression_GreaterThanEqual -> Ordering
Ord, ReadPrec [RelationalExpression_GreaterThanEqual]
ReadPrec RelationalExpression_GreaterThanEqual
Int -> ReadS RelationalExpression_GreaterThanEqual
ReadS [RelationalExpression_GreaterThanEqual]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RelationalExpression_GreaterThanEqual]
$creadListPrec :: ReadPrec [RelationalExpression_GreaterThanEqual]
readPrec :: ReadPrec RelationalExpression_GreaterThanEqual
$creadPrec :: ReadPrec RelationalExpression_GreaterThanEqual
readList :: ReadS [RelationalExpression_GreaterThanEqual]
$creadList :: ReadS [RelationalExpression_GreaterThanEqual]
readsPrec :: Int -> ReadS RelationalExpression_GreaterThanEqual
$creadsPrec :: Int -> ReadS RelationalExpression_GreaterThanEqual
Read, Int -> RelationalExpression_GreaterThanEqual -> String -> String
[RelationalExpression_GreaterThanEqual] -> String -> String
RelationalExpression_GreaterThanEqual -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [RelationalExpression_GreaterThanEqual] -> String -> String
$cshowList :: [RelationalExpression_GreaterThanEqual] -> String -> String
show :: RelationalExpression_GreaterThanEqual -> String
$cshow :: RelationalExpression_GreaterThanEqual -> String
showsPrec :: Int -> RelationalExpression_GreaterThanEqual -> String -> String
$cshowsPrec :: Int -> RelationalExpression_GreaterThanEqual -> String -> String
Show)

_RelationalExpression_GreaterThanEqual :: Name
_RelationalExpression_GreaterThanEqual = (String -> Name
Core.Name String
"hydra/ext/java/syntax.RelationalExpression.GreaterThanEqual")

_RelationalExpression_GreaterThanEqual_lhs :: FieldName
_RelationalExpression_GreaterThanEqual_lhs = (String -> FieldName
Core.FieldName String
"lhs")

_RelationalExpression_GreaterThanEqual_rhs :: FieldName
_RelationalExpression_GreaterThanEqual_rhs = (String -> FieldName
Core.FieldName String
"rhs")

data RelationalExpression_InstanceOf = 
  RelationalExpression_InstanceOf {
    RelationalExpression_InstanceOf -> RelationalExpression
relationalExpression_InstanceOfLhs :: RelationalExpression,
    RelationalExpression_InstanceOf -> ReferenceType
relationalExpression_InstanceOfRhs :: ReferenceType}
  deriving (RelationalExpression_InstanceOf
-> RelationalExpression_InstanceOf -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RelationalExpression_InstanceOf
-> RelationalExpression_InstanceOf -> Bool
$c/= :: RelationalExpression_InstanceOf
-> RelationalExpression_InstanceOf -> Bool
== :: RelationalExpression_InstanceOf
-> RelationalExpression_InstanceOf -> Bool
$c== :: RelationalExpression_InstanceOf
-> RelationalExpression_InstanceOf -> Bool
Eq, Eq RelationalExpression_InstanceOf
RelationalExpression_InstanceOf
-> RelationalExpression_InstanceOf -> Bool
RelationalExpression_InstanceOf
-> RelationalExpression_InstanceOf -> Ordering
RelationalExpression_InstanceOf
-> RelationalExpression_InstanceOf
-> RelationalExpression_InstanceOf
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: RelationalExpression_InstanceOf
-> RelationalExpression_InstanceOf
-> RelationalExpression_InstanceOf
$cmin :: RelationalExpression_InstanceOf
-> RelationalExpression_InstanceOf
-> RelationalExpression_InstanceOf
max :: RelationalExpression_InstanceOf
-> RelationalExpression_InstanceOf
-> RelationalExpression_InstanceOf
$cmax :: RelationalExpression_InstanceOf
-> RelationalExpression_InstanceOf
-> RelationalExpression_InstanceOf
>= :: RelationalExpression_InstanceOf
-> RelationalExpression_InstanceOf -> Bool
$c>= :: RelationalExpression_InstanceOf
-> RelationalExpression_InstanceOf -> Bool
> :: RelationalExpression_InstanceOf
-> RelationalExpression_InstanceOf -> Bool
$c> :: RelationalExpression_InstanceOf
-> RelationalExpression_InstanceOf -> Bool
<= :: RelationalExpression_InstanceOf
-> RelationalExpression_InstanceOf -> Bool
$c<= :: RelationalExpression_InstanceOf
-> RelationalExpression_InstanceOf -> Bool
< :: RelationalExpression_InstanceOf
-> RelationalExpression_InstanceOf -> Bool
$c< :: RelationalExpression_InstanceOf
-> RelationalExpression_InstanceOf -> Bool
compare :: RelationalExpression_InstanceOf
-> RelationalExpression_InstanceOf -> Ordering
$ccompare :: RelationalExpression_InstanceOf
-> RelationalExpression_InstanceOf -> Ordering
Ord, ReadPrec [RelationalExpression_InstanceOf]
ReadPrec RelationalExpression_InstanceOf
Int -> ReadS RelationalExpression_InstanceOf
ReadS [RelationalExpression_InstanceOf]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RelationalExpression_InstanceOf]
$creadListPrec :: ReadPrec [RelationalExpression_InstanceOf]
readPrec :: ReadPrec RelationalExpression_InstanceOf
$creadPrec :: ReadPrec RelationalExpression_InstanceOf
readList :: ReadS [RelationalExpression_InstanceOf]
$creadList :: ReadS [RelationalExpression_InstanceOf]
readsPrec :: Int -> ReadS RelationalExpression_InstanceOf
$creadsPrec :: Int -> ReadS RelationalExpression_InstanceOf
Read, Int -> RelationalExpression_InstanceOf -> String -> String
[RelationalExpression_InstanceOf] -> String -> String
RelationalExpression_InstanceOf -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [RelationalExpression_InstanceOf] -> String -> String
$cshowList :: [RelationalExpression_InstanceOf] -> String -> String
show :: RelationalExpression_InstanceOf -> String
$cshow :: RelationalExpression_InstanceOf -> String
showsPrec :: Int -> RelationalExpression_InstanceOf -> String -> String
$cshowsPrec :: Int -> RelationalExpression_InstanceOf -> String -> String
Show)

_RelationalExpression_InstanceOf :: Name
_RelationalExpression_InstanceOf = (String -> Name
Core.Name String
"hydra/ext/java/syntax.RelationalExpression.InstanceOf")

_RelationalExpression_InstanceOf_lhs :: FieldName
_RelationalExpression_InstanceOf_lhs = (String -> FieldName
Core.FieldName String
"lhs")

_RelationalExpression_InstanceOf_rhs :: FieldName
_RelationalExpression_InstanceOf_rhs = (String -> FieldName
Core.FieldName String
"rhs")

data ShiftExpression = 
  ShiftExpressionUnary AdditiveExpression |
  ShiftExpressionShiftLeft ShiftExpression_Binary |
  ShiftExpressionShiftRight ShiftExpression_Binary |
  ShiftExpressionShiftRightZeroFill ShiftExpression_Binary
  deriving (ShiftExpression -> ShiftExpression -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ShiftExpression -> ShiftExpression -> Bool
$c/= :: ShiftExpression -> ShiftExpression -> Bool
== :: ShiftExpression -> ShiftExpression -> Bool
$c== :: ShiftExpression -> ShiftExpression -> Bool
Eq, Eq ShiftExpression
ShiftExpression -> ShiftExpression -> Bool
ShiftExpression -> ShiftExpression -> Ordering
ShiftExpression -> ShiftExpression -> ShiftExpression
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ShiftExpression -> ShiftExpression -> ShiftExpression
$cmin :: ShiftExpression -> ShiftExpression -> ShiftExpression
max :: ShiftExpression -> ShiftExpression -> ShiftExpression
$cmax :: ShiftExpression -> ShiftExpression -> ShiftExpression
>= :: ShiftExpression -> ShiftExpression -> Bool
$c>= :: ShiftExpression -> ShiftExpression -> Bool
> :: ShiftExpression -> ShiftExpression -> Bool
$c> :: ShiftExpression -> ShiftExpression -> Bool
<= :: ShiftExpression -> ShiftExpression -> Bool
$c<= :: ShiftExpression -> ShiftExpression -> Bool
< :: ShiftExpression -> ShiftExpression -> Bool
$c< :: ShiftExpression -> ShiftExpression -> Bool
compare :: ShiftExpression -> ShiftExpression -> Ordering
$ccompare :: ShiftExpression -> ShiftExpression -> Ordering
Ord, ReadPrec [ShiftExpression]
ReadPrec ShiftExpression
Int -> ReadS ShiftExpression
ReadS [ShiftExpression]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ShiftExpression]
$creadListPrec :: ReadPrec [ShiftExpression]
readPrec :: ReadPrec ShiftExpression
$creadPrec :: ReadPrec ShiftExpression
readList :: ReadS [ShiftExpression]
$creadList :: ReadS [ShiftExpression]
readsPrec :: Int -> ReadS ShiftExpression
$creadsPrec :: Int -> ReadS ShiftExpression
Read, Int -> ShiftExpression -> String -> String
[ShiftExpression] -> String -> String
ShiftExpression -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ShiftExpression] -> String -> String
$cshowList :: [ShiftExpression] -> String -> String
show :: ShiftExpression -> String
$cshow :: ShiftExpression -> String
showsPrec :: Int -> ShiftExpression -> String -> String
$cshowsPrec :: Int -> ShiftExpression -> String -> String
Show)

_ShiftExpression :: Name
_ShiftExpression = (String -> Name
Core.Name String
"hydra/ext/java/syntax.ShiftExpression")

_ShiftExpression_unary :: FieldName
_ShiftExpression_unary = (String -> FieldName
Core.FieldName String
"unary")

_ShiftExpression_shiftLeft :: FieldName
_ShiftExpression_shiftLeft = (String -> FieldName
Core.FieldName String
"shiftLeft")

_ShiftExpression_shiftRight :: FieldName
_ShiftExpression_shiftRight = (String -> FieldName
Core.FieldName String
"shiftRight")

_ShiftExpression_shiftRightZeroFill :: FieldName
_ShiftExpression_shiftRightZeroFill = (String -> FieldName
Core.FieldName String
"shiftRightZeroFill")

data ShiftExpression_Binary = 
  ShiftExpression_Binary {
    ShiftExpression_Binary -> ShiftExpression
shiftExpression_BinaryLhs :: ShiftExpression,
    ShiftExpression_Binary -> AdditiveExpression
shiftExpression_BinaryRhs :: AdditiveExpression}
  deriving (ShiftExpression_Binary -> ShiftExpression_Binary -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ShiftExpression_Binary -> ShiftExpression_Binary -> Bool
$c/= :: ShiftExpression_Binary -> ShiftExpression_Binary -> Bool
== :: ShiftExpression_Binary -> ShiftExpression_Binary -> Bool
$c== :: ShiftExpression_Binary -> ShiftExpression_Binary -> Bool
Eq, Eq ShiftExpression_Binary
ShiftExpression_Binary -> ShiftExpression_Binary -> Bool
ShiftExpression_Binary -> ShiftExpression_Binary -> Ordering
ShiftExpression_Binary
-> ShiftExpression_Binary -> ShiftExpression_Binary
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ShiftExpression_Binary
-> ShiftExpression_Binary -> ShiftExpression_Binary
$cmin :: ShiftExpression_Binary
-> ShiftExpression_Binary -> ShiftExpression_Binary
max :: ShiftExpression_Binary
-> ShiftExpression_Binary -> ShiftExpression_Binary
$cmax :: ShiftExpression_Binary
-> ShiftExpression_Binary -> ShiftExpression_Binary
>= :: ShiftExpression_Binary -> ShiftExpression_Binary -> Bool
$c>= :: ShiftExpression_Binary -> ShiftExpression_Binary -> Bool
> :: ShiftExpression_Binary -> ShiftExpression_Binary -> Bool
$c> :: ShiftExpression_Binary -> ShiftExpression_Binary -> Bool
<= :: ShiftExpression_Binary -> ShiftExpression_Binary -> Bool
$c<= :: ShiftExpression_Binary -> ShiftExpression_Binary -> Bool
< :: ShiftExpression_Binary -> ShiftExpression_Binary -> Bool
$c< :: ShiftExpression_Binary -> ShiftExpression_Binary -> Bool
compare :: ShiftExpression_Binary -> ShiftExpression_Binary -> Ordering
$ccompare :: ShiftExpression_Binary -> ShiftExpression_Binary -> Ordering
Ord, ReadPrec [ShiftExpression_Binary]
ReadPrec ShiftExpression_Binary
Int -> ReadS ShiftExpression_Binary
ReadS [ShiftExpression_Binary]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ShiftExpression_Binary]
$creadListPrec :: ReadPrec [ShiftExpression_Binary]
readPrec :: ReadPrec ShiftExpression_Binary
$creadPrec :: ReadPrec ShiftExpression_Binary
readList :: ReadS [ShiftExpression_Binary]
$creadList :: ReadS [ShiftExpression_Binary]
readsPrec :: Int -> ReadS ShiftExpression_Binary
$creadsPrec :: Int -> ReadS ShiftExpression_Binary
Read, Int -> ShiftExpression_Binary -> String -> String
[ShiftExpression_Binary] -> String -> String
ShiftExpression_Binary -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ShiftExpression_Binary] -> String -> String
$cshowList :: [ShiftExpression_Binary] -> String -> String
show :: ShiftExpression_Binary -> String
$cshow :: ShiftExpression_Binary -> String
showsPrec :: Int -> ShiftExpression_Binary -> String -> String
$cshowsPrec :: Int -> ShiftExpression_Binary -> String -> String
Show)

_ShiftExpression_Binary :: Name
_ShiftExpression_Binary = (String -> Name
Core.Name String
"hydra/ext/java/syntax.ShiftExpression.Binary")

_ShiftExpression_Binary_lhs :: FieldName
_ShiftExpression_Binary_lhs = (String -> FieldName
Core.FieldName String
"lhs")

_ShiftExpression_Binary_rhs :: FieldName
_ShiftExpression_Binary_rhs = (String -> FieldName
Core.FieldName String
"rhs")

data AdditiveExpression = 
  AdditiveExpressionUnary MultiplicativeExpression |
  AdditiveExpressionPlus AdditiveExpression_Binary |
  AdditiveExpressionMinus AdditiveExpression_Binary
  deriving (AdditiveExpression -> AdditiveExpression -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AdditiveExpression -> AdditiveExpression -> Bool
$c/= :: AdditiveExpression -> AdditiveExpression -> Bool
== :: AdditiveExpression -> AdditiveExpression -> Bool
$c== :: AdditiveExpression -> AdditiveExpression -> Bool
Eq, Eq AdditiveExpression
AdditiveExpression -> AdditiveExpression -> Bool
AdditiveExpression -> AdditiveExpression -> Ordering
AdditiveExpression -> AdditiveExpression -> AdditiveExpression
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: AdditiveExpression -> AdditiveExpression -> AdditiveExpression
$cmin :: AdditiveExpression -> AdditiveExpression -> AdditiveExpression
max :: AdditiveExpression -> AdditiveExpression -> AdditiveExpression
$cmax :: AdditiveExpression -> AdditiveExpression -> AdditiveExpression
>= :: AdditiveExpression -> AdditiveExpression -> Bool
$c>= :: AdditiveExpression -> AdditiveExpression -> Bool
> :: AdditiveExpression -> AdditiveExpression -> Bool
$c> :: AdditiveExpression -> AdditiveExpression -> Bool
<= :: AdditiveExpression -> AdditiveExpression -> Bool
$c<= :: AdditiveExpression -> AdditiveExpression -> Bool
< :: AdditiveExpression -> AdditiveExpression -> Bool
$c< :: AdditiveExpression -> AdditiveExpression -> Bool
compare :: AdditiveExpression -> AdditiveExpression -> Ordering
$ccompare :: AdditiveExpression -> AdditiveExpression -> Ordering
Ord, ReadPrec [AdditiveExpression]
ReadPrec AdditiveExpression
Int -> ReadS AdditiveExpression
ReadS [AdditiveExpression]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AdditiveExpression]
$creadListPrec :: ReadPrec [AdditiveExpression]
readPrec :: ReadPrec AdditiveExpression
$creadPrec :: ReadPrec AdditiveExpression
readList :: ReadS [AdditiveExpression]
$creadList :: ReadS [AdditiveExpression]
readsPrec :: Int -> ReadS AdditiveExpression
$creadsPrec :: Int -> ReadS AdditiveExpression
Read, Int -> AdditiveExpression -> String -> String
[AdditiveExpression] -> String -> String
AdditiveExpression -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [AdditiveExpression] -> String -> String
$cshowList :: [AdditiveExpression] -> String -> String
show :: AdditiveExpression -> String
$cshow :: AdditiveExpression -> String
showsPrec :: Int -> AdditiveExpression -> String -> String
$cshowsPrec :: Int -> AdditiveExpression -> String -> String
Show)

_AdditiveExpression :: Name
_AdditiveExpression = (String -> Name
Core.Name String
"hydra/ext/java/syntax.AdditiveExpression")

_AdditiveExpression_unary :: FieldName
_AdditiveExpression_unary = (String -> FieldName
Core.FieldName String
"unary")

_AdditiveExpression_plus :: FieldName
_AdditiveExpression_plus = (String -> FieldName
Core.FieldName String
"plus")

_AdditiveExpression_minus :: FieldName
_AdditiveExpression_minus = (String -> FieldName
Core.FieldName String
"minus")

data AdditiveExpression_Binary = 
  AdditiveExpression_Binary {
    AdditiveExpression_Binary -> AdditiveExpression
additiveExpression_BinaryLhs :: AdditiveExpression,
    AdditiveExpression_Binary -> MultiplicativeExpression
additiveExpression_BinaryRhs :: MultiplicativeExpression}
  deriving (AdditiveExpression_Binary -> AdditiveExpression_Binary -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AdditiveExpression_Binary -> AdditiveExpression_Binary -> Bool
$c/= :: AdditiveExpression_Binary -> AdditiveExpression_Binary -> Bool
== :: AdditiveExpression_Binary -> AdditiveExpression_Binary -> Bool
$c== :: AdditiveExpression_Binary -> AdditiveExpression_Binary -> Bool
Eq, Eq AdditiveExpression_Binary
AdditiveExpression_Binary -> AdditiveExpression_Binary -> Bool
AdditiveExpression_Binary -> AdditiveExpression_Binary -> Ordering
AdditiveExpression_Binary
-> AdditiveExpression_Binary -> AdditiveExpression_Binary
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: AdditiveExpression_Binary
-> AdditiveExpression_Binary -> AdditiveExpression_Binary
$cmin :: AdditiveExpression_Binary
-> AdditiveExpression_Binary -> AdditiveExpression_Binary
max :: AdditiveExpression_Binary
-> AdditiveExpression_Binary -> AdditiveExpression_Binary
$cmax :: AdditiveExpression_Binary
-> AdditiveExpression_Binary -> AdditiveExpression_Binary
>= :: AdditiveExpression_Binary -> AdditiveExpression_Binary -> Bool
$c>= :: AdditiveExpression_Binary -> AdditiveExpression_Binary -> Bool
> :: AdditiveExpression_Binary -> AdditiveExpression_Binary -> Bool
$c> :: AdditiveExpression_Binary -> AdditiveExpression_Binary -> Bool
<= :: AdditiveExpression_Binary -> AdditiveExpression_Binary -> Bool
$c<= :: AdditiveExpression_Binary -> AdditiveExpression_Binary -> Bool
< :: AdditiveExpression_Binary -> AdditiveExpression_Binary -> Bool
$c< :: AdditiveExpression_Binary -> AdditiveExpression_Binary -> Bool
compare :: AdditiveExpression_Binary -> AdditiveExpression_Binary -> Ordering
$ccompare :: AdditiveExpression_Binary -> AdditiveExpression_Binary -> Ordering
Ord, ReadPrec [AdditiveExpression_Binary]
ReadPrec AdditiveExpression_Binary
Int -> ReadS AdditiveExpression_Binary
ReadS [AdditiveExpression_Binary]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AdditiveExpression_Binary]
$creadListPrec :: ReadPrec [AdditiveExpression_Binary]
readPrec :: ReadPrec AdditiveExpression_Binary
$creadPrec :: ReadPrec AdditiveExpression_Binary
readList :: ReadS [AdditiveExpression_Binary]
$creadList :: ReadS [AdditiveExpression_Binary]
readsPrec :: Int -> ReadS AdditiveExpression_Binary
$creadsPrec :: Int -> ReadS AdditiveExpression_Binary
Read, Int -> AdditiveExpression_Binary -> String -> String
[AdditiveExpression_Binary] -> String -> String
AdditiveExpression_Binary -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [AdditiveExpression_Binary] -> String -> String
$cshowList :: [AdditiveExpression_Binary] -> String -> String
show :: AdditiveExpression_Binary -> String
$cshow :: AdditiveExpression_Binary -> String
showsPrec :: Int -> AdditiveExpression_Binary -> String -> String
$cshowsPrec :: Int -> AdditiveExpression_Binary -> String -> String
Show)

_AdditiveExpression_Binary :: Name
_AdditiveExpression_Binary = (String -> Name
Core.Name String
"hydra/ext/java/syntax.AdditiveExpression.Binary")

_AdditiveExpression_Binary_lhs :: FieldName
_AdditiveExpression_Binary_lhs = (String -> FieldName
Core.FieldName String
"lhs")

_AdditiveExpression_Binary_rhs :: FieldName
_AdditiveExpression_Binary_rhs = (String -> FieldName
Core.FieldName String
"rhs")

data MultiplicativeExpression = 
  MultiplicativeExpressionUnary UnaryExpression |
  MultiplicativeExpressionTimes MultiplicativeExpression_Binary |
  MultiplicativeExpressionDivide MultiplicativeExpression_Binary |
  MultiplicativeExpressionMod MultiplicativeExpression_Binary
  deriving (MultiplicativeExpression -> MultiplicativeExpression -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MultiplicativeExpression -> MultiplicativeExpression -> Bool
$c/= :: MultiplicativeExpression -> MultiplicativeExpression -> Bool
== :: MultiplicativeExpression -> MultiplicativeExpression -> Bool
$c== :: MultiplicativeExpression -> MultiplicativeExpression -> Bool
Eq, Eq MultiplicativeExpression
MultiplicativeExpression -> MultiplicativeExpression -> Bool
MultiplicativeExpression -> MultiplicativeExpression -> Ordering
MultiplicativeExpression
-> MultiplicativeExpression -> MultiplicativeExpression
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: MultiplicativeExpression
-> MultiplicativeExpression -> MultiplicativeExpression
$cmin :: MultiplicativeExpression
-> MultiplicativeExpression -> MultiplicativeExpression
max :: MultiplicativeExpression
-> MultiplicativeExpression -> MultiplicativeExpression
$cmax :: MultiplicativeExpression
-> MultiplicativeExpression -> MultiplicativeExpression
>= :: MultiplicativeExpression -> MultiplicativeExpression -> Bool
$c>= :: MultiplicativeExpression -> MultiplicativeExpression -> Bool
> :: MultiplicativeExpression -> MultiplicativeExpression -> Bool
$c> :: MultiplicativeExpression -> MultiplicativeExpression -> Bool
<= :: MultiplicativeExpression -> MultiplicativeExpression -> Bool
$c<= :: MultiplicativeExpression -> MultiplicativeExpression -> Bool
< :: MultiplicativeExpression -> MultiplicativeExpression -> Bool
$c< :: MultiplicativeExpression -> MultiplicativeExpression -> Bool
compare :: MultiplicativeExpression -> MultiplicativeExpression -> Ordering
$ccompare :: MultiplicativeExpression -> MultiplicativeExpression -> Ordering
Ord, ReadPrec [MultiplicativeExpression]
ReadPrec MultiplicativeExpression
Int -> ReadS MultiplicativeExpression
ReadS [MultiplicativeExpression]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [MultiplicativeExpression]
$creadListPrec :: ReadPrec [MultiplicativeExpression]
readPrec :: ReadPrec MultiplicativeExpression
$creadPrec :: ReadPrec MultiplicativeExpression
readList :: ReadS [MultiplicativeExpression]
$creadList :: ReadS [MultiplicativeExpression]
readsPrec :: Int -> ReadS MultiplicativeExpression
$creadsPrec :: Int -> ReadS MultiplicativeExpression
Read, Int -> MultiplicativeExpression -> String -> String
[MultiplicativeExpression] -> String -> String
MultiplicativeExpression -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [MultiplicativeExpression] -> String -> String
$cshowList :: [MultiplicativeExpression] -> String -> String
show :: MultiplicativeExpression -> String
$cshow :: MultiplicativeExpression -> String
showsPrec :: Int -> MultiplicativeExpression -> String -> String
$cshowsPrec :: Int -> MultiplicativeExpression -> String -> String
Show)

_MultiplicativeExpression :: Name
_MultiplicativeExpression = (String -> Name
Core.Name String
"hydra/ext/java/syntax.MultiplicativeExpression")

_MultiplicativeExpression_unary :: FieldName
_MultiplicativeExpression_unary = (String -> FieldName
Core.FieldName String
"unary")

_MultiplicativeExpression_times :: FieldName
_MultiplicativeExpression_times = (String -> FieldName
Core.FieldName String
"times")

_MultiplicativeExpression_divide :: FieldName
_MultiplicativeExpression_divide = (String -> FieldName
Core.FieldName String
"divide")

_MultiplicativeExpression_mod :: FieldName
_MultiplicativeExpression_mod = (String -> FieldName
Core.FieldName String
"mod")

data MultiplicativeExpression_Binary = 
  MultiplicativeExpression_Binary {
    MultiplicativeExpression_Binary -> MultiplicativeExpression
multiplicativeExpression_BinaryLhs :: MultiplicativeExpression,
    MultiplicativeExpression_Binary -> UnaryExpression
multiplicativeExpression_BinaryRhs :: UnaryExpression}
  deriving (MultiplicativeExpression_Binary
-> MultiplicativeExpression_Binary -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MultiplicativeExpression_Binary
-> MultiplicativeExpression_Binary -> Bool
$c/= :: MultiplicativeExpression_Binary
-> MultiplicativeExpression_Binary -> Bool
== :: MultiplicativeExpression_Binary
-> MultiplicativeExpression_Binary -> Bool
$c== :: MultiplicativeExpression_Binary
-> MultiplicativeExpression_Binary -> Bool
Eq, Eq MultiplicativeExpression_Binary
MultiplicativeExpression_Binary
-> MultiplicativeExpression_Binary -> Bool
MultiplicativeExpression_Binary
-> MultiplicativeExpression_Binary -> Ordering
MultiplicativeExpression_Binary
-> MultiplicativeExpression_Binary
-> MultiplicativeExpression_Binary
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: MultiplicativeExpression_Binary
-> MultiplicativeExpression_Binary
-> MultiplicativeExpression_Binary
$cmin :: MultiplicativeExpression_Binary
-> MultiplicativeExpression_Binary
-> MultiplicativeExpression_Binary
max :: MultiplicativeExpression_Binary
-> MultiplicativeExpression_Binary
-> MultiplicativeExpression_Binary
$cmax :: MultiplicativeExpression_Binary
-> MultiplicativeExpression_Binary
-> MultiplicativeExpression_Binary
>= :: MultiplicativeExpression_Binary
-> MultiplicativeExpression_Binary -> Bool
$c>= :: MultiplicativeExpression_Binary
-> MultiplicativeExpression_Binary -> Bool
> :: MultiplicativeExpression_Binary
-> MultiplicativeExpression_Binary -> Bool
$c> :: MultiplicativeExpression_Binary
-> MultiplicativeExpression_Binary -> Bool
<= :: MultiplicativeExpression_Binary
-> MultiplicativeExpression_Binary -> Bool
$c<= :: MultiplicativeExpression_Binary
-> MultiplicativeExpression_Binary -> Bool
< :: MultiplicativeExpression_Binary
-> MultiplicativeExpression_Binary -> Bool
$c< :: MultiplicativeExpression_Binary
-> MultiplicativeExpression_Binary -> Bool
compare :: MultiplicativeExpression_Binary
-> MultiplicativeExpression_Binary -> Ordering
$ccompare :: MultiplicativeExpression_Binary
-> MultiplicativeExpression_Binary -> Ordering
Ord, ReadPrec [MultiplicativeExpression_Binary]
ReadPrec MultiplicativeExpression_Binary
Int -> ReadS MultiplicativeExpression_Binary
ReadS [MultiplicativeExpression_Binary]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [MultiplicativeExpression_Binary]
$creadListPrec :: ReadPrec [MultiplicativeExpression_Binary]
readPrec :: ReadPrec MultiplicativeExpression_Binary
$creadPrec :: ReadPrec MultiplicativeExpression_Binary
readList :: ReadS [MultiplicativeExpression_Binary]
$creadList :: ReadS [MultiplicativeExpression_Binary]
readsPrec :: Int -> ReadS MultiplicativeExpression_Binary
$creadsPrec :: Int -> ReadS MultiplicativeExpression_Binary
Read, Int -> MultiplicativeExpression_Binary -> String -> String
[MultiplicativeExpression_Binary] -> String -> String
MultiplicativeExpression_Binary -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [MultiplicativeExpression_Binary] -> String -> String
$cshowList :: [MultiplicativeExpression_Binary] -> String -> String
show :: MultiplicativeExpression_Binary -> String
$cshow :: MultiplicativeExpression_Binary -> String
showsPrec :: Int -> MultiplicativeExpression_Binary -> String -> String
$cshowsPrec :: Int -> MultiplicativeExpression_Binary -> String -> String
Show)

_MultiplicativeExpression_Binary :: Name
_MultiplicativeExpression_Binary = (String -> Name
Core.Name String
"hydra/ext/java/syntax.MultiplicativeExpression.Binary")

_MultiplicativeExpression_Binary_lhs :: FieldName
_MultiplicativeExpression_Binary_lhs = (String -> FieldName
Core.FieldName String
"lhs")

_MultiplicativeExpression_Binary_rhs :: FieldName
_MultiplicativeExpression_Binary_rhs = (String -> FieldName
Core.FieldName String
"rhs")

data UnaryExpression = 
  UnaryExpressionPreIncrement PreIncrementExpression |
  UnaryExpressionPreDecrement PreDecrementExpression |
  UnaryExpressionPlus UnaryExpression |
  UnaryExpressionMinus UnaryExpression |
  UnaryExpressionOther UnaryExpressionNotPlusMinus
  deriving (UnaryExpression -> UnaryExpression -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UnaryExpression -> UnaryExpression -> Bool
$c/= :: UnaryExpression -> UnaryExpression -> Bool
== :: UnaryExpression -> UnaryExpression -> Bool
$c== :: UnaryExpression -> UnaryExpression -> Bool
Eq, Eq UnaryExpression
UnaryExpression -> UnaryExpression -> Bool
UnaryExpression -> UnaryExpression -> Ordering
UnaryExpression -> UnaryExpression -> UnaryExpression
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: UnaryExpression -> UnaryExpression -> UnaryExpression
$cmin :: UnaryExpression -> UnaryExpression -> UnaryExpression
max :: UnaryExpression -> UnaryExpression -> UnaryExpression
$cmax :: UnaryExpression -> UnaryExpression -> UnaryExpression
>= :: UnaryExpression -> UnaryExpression -> Bool
$c>= :: UnaryExpression -> UnaryExpression -> Bool
> :: UnaryExpression -> UnaryExpression -> Bool
$c> :: UnaryExpression -> UnaryExpression -> Bool
<= :: UnaryExpression -> UnaryExpression -> Bool
$c<= :: UnaryExpression -> UnaryExpression -> Bool
< :: UnaryExpression -> UnaryExpression -> Bool
$c< :: UnaryExpression -> UnaryExpression -> Bool
compare :: UnaryExpression -> UnaryExpression -> Ordering
$ccompare :: UnaryExpression -> UnaryExpression -> Ordering
Ord, ReadPrec [UnaryExpression]
ReadPrec UnaryExpression
Int -> ReadS UnaryExpression
ReadS [UnaryExpression]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UnaryExpression]
$creadListPrec :: ReadPrec [UnaryExpression]
readPrec :: ReadPrec UnaryExpression
$creadPrec :: ReadPrec UnaryExpression
readList :: ReadS [UnaryExpression]
$creadList :: ReadS [UnaryExpression]
readsPrec :: Int -> ReadS UnaryExpression
$creadsPrec :: Int -> ReadS UnaryExpression
Read, Int -> UnaryExpression -> String -> String
[UnaryExpression] -> String -> String
UnaryExpression -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [UnaryExpression] -> String -> String
$cshowList :: [UnaryExpression] -> String -> String
show :: UnaryExpression -> String
$cshow :: UnaryExpression -> String
showsPrec :: Int -> UnaryExpression -> String -> String
$cshowsPrec :: Int -> UnaryExpression -> String -> String
Show)

_UnaryExpression :: Name
_UnaryExpression = (String -> Name
Core.Name String
"hydra/ext/java/syntax.UnaryExpression")

_UnaryExpression_preIncrement :: FieldName
_UnaryExpression_preIncrement = (String -> FieldName
Core.FieldName String
"preIncrement")

_UnaryExpression_preDecrement :: FieldName
_UnaryExpression_preDecrement = (String -> FieldName
Core.FieldName String
"preDecrement")

_UnaryExpression_plus :: FieldName
_UnaryExpression_plus = (String -> FieldName
Core.FieldName String
"plus")

_UnaryExpression_minus :: FieldName
_UnaryExpression_minus = (String -> FieldName
Core.FieldName String
"minus")

_UnaryExpression_other :: FieldName
_UnaryExpression_other = (String -> FieldName
Core.FieldName String
"other")

newtype PreIncrementExpression = 
  PreIncrementExpression {
    PreIncrementExpression -> UnaryExpression
unPreIncrementExpression :: UnaryExpression}
  deriving (PreIncrementExpression -> PreIncrementExpression -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PreIncrementExpression -> PreIncrementExpression -> Bool
$c/= :: PreIncrementExpression -> PreIncrementExpression -> Bool
== :: PreIncrementExpression -> PreIncrementExpression -> Bool
$c== :: PreIncrementExpression -> PreIncrementExpression -> Bool
Eq, Eq PreIncrementExpression
PreIncrementExpression -> PreIncrementExpression -> Bool
PreIncrementExpression -> PreIncrementExpression -> Ordering
PreIncrementExpression
-> PreIncrementExpression -> PreIncrementExpression
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: PreIncrementExpression
-> PreIncrementExpression -> PreIncrementExpression
$cmin :: PreIncrementExpression
-> PreIncrementExpression -> PreIncrementExpression
max :: PreIncrementExpression
-> PreIncrementExpression -> PreIncrementExpression
$cmax :: PreIncrementExpression
-> PreIncrementExpression -> PreIncrementExpression
>= :: PreIncrementExpression -> PreIncrementExpression -> Bool
$c>= :: PreIncrementExpression -> PreIncrementExpression -> Bool
> :: PreIncrementExpression -> PreIncrementExpression -> Bool
$c> :: PreIncrementExpression -> PreIncrementExpression -> Bool
<= :: PreIncrementExpression -> PreIncrementExpression -> Bool
$c<= :: PreIncrementExpression -> PreIncrementExpression -> Bool
< :: PreIncrementExpression -> PreIncrementExpression -> Bool
$c< :: PreIncrementExpression -> PreIncrementExpression -> Bool
compare :: PreIncrementExpression -> PreIncrementExpression -> Ordering
$ccompare :: PreIncrementExpression -> PreIncrementExpression -> Ordering
Ord, ReadPrec [PreIncrementExpression]
ReadPrec PreIncrementExpression
Int -> ReadS PreIncrementExpression
ReadS [PreIncrementExpression]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [PreIncrementExpression]
$creadListPrec :: ReadPrec [PreIncrementExpression]
readPrec :: ReadPrec PreIncrementExpression
$creadPrec :: ReadPrec PreIncrementExpression
readList :: ReadS [PreIncrementExpression]
$creadList :: ReadS [PreIncrementExpression]
readsPrec :: Int -> ReadS PreIncrementExpression
$creadsPrec :: Int -> ReadS PreIncrementExpression
Read, Int -> PreIncrementExpression -> String -> String
[PreIncrementExpression] -> String -> String
PreIncrementExpression -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [PreIncrementExpression] -> String -> String
$cshowList :: [PreIncrementExpression] -> String -> String
show :: PreIncrementExpression -> String
$cshow :: PreIncrementExpression -> String
showsPrec :: Int -> PreIncrementExpression -> String -> String
$cshowsPrec :: Int -> PreIncrementExpression -> String -> String
Show)

_PreIncrementExpression :: Name
_PreIncrementExpression = (String -> Name
Core.Name String
"hydra/ext/java/syntax.PreIncrementExpression")

newtype PreDecrementExpression = 
  PreDecrementExpression {
    PreDecrementExpression -> UnaryExpression
unPreDecrementExpression :: UnaryExpression}
  deriving (PreDecrementExpression -> PreDecrementExpression -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PreDecrementExpression -> PreDecrementExpression -> Bool
$c/= :: PreDecrementExpression -> PreDecrementExpression -> Bool
== :: PreDecrementExpression -> PreDecrementExpression -> Bool
$c== :: PreDecrementExpression -> PreDecrementExpression -> Bool
Eq, Eq PreDecrementExpression
PreDecrementExpression -> PreDecrementExpression -> Bool
PreDecrementExpression -> PreDecrementExpression -> Ordering
PreDecrementExpression
-> PreDecrementExpression -> PreDecrementExpression
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: PreDecrementExpression
-> PreDecrementExpression -> PreDecrementExpression
$cmin :: PreDecrementExpression
-> PreDecrementExpression -> PreDecrementExpression
max :: PreDecrementExpression
-> PreDecrementExpression -> PreDecrementExpression
$cmax :: PreDecrementExpression
-> PreDecrementExpression -> PreDecrementExpression
>= :: PreDecrementExpression -> PreDecrementExpression -> Bool
$c>= :: PreDecrementExpression -> PreDecrementExpression -> Bool
> :: PreDecrementExpression -> PreDecrementExpression -> Bool
$c> :: PreDecrementExpression -> PreDecrementExpression -> Bool
<= :: PreDecrementExpression -> PreDecrementExpression -> Bool
$c<= :: PreDecrementExpression -> PreDecrementExpression -> Bool
< :: PreDecrementExpression -> PreDecrementExpression -> Bool
$c< :: PreDecrementExpression -> PreDecrementExpression -> Bool
compare :: PreDecrementExpression -> PreDecrementExpression -> Ordering
$ccompare :: PreDecrementExpression -> PreDecrementExpression -> Ordering
Ord, ReadPrec [PreDecrementExpression]
ReadPrec PreDecrementExpression
Int -> ReadS PreDecrementExpression
ReadS [PreDecrementExpression]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [PreDecrementExpression]
$creadListPrec :: ReadPrec [PreDecrementExpression]
readPrec :: ReadPrec PreDecrementExpression
$creadPrec :: ReadPrec PreDecrementExpression
readList :: ReadS [PreDecrementExpression]
$creadList :: ReadS [PreDecrementExpression]
readsPrec :: Int -> ReadS PreDecrementExpression
$creadsPrec :: Int -> ReadS PreDecrementExpression
Read, Int -> PreDecrementExpression -> String -> String
[PreDecrementExpression] -> String -> String
PreDecrementExpression -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [PreDecrementExpression] -> String -> String
$cshowList :: [PreDecrementExpression] -> String -> String
show :: PreDecrementExpression -> String
$cshow :: PreDecrementExpression -> String
showsPrec :: Int -> PreDecrementExpression -> String -> String
$cshowsPrec :: Int -> PreDecrementExpression -> String -> String
Show)

_PreDecrementExpression :: Name
_PreDecrementExpression = (String -> Name
Core.Name String
"hydra/ext/java/syntax.PreDecrementExpression")

data UnaryExpressionNotPlusMinus = 
  UnaryExpressionNotPlusMinusPostfix PostfixExpression |
  UnaryExpressionNotPlusMinusTilde UnaryExpression |
  UnaryExpressionNotPlusMinusNot UnaryExpression |
  UnaryExpressionNotPlusMinusCast CastExpression
  deriving (UnaryExpressionNotPlusMinus -> UnaryExpressionNotPlusMinus -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UnaryExpressionNotPlusMinus -> UnaryExpressionNotPlusMinus -> Bool
$c/= :: UnaryExpressionNotPlusMinus -> UnaryExpressionNotPlusMinus -> Bool
== :: UnaryExpressionNotPlusMinus -> UnaryExpressionNotPlusMinus -> Bool
$c== :: UnaryExpressionNotPlusMinus -> UnaryExpressionNotPlusMinus -> Bool
Eq, Eq UnaryExpressionNotPlusMinus
UnaryExpressionNotPlusMinus -> UnaryExpressionNotPlusMinus -> Bool
UnaryExpressionNotPlusMinus
-> UnaryExpressionNotPlusMinus -> Ordering
UnaryExpressionNotPlusMinus
-> UnaryExpressionNotPlusMinus -> UnaryExpressionNotPlusMinus
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: UnaryExpressionNotPlusMinus
-> UnaryExpressionNotPlusMinus -> UnaryExpressionNotPlusMinus
$cmin :: UnaryExpressionNotPlusMinus
-> UnaryExpressionNotPlusMinus -> UnaryExpressionNotPlusMinus
max :: UnaryExpressionNotPlusMinus
-> UnaryExpressionNotPlusMinus -> UnaryExpressionNotPlusMinus
$cmax :: UnaryExpressionNotPlusMinus
-> UnaryExpressionNotPlusMinus -> UnaryExpressionNotPlusMinus
>= :: UnaryExpressionNotPlusMinus -> UnaryExpressionNotPlusMinus -> Bool
$c>= :: UnaryExpressionNotPlusMinus -> UnaryExpressionNotPlusMinus -> Bool
> :: UnaryExpressionNotPlusMinus -> UnaryExpressionNotPlusMinus -> Bool
$c> :: UnaryExpressionNotPlusMinus -> UnaryExpressionNotPlusMinus -> Bool
<= :: UnaryExpressionNotPlusMinus -> UnaryExpressionNotPlusMinus -> Bool
$c<= :: UnaryExpressionNotPlusMinus -> UnaryExpressionNotPlusMinus -> Bool
< :: UnaryExpressionNotPlusMinus -> UnaryExpressionNotPlusMinus -> Bool
$c< :: UnaryExpressionNotPlusMinus -> UnaryExpressionNotPlusMinus -> Bool
compare :: UnaryExpressionNotPlusMinus
-> UnaryExpressionNotPlusMinus -> Ordering
$ccompare :: UnaryExpressionNotPlusMinus
-> UnaryExpressionNotPlusMinus -> Ordering
Ord, ReadPrec [UnaryExpressionNotPlusMinus]
ReadPrec UnaryExpressionNotPlusMinus
Int -> ReadS UnaryExpressionNotPlusMinus
ReadS [UnaryExpressionNotPlusMinus]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UnaryExpressionNotPlusMinus]
$creadListPrec :: ReadPrec [UnaryExpressionNotPlusMinus]
readPrec :: ReadPrec UnaryExpressionNotPlusMinus
$creadPrec :: ReadPrec UnaryExpressionNotPlusMinus
readList :: ReadS [UnaryExpressionNotPlusMinus]
$creadList :: ReadS [UnaryExpressionNotPlusMinus]
readsPrec :: Int -> ReadS UnaryExpressionNotPlusMinus
$creadsPrec :: Int -> ReadS UnaryExpressionNotPlusMinus
Read, Int -> UnaryExpressionNotPlusMinus -> String -> String
[UnaryExpressionNotPlusMinus] -> String -> String
UnaryExpressionNotPlusMinus -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [UnaryExpressionNotPlusMinus] -> String -> String
$cshowList :: [UnaryExpressionNotPlusMinus] -> String -> String
show :: UnaryExpressionNotPlusMinus -> String
$cshow :: UnaryExpressionNotPlusMinus -> String
showsPrec :: Int -> UnaryExpressionNotPlusMinus -> String -> String
$cshowsPrec :: Int -> UnaryExpressionNotPlusMinus -> String -> String
Show)

_UnaryExpressionNotPlusMinus :: Name
_UnaryExpressionNotPlusMinus = (String -> Name
Core.Name String
"hydra/ext/java/syntax.UnaryExpressionNotPlusMinus")

_UnaryExpressionNotPlusMinus_postfix :: FieldName
_UnaryExpressionNotPlusMinus_postfix = (String -> FieldName
Core.FieldName String
"postfix")

_UnaryExpressionNotPlusMinus_tilde :: FieldName
_UnaryExpressionNotPlusMinus_tilde = (String -> FieldName
Core.FieldName String
"tilde")

_UnaryExpressionNotPlusMinus_not :: FieldName
_UnaryExpressionNotPlusMinus_not = (String -> FieldName
Core.FieldName String
"not")

_UnaryExpressionNotPlusMinus_cast :: FieldName
_UnaryExpressionNotPlusMinus_cast = (String -> FieldName
Core.FieldName String
"cast")

data PostfixExpression = 
  PostfixExpressionPrimary Primary |
  PostfixExpressionName ExpressionName |
  PostfixExpressionPostIncrement PostIncrementExpression |
  PostfixExpressionPostDecrement PostDecrementExpression
  deriving (PostfixExpression -> PostfixExpression -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostfixExpression -> PostfixExpression -> Bool
$c/= :: PostfixExpression -> PostfixExpression -> Bool
== :: PostfixExpression -> PostfixExpression -> Bool
$c== :: PostfixExpression -> PostfixExpression -> Bool
Eq, Eq PostfixExpression
PostfixExpression -> PostfixExpression -> Bool
PostfixExpression -> PostfixExpression -> Ordering
PostfixExpression -> PostfixExpression -> PostfixExpression
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: PostfixExpression -> PostfixExpression -> PostfixExpression
$cmin :: PostfixExpression -> PostfixExpression -> PostfixExpression
max :: PostfixExpression -> PostfixExpression -> PostfixExpression
$cmax :: PostfixExpression -> PostfixExpression -> PostfixExpression
>= :: PostfixExpression -> PostfixExpression -> Bool
$c>= :: PostfixExpression -> PostfixExpression -> Bool
> :: PostfixExpression -> PostfixExpression -> Bool
$c> :: PostfixExpression -> PostfixExpression -> Bool
<= :: PostfixExpression -> PostfixExpression -> Bool
$c<= :: PostfixExpression -> PostfixExpression -> Bool
< :: PostfixExpression -> PostfixExpression -> Bool
$c< :: PostfixExpression -> PostfixExpression -> Bool
compare :: PostfixExpression -> PostfixExpression -> Ordering
$ccompare :: PostfixExpression -> PostfixExpression -> Ordering
Ord, ReadPrec [PostfixExpression]
ReadPrec PostfixExpression
Int -> ReadS PostfixExpression
ReadS [PostfixExpression]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [PostfixExpression]
$creadListPrec :: ReadPrec [PostfixExpression]
readPrec :: ReadPrec PostfixExpression
$creadPrec :: ReadPrec PostfixExpression
readList :: ReadS [PostfixExpression]
$creadList :: ReadS [PostfixExpression]
readsPrec :: Int -> ReadS PostfixExpression
$creadsPrec :: Int -> ReadS PostfixExpression
Read, Int -> PostfixExpression -> String -> String
[PostfixExpression] -> String -> String
PostfixExpression -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [PostfixExpression] -> String -> String
$cshowList :: [PostfixExpression] -> String -> String
show :: PostfixExpression -> String
$cshow :: PostfixExpression -> String
showsPrec :: Int -> PostfixExpression -> String -> String
$cshowsPrec :: Int -> PostfixExpression -> String -> String
Show)

_PostfixExpression :: Name
_PostfixExpression = (String -> Name
Core.Name String
"hydra/ext/java/syntax.PostfixExpression")

_PostfixExpression_primary :: FieldName
_PostfixExpression_primary = (String -> FieldName
Core.FieldName String
"primary")

_PostfixExpression_name :: FieldName
_PostfixExpression_name = (String -> FieldName
Core.FieldName String
"name")

_PostfixExpression_postIncrement :: FieldName
_PostfixExpression_postIncrement = (String -> FieldName
Core.FieldName String
"postIncrement")

_PostfixExpression_postDecrement :: FieldName
_PostfixExpression_postDecrement = (String -> FieldName
Core.FieldName String
"postDecrement")

newtype PostIncrementExpression = 
  PostIncrementExpression {
    PostIncrementExpression -> PostfixExpression
unPostIncrementExpression :: PostfixExpression}
  deriving (PostIncrementExpression -> PostIncrementExpression -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostIncrementExpression -> PostIncrementExpression -> Bool
$c/= :: PostIncrementExpression -> PostIncrementExpression -> Bool
== :: PostIncrementExpression -> PostIncrementExpression -> Bool
$c== :: PostIncrementExpression -> PostIncrementExpression -> Bool
Eq, Eq PostIncrementExpression
PostIncrementExpression -> PostIncrementExpression -> Bool
PostIncrementExpression -> PostIncrementExpression -> Ordering
PostIncrementExpression
-> PostIncrementExpression -> PostIncrementExpression
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: PostIncrementExpression
-> PostIncrementExpression -> PostIncrementExpression
$cmin :: PostIncrementExpression
-> PostIncrementExpression -> PostIncrementExpression
max :: PostIncrementExpression
-> PostIncrementExpression -> PostIncrementExpression
$cmax :: PostIncrementExpression
-> PostIncrementExpression -> PostIncrementExpression
>= :: PostIncrementExpression -> PostIncrementExpression -> Bool
$c>= :: PostIncrementExpression -> PostIncrementExpression -> Bool
> :: PostIncrementExpression -> PostIncrementExpression -> Bool
$c> :: PostIncrementExpression -> PostIncrementExpression -> Bool
<= :: PostIncrementExpression -> PostIncrementExpression -> Bool
$c<= :: PostIncrementExpression -> PostIncrementExpression -> Bool
< :: PostIncrementExpression -> PostIncrementExpression -> Bool
$c< :: PostIncrementExpression -> PostIncrementExpression -> Bool
compare :: PostIncrementExpression -> PostIncrementExpression -> Ordering
$ccompare :: PostIncrementExpression -> PostIncrementExpression -> Ordering
Ord, ReadPrec [PostIncrementExpression]
ReadPrec PostIncrementExpression
Int -> ReadS PostIncrementExpression
ReadS [PostIncrementExpression]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [PostIncrementExpression]
$creadListPrec :: ReadPrec [PostIncrementExpression]
readPrec :: ReadPrec PostIncrementExpression
$creadPrec :: ReadPrec PostIncrementExpression
readList :: ReadS [PostIncrementExpression]
$creadList :: ReadS [PostIncrementExpression]
readsPrec :: Int -> ReadS PostIncrementExpression
$creadsPrec :: Int -> ReadS PostIncrementExpression
Read, Int -> PostIncrementExpression -> String -> String
[PostIncrementExpression] -> String -> String
PostIncrementExpression -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [PostIncrementExpression] -> String -> String
$cshowList :: [PostIncrementExpression] -> String -> String
show :: PostIncrementExpression -> String
$cshow :: PostIncrementExpression -> String
showsPrec :: Int -> PostIncrementExpression -> String -> String
$cshowsPrec :: Int -> PostIncrementExpression -> String -> String
Show)

_PostIncrementExpression :: Name
_PostIncrementExpression = (String -> Name
Core.Name String
"hydra/ext/java/syntax.PostIncrementExpression")

newtype PostDecrementExpression = 
  PostDecrementExpression {
    PostDecrementExpression -> PostfixExpression
unPostDecrementExpression :: PostfixExpression}
  deriving (PostDecrementExpression -> PostDecrementExpression -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostDecrementExpression -> PostDecrementExpression -> Bool
$c/= :: PostDecrementExpression -> PostDecrementExpression -> Bool
== :: PostDecrementExpression -> PostDecrementExpression -> Bool
$c== :: PostDecrementExpression -> PostDecrementExpression -> Bool
Eq, Eq PostDecrementExpression
PostDecrementExpression -> PostDecrementExpression -> Bool
PostDecrementExpression -> PostDecrementExpression -> Ordering
PostDecrementExpression
-> PostDecrementExpression -> PostDecrementExpression
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: PostDecrementExpression
-> PostDecrementExpression -> PostDecrementExpression
$cmin :: PostDecrementExpression
-> PostDecrementExpression -> PostDecrementExpression
max :: PostDecrementExpression
-> PostDecrementExpression -> PostDecrementExpression
$cmax :: PostDecrementExpression
-> PostDecrementExpression -> PostDecrementExpression
>= :: PostDecrementExpression -> PostDecrementExpression -> Bool
$c>= :: PostDecrementExpression -> PostDecrementExpression -> Bool
> :: PostDecrementExpression -> PostDecrementExpression -> Bool
$c> :: PostDecrementExpression -> PostDecrementExpression -> Bool
<= :: PostDecrementExpression -> PostDecrementExpression -> Bool
$c<= :: PostDecrementExpression -> PostDecrementExpression -> Bool
< :: PostDecrementExpression -> PostDecrementExpression -> Bool
$c< :: PostDecrementExpression -> PostDecrementExpression -> Bool
compare :: PostDecrementExpression -> PostDecrementExpression -> Ordering
$ccompare :: PostDecrementExpression -> PostDecrementExpression -> Ordering
Ord, ReadPrec [PostDecrementExpression]
ReadPrec PostDecrementExpression
Int -> ReadS PostDecrementExpression
ReadS [PostDecrementExpression]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [PostDecrementExpression]
$creadListPrec :: ReadPrec [PostDecrementExpression]
readPrec :: ReadPrec PostDecrementExpression
$creadPrec :: ReadPrec PostDecrementExpression
readList :: ReadS [PostDecrementExpression]
$creadList :: ReadS [PostDecrementExpression]
readsPrec :: Int -> ReadS PostDecrementExpression
$creadsPrec :: Int -> ReadS PostDecrementExpression
Read, Int -> PostDecrementExpression -> String -> String
[PostDecrementExpression] -> String -> String
PostDecrementExpression -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [PostDecrementExpression] -> String -> String
$cshowList :: [PostDecrementExpression] -> String -> String
show :: PostDecrementExpression -> String
$cshow :: PostDecrementExpression -> String
showsPrec :: Int -> PostDecrementExpression -> String -> String
$cshowsPrec :: Int -> PostDecrementExpression -> String -> String
Show)

_PostDecrementExpression :: Name
_PostDecrementExpression = (String -> Name
Core.Name String
"hydra/ext/java/syntax.PostDecrementExpression")

data CastExpression = 
  CastExpressionPrimitive CastExpression_Primitive |
  CastExpressionNotPlusMinus CastExpression_NotPlusMinus |
  CastExpressionLambda CastExpression_Lambda
  deriving (CastExpression -> CastExpression -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CastExpression -> CastExpression -> Bool
$c/= :: CastExpression -> CastExpression -> Bool
== :: CastExpression -> CastExpression -> Bool
$c== :: CastExpression -> CastExpression -> Bool
Eq, Eq CastExpression
CastExpression -> CastExpression -> Bool
CastExpression -> CastExpression -> Ordering
CastExpression -> CastExpression -> CastExpression
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CastExpression -> CastExpression -> CastExpression
$cmin :: CastExpression -> CastExpression -> CastExpression
max :: CastExpression -> CastExpression -> CastExpression
$cmax :: CastExpression -> CastExpression -> CastExpression
>= :: CastExpression -> CastExpression -> Bool
$c>= :: CastExpression -> CastExpression -> Bool
> :: CastExpression -> CastExpression -> Bool
$c> :: CastExpression -> CastExpression -> Bool
<= :: CastExpression -> CastExpression -> Bool
$c<= :: CastExpression -> CastExpression -> Bool
< :: CastExpression -> CastExpression -> Bool
$c< :: CastExpression -> CastExpression -> Bool
compare :: CastExpression -> CastExpression -> Ordering
$ccompare :: CastExpression -> CastExpression -> Ordering
Ord, ReadPrec [CastExpression]
ReadPrec CastExpression
Int -> ReadS CastExpression
ReadS [CastExpression]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CastExpression]
$creadListPrec :: ReadPrec [CastExpression]
readPrec :: ReadPrec CastExpression
$creadPrec :: ReadPrec CastExpression
readList :: ReadS [CastExpression]
$creadList :: ReadS [CastExpression]
readsPrec :: Int -> ReadS CastExpression
$creadsPrec :: Int -> ReadS CastExpression
Read, Int -> CastExpression -> String -> String
[CastExpression] -> String -> String
CastExpression -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [CastExpression] -> String -> String
$cshowList :: [CastExpression] -> String -> String
show :: CastExpression -> String
$cshow :: CastExpression -> String
showsPrec :: Int -> CastExpression -> String -> String
$cshowsPrec :: Int -> CastExpression -> String -> String
Show)

_CastExpression :: Name
_CastExpression = (String -> Name
Core.Name String
"hydra/ext/java/syntax.CastExpression")

_CastExpression_primitive :: FieldName
_CastExpression_primitive = (String -> FieldName
Core.FieldName String
"primitive")

_CastExpression_notPlusMinus :: FieldName
_CastExpression_notPlusMinus = (String -> FieldName
Core.FieldName String
"notPlusMinus")

_CastExpression_lambda :: FieldName
_CastExpression_lambda = (String -> FieldName
Core.FieldName String
"lambda")

data CastExpression_Primitive = 
  CastExpression_Primitive {
    CastExpression_Primitive -> PrimitiveTypeWithAnnotations
castExpression_PrimitiveType :: PrimitiveTypeWithAnnotations,
    CastExpression_Primitive -> UnaryExpression
castExpression_PrimitiveExpression :: UnaryExpression}
  deriving (CastExpression_Primitive -> CastExpression_Primitive -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CastExpression_Primitive -> CastExpression_Primitive -> Bool
$c/= :: CastExpression_Primitive -> CastExpression_Primitive -> Bool
== :: CastExpression_Primitive -> CastExpression_Primitive -> Bool
$c== :: CastExpression_Primitive -> CastExpression_Primitive -> Bool
Eq, Eq CastExpression_Primitive
CastExpression_Primitive -> CastExpression_Primitive -> Bool
CastExpression_Primitive -> CastExpression_Primitive -> Ordering
CastExpression_Primitive
-> CastExpression_Primitive -> CastExpression_Primitive
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CastExpression_Primitive
-> CastExpression_Primitive -> CastExpression_Primitive
$cmin :: CastExpression_Primitive
-> CastExpression_Primitive -> CastExpression_Primitive
max :: CastExpression_Primitive
-> CastExpression_Primitive -> CastExpression_Primitive
$cmax :: CastExpression_Primitive
-> CastExpression_Primitive -> CastExpression_Primitive
>= :: CastExpression_Primitive -> CastExpression_Primitive -> Bool
$c>= :: CastExpression_Primitive -> CastExpression_Primitive -> Bool
> :: CastExpression_Primitive -> CastExpression_Primitive -> Bool
$c> :: CastExpression_Primitive -> CastExpression_Primitive -> Bool
<= :: CastExpression_Primitive -> CastExpression_Primitive -> Bool
$c<= :: CastExpression_Primitive -> CastExpression_Primitive -> Bool
< :: CastExpression_Primitive -> CastExpression_Primitive -> Bool
$c< :: CastExpression_Primitive -> CastExpression_Primitive -> Bool
compare :: CastExpression_Primitive -> CastExpression_Primitive -> Ordering
$ccompare :: CastExpression_Primitive -> CastExpression_Primitive -> Ordering
Ord, ReadPrec [CastExpression_Primitive]
ReadPrec CastExpression_Primitive
Int -> ReadS CastExpression_Primitive
ReadS [CastExpression_Primitive]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CastExpression_Primitive]
$creadListPrec :: ReadPrec [CastExpression_Primitive]
readPrec :: ReadPrec CastExpression_Primitive
$creadPrec :: ReadPrec CastExpression_Primitive
readList :: ReadS [CastExpression_Primitive]
$creadList :: ReadS [CastExpression_Primitive]
readsPrec :: Int -> ReadS CastExpression_Primitive
$creadsPrec :: Int -> ReadS CastExpression_Primitive
Read, Int -> CastExpression_Primitive -> String -> String
[CastExpression_Primitive] -> String -> String
CastExpression_Primitive -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [CastExpression_Primitive] -> String -> String
$cshowList :: [CastExpression_Primitive] -> String -> String
show :: CastExpression_Primitive -> String
$cshow :: CastExpression_Primitive -> String
showsPrec :: Int -> CastExpression_Primitive -> String -> String
$cshowsPrec :: Int -> CastExpression_Primitive -> String -> String
Show)

_CastExpression_Primitive :: Name
_CastExpression_Primitive = (String -> Name
Core.Name String
"hydra/ext/java/syntax.CastExpression.Primitive")

_CastExpression_Primitive_type :: FieldName
_CastExpression_Primitive_type = (String -> FieldName
Core.FieldName String
"type")

_CastExpression_Primitive_expression :: FieldName
_CastExpression_Primitive_expression = (String -> FieldName
Core.FieldName String
"expression")

data CastExpression_NotPlusMinus = 
  CastExpression_NotPlusMinus {
    CastExpression_NotPlusMinus -> CastExpression_RefAndBounds
castExpression_NotPlusMinusRefAndBounds :: CastExpression_RefAndBounds,
    CastExpression_NotPlusMinus -> UnaryExpression
castExpression_NotPlusMinusExpression :: UnaryExpression}
  deriving (CastExpression_NotPlusMinus -> CastExpression_NotPlusMinus -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CastExpression_NotPlusMinus -> CastExpression_NotPlusMinus -> Bool
$c/= :: CastExpression_NotPlusMinus -> CastExpression_NotPlusMinus -> Bool
== :: CastExpression_NotPlusMinus -> CastExpression_NotPlusMinus -> Bool
$c== :: CastExpression_NotPlusMinus -> CastExpression_NotPlusMinus -> Bool
Eq, Eq CastExpression_NotPlusMinus
CastExpression_NotPlusMinus -> CastExpression_NotPlusMinus -> Bool
CastExpression_NotPlusMinus
-> CastExpression_NotPlusMinus -> Ordering
CastExpression_NotPlusMinus
-> CastExpression_NotPlusMinus -> CastExpression_NotPlusMinus
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CastExpression_NotPlusMinus
-> CastExpression_NotPlusMinus -> CastExpression_NotPlusMinus
$cmin :: CastExpression_NotPlusMinus
-> CastExpression_NotPlusMinus -> CastExpression_NotPlusMinus
max :: CastExpression_NotPlusMinus
-> CastExpression_NotPlusMinus -> CastExpression_NotPlusMinus
$cmax :: CastExpression_NotPlusMinus
-> CastExpression_NotPlusMinus -> CastExpression_NotPlusMinus
>= :: CastExpression_NotPlusMinus -> CastExpression_NotPlusMinus -> Bool
$c>= :: CastExpression_NotPlusMinus -> CastExpression_NotPlusMinus -> Bool
> :: CastExpression_NotPlusMinus -> CastExpression_NotPlusMinus -> Bool
$c> :: CastExpression_NotPlusMinus -> CastExpression_NotPlusMinus -> Bool
<= :: CastExpression_NotPlusMinus -> CastExpression_NotPlusMinus -> Bool
$c<= :: CastExpression_NotPlusMinus -> CastExpression_NotPlusMinus -> Bool
< :: CastExpression_NotPlusMinus -> CastExpression_NotPlusMinus -> Bool
$c< :: CastExpression_NotPlusMinus -> CastExpression_NotPlusMinus -> Bool
compare :: CastExpression_NotPlusMinus
-> CastExpression_NotPlusMinus -> Ordering
$ccompare :: CastExpression_NotPlusMinus
-> CastExpression_NotPlusMinus -> Ordering
Ord, ReadPrec [CastExpression_NotPlusMinus]
ReadPrec CastExpression_NotPlusMinus
Int -> ReadS CastExpression_NotPlusMinus
ReadS [CastExpression_NotPlusMinus]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CastExpression_NotPlusMinus]
$creadListPrec :: ReadPrec [CastExpression_NotPlusMinus]
readPrec :: ReadPrec CastExpression_NotPlusMinus
$creadPrec :: ReadPrec CastExpression_NotPlusMinus
readList :: ReadS [CastExpression_NotPlusMinus]
$creadList :: ReadS [CastExpression_NotPlusMinus]
readsPrec :: Int -> ReadS CastExpression_NotPlusMinus
$creadsPrec :: Int -> ReadS CastExpression_NotPlusMinus
Read, Int -> CastExpression_NotPlusMinus -> String -> String
[CastExpression_NotPlusMinus] -> String -> String
CastExpression_NotPlusMinus -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [CastExpression_NotPlusMinus] -> String -> String
$cshowList :: [CastExpression_NotPlusMinus] -> String -> String
show :: CastExpression_NotPlusMinus -> String
$cshow :: CastExpression_NotPlusMinus -> String
showsPrec :: Int -> CastExpression_NotPlusMinus -> String -> String
$cshowsPrec :: Int -> CastExpression_NotPlusMinus -> String -> String
Show)

_CastExpression_NotPlusMinus :: Name
_CastExpression_NotPlusMinus = (String -> Name
Core.Name String
"hydra/ext/java/syntax.CastExpression.NotPlusMinus")

_CastExpression_NotPlusMinus_refAndBounds :: FieldName
_CastExpression_NotPlusMinus_refAndBounds = (String -> FieldName
Core.FieldName String
"refAndBounds")

_CastExpression_NotPlusMinus_expression :: FieldName
_CastExpression_NotPlusMinus_expression = (String -> FieldName
Core.FieldName String
"expression")

data CastExpression_Lambda = 
  CastExpression_Lambda {
    CastExpression_Lambda -> CastExpression_RefAndBounds
castExpression_LambdaRefAndBounds :: CastExpression_RefAndBounds,
    CastExpression_Lambda -> LambdaExpression
castExpression_LambdaExpression :: LambdaExpression}
  deriving (CastExpression_Lambda -> CastExpression_Lambda -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CastExpression_Lambda -> CastExpression_Lambda -> Bool
$c/= :: CastExpression_Lambda -> CastExpression_Lambda -> Bool
== :: CastExpression_Lambda -> CastExpression_Lambda -> Bool
$c== :: CastExpression_Lambda -> CastExpression_Lambda -> Bool
Eq, Eq CastExpression_Lambda
CastExpression_Lambda -> CastExpression_Lambda -> Bool
CastExpression_Lambda -> CastExpression_Lambda -> Ordering
CastExpression_Lambda
-> CastExpression_Lambda -> CastExpression_Lambda
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CastExpression_Lambda
-> CastExpression_Lambda -> CastExpression_Lambda
$cmin :: CastExpression_Lambda
-> CastExpression_Lambda -> CastExpression_Lambda
max :: CastExpression_Lambda
-> CastExpression_Lambda -> CastExpression_Lambda
$cmax :: CastExpression_Lambda
-> CastExpression_Lambda -> CastExpression_Lambda
>= :: CastExpression_Lambda -> CastExpression_Lambda -> Bool
$c>= :: CastExpression_Lambda -> CastExpression_Lambda -> Bool
> :: CastExpression_Lambda -> CastExpression_Lambda -> Bool
$c> :: CastExpression_Lambda -> CastExpression_Lambda -> Bool
<= :: CastExpression_Lambda -> CastExpression_Lambda -> Bool
$c<= :: CastExpression_Lambda -> CastExpression_Lambda -> Bool
< :: CastExpression_Lambda -> CastExpression_Lambda -> Bool
$c< :: CastExpression_Lambda -> CastExpression_Lambda -> Bool
compare :: CastExpression_Lambda -> CastExpression_Lambda -> Ordering
$ccompare :: CastExpression_Lambda -> CastExpression_Lambda -> Ordering
Ord, ReadPrec [CastExpression_Lambda]
ReadPrec CastExpression_Lambda
Int -> ReadS CastExpression_Lambda
ReadS [CastExpression_Lambda]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CastExpression_Lambda]
$creadListPrec :: ReadPrec [CastExpression_Lambda]
readPrec :: ReadPrec CastExpression_Lambda
$creadPrec :: ReadPrec CastExpression_Lambda
readList :: ReadS [CastExpression_Lambda]
$creadList :: ReadS [CastExpression_Lambda]
readsPrec :: Int -> ReadS CastExpression_Lambda
$creadsPrec :: Int -> ReadS CastExpression_Lambda
Read, Int -> CastExpression_Lambda -> String -> String
[CastExpression_Lambda] -> String -> String
CastExpression_Lambda -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [CastExpression_Lambda] -> String -> String
$cshowList :: [CastExpression_Lambda] -> String -> String
show :: CastExpression_Lambda -> String
$cshow :: CastExpression_Lambda -> String
showsPrec :: Int -> CastExpression_Lambda -> String -> String
$cshowsPrec :: Int -> CastExpression_Lambda -> String -> String
Show)

_CastExpression_Lambda :: Name
_CastExpression_Lambda = (String -> Name
Core.Name String
"hydra/ext/java/syntax.CastExpression.Lambda")

_CastExpression_Lambda_refAndBounds :: FieldName
_CastExpression_Lambda_refAndBounds = (String -> FieldName
Core.FieldName String
"refAndBounds")

_CastExpression_Lambda_expression :: FieldName
_CastExpression_Lambda_expression = (String -> FieldName
Core.FieldName String
"expression")

data CastExpression_RefAndBounds = 
  CastExpression_RefAndBounds {
    CastExpression_RefAndBounds -> ReferenceType
castExpression_RefAndBoundsType :: ReferenceType,
    CastExpression_RefAndBounds -> [AdditionalBound]
castExpression_RefAndBoundsBounds :: [AdditionalBound]}
  deriving (CastExpression_RefAndBounds -> CastExpression_RefAndBounds -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CastExpression_RefAndBounds -> CastExpression_RefAndBounds -> Bool
$c/= :: CastExpression_RefAndBounds -> CastExpression_RefAndBounds -> Bool
== :: CastExpression_RefAndBounds -> CastExpression_RefAndBounds -> Bool
$c== :: CastExpression_RefAndBounds -> CastExpression_RefAndBounds -> Bool
Eq, Eq CastExpression_RefAndBounds
CastExpression_RefAndBounds -> CastExpression_RefAndBounds -> Bool
CastExpression_RefAndBounds
-> CastExpression_RefAndBounds -> Ordering
CastExpression_RefAndBounds
-> CastExpression_RefAndBounds -> CastExpression_RefAndBounds
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CastExpression_RefAndBounds
-> CastExpression_RefAndBounds -> CastExpression_RefAndBounds
$cmin :: CastExpression_RefAndBounds
-> CastExpression_RefAndBounds -> CastExpression_RefAndBounds
max :: CastExpression_RefAndBounds
-> CastExpression_RefAndBounds -> CastExpression_RefAndBounds
$cmax :: CastExpression_RefAndBounds
-> CastExpression_RefAndBounds -> CastExpression_RefAndBounds
>= :: CastExpression_RefAndBounds -> CastExpression_RefAndBounds -> Bool
$c>= :: CastExpression_RefAndBounds -> CastExpression_RefAndBounds -> Bool
> :: CastExpression_RefAndBounds -> CastExpression_RefAndBounds -> Bool
$c> :: CastExpression_RefAndBounds -> CastExpression_RefAndBounds -> Bool
<= :: CastExpression_RefAndBounds -> CastExpression_RefAndBounds -> Bool
$c<= :: CastExpression_RefAndBounds -> CastExpression_RefAndBounds -> Bool
< :: CastExpression_RefAndBounds -> CastExpression_RefAndBounds -> Bool
$c< :: CastExpression_RefAndBounds -> CastExpression_RefAndBounds -> Bool
compare :: CastExpression_RefAndBounds
-> CastExpression_RefAndBounds -> Ordering
$ccompare :: CastExpression_RefAndBounds
-> CastExpression_RefAndBounds -> Ordering
Ord, ReadPrec [CastExpression_RefAndBounds]
ReadPrec CastExpression_RefAndBounds
Int -> ReadS CastExpression_RefAndBounds
ReadS [CastExpression_RefAndBounds]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CastExpression_RefAndBounds]
$creadListPrec :: ReadPrec [CastExpression_RefAndBounds]
readPrec :: ReadPrec CastExpression_RefAndBounds
$creadPrec :: ReadPrec CastExpression_RefAndBounds
readList :: ReadS [CastExpression_RefAndBounds]
$creadList :: ReadS [CastExpression_RefAndBounds]
readsPrec :: Int -> ReadS CastExpression_RefAndBounds
$creadsPrec :: Int -> ReadS CastExpression_RefAndBounds
Read, Int -> CastExpression_RefAndBounds -> String -> String
[CastExpression_RefAndBounds] -> String -> String
CastExpression_RefAndBounds -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [CastExpression_RefAndBounds] -> String -> String
$cshowList :: [CastExpression_RefAndBounds] -> String -> String
show :: CastExpression_RefAndBounds -> String
$cshow :: CastExpression_RefAndBounds -> String
showsPrec :: Int -> CastExpression_RefAndBounds -> String -> String
$cshowsPrec :: Int -> CastExpression_RefAndBounds -> String -> String
Show)

_CastExpression_RefAndBounds :: Name
_CastExpression_RefAndBounds = (String -> Name
Core.Name String
"hydra/ext/java/syntax.CastExpression.RefAndBounds")

_CastExpression_RefAndBounds_type :: FieldName
_CastExpression_RefAndBounds_type = (String -> FieldName
Core.FieldName String
"type")

_CastExpression_RefAndBounds_bounds :: FieldName
_CastExpression_RefAndBounds_bounds = (String -> FieldName
Core.FieldName String
"bounds")

newtype ConstantExpression = 
  ConstantExpression {
    ConstantExpression -> Expression
unConstantExpression :: Expression}
  deriving (ConstantExpression -> ConstantExpression -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ConstantExpression -> ConstantExpression -> Bool
$c/= :: ConstantExpression -> ConstantExpression -> Bool
== :: ConstantExpression -> ConstantExpression -> Bool
$c== :: ConstantExpression -> ConstantExpression -> Bool
Eq, Eq ConstantExpression
ConstantExpression -> ConstantExpression -> Bool
ConstantExpression -> ConstantExpression -> Ordering
ConstantExpression -> ConstantExpression -> ConstantExpression
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ConstantExpression -> ConstantExpression -> ConstantExpression
$cmin :: ConstantExpression -> ConstantExpression -> ConstantExpression
max :: ConstantExpression -> ConstantExpression -> ConstantExpression
$cmax :: ConstantExpression -> ConstantExpression -> ConstantExpression
>= :: ConstantExpression -> ConstantExpression -> Bool
$c>= :: ConstantExpression -> ConstantExpression -> Bool
> :: ConstantExpression -> ConstantExpression -> Bool
$c> :: ConstantExpression -> ConstantExpression -> Bool
<= :: ConstantExpression -> ConstantExpression -> Bool
$c<= :: ConstantExpression -> ConstantExpression -> Bool
< :: ConstantExpression -> ConstantExpression -> Bool
$c< :: ConstantExpression -> ConstantExpression -> Bool
compare :: ConstantExpression -> ConstantExpression -> Ordering
$ccompare :: ConstantExpression -> ConstantExpression -> Ordering
Ord, ReadPrec [ConstantExpression]
ReadPrec ConstantExpression
Int -> ReadS ConstantExpression
ReadS [ConstantExpression]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ConstantExpression]
$creadListPrec :: ReadPrec [ConstantExpression]
readPrec :: ReadPrec ConstantExpression
$creadPrec :: ReadPrec ConstantExpression
readList :: ReadS [ConstantExpression]
$creadList :: ReadS [ConstantExpression]
readsPrec :: Int -> ReadS ConstantExpression
$creadsPrec :: Int -> ReadS ConstantExpression
Read, Int -> ConstantExpression -> String -> String
[ConstantExpression] -> String -> String
ConstantExpression -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ConstantExpression] -> String -> String
$cshowList :: [ConstantExpression] -> String -> String
show :: ConstantExpression -> String
$cshow :: ConstantExpression -> String
showsPrec :: Int -> ConstantExpression -> String -> String
$cshowsPrec :: Int -> ConstantExpression -> String -> String
Show)

_ConstantExpression :: Name
_ConstantExpression = (String -> Name
Core.Name String
"hydra/ext/java/syntax.ConstantExpression")