-- | 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.Langs.Java.Syntax where

import qualified Hydra.Core as Core
import Data.Int
import Data.List as L
import Data.Map as M
import Data.Set as S

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

_FieldAccess :: Name
_FieldAccess = (String -> Name
Core.Name String
"hydra/langs/java/syntax.FieldAccess")

_FieldAccess_qualifier :: Name
_FieldAccess_qualifier = (String -> Name
Core.Name String
"qualifier")

_FieldAccess_identifier :: Name
_FieldAccess_identifier = (String -> Name
Core.Name String
"identifier")

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

_FieldAccess_Qualifier :: Name
_FieldAccess_Qualifier = (String -> Name
Core.Name String
"hydra/langs/java/syntax.FieldAccess.Qualifier")

_FieldAccess_Qualifier_primary :: Name
_FieldAccess_Qualifier_primary = (String -> Name
Core.Name String
"primary")

_FieldAccess_Qualifier_super :: Name
_FieldAccess_Qualifier_super = (String -> Name
Core.Name String
"super")

_FieldAccess_Qualifier_typed :: Name
_FieldAccess_Qualifier_typed = (String -> Name
Core.Name String
"typed")

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

_ArrayAccess :: Name
_ArrayAccess = (String -> Name
Core.Name String
"hydra/langs/java/syntax.ArrayAccess")

_ArrayAccess_expression :: Name
_ArrayAccess_expression = (String -> Name
Core.Name String
"expression")

_ArrayAccess_variant :: Name
_ArrayAccess_variant = (String -> Name
Core.Name String
"variant")

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

_ArrayAccess_Variant :: Name
_ArrayAccess_Variant = (String -> Name
Core.Name String
"hydra/langs/java/syntax.ArrayAccess.Variant")

_ArrayAccess_Variant_name :: Name
_ArrayAccess_Variant_name = (String -> Name
Core.Name String
"name")

_ArrayAccess_Variant_primary :: Name
_ArrayAccess_Variant_primary = (String -> Name
Core.Name String
"primary")

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

_MethodInvocation :: Name
_MethodInvocation = (String -> Name
Core.Name String
"hydra/langs/java/syntax.MethodInvocation")

_MethodInvocation_header :: Name
_MethodInvocation_header = (String -> Name
Core.Name String
"header")

_MethodInvocation_arguments :: Name
_MethodInvocation_arguments = (String -> Name
Core.Name String
"arguments")

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

_MethodInvocation_Header :: Name
_MethodInvocation_Header = (String -> Name
Core.Name String
"hydra/langs/java/syntax.MethodInvocation.Header")

_MethodInvocation_Header_simple :: Name
_MethodInvocation_Header_simple = (String -> Name
Core.Name String
"simple")

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

_MethodInvocation_Complex :: Name
_MethodInvocation_Complex = (String -> Name
Core.Name String
"hydra/langs/java/syntax.MethodInvocation.Complex")

_MethodInvocation_Complex_variant :: Name
_MethodInvocation_Complex_variant = (String -> Name
Core.Name String
"variant")

_MethodInvocation_Complex_typeArguments :: Name
_MethodInvocation_Complex_typeArguments = (String -> Name
Core.Name String
"typeArguments")

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

_MethodInvocation_Variant :: Name
_MethodInvocation_Variant = (String -> Name
Core.Name String
"hydra/langs/java/syntax.MethodInvocation.Variant")

_MethodInvocation_Variant_type :: Name
_MethodInvocation_Variant_type = (String -> Name
Core.Name String
"type")

_MethodInvocation_Variant_expression :: Name
_MethodInvocation_Variant_expression = (String -> Name
Core.Name String
"expression")

_MethodInvocation_Variant_primary :: Name
_MethodInvocation_Variant_primary = (String -> Name
Core.Name String
"primary")

_MethodInvocation_Variant_super :: Name
_MethodInvocation_Variant_super = (String -> Name
Core.Name String
"super")

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

_MethodReference :: Name
_MethodReference = (String -> Name
Core.Name String
"hydra/langs/java/syntax.MethodReference")

_MethodReference_expression :: Name
_MethodReference_expression = (String -> Name
Core.Name String
"expression")

_MethodReference_primary :: Name
_MethodReference_primary = (String -> Name
Core.Name String
"primary")

_MethodReference_referenceType :: Name
_MethodReference_referenceType = (String -> Name
Core.Name String
"referenceType")

_MethodReference_super :: Name
_MethodReference_super = (String -> Name
Core.Name String
"super")

_MethodReference_new :: Name
_MethodReference_new = (String -> Name
Core.Name String
"new")

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

_MethodReference_Expression :: Name
_MethodReference_Expression = (String -> Name
Core.Name String
"hydra/langs/java/syntax.MethodReference.Expression")

_MethodReference_Expression_name :: Name
_MethodReference_Expression_name = (String -> Name
Core.Name String
"name")

_MethodReference_Expression_typeArguments :: Name
_MethodReference_Expression_typeArguments = (String -> Name
Core.Name String
"typeArguments")

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

_MethodReference_Primary :: Name
_MethodReference_Primary = (String -> Name
Core.Name String
"hydra/langs/java/syntax.MethodReference.Primary")

_MethodReference_Primary_primary :: Name
_MethodReference_Primary_primary = (String -> Name
Core.Name String
"primary")

_MethodReference_Primary_typeArguments :: Name
_MethodReference_Primary_typeArguments = (String -> Name
Core.Name String
"typeArguments")

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

_MethodReference_ReferenceType :: Name
_MethodReference_ReferenceType = (String -> Name
Core.Name String
"hydra/langs/java/syntax.MethodReference.ReferenceType")

_MethodReference_ReferenceType_referenceType :: Name
_MethodReference_ReferenceType_referenceType = (String -> Name
Core.Name String
"referenceType")

_MethodReference_ReferenceType_typeArguments :: Name
_MethodReference_ReferenceType_typeArguments = (String -> Name
Core.Name String
"typeArguments")

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

_MethodReference_Super :: Name
_MethodReference_Super = (String -> Name
Core.Name String
"hydra/langs/java/syntax.MethodReference.Super")

_MethodReference_Super_typeArguments :: Name
_MethodReference_Super_typeArguments = (String -> Name
Core.Name String
"typeArguments")

_MethodReference_Super_identifier :: Name
_MethodReference_Super_identifier = (String -> Name
Core.Name String
"identifier")

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

_MethodReference_New :: Name
_MethodReference_New = (String -> Name
Core.Name String
"hydra/langs/java/syntax.MethodReference.New")

_MethodReference_New_classType :: Name
_MethodReference_New_classType = (String -> Name
Core.Name String
"classType")

_MethodReference_New_typeArguments :: Name
_MethodReference_New_typeArguments = (String -> Name
Core.Name String
"typeArguments")

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

_MethodReference_Array :: Name
_MethodReference_Array = (String -> Name
Core.Name String
"hydra/langs/java/syntax.MethodReference.Array")

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

_ArrayCreationExpression :: Name
_ArrayCreationExpression = (String -> Name
Core.Name String
"hydra/langs/java/syntax.ArrayCreationExpression")

_ArrayCreationExpression_primitive :: Name
_ArrayCreationExpression_primitive = (String -> Name
Core.Name String
"primitive")

_ArrayCreationExpression_classOrInterface :: Name
_ArrayCreationExpression_classOrInterface = (String -> Name
Core.Name String
"classOrInterface")

_ArrayCreationExpression_primitiveArray :: Name
_ArrayCreationExpression_primitiveArray = (String -> Name
Core.Name String
"primitiveArray")

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

_ArrayCreationExpression_Primitive :: Name
_ArrayCreationExpression_Primitive = (String -> Name
Core.Name String
"hydra/langs/java/syntax.ArrayCreationExpression.Primitive")

_ArrayCreationExpression_Primitive_type :: Name
_ArrayCreationExpression_Primitive_type = (String -> Name
Core.Name String
"type")

_ArrayCreationExpression_Primitive_dimExprs :: Name
_ArrayCreationExpression_Primitive_dimExprs = (String -> Name
Core.Name String
"dimExprs")

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

_ArrayCreationExpression_ClassOrInterface :: Name
_ArrayCreationExpression_ClassOrInterface = (String -> Name
Core.Name String
"hydra/langs/java/syntax.ArrayCreationExpression.ClassOrInterface")

_ArrayCreationExpression_ClassOrInterface_type :: Name
_ArrayCreationExpression_ClassOrInterface_type = (String -> Name
Core.Name String
"type")

_ArrayCreationExpression_ClassOrInterface_dimExprs :: Name
_ArrayCreationExpression_ClassOrInterface_dimExprs = (String -> Name
Core.Name String
"dimExprs")

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

_ArrayCreationExpression_PrimitiveArray :: Name
_ArrayCreationExpression_PrimitiveArray = (String -> Name
Core.Name String
"hydra/langs/java/syntax.ArrayCreationExpression.PrimitiveArray")

_ArrayCreationExpression_PrimitiveArray_type :: Name
_ArrayCreationExpression_PrimitiveArray_type = (String -> Name
Core.Name String
"type")

_ArrayCreationExpression_PrimitiveArray_dims :: Name
_ArrayCreationExpression_PrimitiveArray_dims = (String -> Name
Core.Name String
"dims")

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

_ArrayCreationExpression_ClassOrInterfaceArray :: Name
_ArrayCreationExpression_ClassOrInterfaceArray = (String -> Name
Core.Name String
"hydra/langs/java/syntax.ArrayCreationExpression.ClassOrInterfaceArray")

_ArrayCreationExpression_ClassOrInterfaceArray_type :: Name
_ArrayCreationExpression_ClassOrInterfaceArray_type = (String -> Name
Core.Name String
"type")

_ArrayCreationExpression_ClassOrInterfaceArray_dims :: Name
_ArrayCreationExpression_ClassOrInterfaceArray_dims = (String -> Name
Core.Name String
"dims")

_ArrayCreationExpression_ClassOrInterfaceArray_array :: Name
_ArrayCreationExpression_ClassOrInterfaceArray_array = (String -> Name
Core.Name String
"array")

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

_DimExpr :: Name
_DimExpr = (String -> Name
Core.Name String
"hydra/langs/java/syntax.DimExpr")

_DimExpr_annotations :: Name
_DimExpr_annotations = (String -> Name
Core.Name String
"annotations")

_DimExpr_expression :: Name
_DimExpr_expression = (String -> Name
Core.Name String
"expression")

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

_Expression :: Name
_Expression = (String -> Name
Core.Name String
"hydra/langs/java/syntax.Expression")

_Expression_lambda :: Name
_Expression_lambda = (String -> Name
Core.Name String
"lambda")

_Expression_assignment :: Name
_Expression_assignment = (String -> Name
Core.Name String
"assignment")

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

_LambdaExpression :: Name
_LambdaExpression = (String -> Name
Core.Name String
"hydra/langs/java/syntax.LambdaExpression")

_LambdaExpression_parameters :: Name
_LambdaExpression_parameters = (String -> Name
Core.Name String
"parameters")

_LambdaExpression_body :: Name
_LambdaExpression_body = (String -> Name
Core.Name String
"body")

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

_LambdaParameters :: Name
_LambdaParameters = (String -> Name
Core.Name String
"hydra/langs/java/syntax.LambdaParameters")

_LambdaParameters_tuple :: Name
_LambdaParameters_tuple = (String -> Name
Core.Name String
"tuple")

_LambdaParameters_single :: Name
_LambdaParameters_single = (String -> Name
Core.Name String
"single")

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

_LambdaParameter :: Name
_LambdaParameter = (String -> Name
Core.Name String
"hydra/langs/java/syntax.LambdaParameter")

_LambdaParameter_normal :: Name
_LambdaParameter_normal = (String -> Name
Core.Name String
"normal")

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

_LambdaParameter_Normal :: Name
_LambdaParameter_Normal = (String -> Name
Core.Name String
"hydra/langs/java/syntax.LambdaParameter.Normal")

_LambdaParameter_Normal_modifiers :: Name
_LambdaParameter_Normal_modifiers = (String -> Name
Core.Name String
"modifiers")

_LambdaParameter_Normal_type :: Name
_LambdaParameter_Normal_type = (String -> Name
Core.Name String
"type")

_LambdaParameter_Normal_id :: Name
_LambdaParameter_Normal_id = (String -> Name
Core.Name String
"id")

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

_LambdaParameterType :: Name
_LambdaParameterType = (String -> Name
Core.Name String
"hydra/langs/java/syntax.LambdaParameterType")

_LambdaParameterType_type :: Name
_LambdaParameterType_type = (String -> Name
Core.Name String
"type")

_LambdaParameterType_var :: Name
_LambdaParameterType_var = (String -> Name
Core.Name String
"var")

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

_LambdaBody :: Name
_LambdaBody = (String -> Name
Core.Name String
"hydra/langs/java/syntax.LambdaBody")

_LambdaBody_expression :: Name
_LambdaBody_expression = (String -> Name
Core.Name String
"expression")

_LambdaBody_block :: Name
_LambdaBody_block = (String -> Name
Core.Name String
"block")

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

_AssignmentExpression :: Name
_AssignmentExpression = (String -> Name
Core.Name String
"hydra/langs/java/syntax.AssignmentExpression")

_AssignmentExpression_conditional :: Name
_AssignmentExpression_conditional = (String -> Name
Core.Name String
"conditional")

_AssignmentExpression_assignment :: Name
_AssignmentExpression_assignment = (String -> Name
Core.Name String
"assignment")

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

_Assignment :: Name
_Assignment = (String -> Name
Core.Name String
"hydra/langs/java/syntax.Assignment")

_Assignment_lhs :: Name
_Assignment_lhs = (String -> Name
Core.Name String
"lhs")

_Assignment_op :: Name
_Assignment_op = (String -> Name
Core.Name String
"op")

_Assignment_expression :: Name
_Assignment_expression = (String -> Name
Core.Name String
"expression")

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

_LeftHandSide :: Name
_LeftHandSide = (String -> Name
Core.Name String
"hydra/langs/java/syntax.LeftHandSide")

_LeftHandSide_expressionName :: Name
_LeftHandSide_expressionName = (String -> Name
Core.Name String
"expressionName")

_LeftHandSide_fieldAccess :: Name
_LeftHandSide_fieldAccess = (String -> Name
Core.Name String
"fieldAccess")

_LeftHandSide_arrayAccess :: Name
_LeftHandSide_arrayAccess = (String -> Name
Core.Name String
"arrayAccess")

data AssignmentOperator = 
  AssignmentOperatorSimple  |
  AssignmentOperatorTimes  |
  AssignmentOperatorDiv  |
  AssignmentOperatorMod  |
  AssignmentOperatorPlus  |
  AssignmentOperatorMinus  |
  AssignmentOperatorShiftLeft  |
  AssignmentOperatorShiftRight  |
  AssignmentOperatorShiftRightZeroFill  |
  AssignmentOperatorAnd  |
  AssignmentOperatorXor  |
  AssignmentOperatorOr 
  deriving (AssignmentOperator -> AssignmentOperator -> Bool
(AssignmentOperator -> AssignmentOperator -> Bool)
-> (AssignmentOperator -> AssignmentOperator -> Bool)
-> Eq AssignmentOperator
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AssignmentOperator -> AssignmentOperator -> Bool
== :: AssignmentOperator -> AssignmentOperator -> Bool
$c/= :: AssignmentOperator -> AssignmentOperator -> Bool
/= :: AssignmentOperator -> AssignmentOperator -> Bool
Eq, Eq AssignmentOperator
Eq AssignmentOperator =>
(AssignmentOperator -> AssignmentOperator -> Ordering)
-> (AssignmentOperator -> AssignmentOperator -> Bool)
-> (AssignmentOperator -> AssignmentOperator -> Bool)
-> (AssignmentOperator -> AssignmentOperator -> Bool)
-> (AssignmentOperator -> AssignmentOperator -> Bool)
-> (AssignmentOperator -> AssignmentOperator -> AssignmentOperator)
-> (AssignmentOperator -> AssignmentOperator -> AssignmentOperator)
-> Ord 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
$ccompare :: AssignmentOperator -> AssignmentOperator -> Ordering
compare :: AssignmentOperator -> AssignmentOperator -> Ordering
$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
>= :: AssignmentOperator -> AssignmentOperator -> Bool
$cmax :: AssignmentOperator -> AssignmentOperator -> AssignmentOperator
max :: AssignmentOperator -> AssignmentOperator -> AssignmentOperator
$cmin :: AssignmentOperator -> AssignmentOperator -> AssignmentOperator
min :: AssignmentOperator -> AssignmentOperator -> AssignmentOperator
Ord, ReadPrec [AssignmentOperator]
ReadPrec AssignmentOperator
Int -> ReadS AssignmentOperator
ReadS [AssignmentOperator]
(Int -> ReadS AssignmentOperator)
-> ReadS [AssignmentOperator]
-> ReadPrec AssignmentOperator
-> ReadPrec [AssignmentOperator]
-> Read AssignmentOperator
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS AssignmentOperator
readsPrec :: Int -> ReadS AssignmentOperator
$creadList :: ReadS [AssignmentOperator]
readList :: ReadS [AssignmentOperator]
$creadPrec :: ReadPrec AssignmentOperator
readPrec :: ReadPrec AssignmentOperator
$creadListPrec :: ReadPrec [AssignmentOperator]
readListPrec :: ReadPrec [AssignmentOperator]
Read, Int -> AssignmentOperator -> String -> String
[AssignmentOperator] -> String -> String
AssignmentOperator -> String
(Int -> AssignmentOperator -> String -> String)
-> (AssignmentOperator -> String)
-> ([AssignmentOperator] -> String -> String)
-> Show AssignmentOperator
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> AssignmentOperator -> String -> String
showsPrec :: Int -> AssignmentOperator -> String -> String
$cshow :: AssignmentOperator -> String
show :: AssignmentOperator -> String
$cshowList :: [AssignmentOperator] -> String -> String
showList :: [AssignmentOperator] -> String -> String
Show)

_AssignmentOperator :: Name
_AssignmentOperator = (String -> Name
Core.Name String
"hydra/langs/java/syntax.AssignmentOperator")

_AssignmentOperator_simple :: Name
_AssignmentOperator_simple = (String -> Name
Core.Name String
"simple")

_AssignmentOperator_times :: Name
_AssignmentOperator_times = (String -> Name
Core.Name String
"times")

_AssignmentOperator_div :: Name
_AssignmentOperator_div = (String -> Name
Core.Name String
"div")

_AssignmentOperator_mod :: Name
_AssignmentOperator_mod = (String -> Name
Core.Name String
"mod")

_AssignmentOperator_plus :: Name
_AssignmentOperator_plus = (String -> Name
Core.Name String
"plus")

_AssignmentOperator_minus :: Name
_AssignmentOperator_minus = (String -> Name
Core.Name String
"minus")

_AssignmentOperator_shiftLeft :: Name
_AssignmentOperator_shiftLeft = (String -> Name
Core.Name String
"shiftLeft")

_AssignmentOperator_shiftRight :: Name
_AssignmentOperator_shiftRight = (String -> Name
Core.Name String
"shiftRight")

_AssignmentOperator_shiftRightZeroFill :: Name
_AssignmentOperator_shiftRightZeroFill = (String -> Name
Core.Name String
"shiftRightZeroFill")

_AssignmentOperator_and :: Name
_AssignmentOperator_and = (String -> Name
Core.Name String
"and")

_AssignmentOperator_xor :: Name
_AssignmentOperator_xor = (String -> Name
Core.Name String
"xor")

_AssignmentOperator_or :: Name
_AssignmentOperator_or = (String -> Name
Core.Name String
"or")

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

_ConditionalExpression :: Name
_ConditionalExpression = (String -> Name
Core.Name String
"hydra/langs/java/syntax.ConditionalExpression")

_ConditionalExpression_simple :: Name
_ConditionalExpression_simple = (String -> Name
Core.Name String
"simple")

_ConditionalExpression_ternaryCond :: Name
_ConditionalExpression_ternaryCond = (String -> Name
Core.Name String
"ternaryCond")

_ConditionalExpression_ternaryLambda :: Name
_ConditionalExpression_ternaryLambda = (String -> Name
Core.Name 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
(ConditionalExpression_TernaryCond
 -> ConditionalExpression_TernaryCond -> Bool)
-> (ConditionalExpression_TernaryCond
    -> ConditionalExpression_TernaryCond -> Bool)
-> Eq ConditionalExpression_TernaryCond
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ConditionalExpression_TernaryCond
-> ConditionalExpression_TernaryCond -> Bool
== :: ConditionalExpression_TernaryCond
-> ConditionalExpression_TernaryCond -> Bool
$c/= :: ConditionalExpression_TernaryCond
-> ConditionalExpression_TernaryCond -> Bool
/= :: ConditionalExpression_TernaryCond
-> ConditionalExpression_TernaryCond -> Bool
Eq, Eq ConditionalExpression_TernaryCond
Eq ConditionalExpression_TernaryCond =>
(ConditionalExpression_TernaryCond
 -> ConditionalExpression_TernaryCond -> Ordering)
-> (ConditionalExpression_TernaryCond
    -> ConditionalExpression_TernaryCond -> Bool)
-> (ConditionalExpression_TernaryCond
    -> ConditionalExpression_TernaryCond -> Bool)
-> (ConditionalExpression_TernaryCond
    -> ConditionalExpression_TernaryCond -> Bool)
-> (ConditionalExpression_TernaryCond
    -> ConditionalExpression_TernaryCond -> Bool)
-> (ConditionalExpression_TernaryCond
    -> ConditionalExpression_TernaryCond
    -> ConditionalExpression_TernaryCond)
-> (ConditionalExpression_TernaryCond
    -> ConditionalExpression_TernaryCond
    -> ConditionalExpression_TernaryCond)
-> Ord 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
$ccompare :: ConditionalExpression_TernaryCond
-> ConditionalExpression_TernaryCond -> Ordering
compare :: ConditionalExpression_TernaryCond
-> ConditionalExpression_TernaryCond -> Ordering
$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
>= :: ConditionalExpression_TernaryCond
-> ConditionalExpression_TernaryCond -> Bool
$cmax :: ConditionalExpression_TernaryCond
-> ConditionalExpression_TernaryCond
-> ConditionalExpression_TernaryCond
max :: ConditionalExpression_TernaryCond
-> ConditionalExpression_TernaryCond
-> ConditionalExpression_TernaryCond
$cmin :: ConditionalExpression_TernaryCond
-> ConditionalExpression_TernaryCond
-> ConditionalExpression_TernaryCond
min :: ConditionalExpression_TernaryCond
-> ConditionalExpression_TernaryCond
-> ConditionalExpression_TernaryCond
Ord, ReadPrec [ConditionalExpression_TernaryCond]
ReadPrec ConditionalExpression_TernaryCond
Int -> ReadS ConditionalExpression_TernaryCond
ReadS [ConditionalExpression_TernaryCond]
(Int -> ReadS ConditionalExpression_TernaryCond)
-> ReadS [ConditionalExpression_TernaryCond]
-> ReadPrec ConditionalExpression_TernaryCond
-> ReadPrec [ConditionalExpression_TernaryCond]
-> Read ConditionalExpression_TernaryCond
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ConditionalExpression_TernaryCond
readsPrec :: Int -> ReadS ConditionalExpression_TernaryCond
$creadList :: ReadS [ConditionalExpression_TernaryCond]
readList :: ReadS [ConditionalExpression_TernaryCond]
$creadPrec :: ReadPrec ConditionalExpression_TernaryCond
readPrec :: ReadPrec ConditionalExpression_TernaryCond
$creadListPrec :: ReadPrec [ConditionalExpression_TernaryCond]
readListPrec :: ReadPrec [ConditionalExpression_TernaryCond]
Read, Int -> ConditionalExpression_TernaryCond -> String -> String
[ConditionalExpression_TernaryCond] -> String -> String
ConditionalExpression_TernaryCond -> String
(Int -> ConditionalExpression_TernaryCond -> String -> String)
-> (ConditionalExpression_TernaryCond -> String)
-> ([ConditionalExpression_TernaryCond] -> String -> String)
-> Show ConditionalExpression_TernaryCond
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> ConditionalExpression_TernaryCond -> String -> String
showsPrec :: Int -> ConditionalExpression_TernaryCond -> String -> String
$cshow :: ConditionalExpression_TernaryCond -> String
show :: ConditionalExpression_TernaryCond -> String
$cshowList :: [ConditionalExpression_TernaryCond] -> String -> String
showList :: [ConditionalExpression_TernaryCond] -> String -> String
Show)

_ConditionalExpression_TernaryCond :: Name
_ConditionalExpression_TernaryCond = (String -> Name
Core.Name String
"hydra/langs/java/syntax.ConditionalExpression.TernaryCond")

_ConditionalExpression_TernaryCond_cond :: Name
_ConditionalExpression_TernaryCond_cond = (String -> Name
Core.Name String
"cond")

_ConditionalExpression_TernaryCond_ifTrue :: Name
_ConditionalExpression_TernaryCond_ifTrue = (String -> Name
Core.Name String
"ifTrue")

_ConditionalExpression_TernaryCond_ifFalse :: Name
_ConditionalExpression_TernaryCond_ifFalse = (String -> Name
Core.Name 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
(ConditionalExpression_TernaryLambda
 -> ConditionalExpression_TernaryLambda -> Bool)
-> (ConditionalExpression_TernaryLambda
    -> ConditionalExpression_TernaryLambda -> Bool)
-> Eq ConditionalExpression_TernaryLambda
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ConditionalExpression_TernaryLambda
-> ConditionalExpression_TernaryLambda -> Bool
== :: ConditionalExpression_TernaryLambda
-> ConditionalExpression_TernaryLambda -> Bool
$c/= :: ConditionalExpression_TernaryLambda
-> ConditionalExpression_TernaryLambda -> Bool
/= :: ConditionalExpression_TernaryLambda
-> ConditionalExpression_TernaryLambda -> Bool
Eq, Eq ConditionalExpression_TernaryLambda
Eq ConditionalExpression_TernaryLambda =>
(ConditionalExpression_TernaryLambda
 -> ConditionalExpression_TernaryLambda -> Ordering)
-> (ConditionalExpression_TernaryLambda
    -> ConditionalExpression_TernaryLambda -> Bool)
-> (ConditionalExpression_TernaryLambda
    -> ConditionalExpression_TernaryLambda -> Bool)
-> (ConditionalExpression_TernaryLambda
    -> ConditionalExpression_TernaryLambda -> Bool)
-> (ConditionalExpression_TernaryLambda
    -> ConditionalExpression_TernaryLambda -> Bool)
-> (ConditionalExpression_TernaryLambda
    -> ConditionalExpression_TernaryLambda
    -> ConditionalExpression_TernaryLambda)
-> (ConditionalExpression_TernaryLambda
    -> ConditionalExpression_TernaryLambda
    -> ConditionalExpression_TernaryLambda)
-> Ord 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
$ccompare :: ConditionalExpression_TernaryLambda
-> ConditionalExpression_TernaryLambda -> Ordering
compare :: ConditionalExpression_TernaryLambda
-> ConditionalExpression_TernaryLambda -> Ordering
$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
>= :: ConditionalExpression_TernaryLambda
-> ConditionalExpression_TernaryLambda -> Bool
$cmax :: ConditionalExpression_TernaryLambda
-> ConditionalExpression_TernaryLambda
-> ConditionalExpression_TernaryLambda
max :: ConditionalExpression_TernaryLambda
-> ConditionalExpression_TernaryLambda
-> ConditionalExpression_TernaryLambda
$cmin :: ConditionalExpression_TernaryLambda
-> ConditionalExpression_TernaryLambda
-> ConditionalExpression_TernaryLambda
min :: ConditionalExpression_TernaryLambda
-> ConditionalExpression_TernaryLambda
-> ConditionalExpression_TernaryLambda
Ord, ReadPrec [ConditionalExpression_TernaryLambda]
ReadPrec ConditionalExpression_TernaryLambda
Int -> ReadS ConditionalExpression_TernaryLambda
ReadS [ConditionalExpression_TernaryLambda]
(Int -> ReadS ConditionalExpression_TernaryLambda)
-> ReadS [ConditionalExpression_TernaryLambda]
-> ReadPrec ConditionalExpression_TernaryLambda
-> ReadPrec [ConditionalExpression_TernaryLambda]
-> Read ConditionalExpression_TernaryLambda
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ConditionalExpression_TernaryLambda
readsPrec :: Int -> ReadS ConditionalExpression_TernaryLambda
$creadList :: ReadS [ConditionalExpression_TernaryLambda]
readList :: ReadS [ConditionalExpression_TernaryLambda]
$creadPrec :: ReadPrec ConditionalExpression_TernaryLambda
readPrec :: ReadPrec ConditionalExpression_TernaryLambda
$creadListPrec :: ReadPrec [ConditionalExpression_TernaryLambda]
readListPrec :: ReadPrec [ConditionalExpression_TernaryLambda]
Read, Int -> ConditionalExpression_TernaryLambda -> String -> String
[ConditionalExpression_TernaryLambda] -> String -> String
ConditionalExpression_TernaryLambda -> String
(Int -> ConditionalExpression_TernaryLambda -> String -> String)
-> (ConditionalExpression_TernaryLambda -> String)
-> ([ConditionalExpression_TernaryLambda] -> String -> String)
-> Show ConditionalExpression_TernaryLambda
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> ConditionalExpression_TernaryLambda -> String -> String
showsPrec :: Int -> ConditionalExpression_TernaryLambda -> String -> String
$cshow :: ConditionalExpression_TernaryLambda -> String
show :: ConditionalExpression_TernaryLambda -> String
$cshowList :: [ConditionalExpression_TernaryLambda] -> String -> String
showList :: [ConditionalExpression_TernaryLambda] -> String -> String
Show)

_ConditionalExpression_TernaryLambda :: Name
_ConditionalExpression_TernaryLambda = (String -> Name
Core.Name String
"hydra/langs/java/syntax.ConditionalExpression.TernaryLambda")

_ConditionalExpression_TernaryLambda_cond :: Name
_ConditionalExpression_TernaryLambda_cond = (String -> Name
Core.Name String
"cond")

_ConditionalExpression_TernaryLambda_ifTrue :: Name
_ConditionalExpression_TernaryLambda_ifTrue = (String -> Name
Core.Name String
"ifTrue")

_ConditionalExpression_TernaryLambda_ifFalse :: Name
_ConditionalExpression_TernaryLambda_ifFalse = (String -> Name
Core.Name String
"ifFalse")

newtype ConditionalOrExpression = 
  ConditionalOrExpression {
    ConditionalOrExpression -> [ConditionalAndExpression]
unConditionalOrExpression :: [ConditionalAndExpression]}
  deriving (ConditionalOrExpression -> ConditionalOrExpression -> Bool
(ConditionalOrExpression -> ConditionalOrExpression -> Bool)
-> (ConditionalOrExpression -> ConditionalOrExpression -> Bool)
-> Eq ConditionalOrExpression
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ConditionalOrExpression -> ConditionalOrExpression -> Bool
== :: ConditionalOrExpression -> ConditionalOrExpression -> Bool
$c/= :: ConditionalOrExpression -> ConditionalOrExpression -> Bool
/= :: ConditionalOrExpression -> ConditionalOrExpression -> Bool
Eq, Eq ConditionalOrExpression
Eq ConditionalOrExpression =>
(ConditionalOrExpression -> ConditionalOrExpression -> Ordering)
-> (ConditionalOrExpression -> ConditionalOrExpression -> Bool)
-> (ConditionalOrExpression -> ConditionalOrExpression -> Bool)
-> (ConditionalOrExpression -> ConditionalOrExpression -> Bool)
-> (ConditionalOrExpression -> ConditionalOrExpression -> Bool)
-> (ConditionalOrExpression
    -> ConditionalOrExpression -> ConditionalOrExpression)
-> (ConditionalOrExpression
    -> ConditionalOrExpression -> ConditionalOrExpression)
-> Ord 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
$ccompare :: ConditionalOrExpression -> ConditionalOrExpression -> Ordering
compare :: ConditionalOrExpression -> ConditionalOrExpression -> Ordering
$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
>= :: ConditionalOrExpression -> ConditionalOrExpression -> Bool
$cmax :: ConditionalOrExpression
-> ConditionalOrExpression -> ConditionalOrExpression
max :: ConditionalOrExpression
-> ConditionalOrExpression -> ConditionalOrExpression
$cmin :: ConditionalOrExpression
-> ConditionalOrExpression -> ConditionalOrExpression
min :: ConditionalOrExpression
-> ConditionalOrExpression -> ConditionalOrExpression
Ord, ReadPrec [ConditionalOrExpression]
ReadPrec ConditionalOrExpression
Int -> ReadS ConditionalOrExpression
ReadS [ConditionalOrExpression]
(Int -> ReadS ConditionalOrExpression)
-> ReadS [ConditionalOrExpression]
-> ReadPrec ConditionalOrExpression
-> ReadPrec [ConditionalOrExpression]
-> Read ConditionalOrExpression
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ConditionalOrExpression
readsPrec :: Int -> ReadS ConditionalOrExpression
$creadList :: ReadS [ConditionalOrExpression]
readList :: ReadS [ConditionalOrExpression]
$creadPrec :: ReadPrec ConditionalOrExpression
readPrec :: ReadPrec ConditionalOrExpression
$creadListPrec :: ReadPrec [ConditionalOrExpression]
readListPrec :: ReadPrec [ConditionalOrExpression]
Read, Int -> ConditionalOrExpression -> String -> String
[ConditionalOrExpression] -> String -> String
ConditionalOrExpression -> String
(Int -> ConditionalOrExpression -> String -> String)
-> (ConditionalOrExpression -> String)
-> ([ConditionalOrExpression] -> String -> String)
-> Show ConditionalOrExpression
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> ConditionalOrExpression -> String -> String
showsPrec :: Int -> ConditionalOrExpression -> String -> String
$cshow :: ConditionalOrExpression -> String
show :: ConditionalOrExpression -> String
$cshowList :: [ConditionalOrExpression] -> String -> String
showList :: [ConditionalOrExpression] -> String -> String
Show)

_ConditionalOrExpression :: Name
_ConditionalOrExpression = (String -> Name
Core.Name String
"hydra/langs/java/syntax.ConditionalOrExpression")

newtype ConditionalAndExpression = 
  ConditionalAndExpression {
    ConditionalAndExpression -> [InclusiveOrExpression]
unConditionalAndExpression :: [InclusiveOrExpression]}
  deriving (ConditionalAndExpression -> ConditionalAndExpression -> Bool
(ConditionalAndExpression -> ConditionalAndExpression -> Bool)
-> (ConditionalAndExpression -> ConditionalAndExpression -> Bool)
-> Eq ConditionalAndExpression
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ConditionalAndExpression -> ConditionalAndExpression -> Bool
== :: ConditionalAndExpression -> ConditionalAndExpression -> Bool
$c/= :: ConditionalAndExpression -> ConditionalAndExpression -> Bool
/= :: ConditionalAndExpression -> ConditionalAndExpression -> Bool
Eq, Eq ConditionalAndExpression
Eq ConditionalAndExpression =>
(ConditionalAndExpression -> ConditionalAndExpression -> Ordering)
-> (ConditionalAndExpression -> ConditionalAndExpression -> Bool)
-> (ConditionalAndExpression -> ConditionalAndExpression -> Bool)
-> (ConditionalAndExpression -> ConditionalAndExpression -> Bool)
-> (ConditionalAndExpression -> ConditionalAndExpression -> Bool)
-> (ConditionalAndExpression
    -> ConditionalAndExpression -> ConditionalAndExpression)
-> (ConditionalAndExpression
    -> ConditionalAndExpression -> ConditionalAndExpression)
-> Ord 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
$ccompare :: ConditionalAndExpression -> ConditionalAndExpression -> Ordering
compare :: ConditionalAndExpression -> ConditionalAndExpression -> Ordering
$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
>= :: ConditionalAndExpression -> ConditionalAndExpression -> Bool
$cmax :: ConditionalAndExpression
-> ConditionalAndExpression -> ConditionalAndExpression
max :: ConditionalAndExpression
-> ConditionalAndExpression -> ConditionalAndExpression
$cmin :: ConditionalAndExpression
-> ConditionalAndExpression -> ConditionalAndExpression
min :: ConditionalAndExpression
-> ConditionalAndExpression -> ConditionalAndExpression
Ord, ReadPrec [ConditionalAndExpression]
ReadPrec ConditionalAndExpression
Int -> ReadS ConditionalAndExpression
ReadS [ConditionalAndExpression]
(Int -> ReadS ConditionalAndExpression)
-> ReadS [ConditionalAndExpression]
-> ReadPrec ConditionalAndExpression
-> ReadPrec [ConditionalAndExpression]
-> Read ConditionalAndExpression
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ConditionalAndExpression
readsPrec :: Int -> ReadS ConditionalAndExpression
$creadList :: ReadS [ConditionalAndExpression]
readList :: ReadS [ConditionalAndExpression]
$creadPrec :: ReadPrec ConditionalAndExpression
readPrec :: ReadPrec ConditionalAndExpression
$creadListPrec :: ReadPrec [ConditionalAndExpression]
readListPrec :: ReadPrec [ConditionalAndExpression]
Read, Int -> ConditionalAndExpression -> String -> String
[ConditionalAndExpression] -> String -> String
ConditionalAndExpression -> String
(Int -> ConditionalAndExpression -> String -> String)
-> (ConditionalAndExpression -> String)
-> ([ConditionalAndExpression] -> String -> String)
-> Show ConditionalAndExpression
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> ConditionalAndExpression -> String -> String
showsPrec :: Int -> ConditionalAndExpression -> String -> String
$cshow :: ConditionalAndExpression -> String
show :: ConditionalAndExpression -> String
$cshowList :: [ConditionalAndExpression] -> String -> String
showList :: [ConditionalAndExpression] -> String -> String
Show)

_ConditionalAndExpression :: Name
_ConditionalAndExpression = (String -> Name
Core.Name String
"hydra/langs/java/syntax.ConditionalAndExpression")

newtype InclusiveOrExpression = 
  InclusiveOrExpression {
    InclusiveOrExpression -> [ExclusiveOrExpression]
unInclusiveOrExpression :: [ExclusiveOrExpression]}
  deriving (InclusiveOrExpression -> InclusiveOrExpression -> Bool
(InclusiveOrExpression -> InclusiveOrExpression -> Bool)
-> (InclusiveOrExpression -> InclusiveOrExpression -> Bool)
-> Eq InclusiveOrExpression
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: InclusiveOrExpression -> InclusiveOrExpression -> Bool
== :: InclusiveOrExpression -> InclusiveOrExpression -> Bool
$c/= :: InclusiveOrExpression -> InclusiveOrExpression -> Bool
/= :: InclusiveOrExpression -> InclusiveOrExpression -> Bool
Eq, Eq InclusiveOrExpression
Eq InclusiveOrExpression =>
(InclusiveOrExpression -> InclusiveOrExpression -> Ordering)
-> (InclusiveOrExpression -> InclusiveOrExpression -> Bool)
-> (InclusiveOrExpression -> InclusiveOrExpression -> Bool)
-> (InclusiveOrExpression -> InclusiveOrExpression -> Bool)
-> (InclusiveOrExpression -> InclusiveOrExpression -> Bool)
-> (InclusiveOrExpression
    -> InclusiveOrExpression -> InclusiveOrExpression)
-> (InclusiveOrExpression
    -> InclusiveOrExpression -> InclusiveOrExpression)
-> Ord 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
$ccompare :: InclusiveOrExpression -> InclusiveOrExpression -> Ordering
compare :: InclusiveOrExpression -> InclusiveOrExpression -> Ordering
$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
>= :: InclusiveOrExpression -> InclusiveOrExpression -> Bool
$cmax :: InclusiveOrExpression
-> InclusiveOrExpression -> InclusiveOrExpression
max :: InclusiveOrExpression
-> InclusiveOrExpression -> InclusiveOrExpression
$cmin :: InclusiveOrExpression
-> InclusiveOrExpression -> InclusiveOrExpression
min :: InclusiveOrExpression
-> InclusiveOrExpression -> InclusiveOrExpression
Ord, ReadPrec [InclusiveOrExpression]
ReadPrec InclusiveOrExpression
Int -> ReadS InclusiveOrExpression
ReadS [InclusiveOrExpression]
(Int -> ReadS InclusiveOrExpression)
-> ReadS [InclusiveOrExpression]
-> ReadPrec InclusiveOrExpression
-> ReadPrec [InclusiveOrExpression]
-> Read InclusiveOrExpression
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS InclusiveOrExpression
readsPrec :: Int -> ReadS InclusiveOrExpression
$creadList :: ReadS [InclusiveOrExpression]
readList :: ReadS [InclusiveOrExpression]
$creadPrec :: ReadPrec InclusiveOrExpression
readPrec :: ReadPrec InclusiveOrExpression
$creadListPrec :: ReadPrec [InclusiveOrExpression]
readListPrec :: ReadPrec [InclusiveOrExpression]
Read, Int -> InclusiveOrExpression -> String -> String
[InclusiveOrExpression] -> String -> String
InclusiveOrExpression -> String
(Int -> InclusiveOrExpression -> String -> String)
-> (InclusiveOrExpression -> String)
-> ([InclusiveOrExpression] -> String -> String)
-> Show InclusiveOrExpression
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> InclusiveOrExpression -> String -> String
showsPrec :: Int -> InclusiveOrExpression -> String -> String
$cshow :: InclusiveOrExpression -> String
show :: InclusiveOrExpression -> String
$cshowList :: [InclusiveOrExpression] -> String -> String
showList :: [InclusiveOrExpression] -> String -> String
Show)

_InclusiveOrExpression :: Name
_InclusiveOrExpression = (String -> Name
Core.Name String
"hydra/langs/java/syntax.InclusiveOrExpression")

newtype ExclusiveOrExpression = 
  ExclusiveOrExpression {
    ExclusiveOrExpression -> [AndExpression]
unExclusiveOrExpression :: [AndExpression]}
  deriving (ExclusiveOrExpression -> ExclusiveOrExpression -> Bool
(ExclusiveOrExpression -> ExclusiveOrExpression -> Bool)
-> (ExclusiveOrExpression -> ExclusiveOrExpression -> Bool)
-> Eq ExclusiveOrExpression
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ExclusiveOrExpression -> ExclusiveOrExpression -> Bool
== :: ExclusiveOrExpression -> ExclusiveOrExpression -> Bool
$c/= :: ExclusiveOrExpression -> ExclusiveOrExpression -> Bool
/= :: ExclusiveOrExpression -> ExclusiveOrExpression -> Bool
Eq, Eq ExclusiveOrExpression
Eq ExclusiveOrExpression =>
(ExclusiveOrExpression -> ExclusiveOrExpression -> Ordering)
-> (ExclusiveOrExpression -> ExclusiveOrExpression -> Bool)
-> (ExclusiveOrExpression -> ExclusiveOrExpression -> Bool)
-> (ExclusiveOrExpression -> ExclusiveOrExpression -> Bool)
-> (ExclusiveOrExpression -> ExclusiveOrExpression -> Bool)
-> (ExclusiveOrExpression
    -> ExclusiveOrExpression -> ExclusiveOrExpression)
-> (ExclusiveOrExpression
    -> ExclusiveOrExpression -> ExclusiveOrExpression)
-> Ord 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
$ccompare :: ExclusiveOrExpression -> ExclusiveOrExpression -> Ordering
compare :: ExclusiveOrExpression -> ExclusiveOrExpression -> Ordering
$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
>= :: ExclusiveOrExpression -> ExclusiveOrExpression -> Bool
$cmax :: ExclusiveOrExpression
-> ExclusiveOrExpression -> ExclusiveOrExpression
max :: ExclusiveOrExpression
-> ExclusiveOrExpression -> ExclusiveOrExpression
$cmin :: ExclusiveOrExpression
-> ExclusiveOrExpression -> ExclusiveOrExpression
min :: ExclusiveOrExpression
-> ExclusiveOrExpression -> ExclusiveOrExpression
Ord, ReadPrec [ExclusiveOrExpression]
ReadPrec ExclusiveOrExpression
Int -> ReadS ExclusiveOrExpression
ReadS [ExclusiveOrExpression]
(Int -> ReadS ExclusiveOrExpression)
-> ReadS [ExclusiveOrExpression]
-> ReadPrec ExclusiveOrExpression
-> ReadPrec [ExclusiveOrExpression]
-> Read ExclusiveOrExpression
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ExclusiveOrExpression
readsPrec :: Int -> ReadS ExclusiveOrExpression
$creadList :: ReadS [ExclusiveOrExpression]
readList :: ReadS [ExclusiveOrExpression]
$creadPrec :: ReadPrec ExclusiveOrExpression
readPrec :: ReadPrec ExclusiveOrExpression
$creadListPrec :: ReadPrec [ExclusiveOrExpression]
readListPrec :: ReadPrec [ExclusiveOrExpression]
Read, Int -> ExclusiveOrExpression -> String -> String
[ExclusiveOrExpression] -> String -> String
ExclusiveOrExpression -> String
(Int -> ExclusiveOrExpression -> String -> String)
-> (ExclusiveOrExpression -> String)
-> ([ExclusiveOrExpression] -> String -> String)
-> Show ExclusiveOrExpression
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> ExclusiveOrExpression -> String -> String
showsPrec :: Int -> ExclusiveOrExpression -> String -> String
$cshow :: ExclusiveOrExpression -> String
show :: ExclusiveOrExpression -> String
$cshowList :: [ExclusiveOrExpression] -> String -> String
showList :: [ExclusiveOrExpression] -> String -> String
Show)

_ExclusiveOrExpression :: Name
_ExclusiveOrExpression = (String -> Name
Core.Name String
"hydra/langs/java/syntax.ExclusiveOrExpression")

newtype AndExpression = 
  AndExpression {
    AndExpression -> [EqualityExpression]
unAndExpression :: [EqualityExpression]}
  deriving (AndExpression -> AndExpression -> Bool
(AndExpression -> AndExpression -> Bool)
-> (AndExpression -> AndExpression -> Bool) -> Eq AndExpression
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AndExpression -> AndExpression -> Bool
== :: AndExpression -> AndExpression -> Bool
$c/= :: AndExpression -> AndExpression -> Bool
/= :: AndExpression -> AndExpression -> Bool
Eq, Eq AndExpression
Eq AndExpression =>
(AndExpression -> AndExpression -> Ordering)
-> (AndExpression -> AndExpression -> Bool)
-> (AndExpression -> AndExpression -> Bool)
-> (AndExpression -> AndExpression -> Bool)
-> (AndExpression -> AndExpression -> Bool)
-> (AndExpression -> AndExpression -> AndExpression)
-> (AndExpression -> AndExpression -> AndExpression)
-> Ord 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
$ccompare :: AndExpression -> AndExpression -> Ordering
compare :: AndExpression -> AndExpression -> Ordering
$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
>= :: AndExpression -> AndExpression -> Bool
$cmax :: AndExpression -> AndExpression -> AndExpression
max :: AndExpression -> AndExpression -> AndExpression
$cmin :: AndExpression -> AndExpression -> AndExpression
min :: AndExpression -> AndExpression -> AndExpression
Ord, ReadPrec [AndExpression]
ReadPrec AndExpression
Int -> ReadS AndExpression
ReadS [AndExpression]
(Int -> ReadS AndExpression)
-> ReadS [AndExpression]
-> ReadPrec AndExpression
-> ReadPrec [AndExpression]
-> Read AndExpression
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS AndExpression
readsPrec :: Int -> ReadS AndExpression
$creadList :: ReadS [AndExpression]
readList :: ReadS [AndExpression]
$creadPrec :: ReadPrec AndExpression
readPrec :: ReadPrec AndExpression
$creadListPrec :: ReadPrec [AndExpression]
readListPrec :: ReadPrec [AndExpression]
Read, Int -> AndExpression -> String -> String
[AndExpression] -> String -> String
AndExpression -> String
(Int -> AndExpression -> String -> String)
-> (AndExpression -> String)
-> ([AndExpression] -> String -> String)
-> Show AndExpression
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> AndExpression -> String -> String
showsPrec :: Int -> AndExpression -> String -> String
$cshow :: AndExpression -> String
show :: AndExpression -> String
$cshowList :: [AndExpression] -> String -> String
showList :: [AndExpression] -> String -> String
Show)

_AndExpression :: Name
_AndExpression = (String -> Name
Core.Name String
"hydra/langs/java/syntax.AndExpression")

data EqualityExpression = 
  EqualityExpressionUnary RelationalExpression |
  EqualityExpressionEqual EqualityExpression_Binary |
  EqualityExpressionNotEqual EqualityExpression_Binary
  deriving (EqualityExpression -> EqualityExpression -> Bool
(EqualityExpression -> EqualityExpression -> Bool)
-> (EqualityExpression -> EqualityExpression -> Bool)
-> Eq EqualityExpression
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: EqualityExpression -> EqualityExpression -> Bool
== :: EqualityExpression -> EqualityExpression -> Bool
$c/= :: EqualityExpression -> EqualityExpression -> Bool
/= :: EqualityExpression -> EqualityExpression -> Bool
Eq, Eq EqualityExpression
Eq EqualityExpression =>
(EqualityExpression -> EqualityExpression -> Ordering)
-> (EqualityExpression -> EqualityExpression -> Bool)
-> (EqualityExpression -> EqualityExpression -> Bool)
-> (EqualityExpression -> EqualityExpression -> Bool)
-> (EqualityExpression -> EqualityExpression -> Bool)
-> (EqualityExpression -> EqualityExpression -> EqualityExpression)
-> (EqualityExpression -> EqualityExpression -> EqualityExpression)
-> Ord 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
$ccompare :: EqualityExpression -> EqualityExpression -> Ordering
compare :: EqualityExpression -> EqualityExpression -> Ordering
$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
>= :: EqualityExpression -> EqualityExpression -> Bool
$cmax :: EqualityExpression -> EqualityExpression -> EqualityExpression
max :: EqualityExpression -> EqualityExpression -> EqualityExpression
$cmin :: EqualityExpression -> EqualityExpression -> EqualityExpression
min :: EqualityExpression -> EqualityExpression -> EqualityExpression
Ord, ReadPrec [EqualityExpression]
ReadPrec EqualityExpression
Int -> ReadS EqualityExpression
ReadS [EqualityExpression]
(Int -> ReadS EqualityExpression)
-> ReadS [EqualityExpression]
-> ReadPrec EqualityExpression
-> ReadPrec [EqualityExpression]
-> Read EqualityExpression
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS EqualityExpression
readsPrec :: Int -> ReadS EqualityExpression
$creadList :: ReadS [EqualityExpression]
readList :: ReadS [EqualityExpression]
$creadPrec :: ReadPrec EqualityExpression
readPrec :: ReadPrec EqualityExpression
$creadListPrec :: ReadPrec [EqualityExpression]
readListPrec :: ReadPrec [EqualityExpression]
Read, Int -> EqualityExpression -> String -> String
[EqualityExpression] -> String -> String
EqualityExpression -> String
(Int -> EqualityExpression -> String -> String)
-> (EqualityExpression -> String)
-> ([EqualityExpression] -> String -> String)
-> Show EqualityExpression
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> EqualityExpression -> String -> String
showsPrec :: Int -> EqualityExpression -> String -> String
$cshow :: EqualityExpression -> String
show :: EqualityExpression -> String
$cshowList :: [EqualityExpression] -> String -> String
showList :: [EqualityExpression] -> String -> String
Show)

_EqualityExpression :: Name
_EqualityExpression = (String -> Name
Core.Name String
"hydra/langs/java/syntax.EqualityExpression")

_EqualityExpression_unary :: Name
_EqualityExpression_unary = (String -> Name
Core.Name String
"unary")

_EqualityExpression_equal :: Name
_EqualityExpression_equal = (String -> Name
Core.Name String
"equal")

_EqualityExpression_notEqual :: Name
_EqualityExpression_notEqual = (String -> Name
Core.Name 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
(EqualityExpression_Binary -> EqualityExpression_Binary -> Bool)
-> (EqualityExpression_Binary -> EqualityExpression_Binary -> Bool)
-> Eq EqualityExpression_Binary
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: EqualityExpression_Binary -> EqualityExpression_Binary -> Bool
== :: EqualityExpression_Binary -> EqualityExpression_Binary -> Bool
$c/= :: EqualityExpression_Binary -> EqualityExpression_Binary -> Bool
/= :: EqualityExpression_Binary -> EqualityExpression_Binary -> Bool
Eq, Eq EqualityExpression_Binary
Eq EqualityExpression_Binary =>
(EqualityExpression_Binary
 -> EqualityExpression_Binary -> Ordering)
-> (EqualityExpression_Binary -> EqualityExpression_Binary -> Bool)
-> (EqualityExpression_Binary -> EqualityExpression_Binary -> Bool)
-> (EqualityExpression_Binary -> EqualityExpression_Binary -> Bool)
-> (EqualityExpression_Binary -> EqualityExpression_Binary -> Bool)
-> (EqualityExpression_Binary
    -> EqualityExpression_Binary -> EqualityExpression_Binary)
-> (EqualityExpression_Binary
    -> EqualityExpression_Binary -> EqualityExpression_Binary)
-> Ord 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
$ccompare :: EqualityExpression_Binary -> EqualityExpression_Binary -> Ordering
compare :: EqualityExpression_Binary -> EqualityExpression_Binary -> Ordering
$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
>= :: EqualityExpression_Binary -> EqualityExpression_Binary -> Bool
$cmax :: EqualityExpression_Binary
-> EqualityExpression_Binary -> EqualityExpression_Binary
max :: EqualityExpression_Binary
-> EqualityExpression_Binary -> EqualityExpression_Binary
$cmin :: EqualityExpression_Binary
-> EqualityExpression_Binary -> EqualityExpression_Binary
min :: EqualityExpression_Binary
-> EqualityExpression_Binary -> EqualityExpression_Binary
Ord, ReadPrec [EqualityExpression_Binary]
ReadPrec EqualityExpression_Binary
Int -> ReadS EqualityExpression_Binary
ReadS [EqualityExpression_Binary]
(Int -> ReadS EqualityExpression_Binary)
-> ReadS [EqualityExpression_Binary]
-> ReadPrec EqualityExpression_Binary
-> ReadPrec [EqualityExpression_Binary]
-> Read EqualityExpression_Binary
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS EqualityExpression_Binary
readsPrec :: Int -> ReadS EqualityExpression_Binary
$creadList :: ReadS [EqualityExpression_Binary]
readList :: ReadS [EqualityExpression_Binary]
$creadPrec :: ReadPrec EqualityExpression_Binary
readPrec :: ReadPrec EqualityExpression_Binary
$creadListPrec :: ReadPrec [EqualityExpression_Binary]
readListPrec :: ReadPrec [EqualityExpression_Binary]
Read, Int -> EqualityExpression_Binary -> String -> String
[EqualityExpression_Binary] -> String -> String
EqualityExpression_Binary -> String
(Int -> EqualityExpression_Binary -> String -> String)
-> (EqualityExpression_Binary -> String)
-> ([EqualityExpression_Binary] -> String -> String)
-> Show EqualityExpression_Binary
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> EqualityExpression_Binary -> String -> String
showsPrec :: Int -> EqualityExpression_Binary -> String -> String
$cshow :: EqualityExpression_Binary -> String
show :: EqualityExpression_Binary -> String
$cshowList :: [EqualityExpression_Binary] -> String -> String
showList :: [EqualityExpression_Binary] -> String -> String
Show)

_EqualityExpression_Binary :: Name
_EqualityExpression_Binary = (String -> Name
Core.Name String
"hydra/langs/java/syntax.EqualityExpression.Binary")

_EqualityExpression_Binary_lhs :: Name
_EqualityExpression_Binary_lhs = (String -> Name
Core.Name String
"lhs")

_EqualityExpression_Binary_rhs :: Name
_EqualityExpression_Binary_rhs = (String -> Name
Core.Name 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
(RelationalExpression -> RelationalExpression -> Bool)
-> (RelationalExpression -> RelationalExpression -> Bool)
-> Eq RelationalExpression
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RelationalExpression -> RelationalExpression -> Bool
== :: RelationalExpression -> RelationalExpression -> Bool
$c/= :: RelationalExpression -> RelationalExpression -> Bool
/= :: RelationalExpression -> RelationalExpression -> Bool
Eq, Eq RelationalExpression
Eq RelationalExpression =>
(RelationalExpression -> RelationalExpression -> Ordering)
-> (RelationalExpression -> RelationalExpression -> Bool)
-> (RelationalExpression -> RelationalExpression -> Bool)
-> (RelationalExpression -> RelationalExpression -> Bool)
-> (RelationalExpression -> RelationalExpression -> Bool)
-> (RelationalExpression
    -> RelationalExpression -> RelationalExpression)
-> (RelationalExpression
    -> RelationalExpression -> RelationalExpression)
-> Ord 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
$ccompare :: RelationalExpression -> RelationalExpression -> Ordering
compare :: RelationalExpression -> RelationalExpression -> Ordering
$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
>= :: RelationalExpression -> RelationalExpression -> Bool
$cmax :: RelationalExpression
-> RelationalExpression -> RelationalExpression
max :: RelationalExpression
-> RelationalExpression -> RelationalExpression
$cmin :: RelationalExpression
-> RelationalExpression -> RelationalExpression
min :: RelationalExpression
-> RelationalExpression -> RelationalExpression
Ord, ReadPrec [RelationalExpression]
ReadPrec RelationalExpression
Int -> ReadS RelationalExpression
ReadS [RelationalExpression]
(Int -> ReadS RelationalExpression)
-> ReadS [RelationalExpression]
-> ReadPrec RelationalExpression
-> ReadPrec [RelationalExpression]
-> Read RelationalExpression
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS RelationalExpression
readsPrec :: Int -> ReadS RelationalExpression
$creadList :: ReadS [RelationalExpression]
readList :: ReadS [RelationalExpression]
$creadPrec :: ReadPrec RelationalExpression
readPrec :: ReadPrec RelationalExpression
$creadListPrec :: ReadPrec [RelationalExpression]
readListPrec :: ReadPrec [RelationalExpression]
Read, Int -> RelationalExpression -> String -> String
[RelationalExpression] -> String -> String
RelationalExpression -> String
(Int -> RelationalExpression -> String -> String)
-> (RelationalExpression -> String)
-> ([RelationalExpression] -> String -> String)
-> Show RelationalExpression
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> RelationalExpression -> String -> String
showsPrec :: Int -> RelationalExpression -> String -> String
$cshow :: RelationalExpression -> String
show :: RelationalExpression -> String
$cshowList :: [RelationalExpression] -> String -> String
showList :: [RelationalExpression] -> String -> String
Show)

_RelationalExpression :: Name
_RelationalExpression = (String -> Name
Core.Name String
"hydra/langs/java/syntax.RelationalExpression")

_RelationalExpression_simple :: Name
_RelationalExpression_simple = (String -> Name
Core.Name String
"simple")

_RelationalExpression_lessThan :: Name
_RelationalExpression_lessThan = (String -> Name
Core.Name String
"lessThan")

_RelationalExpression_greaterThan :: Name
_RelationalExpression_greaterThan = (String -> Name
Core.Name String
"greaterThan")

_RelationalExpression_lessThanEqual :: Name
_RelationalExpression_lessThanEqual = (String -> Name
Core.Name String
"lessThanEqual")

_RelationalExpression_greaterThanEqual :: Name
_RelationalExpression_greaterThanEqual = (String -> Name
Core.Name String
"greaterThanEqual")

_RelationalExpression_instanceof :: Name
_RelationalExpression_instanceof = (String -> Name
Core.Name 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
(RelationalExpression_LessThan
 -> RelationalExpression_LessThan -> Bool)
-> (RelationalExpression_LessThan
    -> RelationalExpression_LessThan -> Bool)
-> Eq RelationalExpression_LessThan
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RelationalExpression_LessThan
-> RelationalExpression_LessThan -> Bool
== :: RelationalExpression_LessThan
-> RelationalExpression_LessThan -> Bool
$c/= :: RelationalExpression_LessThan
-> RelationalExpression_LessThan -> Bool
/= :: RelationalExpression_LessThan
-> RelationalExpression_LessThan -> Bool
Eq, Eq RelationalExpression_LessThan
Eq RelationalExpression_LessThan =>
(RelationalExpression_LessThan
 -> RelationalExpression_LessThan -> Ordering)
-> (RelationalExpression_LessThan
    -> RelationalExpression_LessThan -> Bool)
-> (RelationalExpression_LessThan
    -> RelationalExpression_LessThan -> Bool)
-> (RelationalExpression_LessThan
    -> RelationalExpression_LessThan -> Bool)
-> (RelationalExpression_LessThan
    -> RelationalExpression_LessThan -> Bool)
-> (RelationalExpression_LessThan
    -> RelationalExpression_LessThan -> RelationalExpression_LessThan)
-> (RelationalExpression_LessThan
    -> RelationalExpression_LessThan -> RelationalExpression_LessThan)
-> Ord 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
$ccompare :: RelationalExpression_LessThan
-> RelationalExpression_LessThan -> Ordering
compare :: RelationalExpression_LessThan
-> RelationalExpression_LessThan -> Ordering
$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
>= :: RelationalExpression_LessThan
-> RelationalExpression_LessThan -> Bool
$cmax :: RelationalExpression_LessThan
-> RelationalExpression_LessThan -> RelationalExpression_LessThan
max :: RelationalExpression_LessThan
-> RelationalExpression_LessThan -> RelationalExpression_LessThan
$cmin :: RelationalExpression_LessThan
-> RelationalExpression_LessThan -> RelationalExpression_LessThan
min :: RelationalExpression_LessThan
-> RelationalExpression_LessThan -> RelationalExpression_LessThan
Ord, ReadPrec [RelationalExpression_LessThan]
ReadPrec RelationalExpression_LessThan
Int -> ReadS RelationalExpression_LessThan
ReadS [RelationalExpression_LessThan]
(Int -> ReadS RelationalExpression_LessThan)
-> ReadS [RelationalExpression_LessThan]
-> ReadPrec RelationalExpression_LessThan
-> ReadPrec [RelationalExpression_LessThan]
-> Read RelationalExpression_LessThan
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS RelationalExpression_LessThan
readsPrec :: Int -> ReadS RelationalExpression_LessThan
$creadList :: ReadS [RelationalExpression_LessThan]
readList :: ReadS [RelationalExpression_LessThan]
$creadPrec :: ReadPrec RelationalExpression_LessThan
readPrec :: ReadPrec RelationalExpression_LessThan
$creadListPrec :: ReadPrec [RelationalExpression_LessThan]
readListPrec :: ReadPrec [RelationalExpression_LessThan]
Read, Int -> RelationalExpression_LessThan -> String -> String
[RelationalExpression_LessThan] -> String -> String
RelationalExpression_LessThan -> String
(Int -> RelationalExpression_LessThan -> String -> String)
-> (RelationalExpression_LessThan -> String)
-> ([RelationalExpression_LessThan] -> String -> String)
-> Show RelationalExpression_LessThan
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> RelationalExpression_LessThan -> String -> String
showsPrec :: Int -> RelationalExpression_LessThan -> String -> String
$cshow :: RelationalExpression_LessThan -> String
show :: RelationalExpression_LessThan -> String
$cshowList :: [RelationalExpression_LessThan] -> String -> String
showList :: [RelationalExpression_LessThan] -> String -> String
Show)

_RelationalExpression_LessThan :: Name
_RelationalExpression_LessThan = (String -> Name
Core.Name String
"hydra/langs/java/syntax.RelationalExpression.LessThan")

_RelationalExpression_LessThan_lhs :: Name
_RelationalExpression_LessThan_lhs = (String -> Name
Core.Name String
"lhs")

_RelationalExpression_LessThan_rhs :: Name
_RelationalExpression_LessThan_rhs = (String -> Name
Core.Name 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
(RelationalExpression_GreaterThan
 -> RelationalExpression_GreaterThan -> Bool)
-> (RelationalExpression_GreaterThan
    -> RelationalExpression_GreaterThan -> Bool)
-> Eq RelationalExpression_GreaterThan
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RelationalExpression_GreaterThan
-> RelationalExpression_GreaterThan -> Bool
== :: RelationalExpression_GreaterThan
-> RelationalExpression_GreaterThan -> Bool
$c/= :: RelationalExpression_GreaterThan
-> RelationalExpression_GreaterThan -> Bool
/= :: RelationalExpression_GreaterThan
-> RelationalExpression_GreaterThan -> Bool
Eq, Eq RelationalExpression_GreaterThan
Eq RelationalExpression_GreaterThan =>
(RelationalExpression_GreaterThan
 -> RelationalExpression_GreaterThan -> Ordering)
-> (RelationalExpression_GreaterThan
    -> RelationalExpression_GreaterThan -> Bool)
-> (RelationalExpression_GreaterThan
    -> RelationalExpression_GreaterThan -> Bool)
-> (RelationalExpression_GreaterThan
    -> RelationalExpression_GreaterThan -> Bool)
-> (RelationalExpression_GreaterThan
    -> RelationalExpression_GreaterThan -> Bool)
-> (RelationalExpression_GreaterThan
    -> RelationalExpression_GreaterThan
    -> RelationalExpression_GreaterThan)
-> (RelationalExpression_GreaterThan
    -> RelationalExpression_GreaterThan
    -> RelationalExpression_GreaterThan)
-> Ord 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
$ccompare :: RelationalExpression_GreaterThan
-> RelationalExpression_GreaterThan -> Ordering
compare :: RelationalExpression_GreaterThan
-> RelationalExpression_GreaterThan -> Ordering
$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
>= :: RelationalExpression_GreaterThan
-> RelationalExpression_GreaterThan -> Bool
$cmax :: RelationalExpression_GreaterThan
-> RelationalExpression_GreaterThan
-> RelationalExpression_GreaterThan
max :: RelationalExpression_GreaterThan
-> RelationalExpression_GreaterThan
-> RelationalExpression_GreaterThan
$cmin :: RelationalExpression_GreaterThan
-> RelationalExpression_GreaterThan
-> RelationalExpression_GreaterThan
min :: RelationalExpression_GreaterThan
-> RelationalExpression_GreaterThan
-> RelationalExpression_GreaterThan
Ord, ReadPrec [RelationalExpression_GreaterThan]
ReadPrec RelationalExpression_GreaterThan
Int -> ReadS RelationalExpression_GreaterThan
ReadS [RelationalExpression_GreaterThan]
(Int -> ReadS RelationalExpression_GreaterThan)
-> ReadS [RelationalExpression_GreaterThan]
-> ReadPrec RelationalExpression_GreaterThan
-> ReadPrec [RelationalExpression_GreaterThan]
-> Read RelationalExpression_GreaterThan
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS RelationalExpression_GreaterThan
readsPrec :: Int -> ReadS RelationalExpression_GreaterThan
$creadList :: ReadS [RelationalExpression_GreaterThan]
readList :: ReadS [RelationalExpression_GreaterThan]
$creadPrec :: ReadPrec RelationalExpression_GreaterThan
readPrec :: ReadPrec RelationalExpression_GreaterThan
$creadListPrec :: ReadPrec [RelationalExpression_GreaterThan]
readListPrec :: ReadPrec [RelationalExpression_GreaterThan]
Read, Int -> RelationalExpression_GreaterThan -> String -> String
[RelationalExpression_GreaterThan] -> String -> String
RelationalExpression_GreaterThan -> String
(Int -> RelationalExpression_GreaterThan -> String -> String)
-> (RelationalExpression_GreaterThan -> String)
-> ([RelationalExpression_GreaterThan] -> String -> String)
-> Show RelationalExpression_GreaterThan
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> RelationalExpression_GreaterThan -> String -> String
showsPrec :: Int -> RelationalExpression_GreaterThan -> String -> String
$cshow :: RelationalExpression_GreaterThan -> String
show :: RelationalExpression_GreaterThan -> String
$cshowList :: [RelationalExpression_GreaterThan] -> String -> String
showList :: [RelationalExpression_GreaterThan] -> String -> String
Show)

_RelationalExpression_GreaterThan :: Name
_RelationalExpression_GreaterThan = (String -> Name
Core.Name String
"hydra/langs/java/syntax.RelationalExpression.GreaterThan")

_RelationalExpression_GreaterThan_lhs :: Name
_RelationalExpression_GreaterThan_lhs = (String -> Name
Core.Name String
"lhs")

_RelationalExpression_GreaterThan_rhs :: Name
_RelationalExpression_GreaterThan_rhs = (String -> Name
Core.Name 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
(RelationalExpression_LessThanEqual
 -> RelationalExpression_LessThanEqual -> Bool)
-> (RelationalExpression_LessThanEqual
    -> RelationalExpression_LessThanEqual -> Bool)
-> Eq RelationalExpression_LessThanEqual
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RelationalExpression_LessThanEqual
-> RelationalExpression_LessThanEqual -> Bool
== :: RelationalExpression_LessThanEqual
-> RelationalExpression_LessThanEqual -> Bool
$c/= :: RelationalExpression_LessThanEqual
-> RelationalExpression_LessThanEqual -> Bool
/= :: RelationalExpression_LessThanEqual
-> RelationalExpression_LessThanEqual -> Bool
Eq, Eq RelationalExpression_LessThanEqual
Eq RelationalExpression_LessThanEqual =>
(RelationalExpression_LessThanEqual
 -> RelationalExpression_LessThanEqual -> Ordering)
-> (RelationalExpression_LessThanEqual
    -> RelationalExpression_LessThanEqual -> Bool)
-> (RelationalExpression_LessThanEqual
    -> RelationalExpression_LessThanEqual -> Bool)
-> (RelationalExpression_LessThanEqual
    -> RelationalExpression_LessThanEqual -> Bool)
-> (RelationalExpression_LessThanEqual
    -> RelationalExpression_LessThanEqual -> Bool)
-> (RelationalExpression_LessThanEqual
    -> RelationalExpression_LessThanEqual
    -> RelationalExpression_LessThanEqual)
-> (RelationalExpression_LessThanEqual
    -> RelationalExpression_LessThanEqual
    -> RelationalExpression_LessThanEqual)
-> Ord 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
$ccompare :: RelationalExpression_LessThanEqual
-> RelationalExpression_LessThanEqual -> Ordering
compare :: RelationalExpression_LessThanEqual
-> RelationalExpression_LessThanEqual -> Ordering
$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
>= :: RelationalExpression_LessThanEqual
-> RelationalExpression_LessThanEqual -> Bool
$cmax :: RelationalExpression_LessThanEqual
-> RelationalExpression_LessThanEqual
-> RelationalExpression_LessThanEqual
max :: RelationalExpression_LessThanEqual
-> RelationalExpression_LessThanEqual
-> RelationalExpression_LessThanEqual
$cmin :: RelationalExpression_LessThanEqual
-> RelationalExpression_LessThanEqual
-> RelationalExpression_LessThanEqual
min :: RelationalExpression_LessThanEqual
-> RelationalExpression_LessThanEqual
-> RelationalExpression_LessThanEqual
Ord, ReadPrec [RelationalExpression_LessThanEqual]
ReadPrec RelationalExpression_LessThanEqual
Int -> ReadS RelationalExpression_LessThanEqual
ReadS [RelationalExpression_LessThanEqual]
(Int -> ReadS RelationalExpression_LessThanEqual)
-> ReadS [RelationalExpression_LessThanEqual]
-> ReadPrec RelationalExpression_LessThanEqual
-> ReadPrec [RelationalExpression_LessThanEqual]
-> Read RelationalExpression_LessThanEqual
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS RelationalExpression_LessThanEqual
readsPrec :: Int -> ReadS RelationalExpression_LessThanEqual
$creadList :: ReadS [RelationalExpression_LessThanEqual]
readList :: ReadS [RelationalExpression_LessThanEqual]
$creadPrec :: ReadPrec RelationalExpression_LessThanEqual
readPrec :: ReadPrec RelationalExpression_LessThanEqual
$creadListPrec :: ReadPrec [RelationalExpression_LessThanEqual]
readListPrec :: ReadPrec [RelationalExpression_LessThanEqual]
Read, Int -> RelationalExpression_LessThanEqual -> String -> String
[RelationalExpression_LessThanEqual] -> String -> String
RelationalExpression_LessThanEqual -> String
(Int -> RelationalExpression_LessThanEqual -> String -> String)
-> (RelationalExpression_LessThanEqual -> String)
-> ([RelationalExpression_LessThanEqual] -> String -> String)
-> Show RelationalExpression_LessThanEqual
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> RelationalExpression_LessThanEqual -> String -> String
showsPrec :: Int -> RelationalExpression_LessThanEqual -> String -> String
$cshow :: RelationalExpression_LessThanEqual -> String
show :: RelationalExpression_LessThanEqual -> String
$cshowList :: [RelationalExpression_LessThanEqual] -> String -> String
showList :: [RelationalExpression_LessThanEqual] -> String -> String
Show)

_RelationalExpression_LessThanEqual :: Name
_RelationalExpression_LessThanEqual = (String -> Name
Core.Name String
"hydra/langs/java/syntax.RelationalExpression.LessThanEqual")

_RelationalExpression_LessThanEqual_lhs :: Name
_RelationalExpression_LessThanEqual_lhs = (String -> Name
Core.Name String
"lhs")

_RelationalExpression_LessThanEqual_rhs :: Name
_RelationalExpression_LessThanEqual_rhs = (String -> Name
Core.Name 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
(RelationalExpression_GreaterThanEqual
 -> RelationalExpression_GreaterThanEqual -> Bool)
-> (RelationalExpression_GreaterThanEqual
    -> RelationalExpression_GreaterThanEqual -> Bool)
-> Eq RelationalExpression_GreaterThanEqual
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RelationalExpression_GreaterThanEqual
-> RelationalExpression_GreaterThanEqual -> Bool
== :: RelationalExpression_GreaterThanEqual
-> RelationalExpression_GreaterThanEqual -> Bool
$c/= :: RelationalExpression_GreaterThanEqual
-> RelationalExpression_GreaterThanEqual -> Bool
/= :: RelationalExpression_GreaterThanEqual
-> RelationalExpression_GreaterThanEqual -> Bool
Eq, Eq RelationalExpression_GreaterThanEqual
Eq RelationalExpression_GreaterThanEqual =>
(RelationalExpression_GreaterThanEqual
 -> RelationalExpression_GreaterThanEqual -> Ordering)
-> (RelationalExpression_GreaterThanEqual
    -> RelationalExpression_GreaterThanEqual -> Bool)
-> (RelationalExpression_GreaterThanEqual
    -> RelationalExpression_GreaterThanEqual -> Bool)
-> (RelationalExpression_GreaterThanEqual
    -> RelationalExpression_GreaterThanEqual -> Bool)
-> (RelationalExpression_GreaterThanEqual
    -> RelationalExpression_GreaterThanEqual -> Bool)
-> (RelationalExpression_GreaterThanEqual
    -> RelationalExpression_GreaterThanEqual
    -> RelationalExpression_GreaterThanEqual)
-> (RelationalExpression_GreaterThanEqual
    -> RelationalExpression_GreaterThanEqual
    -> RelationalExpression_GreaterThanEqual)
-> Ord 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
$ccompare :: RelationalExpression_GreaterThanEqual
-> RelationalExpression_GreaterThanEqual -> Ordering
compare :: RelationalExpression_GreaterThanEqual
-> RelationalExpression_GreaterThanEqual -> Ordering
$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
>= :: RelationalExpression_GreaterThanEqual
-> RelationalExpression_GreaterThanEqual -> Bool
$cmax :: RelationalExpression_GreaterThanEqual
-> RelationalExpression_GreaterThanEqual
-> RelationalExpression_GreaterThanEqual
max :: RelationalExpression_GreaterThanEqual
-> RelationalExpression_GreaterThanEqual
-> RelationalExpression_GreaterThanEqual
$cmin :: RelationalExpression_GreaterThanEqual
-> RelationalExpression_GreaterThanEqual
-> RelationalExpression_GreaterThanEqual
min :: RelationalExpression_GreaterThanEqual
-> RelationalExpression_GreaterThanEqual
-> RelationalExpression_GreaterThanEqual
Ord, ReadPrec [RelationalExpression_GreaterThanEqual]
ReadPrec RelationalExpression_GreaterThanEqual
Int -> ReadS RelationalExpression_GreaterThanEqual
ReadS [RelationalExpression_GreaterThanEqual]
(Int -> ReadS RelationalExpression_GreaterThanEqual)
-> ReadS [RelationalExpression_GreaterThanEqual]
-> ReadPrec RelationalExpression_GreaterThanEqual
-> ReadPrec [RelationalExpression_GreaterThanEqual]
-> Read RelationalExpression_GreaterThanEqual
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS RelationalExpression_GreaterThanEqual
readsPrec :: Int -> ReadS RelationalExpression_GreaterThanEqual
$creadList :: ReadS [RelationalExpression_GreaterThanEqual]
readList :: ReadS [RelationalExpression_GreaterThanEqual]
$creadPrec :: ReadPrec RelationalExpression_GreaterThanEqual
readPrec :: ReadPrec RelationalExpression_GreaterThanEqual
$creadListPrec :: ReadPrec [RelationalExpression_GreaterThanEqual]
readListPrec :: ReadPrec [RelationalExpression_GreaterThanEqual]
Read, Int -> RelationalExpression_GreaterThanEqual -> String -> String
[RelationalExpression_GreaterThanEqual] -> String -> String
RelationalExpression_GreaterThanEqual -> String
(Int -> RelationalExpression_GreaterThanEqual -> String -> String)
-> (RelationalExpression_GreaterThanEqual -> String)
-> ([RelationalExpression_GreaterThanEqual] -> String -> String)
-> Show RelationalExpression_GreaterThanEqual
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> RelationalExpression_GreaterThanEqual -> String -> String
showsPrec :: Int -> RelationalExpression_GreaterThanEqual -> String -> String
$cshow :: RelationalExpression_GreaterThanEqual -> String
show :: RelationalExpression_GreaterThanEqual -> String
$cshowList :: [RelationalExpression_GreaterThanEqual] -> String -> String
showList :: [RelationalExpression_GreaterThanEqual] -> String -> String
Show)

_RelationalExpression_GreaterThanEqual :: Name
_RelationalExpression_GreaterThanEqual = (String -> Name
Core.Name String
"hydra/langs/java/syntax.RelationalExpression.GreaterThanEqual")

_RelationalExpression_GreaterThanEqual_lhs :: Name
_RelationalExpression_GreaterThanEqual_lhs = (String -> Name
Core.Name String
"lhs")

_RelationalExpression_GreaterThanEqual_rhs :: Name
_RelationalExpression_GreaterThanEqual_rhs = (String -> Name
Core.Name 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
(RelationalExpression_InstanceOf
 -> RelationalExpression_InstanceOf -> Bool)
-> (RelationalExpression_InstanceOf
    -> RelationalExpression_InstanceOf -> Bool)
-> Eq RelationalExpression_InstanceOf
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RelationalExpression_InstanceOf
-> RelationalExpression_InstanceOf -> Bool
== :: RelationalExpression_InstanceOf
-> RelationalExpression_InstanceOf -> Bool
$c/= :: RelationalExpression_InstanceOf
-> RelationalExpression_InstanceOf -> Bool
/= :: RelationalExpression_InstanceOf
-> RelationalExpression_InstanceOf -> Bool
Eq, Eq RelationalExpression_InstanceOf
Eq RelationalExpression_InstanceOf =>
(RelationalExpression_InstanceOf
 -> RelationalExpression_InstanceOf -> Ordering)
-> (RelationalExpression_InstanceOf
    -> RelationalExpression_InstanceOf -> Bool)
-> (RelationalExpression_InstanceOf
    -> RelationalExpression_InstanceOf -> Bool)
-> (RelationalExpression_InstanceOf
    -> RelationalExpression_InstanceOf -> Bool)
-> (RelationalExpression_InstanceOf
    -> RelationalExpression_InstanceOf -> Bool)
-> (RelationalExpression_InstanceOf
    -> RelationalExpression_InstanceOf
    -> RelationalExpression_InstanceOf)
-> (RelationalExpression_InstanceOf
    -> RelationalExpression_InstanceOf
    -> RelationalExpression_InstanceOf)
-> Ord 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
$ccompare :: RelationalExpression_InstanceOf
-> RelationalExpression_InstanceOf -> Ordering
compare :: RelationalExpression_InstanceOf
-> RelationalExpression_InstanceOf -> Ordering
$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
>= :: RelationalExpression_InstanceOf
-> RelationalExpression_InstanceOf -> Bool
$cmax :: RelationalExpression_InstanceOf
-> RelationalExpression_InstanceOf
-> RelationalExpression_InstanceOf
max :: RelationalExpression_InstanceOf
-> RelationalExpression_InstanceOf
-> RelationalExpression_InstanceOf
$cmin :: RelationalExpression_InstanceOf
-> RelationalExpression_InstanceOf
-> RelationalExpression_InstanceOf
min :: RelationalExpression_InstanceOf
-> RelationalExpression_InstanceOf
-> RelationalExpression_InstanceOf
Ord, ReadPrec [RelationalExpression_InstanceOf]
ReadPrec RelationalExpression_InstanceOf
Int -> ReadS RelationalExpression_InstanceOf
ReadS [RelationalExpression_InstanceOf]
(Int -> ReadS RelationalExpression_InstanceOf)
-> ReadS [RelationalExpression_InstanceOf]
-> ReadPrec RelationalExpression_InstanceOf
-> ReadPrec [RelationalExpression_InstanceOf]
-> Read RelationalExpression_InstanceOf
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS RelationalExpression_InstanceOf
readsPrec :: Int -> ReadS RelationalExpression_InstanceOf
$creadList :: ReadS [RelationalExpression_InstanceOf]
readList :: ReadS [RelationalExpression_InstanceOf]
$creadPrec :: ReadPrec RelationalExpression_InstanceOf
readPrec :: ReadPrec RelationalExpression_InstanceOf
$creadListPrec :: ReadPrec [RelationalExpression_InstanceOf]
readListPrec :: ReadPrec [RelationalExpression_InstanceOf]
Read, Int -> RelationalExpression_InstanceOf -> String -> String
[RelationalExpression_InstanceOf] -> String -> String
RelationalExpression_InstanceOf -> String
(Int -> RelationalExpression_InstanceOf -> String -> String)
-> (RelationalExpression_InstanceOf -> String)
-> ([RelationalExpression_InstanceOf] -> String -> String)
-> Show RelationalExpression_InstanceOf
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> RelationalExpression_InstanceOf -> String -> String
showsPrec :: Int -> RelationalExpression_InstanceOf -> String -> String
$cshow :: RelationalExpression_InstanceOf -> String
show :: RelationalExpression_InstanceOf -> String
$cshowList :: [RelationalExpression_InstanceOf] -> String -> String
showList :: [RelationalExpression_InstanceOf] -> String -> String
Show)

_RelationalExpression_InstanceOf :: Name
_RelationalExpression_InstanceOf = (String -> Name
Core.Name String
"hydra/langs/java/syntax.RelationalExpression.InstanceOf")

_RelationalExpression_InstanceOf_lhs :: Name
_RelationalExpression_InstanceOf_lhs = (String -> Name
Core.Name String
"lhs")

_RelationalExpression_InstanceOf_rhs :: Name
_RelationalExpression_InstanceOf_rhs = (String -> Name
Core.Name String
"rhs")

data ShiftExpression = 
  ShiftExpressionUnary AdditiveExpression |
  ShiftExpressionShiftLeft ShiftExpression_Binary |
  ShiftExpressionShiftRight ShiftExpression_Binary |
  ShiftExpressionShiftRightZeroFill ShiftExpression_Binary
  deriving (ShiftExpression -> ShiftExpression -> Bool
(ShiftExpression -> ShiftExpression -> Bool)
-> (ShiftExpression -> ShiftExpression -> Bool)
-> Eq ShiftExpression
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ShiftExpression -> ShiftExpression -> Bool
== :: ShiftExpression -> ShiftExpression -> Bool
$c/= :: ShiftExpression -> ShiftExpression -> Bool
/= :: ShiftExpression -> ShiftExpression -> Bool
Eq, Eq ShiftExpression
Eq ShiftExpression =>
(ShiftExpression -> ShiftExpression -> Ordering)
-> (ShiftExpression -> ShiftExpression -> Bool)
-> (ShiftExpression -> ShiftExpression -> Bool)
-> (ShiftExpression -> ShiftExpression -> Bool)
-> (ShiftExpression -> ShiftExpression -> Bool)
-> (ShiftExpression -> ShiftExpression -> ShiftExpression)
-> (ShiftExpression -> ShiftExpression -> ShiftExpression)
-> Ord 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
$ccompare :: ShiftExpression -> ShiftExpression -> Ordering
compare :: ShiftExpression -> ShiftExpression -> Ordering
$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
>= :: ShiftExpression -> ShiftExpression -> Bool
$cmax :: ShiftExpression -> ShiftExpression -> ShiftExpression
max :: ShiftExpression -> ShiftExpression -> ShiftExpression
$cmin :: ShiftExpression -> ShiftExpression -> ShiftExpression
min :: ShiftExpression -> ShiftExpression -> ShiftExpression
Ord, ReadPrec [ShiftExpression]
ReadPrec ShiftExpression
Int -> ReadS ShiftExpression
ReadS [ShiftExpression]
(Int -> ReadS ShiftExpression)
-> ReadS [ShiftExpression]
-> ReadPrec ShiftExpression
-> ReadPrec [ShiftExpression]
-> Read ShiftExpression
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ShiftExpression
readsPrec :: Int -> ReadS ShiftExpression
$creadList :: ReadS [ShiftExpression]
readList :: ReadS [ShiftExpression]
$creadPrec :: ReadPrec ShiftExpression
readPrec :: ReadPrec ShiftExpression
$creadListPrec :: ReadPrec [ShiftExpression]
readListPrec :: ReadPrec [ShiftExpression]
Read, Int -> ShiftExpression -> String -> String
[ShiftExpression] -> String -> String
ShiftExpression -> String
(Int -> ShiftExpression -> String -> String)
-> (ShiftExpression -> String)
-> ([ShiftExpression] -> String -> String)
-> Show ShiftExpression
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> ShiftExpression -> String -> String
showsPrec :: Int -> ShiftExpression -> String -> String
$cshow :: ShiftExpression -> String
show :: ShiftExpression -> String
$cshowList :: [ShiftExpression] -> String -> String
showList :: [ShiftExpression] -> String -> String
Show)

_ShiftExpression :: Name
_ShiftExpression = (String -> Name
Core.Name String
"hydra/langs/java/syntax.ShiftExpression")

_ShiftExpression_unary :: Name
_ShiftExpression_unary = (String -> Name
Core.Name String
"unary")

_ShiftExpression_shiftLeft :: Name
_ShiftExpression_shiftLeft = (String -> Name
Core.Name String
"shiftLeft")

_ShiftExpression_shiftRight :: Name
_ShiftExpression_shiftRight = (String -> Name
Core.Name String
"shiftRight")

_ShiftExpression_shiftRightZeroFill :: Name
_ShiftExpression_shiftRightZeroFill = (String -> Name
Core.Name 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
(ShiftExpression_Binary -> ShiftExpression_Binary -> Bool)
-> (ShiftExpression_Binary -> ShiftExpression_Binary -> Bool)
-> Eq ShiftExpression_Binary
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ShiftExpression_Binary -> ShiftExpression_Binary -> Bool
== :: ShiftExpression_Binary -> ShiftExpression_Binary -> Bool
$c/= :: ShiftExpression_Binary -> ShiftExpression_Binary -> Bool
/= :: ShiftExpression_Binary -> ShiftExpression_Binary -> Bool
Eq, Eq ShiftExpression_Binary
Eq ShiftExpression_Binary =>
(ShiftExpression_Binary -> ShiftExpression_Binary -> Ordering)
-> (ShiftExpression_Binary -> ShiftExpression_Binary -> Bool)
-> (ShiftExpression_Binary -> ShiftExpression_Binary -> Bool)
-> (ShiftExpression_Binary -> ShiftExpression_Binary -> Bool)
-> (ShiftExpression_Binary -> ShiftExpression_Binary -> Bool)
-> (ShiftExpression_Binary
    -> ShiftExpression_Binary -> ShiftExpression_Binary)
-> (ShiftExpression_Binary
    -> ShiftExpression_Binary -> ShiftExpression_Binary)
-> Ord 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
$ccompare :: ShiftExpression_Binary -> ShiftExpression_Binary -> Ordering
compare :: ShiftExpression_Binary -> ShiftExpression_Binary -> Ordering
$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
>= :: ShiftExpression_Binary -> ShiftExpression_Binary -> Bool
$cmax :: ShiftExpression_Binary
-> ShiftExpression_Binary -> ShiftExpression_Binary
max :: ShiftExpression_Binary
-> ShiftExpression_Binary -> ShiftExpression_Binary
$cmin :: ShiftExpression_Binary
-> ShiftExpression_Binary -> ShiftExpression_Binary
min :: ShiftExpression_Binary
-> ShiftExpression_Binary -> ShiftExpression_Binary
Ord, ReadPrec [ShiftExpression_Binary]
ReadPrec ShiftExpression_Binary
Int -> ReadS ShiftExpression_Binary
ReadS [ShiftExpression_Binary]
(Int -> ReadS ShiftExpression_Binary)
-> ReadS [ShiftExpression_Binary]
-> ReadPrec ShiftExpression_Binary
-> ReadPrec [ShiftExpression_Binary]
-> Read ShiftExpression_Binary
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ShiftExpression_Binary
readsPrec :: Int -> ReadS ShiftExpression_Binary
$creadList :: ReadS [ShiftExpression_Binary]
readList :: ReadS [ShiftExpression_Binary]
$creadPrec :: ReadPrec ShiftExpression_Binary
readPrec :: ReadPrec ShiftExpression_Binary
$creadListPrec :: ReadPrec [ShiftExpression_Binary]
readListPrec :: ReadPrec [ShiftExpression_Binary]
Read, Int -> ShiftExpression_Binary -> String -> String
[ShiftExpression_Binary] -> String -> String
ShiftExpression_Binary -> String
(Int -> ShiftExpression_Binary -> String -> String)
-> (ShiftExpression_Binary -> String)
-> ([ShiftExpression_Binary] -> String -> String)
-> Show ShiftExpression_Binary
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> ShiftExpression_Binary -> String -> String
showsPrec :: Int -> ShiftExpression_Binary -> String -> String
$cshow :: ShiftExpression_Binary -> String
show :: ShiftExpression_Binary -> String
$cshowList :: [ShiftExpression_Binary] -> String -> String
showList :: [ShiftExpression_Binary] -> String -> String
Show)

_ShiftExpression_Binary :: Name
_ShiftExpression_Binary = (String -> Name
Core.Name String
"hydra/langs/java/syntax.ShiftExpression.Binary")

_ShiftExpression_Binary_lhs :: Name
_ShiftExpression_Binary_lhs = (String -> Name
Core.Name String
"lhs")

_ShiftExpression_Binary_rhs :: Name
_ShiftExpression_Binary_rhs = (String -> Name
Core.Name String
"rhs")

data AdditiveExpression = 
  AdditiveExpressionUnary MultiplicativeExpression |
  AdditiveExpressionPlus AdditiveExpression_Binary |
  AdditiveExpressionMinus AdditiveExpression_Binary
  deriving (AdditiveExpression -> AdditiveExpression -> Bool
(AdditiveExpression -> AdditiveExpression -> Bool)
-> (AdditiveExpression -> AdditiveExpression -> Bool)
-> Eq AdditiveExpression
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AdditiveExpression -> AdditiveExpression -> Bool
== :: AdditiveExpression -> AdditiveExpression -> Bool
$c/= :: AdditiveExpression -> AdditiveExpression -> Bool
/= :: AdditiveExpression -> AdditiveExpression -> Bool
Eq, Eq AdditiveExpression
Eq AdditiveExpression =>
(AdditiveExpression -> AdditiveExpression -> Ordering)
-> (AdditiveExpression -> AdditiveExpression -> Bool)
-> (AdditiveExpression -> AdditiveExpression -> Bool)
-> (AdditiveExpression -> AdditiveExpression -> Bool)
-> (AdditiveExpression -> AdditiveExpression -> Bool)
-> (AdditiveExpression -> AdditiveExpression -> AdditiveExpression)
-> (AdditiveExpression -> AdditiveExpression -> AdditiveExpression)
-> Ord 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
$ccompare :: AdditiveExpression -> AdditiveExpression -> Ordering
compare :: AdditiveExpression -> AdditiveExpression -> Ordering
$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
>= :: AdditiveExpression -> AdditiveExpression -> Bool
$cmax :: AdditiveExpression -> AdditiveExpression -> AdditiveExpression
max :: AdditiveExpression -> AdditiveExpression -> AdditiveExpression
$cmin :: AdditiveExpression -> AdditiveExpression -> AdditiveExpression
min :: AdditiveExpression -> AdditiveExpression -> AdditiveExpression
Ord, ReadPrec [AdditiveExpression]
ReadPrec AdditiveExpression
Int -> ReadS AdditiveExpression
ReadS [AdditiveExpression]
(Int -> ReadS AdditiveExpression)
-> ReadS [AdditiveExpression]
-> ReadPrec AdditiveExpression
-> ReadPrec [AdditiveExpression]
-> Read AdditiveExpression
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS AdditiveExpression
readsPrec :: Int -> ReadS AdditiveExpression
$creadList :: ReadS [AdditiveExpression]
readList :: ReadS [AdditiveExpression]
$creadPrec :: ReadPrec AdditiveExpression
readPrec :: ReadPrec AdditiveExpression
$creadListPrec :: ReadPrec [AdditiveExpression]
readListPrec :: ReadPrec [AdditiveExpression]
Read, Int -> AdditiveExpression -> String -> String
[AdditiveExpression] -> String -> String
AdditiveExpression -> String
(Int -> AdditiveExpression -> String -> String)
-> (AdditiveExpression -> String)
-> ([AdditiveExpression] -> String -> String)
-> Show AdditiveExpression
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> AdditiveExpression -> String -> String
showsPrec :: Int -> AdditiveExpression -> String -> String
$cshow :: AdditiveExpression -> String
show :: AdditiveExpression -> String
$cshowList :: [AdditiveExpression] -> String -> String
showList :: [AdditiveExpression] -> String -> String
Show)

_AdditiveExpression :: Name
_AdditiveExpression = (String -> Name
Core.Name String
"hydra/langs/java/syntax.AdditiveExpression")

_AdditiveExpression_unary :: Name
_AdditiveExpression_unary = (String -> Name
Core.Name String
"unary")

_AdditiveExpression_plus :: Name
_AdditiveExpression_plus = (String -> Name
Core.Name String
"plus")

_AdditiveExpression_minus :: Name
_AdditiveExpression_minus = (String -> Name
Core.Name 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
(AdditiveExpression_Binary -> AdditiveExpression_Binary -> Bool)
-> (AdditiveExpression_Binary -> AdditiveExpression_Binary -> Bool)
-> Eq AdditiveExpression_Binary
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AdditiveExpression_Binary -> AdditiveExpression_Binary -> Bool
== :: AdditiveExpression_Binary -> AdditiveExpression_Binary -> Bool
$c/= :: AdditiveExpression_Binary -> AdditiveExpression_Binary -> Bool
/= :: AdditiveExpression_Binary -> AdditiveExpression_Binary -> Bool
Eq, Eq AdditiveExpression_Binary
Eq AdditiveExpression_Binary =>
(AdditiveExpression_Binary
 -> AdditiveExpression_Binary -> Ordering)
-> (AdditiveExpression_Binary -> AdditiveExpression_Binary -> Bool)
-> (AdditiveExpression_Binary -> AdditiveExpression_Binary -> Bool)
-> (AdditiveExpression_Binary -> AdditiveExpression_Binary -> Bool)
-> (AdditiveExpression_Binary -> AdditiveExpression_Binary -> Bool)
-> (AdditiveExpression_Binary
    -> AdditiveExpression_Binary -> AdditiveExpression_Binary)
-> (AdditiveExpression_Binary
    -> AdditiveExpression_Binary -> AdditiveExpression_Binary)
-> Ord 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
$ccompare :: AdditiveExpression_Binary -> AdditiveExpression_Binary -> Ordering
compare :: AdditiveExpression_Binary -> AdditiveExpression_Binary -> Ordering
$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
>= :: AdditiveExpression_Binary -> AdditiveExpression_Binary -> Bool
$cmax :: AdditiveExpression_Binary
-> AdditiveExpression_Binary -> AdditiveExpression_Binary
max :: AdditiveExpression_Binary
-> AdditiveExpression_Binary -> AdditiveExpression_Binary
$cmin :: AdditiveExpression_Binary
-> AdditiveExpression_Binary -> AdditiveExpression_Binary
min :: AdditiveExpression_Binary
-> AdditiveExpression_Binary -> AdditiveExpression_Binary
Ord, ReadPrec [AdditiveExpression_Binary]
ReadPrec AdditiveExpression_Binary
Int -> ReadS AdditiveExpression_Binary
ReadS [AdditiveExpression_Binary]
(Int -> ReadS AdditiveExpression_Binary)
-> ReadS [AdditiveExpression_Binary]
-> ReadPrec AdditiveExpression_Binary
-> ReadPrec [AdditiveExpression_Binary]
-> Read AdditiveExpression_Binary
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS AdditiveExpression_Binary
readsPrec :: Int -> ReadS AdditiveExpression_Binary
$creadList :: ReadS [AdditiveExpression_Binary]
readList :: ReadS [AdditiveExpression_Binary]
$creadPrec :: ReadPrec AdditiveExpression_Binary
readPrec :: ReadPrec AdditiveExpression_Binary
$creadListPrec :: ReadPrec [AdditiveExpression_Binary]
readListPrec :: ReadPrec [AdditiveExpression_Binary]
Read, Int -> AdditiveExpression_Binary -> String -> String
[AdditiveExpression_Binary] -> String -> String
AdditiveExpression_Binary -> String
(Int -> AdditiveExpression_Binary -> String -> String)
-> (AdditiveExpression_Binary -> String)
-> ([AdditiveExpression_Binary] -> String -> String)
-> Show AdditiveExpression_Binary
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> AdditiveExpression_Binary -> String -> String
showsPrec :: Int -> AdditiveExpression_Binary -> String -> String
$cshow :: AdditiveExpression_Binary -> String
show :: AdditiveExpression_Binary -> String
$cshowList :: [AdditiveExpression_Binary] -> String -> String
showList :: [AdditiveExpression_Binary] -> String -> String
Show)

_AdditiveExpression_Binary :: Name
_AdditiveExpression_Binary = (String -> Name
Core.Name String
"hydra/langs/java/syntax.AdditiveExpression.Binary")

_AdditiveExpression_Binary_lhs :: Name
_AdditiveExpression_Binary_lhs = (String -> Name
Core.Name String
"lhs")

_AdditiveExpression_Binary_rhs :: Name
_AdditiveExpression_Binary_rhs = (String -> Name
Core.Name String
"rhs")

data MultiplicativeExpression = 
  MultiplicativeExpressionUnary UnaryExpression |
  MultiplicativeExpressionTimes MultiplicativeExpression_Binary |
  MultiplicativeExpressionDivide MultiplicativeExpression_Binary |
  MultiplicativeExpressionMod MultiplicativeExpression_Binary
  deriving (MultiplicativeExpression -> MultiplicativeExpression -> Bool
(MultiplicativeExpression -> MultiplicativeExpression -> Bool)
-> (MultiplicativeExpression -> MultiplicativeExpression -> Bool)
-> Eq MultiplicativeExpression
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: MultiplicativeExpression -> MultiplicativeExpression -> Bool
== :: MultiplicativeExpression -> MultiplicativeExpression -> Bool
$c/= :: MultiplicativeExpression -> MultiplicativeExpression -> Bool
/= :: MultiplicativeExpression -> MultiplicativeExpression -> Bool
Eq, Eq MultiplicativeExpression
Eq MultiplicativeExpression =>
(MultiplicativeExpression -> MultiplicativeExpression -> Ordering)
-> (MultiplicativeExpression -> MultiplicativeExpression -> Bool)
-> (MultiplicativeExpression -> MultiplicativeExpression -> Bool)
-> (MultiplicativeExpression -> MultiplicativeExpression -> Bool)
-> (MultiplicativeExpression -> MultiplicativeExpression -> Bool)
-> (MultiplicativeExpression
    -> MultiplicativeExpression -> MultiplicativeExpression)
-> (MultiplicativeExpression
    -> MultiplicativeExpression -> MultiplicativeExpression)
-> Ord 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
$ccompare :: MultiplicativeExpression -> MultiplicativeExpression -> Ordering
compare :: MultiplicativeExpression -> MultiplicativeExpression -> Ordering
$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
>= :: MultiplicativeExpression -> MultiplicativeExpression -> Bool
$cmax :: MultiplicativeExpression
-> MultiplicativeExpression -> MultiplicativeExpression
max :: MultiplicativeExpression
-> MultiplicativeExpression -> MultiplicativeExpression
$cmin :: MultiplicativeExpression
-> MultiplicativeExpression -> MultiplicativeExpression
min :: MultiplicativeExpression
-> MultiplicativeExpression -> MultiplicativeExpression
Ord, ReadPrec [MultiplicativeExpression]
ReadPrec MultiplicativeExpression
Int -> ReadS MultiplicativeExpression
ReadS [MultiplicativeExpression]
(Int -> ReadS MultiplicativeExpression)
-> ReadS [MultiplicativeExpression]
-> ReadPrec MultiplicativeExpression
-> ReadPrec [MultiplicativeExpression]
-> Read MultiplicativeExpression
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS MultiplicativeExpression
readsPrec :: Int -> ReadS MultiplicativeExpression
$creadList :: ReadS [MultiplicativeExpression]
readList :: ReadS [MultiplicativeExpression]
$creadPrec :: ReadPrec MultiplicativeExpression
readPrec :: ReadPrec MultiplicativeExpression
$creadListPrec :: ReadPrec [MultiplicativeExpression]
readListPrec :: ReadPrec [MultiplicativeExpression]
Read, Int -> MultiplicativeExpression -> String -> String
[MultiplicativeExpression] -> String -> String
MultiplicativeExpression -> String
(Int -> MultiplicativeExpression -> String -> String)
-> (MultiplicativeExpression -> String)
-> ([MultiplicativeExpression] -> String -> String)
-> Show MultiplicativeExpression
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> MultiplicativeExpression -> String -> String
showsPrec :: Int -> MultiplicativeExpression -> String -> String
$cshow :: MultiplicativeExpression -> String
show :: MultiplicativeExpression -> String
$cshowList :: [MultiplicativeExpression] -> String -> String
showList :: [MultiplicativeExpression] -> String -> String
Show)

_MultiplicativeExpression :: Name
_MultiplicativeExpression = (String -> Name
Core.Name String
"hydra/langs/java/syntax.MultiplicativeExpression")

_MultiplicativeExpression_unary :: Name
_MultiplicativeExpression_unary = (String -> Name
Core.Name String
"unary")

_MultiplicativeExpression_times :: Name
_MultiplicativeExpression_times = (String -> Name
Core.Name String
"times")

_MultiplicativeExpression_divide :: Name
_MultiplicativeExpression_divide = (String -> Name
Core.Name String
"divide")

_MultiplicativeExpression_mod :: Name
_MultiplicativeExpression_mod = (String -> Name
Core.Name 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
(MultiplicativeExpression_Binary
 -> MultiplicativeExpression_Binary -> Bool)
-> (MultiplicativeExpression_Binary
    -> MultiplicativeExpression_Binary -> Bool)
-> Eq MultiplicativeExpression_Binary
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: MultiplicativeExpression_Binary
-> MultiplicativeExpression_Binary -> Bool
== :: MultiplicativeExpression_Binary
-> MultiplicativeExpression_Binary -> Bool
$c/= :: MultiplicativeExpression_Binary
-> MultiplicativeExpression_Binary -> Bool
/= :: MultiplicativeExpression_Binary
-> MultiplicativeExpression_Binary -> Bool
Eq, Eq MultiplicativeExpression_Binary
Eq MultiplicativeExpression_Binary =>
(MultiplicativeExpression_Binary
 -> MultiplicativeExpression_Binary -> Ordering)
-> (MultiplicativeExpression_Binary
    -> MultiplicativeExpression_Binary -> Bool)
-> (MultiplicativeExpression_Binary
    -> MultiplicativeExpression_Binary -> Bool)
-> (MultiplicativeExpression_Binary
    -> MultiplicativeExpression_Binary -> Bool)
-> (MultiplicativeExpression_Binary
    -> MultiplicativeExpression_Binary -> Bool)
-> (MultiplicativeExpression_Binary
    -> MultiplicativeExpression_Binary
    -> MultiplicativeExpression_Binary)
-> (MultiplicativeExpression_Binary
    -> MultiplicativeExpression_Binary
    -> MultiplicativeExpression_Binary)
-> Ord 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
$ccompare :: MultiplicativeExpression_Binary
-> MultiplicativeExpression_Binary -> Ordering
compare :: MultiplicativeExpression_Binary
-> MultiplicativeExpression_Binary -> Ordering
$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
>= :: MultiplicativeExpression_Binary
-> MultiplicativeExpression_Binary -> Bool
$cmax :: MultiplicativeExpression_Binary
-> MultiplicativeExpression_Binary
-> MultiplicativeExpression_Binary
max :: MultiplicativeExpression_Binary
-> MultiplicativeExpression_Binary
-> MultiplicativeExpression_Binary
$cmin :: MultiplicativeExpression_Binary
-> MultiplicativeExpression_Binary
-> MultiplicativeExpression_Binary
min :: MultiplicativeExpression_Binary
-> MultiplicativeExpression_Binary
-> MultiplicativeExpression_Binary
Ord, ReadPrec [MultiplicativeExpression_Binary]
ReadPrec MultiplicativeExpression_Binary
Int -> ReadS MultiplicativeExpression_Binary
ReadS [MultiplicativeExpression_Binary]
(Int -> ReadS MultiplicativeExpression_Binary)
-> ReadS [MultiplicativeExpression_Binary]
-> ReadPrec MultiplicativeExpression_Binary
-> ReadPrec [MultiplicativeExpression_Binary]
-> Read MultiplicativeExpression_Binary
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS MultiplicativeExpression_Binary
readsPrec :: Int -> ReadS MultiplicativeExpression_Binary
$creadList :: ReadS [MultiplicativeExpression_Binary]
readList :: ReadS [MultiplicativeExpression_Binary]
$creadPrec :: ReadPrec MultiplicativeExpression_Binary
readPrec :: ReadPrec MultiplicativeExpression_Binary
$creadListPrec :: ReadPrec [MultiplicativeExpression_Binary]
readListPrec :: ReadPrec [MultiplicativeExpression_Binary]
Read, Int -> MultiplicativeExpression_Binary -> String -> String
[MultiplicativeExpression_Binary] -> String -> String
MultiplicativeExpression_Binary -> String
(Int -> MultiplicativeExpression_Binary -> String -> String)
-> (MultiplicativeExpression_Binary -> String)
-> ([MultiplicativeExpression_Binary] -> String -> String)
-> Show MultiplicativeExpression_Binary
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> MultiplicativeExpression_Binary -> String -> String
showsPrec :: Int -> MultiplicativeExpression_Binary -> String -> String
$cshow :: MultiplicativeExpression_Binary -> String
show :: MultiplicativeExpression_Binary -> String
$cshowList :: [MultiplicativeExpression_Binary] -> String -> String
showList :: [MultiplicativeExpression_Binary] -> String -> String
Show)

_MultiplicativeExpression_Binary :: Name
_MultiplicativeExpression_Binary = (String -> Name
Core.Name String
"hydra/langs/java/syntax.MultiplicativeExpression.Binary")

_MultiplicativeExpression_Binary_lhs :: Name
_MultiplicativeExpression_Binary_lhs = (String -> Name
Core.Name String
"lhs")

_MultiplicativeExpression_Binary_rhs :: Name
_MultiplicativeExpression_Binary_rhs = (String -> Name
Core.Name String
"rhs")

data UnaryExpression = 
  UnaryExpressionPreIncrement PreIncrementExpression |
  UnaryExpressionPreDecrement PreDecrementExpression |
  UnaryExpressionPlus UnaryExpression |
  UnaryExpressionMinus UnaryExpression |
  UnaryExpressionOther UnaryExpressionNotPlusMinus
  deriving (UnaryExpression -> UnaryExpression -> Bool
(UnaryExpression -> UnaryExpression -> Bool)
-> (UnaryExpression -> UnaryExpression -> Bool)
-> Eq UnaryExpression
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: UnaryExpression -> UnaryExpression -> Bool
== :: UnaryExpression -> UnaryExpression -> Bool
$c/= :: UnaryExpression -> UnaryExpression -> Bool
/= :: UnaryExpression -> UnaryExpression -> Bool
Eq, Eq UnaryExpression
Eq UnaryExpression =>
(UnaryExpression -> UnaryExpression -> Ordering)
-> (UnaryExpression -> UnaryExpression -> Bool)
-> (UnaryExpression -> UnaryExpression -> Bool)
-> (UnaryExpression -> UnaryExpression -> Bool)
-> (UnaryExpression -> UnaryExpression -> Bool)
-> (UnaryExpression -> UnaryExpression -> UnaryExpression)
-> (UnaryExpression -> UnaryExpression -> UnaryExpression)
-> Ord 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
$ccompare :: UnaryExpression -> UnaryExpression -> Ordering
compare :: UnaryExpression -> UnaryExpression -> Ordering
$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
>= :: UnaryExpression -> UnaryExpression -> Bool
$cmax :: UnaryExpression -> UnaryExpression -> UnaryExpression
max :: UnaryExpression -> UnaryExpression -> UnaryExpression
$cmin :: UnaryExpression -> UnaryExpression -> UnaryExpression
min :: UnaryExpression -> UnaryExpression -> UnaryExpression
Ord, ReadPrec [UnaryExpression]
ReadPrec UnaryExpression
Int -> ReadS UnaryExpression
ReadS [UnaryExpression]
(Int -> ReadS UnaryExpression)
-> ReadS [UnaryExpression]
-> ReadPrec UnaryExpression
-> ReadPrec [UnaryExpression]
-> Read UnaryExpression
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS UnaryExpression
readsPrec :: Int -> ReadS UnaryExpression
$creadList :: ReadS [UnaryExpression]
readList :: ReadS [UnaryExpression]
$creadPrec :: ReadPrec UnaryExpression
readPrec :: ReadPrec UnaryExpression
$creadListPrec :: ReadPrec [UnaryExpression]
readListPrec :: ReadPrec [UnaryExpression]
Read, Int -> UnaryExpression -> String -> String
[UnaryExpression] -> String -> String
UnaryExpression -> String
(Int -> UnaryExpression -> String -> String)
-> (UnaryExpression -> String)
-> ([UnaryExpression] -> String -> String)
-> Show UnaryExpression
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> UnaryExpression -> String -> String
showsPrec :: Int -> UnaryExpression -> String -> String
$cshow :: UnaryExpression -> String
show :: UnaryExpression -> String
$cshowList :: [UnaryExpression] -> String -> String
showList :: [UnaryExpression] -> String -> String
Show)

_UnaryExpression :: Name
_UnaryExpression = (String -> Name
Core.Name String
"hydra/langs/java/syntax.UnaryExpression")

_UnaryExpression_preIncrement :: Name
_UnaryExpression_preIncrement = (String -> Name
Core.Name String
"preIncrement")

_UnaryExpression_preDecrement :: Name
_UnaryExpression_preDecrement = (String -> Name
Core.Name String
"preDecrement")

_UnaryExpression_plus :: Name
_UnaryExpression_plus = (String -> Name
Core.Name String
"plus")

_UnaryExpression_minus :: Name
_UnaryExpression_minus = (String -> Name
Core.Name String
"minus")

_UnaryExpression_other :: Name
_UnaryExpression_other = (String -> Name
Core.Name String
"other")

newtype PreIncrementExpression = 
  PreIncrementExpression {
    PreIncrementExpression -> UnaryExpression
unPreIncrementExpression :: UnaryExpression}
  deriving (PreIncrementExpression -> PreIncrementExpression -> Bool
(PreIncrementExpression -> PreIncrementExpression -> Bool)
-> (PreIncrementExpression -> PreIncrementExpression -> Bool)
-> Eq PreIncrementExpression
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PreIncrementExpression -> PreIncrementExpression -> Bool
== :: PreIncrementExpression -> PreIncrementExpression -> Bool
$c/= :: PreIncrementExpression -> PreIncrementExpression -> Bool
/= :: PreIncrementExpression -> PreIncrementExpression -> Bool
Eq, Eq PreIncrementExpression
Eq PreIncrementExpression =>
(PreIncrementExpression -> PreIncrementExpression -> Ordering)
-> (PreIncrementExpression -> PreIncrementExpression -> Bool)
-> (PreIncrementExpression -> PreIncrementExpression -> Bool)
-> (PreIncrementExpression -> PreIncrementExpression -> Bool)
-> (PreIncrementExpression -> PreIncrementExpression -> Bool)
-> (PreIncrementExpression
    -> PreIncrementExpression -> PreIncrementExpression)
-> (PreIncrementExpression
    -> PreIncrementExpression -> PreIncrementExpression)
-> Ord 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
$ccompare :: PreIncrementExpression -> PreIncrementExpression -> Ordering
compare :: PreIncrementExpression -> PreIncrementExpression -> Ordering
$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
>= :: PreIncrementExpression -> PreIncrementExpression -> Bool
$cmax :: PreIncrementExpression
-> PreIncrementExpression -> PreIncrementExpression
max :: PreIncrementExpression
-> PreIncrementExpression -> PreIncrementExpression
$cmin :: PreIncrementExpression
-> PreIncrementExpression -> PreIncrementExpression
min :: PreIncrementExpression
-> PreIncrementExpression -> PreIncrementExpression
Ord, ReadPrec [PreIncrementExpression]
ReadPrec PreIncrementExpression
Int -> ReadS PreIncrementExpression
ReadS [PreIncrementExpression]
(Int -> ReadS PreIncrementExpression)
-> ReadS [PreIncrementExpression]
-> ReadPrec PreIncrementExpression
-> ReadPrec [PreIncrementExpression]
-> Read PreIncrementExpression
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS PreIncrementExpression
readsPrec :: Int -> ReadS PreIncrementExpression
$creadList :: ReadS [PreIncrementExpression]
readList :: ReadS [PreIncrementExpression]
$creadPrec :: ReadPrec PreIncrementExpression
readPrec :: ReadPrec PreIncrementExpression
$creadListPrec :: ReadPrec [PreIncrementExpression]
readListPrec :: ReadPrec [PreIncrementExpression]
Read, Int -> PreIncrementExpression -> String -> String
[PreIncrementExpression] -> String -> String
PreIncrementExpression -> String
(Int -> PreIncrementExpression -> String -> String)
-> (PreIncrementExpression -> String)
-> ([PreIncrementExpression] -> String -> String)
-> Show PreIncrementExpression
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> PreIncrementExpression -> String -> String
showsPrec :: Int -> PreIncrementExpression -> String -> String
$cshow :: PreIncrementExpression -> String
show :: PreIncrementExpression -> String
$cshowList :: [PreIncrementExpression] -> String -> String
showList :: [PreIncrementExpression] -> String -> String
Show)

_PreIncrementExpression :: Name
_PreIncrementExpression = (String -> Name
Core.Name String
"hydra/langs/java/syntax.PreIncrementExpression")

newtype PreDecrementExpression = 
  PreDecrementExpression {
    PreDecrementExpression -> UnaryExpression
unPreDecrementExpression :: UnaryExpression}
  deriving (PreDecrementExpression -> PreDecrementExpression -> Bool
(PreDecrementExpression -> PreDecrementExpression -> Bool)
-> (PreDecrementExpression -> PreDecrementExpression -> Bool)
-> Eq PreDecrementExpression
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PreDecrementExpression -> PreDecrementExpression -> Bool
== :: PreDecrementExpression -> PreDecrementExpression -> Bool
$c/= :: PreDecrementExpression -> PreDecrementExpression -> Bool
/= :: PreDecrementExpression -> PreDecrementExpression -> Bool
Eq, Eq PreDecrementExpression
Eq PreDecrementExpression =>
(PreDecrementExpression -> PreDecrementExpression -> Ordering)
-> (PreDecrementExpression -> PreDecrementExpression -> Bool)
-> (PreDecrementExpression -> PreDecrementExpression -> Bool)
-> (PreDecrementExpression -> PreDecrementExpression -> Bool)
-> (PreDecrementExpression -> PreDecrementExpression -> Bool)
-> (PreDecrementExpression
    -> PreDecrementExpression -> PreDecrementExpression)
-> (PreDecrementExpression
    -> PreDecrementExpression -> PreDecrementExpression)
-> Ord 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
$ccompare :: PreDecrementExpression -> PreDecrementExpression -> Ordering
compare :: PreDecrementExpression -> PreDecrementExpression -> Ordering
$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
>= :: PreDecrementExpression -> PreDecrementExpression -> Bool
$cmax :: PreDecrementExpression
-> PreDecrementExpression -> PreDecrementExpression
max :: PreDecrementExpression
-> PreDecrementExpression -> PreDecrementExpression
$cmin :: PreDecrementExpression
-> PreDecrementExpression -> PreDecrementExpression
min :: PreDecrementExpression
-> PreDecrementExpression -> PreDecrementExpression
Ord, ReadPrec [PreDecrementExpression]
ReadPrec PreDecrementExpression
Int -> ReadS PreDecrementExpression
ReadS [PreDecrementExpression]
(Int -> ReadS PreDecrementExpression)
-> ReadS [PreDecrementExpression]
-> ReadPrec PreDecrementExpression
-> ReadPrec [PreDecrementExpression]
-> Read PreDecrementExpression
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS PreDecrementExpression
readsPrec :: Int -> ReadS PreDecrementExpression
$creadList :: ReadS [PreDecrementExpression]
readList :: ReadS [PreDecrementExpression]
$creadPrec :: ReadPrec PreDecrementExpression
readPrec :: ReadPrec PreDecrementExpression
$creadListPrec :: ReadPrec [PreDecrementExpression]
readListPrec :: ReadPrec [PreDecrementExpression]
Read, Int -> PreDecrementExpression -> String -> String
[PreDecrementExpression] -> String -> String
PreDecrementExpression -> String
(Int -> PreDecrementExpression -> String -> String)
-> (PreDecrementExpression -> String)
-> ([PreDecrementExpression] -> String -> String)
-> Show PreDecrementExpression
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> PreDecrementExpression -> String -> String
showsPrec :: Int -> PreDecrementExpression -> String -> String
$cshow :: PreDecrementExpression -> String
show :: PreDecrementExpression -> String
$cshowList :: [PreDecrementExpression] -> String -> String
showList :: [PreDecrementExpression] -> String -> String
Show)

_PreDecrementExpression :: Name
_PreDecrementExpression = (String -> Name
Core.Name String
"hydra/langs/java/syntax.PreDecrementExpression")

data UnaryExpressionNotPlusMinus = 
  UnaryExpressionNotPlusMinusPostfix PostfixExpression |
  UnaryExpressionNotPlusMinusTilde UnaryExpression |
  UnaryExpressionNotPlusMinusNot UnaryExpression |
  UnaryExpressionNotPlusMinusCast CastExpression
  deriving (UnaryExpressionNotPlusMinus -> UnaryExpressionNotPlusMinus -> Bool
(UnaryExpressionNotPlusMinus
 -> UnaryExpressionNotPlusMinus -> Bool)
-> (UnaryExpressionNotPlusMinus
    -> UnaryExpressionNotPlusMinus -> Bool)
-> Eq UnaryExpressionNotPlusMinus
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: UnaryExpressionNotPlusMinus -> UnaryExpressionNotPlusMinus -> Bool
== :: UnaryExpressionNotPlusMinus -> UnaryExpressionNotPlusMinus -> Bool
$c/= :: UnaryExpressionNotPlusMinus -> UnaryExpressionNotPlusMinus -> Bool
/= :: UnaryExpressionNotPlusMinus -> UnaryExpressionNotPlusMinus -> Bool
Eq, Eq UnaryExpressionNotPlusMinus
Eq UnaryExpressionNotPlusMinus =>
(UnaryExpressionNotPlusMinus
 -> UnaryExpressionNotPlusMinus -> Ordering)
-> (UnaryExpressionNotPlusMinus
    -> UnaryExpressionNotPlusMinus -> Bool)
-> (UnaryExpressionNotPlusMinus
    -> UnaryExpressionNotPlusMinus -> Bool)
-> (UnaryExpressionNotPlusMinus
    -> UnaryExpressionNotPlusMinus -> Bool)
-> (UnaryExpressionNotPlusMinus
    -> UnaryExpressionNotPlusMinus -> Bool)
-> (UnaryExpressionNotPlusMinus
    -> UnaryExpressionNotPlusMinus -> UnaryExpressionNotPlusMinus)
-> (UnaryExpressionNotPlusMinus
    -> UnaryExpressionNotPlusMinus -> UnaryExpressionNotPlusMinus)
-> Ord 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
$ccompare :: UnaryExpressionNotPlusMinus
-> UnaryExpressionNotPlusMinus -> Ordering
compare :: UnaryExpressionNotPlusMinus
-> UnaryExpressionNotPlusMinus -> Ordering
$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
>= :: UnaryExpressionNotPlusMinus -> UnaryExpressionNotPlusMinus -> Bool
$cmax :: UnaryExpressionNotPlusMinus
-> UnaryExpressionNotPlusMinus -> UnaryExpressionNotPlusMinus
max :: UnaryExpressionNotPlusMinus
-> UnaryExpressionNotPlusMinus -> UnaryExpressionNotPlusMinus
$cmin :: UnaryExpressionNotPlusMinus
-> UnaryExpressionNotPlusMinus -> UnaryExpressionNotPlusMinus
min :: UnaryExpressionNotPlusMinus
-> UnaryExpressionNotPlusMinus -> UnaryExpressionNotPlusMinus
Ord, ReadPrec [UnaryExpressionNotPlusMinus]
ReadPrec UnaryExpressionNotPlusMinus
Int -> ReadS UnaryExpressionNotPlusMinus
ReadS [UnaryExpressionNotPlusMinus]
(Int -> ReadS UnaryExpressionNotPlusMinus)
-> ReadS [UnaryExpressionNotPlusMinus]
-> ReadPrec UnaryExpressionNotPlusMinus
-> ReadPrec [UnaryExpressionNotPlusMinus]
-> Read UnaryExpressionNotPlusMinus
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS UnaryExpressionNotPlusMinus
readsPrec :: Int -> ReadS UnaryExpressionNotPlusMinus
$creadList :: ReadS [UnaryExpressionNotPlusMinus]
readList :: ReadS [UnaryExpressionNotPlusMinus]
$creadPrec :: ReadPrec UnaryExpressionNotPlusMinus
readPrec :: ReadPrec UnaryExpressionNotPlusMinus
$creadListPrec :: ReadPrec [UnaryExpressionNotPlusMinus]
readListPrec :: ReadPrec [UnaryExpressionNotPlusMinus]
Read, Int -> UnaryExpressionNotPlusMinus -> String -> String
[UnaryExpressionNotPlusMinus] -> String -> String
UnaryExpressionNotPlusMinus -> String
(Int -> UnaryExpressionNotPlusMinus -> String -> String)
-> (UnaryExpressionNotPlusMinus -> String)
-> ([UnaryExpressionNotPlusMinus] -> String -> String)
-> Show UnaryExpressionNotPlusMinus
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> UnaryExpressionNotPlusMinus -> String -> String
showsPrec :: Int -> UnaryExpressionNotPlusMinus -> String -> String
$cshow :: UnaryExpressionNotPlusMinus -> String
show :: UnaryExpressionNotPlusMinus -> String
$cshowList :: [UnaryExpressionNotPlusMinus] -> String -> String
showList :: [UnaryExpressionNotPlusMinus] -> String -> String
Show)

_UnaryExpressionNotPlusMinus :: Name
_UnaryExpressionNotPlusMinus = (String -> Name
Core.Name String
"hydra/langs/java/syntax.UnaryExpressionNotPlusMinus")

_UnaryExpressionNotPlusMinus_postfix :: Name
_UnaryExpressionNotPlusMinus_postfix = (String -> Name
Core.Name String
"postfix")

_UnaryExpressionNotPlusMinus_tilde :: Name
_UnaryExpressionNotPlusMinus_tilde = (String -> Name
Core.Name String
"tilde")

_UnaryExpressionNotPlusMinus_not :: Name
_UnaryExpressionNotPlusMinus_not = (String -> Name
Core.Name String
"not")

_UnaryExpressionNotPlusMinus_cast :: Name
_UnaryExpressionNotPlusMinus_cast = (String -> Name
Core.Name String
"cast")

data PostfixExpression = 
  PostfixExpressionPrimary Primary |
  PostfixExpressionName ExpressionName |
  PostfixExpressionPostIncrement PostIncrementExpression |
  PostfixExpressionPostDecrement PostDecrementExpression
  deriving (PostfixExpression -> PostfixExpression -> Bool
(PostfixExpression -> PostfixExpression -> Bool)
-> (PostfixExpression -> PostfixExpression -> Bool)
-> Eq PostfixExpression
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PostfixExpression -> PostfixExpression -> Bool
== :: PostfixExpression -> PostfixExpression -> Bool
$c/= :: PostfixExpression -> PostfixExpression -> Bool
/= :: PostfixExpression -> PostfixExpression -> Bool
Eq, Eq PostfixExpression
Eq PostfixExpression =>
(PostfixExpression -> PostfixExpression -> Ordering)
-> (PostfixExpression -> PostfixExpression -> Bool)
-> (PostfixExpression -> PostfixExpression -> Bool)
-> (PostfixExpression -> PostfixExpression -> Bool)
-> (PostfixExpression -> PostfixExpression -> Bool)
-> (PostfixExpression -> PostfixExpression -> PostfixExpression)
-> (PostfixExpression -> PostfixExpression -> PostfixExpression)
-> Ord 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
$ccompare :: PostfixExpression -> PostfixExpression -> Ordering
compare :: PostfixExpression -> PostfixExpression -> Ordering
$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
>= :: PostfixExpression -> PostfixExpression -> Bool
$cmax :: PostfixExpression -> PostfixExpression -> PostfixExpression
max :: PostfixExpression -> PostfixExpression -> PostfixExpression
$cmin :: PostfixExpression -> PostfixExpression -> PostfixExpression
min :: PostfixExpression -> PostfixExpression -> PostfixExpression
Ord, ReadPrec [PostfixExpression]
ReadPrec PostfixExpression
Int -> ReadS PostfixExpression
ReadS [PostfixExpression]
(Int -> ReadS PostfixExpression)
-> ReadS [PostfixExpression]
-> ReadPrec PostfixExpression
-> ReadPrec [PostfixExpression]
-> Read PostfixExpression
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS PostfixExpression
readsPrec :: Int -> ReadS PostfixExpression
$creadList :: ReadS [PostfixExpression]
readList :: ReadS [PostfixExpression]
$creadPrec :: ReadPrec PostfixExpression
readPrec :: ReadPrec PostfixExpression
$creadListPrec :: ReadPrec [PostfixExpression]
readListPrec :: ReadPrec [PostfixExpression]
Read, Int -> PostfixExpression -> String -> String
[PostfixExpression] -> String -> String
PostfixExpression -> String
(Int -> PostfixExpression -> String -> String)
-> (PostfixExpression -> String)
-> ([PostfixExpression] -> String -> String)
-> Show PostfixExpression
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> PostfixExpression -> String -> String
showsPrec :: Int -> PostfixExpression -> String -> String
$cshow :: PostfixExpression -> String
show :: PostfixExpression -> String
$cshowList :: [PostfixExpression] -> String -> String
showList :: [PostfixExpression] -> String -> String
Show)

_PostfixExpression :: Name
_PostfixExpression = (String -> Name
Core.Name String
"hydra/langs/java/syntax.PostfixExpression")

_PostfixExpression_primary :: Name
_PostfixExpression_primary = (String -> Name
Core.Name String
"primary")

_PostfixExpression_name :: Name
_PostfixExpression_name = (String -> Name
Core.Name String
"name")

_PostfixExpression_postIncrement :: Name
_PostfixExpression_postIncrement = (String -> Name
Core.Name String
"postIncrement")

_PostfixExpression_postDecrement :: Name
_PostfixExpression_postDecrement = (String -> Name
Core.Name String
"postDecrement")

newtype PostIncrementExpression = 
  PostIncrementExpression {
    PostIncrementExpression -> PostfixExpression
unPostIncrementExpression :: PostfixExpression}
  deriving (PostIncrementExpression -> PostIncrementExpression -> Bool
(PostIncrementExpression -> PostIncrementExpression -> Bool)
-> (PostIncrementExpression -> PostIncrementExpression -> Bool)
-> Eq PostIncrementExpression
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PostIncrementExpression -> PostIncrementExpression -> Bool
== :: PostIncrementExpression -> PostIncrementExpression -> Bool
$c/= :: PostIncrementExpression -> PostIncrementExpression -> Bool
/= :: PostIncrementExpression -> PostIncrementExpression -> Bool
Eq, Eq PostIncrementExpression
Eq PostIncrementExpression =>
(PostIncrementExpression -> PostIncrementExpression -> Ordering)
-> (PostIncrementExpression -> PostIncrementExpression -> Bool)
-> (PostIncrementExpression -> PostIncrementExpression -> Bool)
-> (PostIncrementExpression -> PostIncrementExpression -> Bool)
-> (PostIncrementExpression -> PostIncrementExpression -> Bool)
-> (PostIncrementExpression
    -> PostIncrementExpression -> PostIncrementExpression)
-> (PostIncrementExpression
    -> PostIncrementExpression -> PostIncrementExpression)
-> Ord 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
$ccompare :: PostIncrementExpression -> PostIncrementExpression -> Ordering
compare :: PostIncrementExpression -> PostIncrementExpression -> Ordering
$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
>= :: PostIncrementExpression -> PostIncrementExpression -> Bool
$cmax :: PostIncrementExpression
-> PostIncrementExpression -> PostIncrementExpression
max :: PostIncrementExpression
-> PostIncrementExpression -> PostIncrementExpression
$cmin :: PostIncrementExpression
-> PostIncrementExpression -> PostIncrementExpression
min :: PostIncrementExpression
-> PostIncrementExpression -> PostIncrementExpression
Ord, ReadPrec [PostIncrementExpression]
ReadPrec PostIncrementExpression
Int -> ReadS PostIncrementExpression
ReadS [PostIncrementExpression]
(Int -> ReadS PostIncrementExpression)
-> ReadS [PostIncrementExpression]
-> ReadPrec PostIncrementExpression
-> ReadPrec [PostIncrementExpression]
-> Read PostIncrementExpression
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS PostIncrementExpression
readsPrec :: Int -> ReadS PostIncrementExpression
$creadList :: ReadS [PostIncrementExpression]
readList :: ReadS [PostIncrementExpression]
$creadPrec :: ReadPrec PostIncrementExpression
readPrec :: ReadPrec PostIncrementExpression
$creadListPrec :: ReadPrec [PostIncrementExpression]
readListPrec :: ReadPrec [PostIncrementExpression]
Read, Int -> PostIncrementExpression -> String -> String
[PostIncrementExpression] -> String -> String
PostIncrementExpression -> String
(Int -> PostIncrementExpression -> String -> String)
-> (PostIncrementExpression -> String)
-> ([PostIncrementExpression] -> String -> String)
-> Show PostIncrementExpression
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> PostIncrementExpression -> String -> String
showsPrec :: Int -> PostIncrementExpression -> String -> String
$cshow :: PostIncrementExpression -> String
show :: PostIncrementExpression -> String
$cshowList :: [PostIncrementExpression] -> String -> String
showList :: [PostIncrementExpression] -> String -> String
Show)

_PostIncrementExpression :: Name
_PostIncrementExpression = (String -> Name
Core.Name String
"hydra/langs/java/syntax.PostIncrementExpression")

newtype PostDecrementExpression = 
  PostDecrementExpression {
    PostDecrementExpression -> PostfixExpression
unPostDecrementExpression :: PostfixExpression}
  deriving (PostDecrementExpression -> PostDecrementExpression -> Bool
(PostDecrementExpression -> PostDecrementExpression -> Bool)
-> (PostDecrementExpression -> PostDecrementExpression -> Bool)
-> Eq PostDecrementExpression
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PostDecrementExpression -> PostDecrementExpression -> Bool
== :: PostDecrementExpression -> PostDecrementExpression -> Bool
$c/= :: PostDecrementExpression -> PostDecrementExpression -> Bool
/= :: PostDecrementExpression -> PostDecrementExpression -> Bool
Eq, Eq PostDecrementExpression
Eq PostDecrementExpression =>
(PostDecrementExpression -> PostDecrementExpression -> Ordering)
-> (PostDecrementExpression -> PostDecrementExpression -> Bool)
-> (PostDecrementExpression -> PostDecrementExpression -> Bool)
-> (PostDecrementExpression -> PostDecrementExpression -> Bool)
-> (PostDecrementExpression -> PostDecrementExpression -> Bool)
-> (PostDecrementExpression
    -> PostDecrementExpression -> PostDecrementExpression)
-> (PostDecrementExpression
    -> PostDecrementExpression -> PostDecrementExpression)
-> Ord 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
$ccompare :: PostDecrementExpression -> PostDecrementExpression -> Ordering
compare :: PostDecrementExpression -> PostDecrementExpression -> Ordering
$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
>= :: PostDecrementExpression -> PostDecrementExpression -> Bool
$cmax :: PostDecrementExpression
-> PostDecrementExpression -> PostDecrementExpression
max :: PostDecrementExpression
-> PostDecrementExpression -> PostDecrementExpression
$cmin :: PostDecrementExpression
-> PostDecrementExpression -> PostDecrementExpression
min :: PostDecrementExpression
-> PostDecrementExpression -> PostDecrementExpression
Ord, ReadPrec [PostDecrementExpression]
ReadPrec PostDecrementExpression
Int -> ReadS PostDecrementExpression
ReadS [PostDecrementExpression]
(Int -> ReadS PostDecrementExpression)
-> ReadS [PostDecrementExpression]
-> ReadPrec PostDecrementExpression
-> ReadPrec [PostDecrementExpression]
-> Read PostDecrementExpression
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS PostDecrementExpression
readsPrec :: Int -> ReadS PostDecrementExpression
$creadList :: ReadS [PostDecrementExpression]
readList :: ReadS [PostDecrementExpression]
$creadPrec :: ReadPrec PostDecrementExpression
readPrec :: ReadPrec PostDecrementExpression
$creadListPrec :: ReadPrec [PostDecrementExpression]
readListPrec :: ReadPrec [PostDecrementExpression]
Read, Int -> PostDecrementExpression -> String -> String
[PostDecrementExpression] -> String -> String
PostDecrementExpression -> String
(Int -> PostDecrementExpression -> String -> String)
-> (PostDecrementExpression -> String)
-> ([PostDecrementExpression] -> String -> String)
-> Show PostDecrementExpression
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> PostDecrementExpression -> String -> String
showsPrec :: Int -> PostDecrementExpression -> String -> String
$cshow :: PostDecrementExpression -> String
show :: PostDecrementExpression -> String
$cshowList :: [PostDecrementExpression] -> String -> String
showList :: [PostDecrementExpression] -> String -> String
Show)

_PostDecrementExpression :: Name
_PostDecrementExpression = (String -> Name
Core.Name String
"hydra/langs/java/syntax.PostDecrementExpression")

data CastExpression = 
  CastExpressionPrimitive CastExpression_Primitive |
  CastExpressionNotPlusMinus CastExpression_NotPlusMinus |
  CastExpressionLambda CastExpression_Lambda
  deriving (CastExpression -> CastExpression -> Bool
(CastExpression -> CastExpression -> Bool)
-> (CastExpression -> CastExpression -> Bool) -> Eq CastExpression
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CastExpression -> CastExpression -> Bool
== :: CastExpression -> CastExpression -> Bool
$c/= :: CastExpression -> CastExpression -> Bool
/= :: CastExpression -> CastExpression -> Bool
Eq, Eq CastExpression
Eq CastExpression =>
(CastExpression -> CastExpression -> Ordering)
-> (CastExpression -> CastExpression -> Bool)
-> (CastExpression -> CastExpression -> Bool)
-> (CastExpression -> CastExpression -> Bool)
-> (CastExpression -> CastExpression -> Bool)
-> (CastExpression -> CastExpression -> CastExpression)
-> (CastExpression -> CastExpression -> CastExpression)
-> Ord 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
$ccompare :: CastExpression -> CastExpression -> Ordering
compare :: CastExpression -> CastExpression -> Ordering
$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
>= :: CastExpression -> CastExpression -> Bool
$cmax :: CastExpression -> CastExpression -> CastExpression
max :: CastExpression -> CastExpression -> CastExpression
$cmin :: CastExpression -> CastExpression -> CastExpression
min :: CastExpression -> CastExpression -> CastExpression
Ord, ReadPrec [CastExpression]
ReadPrec CastExpression
Int -> ReadS CastExpression
ReadS [CastExpression]
(Int -> ReadS CastExpression)
-> ReadS [CastExpression]
-> ReadPrec CastExpression
-> ReadPrec [CastExpression]
-> Read CastExpression
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS CastExpression
readsPrec :: Int -> ReadS CastExpression
$creadList :: ReadS [CastExpression]
readList :: ReadS [CastExpression]
$creadPrec :: ReadPrec CastExpression
readPrec :: ReadPrec CastExpression
$creadListPrec :: ReadPrec [CastExpression]
readListPrec :: ReadPrec [CastExpression]
Read, Int -> CastExpression -> String -> String
[CastExpression] -> String -> String
CastExpression -> String
(Int -> CastExpression -> String -> String)
-> (CastExpression -> String)
-> ([CastExpression] -> String -> String)
-> Show CastExpression
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> CastExpression -> String -> String
showsPrec :: Int -> CastExpression -> String -> String
$cshow :: CastExpression -> String
show :: CastExpression -> String
$cshowList :: [CastExpression] -> String -> String
showList :: [CastExpression] -> String -> String
Show)

_CastExpression :: Name
_CastExpression = (String -> Name
Core.Name String
"hydra/langs/java/syntax.CastExpression")

_CastExpression_primitive :: Name
_CastExpression_primitive = (String -> Name
Core.Name String
"primitive")

_CastExpression_notPlusMinus :: Name
_CastExpression_notPlusMinus = (String -> Name
Core.Name String
"notPlusMinus")

_CastExpression_lambda :: Name
_CastExpression_lambda = (String -> Name
Core.Name 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
(CastExpression_Primitive -> CastExpression_Primitive -> Bool)
-> (CastExpression_Primitive -> CastExpression_Primitive -> Bool)
-> Eq CastExpression_Primitive
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CastExpression_Primitive -> CastExpression_Primitive -> Bool
== :: CastExpression_Primitive -> CastExpression_Primitive -> Bool
$c/= :: CastExpression_Primitive -> CastExpression_Primitive -> Bool
/= :: CastExpression_Primitive -> CastExpression_Primitive -> Bool
Eq, Eq CastExpression_Primitive
Eq CastExpression_Primitive =>
(CastExpression_Primitive -> CastExpression_Primitive -> Ordering)
-> (CastExpression_Primitive -> CastExpression_Primitive -> Bool)
-> (CastExpression_Primitive -> CastExpression_Primitive -> Bool)
-> (CastExpression_Primitive -> CastExpression_Primitive -> Bool)
-> (CastExpression_Primitive -> CastExpression_Primitive -> Bool)
-> (CastExpression_Primitive
    -> CastExpression_Primitive -> CastExpression_Primitive)
-> (CastExpression_Primitive
    -> CastExpression_Primitive -> CastExpression_Primitive)
-> Ord 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
$ccompare :: CastExpression_Primitive -> CastExpression_Primitive -> Ordering
compare :: CastExpression_Primitive -> CastExpression_Primitive -> Ordering
$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
>= :: CastExpression_Primitive -> CastExpression_Primitive -> Bool
$cmax :: CastExpression_Primitive
-> CastExpression_Primitive -> CastExpression_Primitive
max :: CastExpression_Primitive
-> CastExpression_Primitive -> CastExpression_Primitive
$cmin :: CastExpression_Primitive
-> CastExpression_Primitive -> CastExpression_Primitive
min :: CastExpression_Primitive
-> CastExpression_Primitive -> CastExpression_Primitive
Ord, ReadPrec [CastExpression_Primitive]
ReadPrec CastExpression_Primitive
Int -> ReadS CastExpression_Primitive
ReadS [CastExpression_Primitive]
(Int -> ReadS CastExpression_Primitive)
-> ReadS [CastExpression_Primitive]
-> ReadPrec CastExpression_Primitive
-> ReadPrec [CastExpression_Primitive]
-> Read CastExpression_Primitive
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS CastExpression_Primitive
readsPrec :: Int -> ReadS CastExpression_Primitive
$creadList :: ReadS [CastExpression_Primitive]
readList :: ReadS [CastExpression_Primitive]
$creadPrec :: ReadPrec CastExpression_Primitive
readPrec :: ReadPrec CastExpression_Primitive
$creadListPrec :: ReadPrec [CastExpression_Primitive]
readListPrec :: ReadPrec [CastExpression_Primitive]
Read, Int -> CastExpression_Primitive -> String -> String
[CastExpression_Primitive] -> String -> String
CastExpression_Primitive -> String
(Int -> CastExpression_Primitive -> String -> String)
-> (CastExpression_Primitive -> String)
-> ([CastExpression_Primitive] -> String -> String)
-> Show CastExpression_Primitive
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> CastExpression_Primitive -> String -> String
showsPrec :: Int -> CastExpression_Primitive -> String -> String
$cshow :: CastExpression_Primitive -> String
show :: CastExpression_Primitive -> String
$cshowList :: [CastExpression_Primitive] -> String -> String
showList :: [CastExpression_Primitive] -> String -> String
Show)

_CastExpression_Primitive :: Name
_CastExpression_Primitive = (String -> Name
Core.Name String
"hydra/langs/java/syntax.CastExpression.Primitive")

_CastExpression_Primitive_type :: Name
_CastExpression_Primitive_type = (String -> Name
Core.Name String
"type")

_CastExpression_Primitive_expression :: Name
_CastExpression_Primitive_expression = (String -> Name
Core.Name 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
(CastExpression_NotPlusMinus
 -> CastExpression_NotPlusMinus -> Bool)
-> (CastExpression_NotPlusMinus
    -> CastExpression_NotPlusMinus -> Bool)
-> Eq CastExpression_NotPlusMinus
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CastExpression_NotPlusMinus -> CastExpression_NotPlusMinus -> Bool
== :: CastExpression_NotPlusMinus -> CastExpression_NotPlusMinus -> Bool
$c/= :: CastExpression_NotPlusMinus -> CastExpression_NotPlusMinus -> Bool
/= :: CastExpression_NotPlusMinus -> CastExpression_NotPlusMinus -> Bool
Eq, Eq CastExpression_NotPlusMinus
Eq CastExpression_NotPlusMinus =>
(CastExpression_NotPlusMinus
 -> CastExpression_NotPlusMinus -> Ordering)
-> (CastExpression_NotPlusMinus
    -> CastExpression_NotPlusMinus -> Bool)
-> (CastExpression_NotPlusMinus
    -> CastExpression_NotPlusMinus -> Bool)
-> (CastExpression_NotPlusMinus
    -> CastExpression_NotPlusMinus -> Bool)
-> (CastExpression_NotPlusMinus
    -> CastExpression_NotPlusMinus -> Bool)
-> (CastExpression_NotPlusMinus
    -> CastExpression_NotPlusMinus -> CastExpression_NotPlusMinus)
-> (CastExpression_NotPlusMinus
    -> CastExpression_NotPlusMinus -> CastExpression_NotPlusMinus)
-> Ord 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
$ccompare :: CastExpression_NotPlusMinus
-> CastExpression_NotPlusMinus -> Ordering
compare :: CastExpression_NotPlusMinus
-> CastExpression_NotPlusMinus -> Ordering
$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
>= :: CastExpression_NotPlusMinus -> CastExpression_NotPlusMinus -> Bool
$cmax :: CastExpression_NotPlusMinus
-> CastExpression_NotPlusMinus -> CastExpression_NotPlusMinus
max :: CastExpression_NotPlusMinus
-> CastExpression_NotPlusMinus -> CastExpression_NotPlusMinus
$cmin :: CastExpression_NotPlusMinus
-> CastExpression_NotPlusMinus -> CastExpression_NotPlusMinus
min :: CastExpression_NotPlusMinus
-> CastExpression_NotPlusMinus -> CastExpression_NotPlusMinus
Ord, ReadPrec [CastExpression_NotPlusMinus]
ReadPrec CastExpression_NotPlusMinus
Int -> ReadS CastExpression_NotPlusMinus
ReadS [CastExpression_NotPlusMinus]
(Int -> ReadS CastExpression_NotPlusMinus)
-> ReadS [CastExpression_NotPlusMinus]
-> ReadPrec CastExpression_NotPlusMinus
-> ReadPrec [CastExpression_NotPlusMinus]
-> Read CastExpression_NotPlusMinus
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS CastExpression_NotPlusMinus
readsPrec :: Int -> ReadS CastExpression_NotPlusMinus
$creadList :: ReadS [CastExpression_NotPlusMinus]
readList :: ReadS [CastExpression_NotPlusMinus]
$creadPrec :: ReadPrec CastExpression_NotPlusMinus
readPrec :: ReadPrec CastExpression_NotPlusMinus
$creadListPrec :: ReadPrec [CastExpression_NotPlusMinus]
readListPrec :: ReadPrec [CastExpression_NotPlusMinus]
Read, Int -> CastExpression_NotPlusMinus -> String -> String
[CastExpression_NotPlusMinus] -> String -> String
CastExpression_NotPlusMinus -> String
(Int -> CastExpression_NotPlusMinus -> String -> String)
-> (CastExpression_NotPlusMinus -> String)
-> ([CastExpression_NotPlusMinus] -> String -> String)
-> Show CastExpression_NotPlusMinus
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> CastExpression_NotPlusMinus -> String -> String
showsPrec :: Int -> CastExpression_NotPlusMinus -> String -> String
$cshow :: CastExpression_NotPlusMinus -> String
show :: CastExpression_NotPlusMinus -> String
$cshowList :: [CastExpression_NotPlusMinus] -> String -> String
showList :: [CastExpression_NotPlusMinus] -> String -> String
Show)

_CastExpression_NotPlusMinus :: Name
_CastExpression_NotPlusMinus = (String -> Name
Core.Name String
"hydra/langs/java/syntax.CastExpression.NotPlusMinus")

_CastExpression_NotPlusMinus_refAndBounds :: Name
_CastExpression_NotPlusMinus_refAndBounds = (String -> Name
Core.Name String
"refAndBounds")

_CastExpression_NotPlusMinus_expression :: Name
_CastExpression_NotPlusMinus_expression = (String -> Name
Core.Name 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
(CastExpression_Lambda -> CastExpression_Lambda -> Bool)
-> (CastExpression_Lambda -> CastExpression_Lambda -> Bool)
-> Eq CastExpression_Lambda
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CastExpression_Lambda -> CastExpression_Lambda -> Bool
== :: CastExpression_Lambda -> CastExpression_Lambda -> Bool
$c/= :: CastExpression_Lambda -> CastExpression_Lambda -> Bool
/= :: CastExpression_Lambda -> CastExpression_Lambda -> Bool
Eq, Eq CastExpression_Lambda
Eq CastExpression_Lambda =>
(CastExpression_Lambda -> CastExpression_Lambda -> Ordering)
-> (CastExpression_Lambda -> CastExpression_Lambda -> Bool)
-> (CastExpression_Lambda -> CastExpression_Lambda -> Bool)
-> (CastExpression_Lambda -> CastExpression_Lambda -> Bool)
-> (CastExpression_Lambda -> CastExpression_Lambda -> Bool)
-> (CastExpression_Lambda
    -> CastExpression_Lambda -> CastExpression_Lambda)
-> (CastExpression_Lambda
    -> CastExpression_Lambda -> CastExpression_Lambda)
-> Ord 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
$ccompare :: CastExpression_Lambda -> CastExpression_Lambda -> Ordering
compare :: CastExpression_Lambda -> CastExpression_Lambda -> Ordering
$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
>= :: CastExpression_Lambda -> CastExpression_Lambda -> Bool
$cmax :: CastExpression_Lambda
-> CastExpression_Lambda -> CastExpression_Lambda
max :: CastExpression_Lambda
-> CastExpression_Lambda -> CastExpression_Lambda
$cmin :: CastExpression_Lambda
-> CastExpression_Lambda -> CastExpression_Lambda
min :: CastExpression_Lambda
-> CastExpression_Lambda -> CastExpression_Lambda
Ord, ReadPrec [CastExpression_Lambda]
ReadPrec CastExpression_Lambda
Int -> ReadS CastExpression_Lambda
ReadS [CastExpression_Lambda]
(Int -> ReadS CastExpression_Lambda)
-> ReadS [CastExpression_Lambda]
-> ReadPrec CastExpression_Lambda
-> ReadPrec [CastExpression_Lambda]
-> Read CastExpression_Lambda
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS CastExpression_Lambda
readsPrec :: Int -> ReadS CastExpression_Lambda
$creadList :: ReadS [CastExpression_Lambda]
readList :: ReadS [CastExpression_Lambda]
$creadPrec :: ReadPrec CastExpression_Lambda
readPrec :: ReadPrec CastExpression_Lambda
$creadListPrec :: ReadPrec [CastExpression_Lambda]
readListPrec :: ReadPrec [CastExpression_Lambda]
Read, Int -> CastExpression_Lambda -> String -> String
[CastExpression_Lambda] -> String -> String
CastExpression_Lambda -> String
(Int -> CastExpression_Lambda -> String -> String)
-> (CastExpression_Lambda -> String)
-> ([CastExpression_Lambda] -> String -> String)
-> Show CastExpression_Lambda
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> CastExpression_Lambda -> String -> String
showsPrec :: Int -> CastExpression_Lambda -> String -> String
$cshow :: CastExpression_Lambda -> String
show :: CastExpression_Lambda -> String
$cshowList :: [CastExpression_Lambda] -> String -> String
showList :: [CastExpression_Lambda] -> String -> String
Show)

_CastExpression_Lambda :: Name
_CastExpression_Lambda = (String -> Name
Core.Name String
"hydra/langs/java/syntax.CastExpression.Lambda")

_CastExpression_Lambda_refAndBounds :: Name
_CastExpression_Lambda_refAndBounds = (String -> Name
Core.Name String
"refAndBounds")

_CastExpression_Lambda_expression :: Name
_CastExpression_Lambda_expression = (String -> Name
Core.Name 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
(CastExpression_RefAndBounds
 -> CastExpression_RefAndBounds -> Bool)
-> (CastExpression_RefAndBounds
    -> CastExpression_RefAndBounds -> Bool)
-> Eq CastExpression_RefAndBounds
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CastExpression_RefAndBounds -> CastExpression_RefAndBounds -> Bool
== :: CastExpression_RefAndBounds -> CastExpression_RefAndBounds -> Bool
$c/= :: CastExpression_RefAndBounds -> CastExpression_RefAndBounds -> Bool
/= :: CastExpression_RefAndBounds -> CastExpression_RefAndBounds -> Bool
Eq, Eq CastExpression_RefAndBounds
Eq CastExpression_RefAndBounds =>
(CastExpression_RefAndBounds
 -> CastExpression_RefAndBounds -> Ordering)
-> (CastExpression_RefAndBounds
    -> CastExpression_RefAndBounds -> Bool)
-> (CastExpression_RefAndBounds
    -> CastExpression_RefAndBounds -> Bool)
-> (CastExpression_RefAndBounds
    -> CastExpression_RefAndBounds -> Bool)
-> (CastExpression_RefAndBounds
    -> CastExpression_RefAndBounds -> Bool)
-> (CastExpression_RefAndBounds
    -> CastExpression_RefAndBounds -> CastExpression_RefAndBounds)
-> (CastExpression_RefAndBounds
    -> CastExpression_RefAndBounds -> CastExpression_RefAndBounds)
-> Ord 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
$ccompare :: CastExpression_RefAndBounds
-> CastExpression_RefAndBounds -> Ordering
compare :: CastExpression_RefAndBounds
-> CastExpression_RefAndBounds -> Ordering
$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
>= :: CastExpression_RefAndBounds -> CastExpression_RefAndBounds -> Bool
$cmax :: CastExpression_RefAndBounds
-> CastExpression_RefAndBounds -> CastExpression_RefAndBounds
max :: CastExpression_RefAndBounds
-> CastExpression_RefAndBounds -> CastExpression_RefAndBounds
$cmin :: CastExpression_RefAndBounds
-> CastExpression_RefAndBounds -> CastExpression_RefAndBounds
min :: CastExpression_RefAndBounds
-> CastExpression_RefAndBounds -> CastExpression_RefAndBounds
Ord, ReadPrec [CastExpression_RefAndBounds]
ReadPrec CastExpression_RefAndBounds
Int -> ReadS CastExpression_RefAndBounds
ReadS [CastExpression_RefAndBounds]
(Int -> ReadS CastExpression_RefAndBounds)
-> ReadS [CastExpression_RefAndBounds]
-> ReadPrec CastExpression_RefAndBounds
-> ReadPrec [CastExpression_RefAndBounds]
-> Read CastExpression_RefAndBounds
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS CastExpression_RefAndBounds
readsPrec :: Int -> ReadS CastExpression_RefAndBounds
$creadList :: ReadS [CastExpression_RefAndBounds]
readList :: ReadS [CastExpression_RefAndBounds]
$creadPrec :: ReadPrec CastExpression_RefAndBounds
readPrec :: ReadPrec CastExpression_RefAndBounds
$creadListPrec :: ReadPrec [CastExpression_RefAndBounds]
readListPrec :: ReadPrec [CastExpression_RefAndBounds]
Read, Int -> CastExpression_RefAndBounds -> String -> String
[CastExpression_RefAndBounds] -> String -> String
CastExpression_RefAndBounds -> String
(Int -> CastExpression_RefAndBounds -> String -> String)
-> (CastExpression_RefAndBounds -> String)
-> ([CastExpression_RefAndBounds] -> String -> String)
-> Show CastExpression_RefAndBounds
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> CastExpression_RefAndBounds -> String -> String
showsPrec :: Int -> CastExpression_RefAndBounds -> String -> String
$cshow :: CastExpression_RefAndBounds -> String
show :: CastExpression_RefAndBounds -> String
$cshowList :: [CastExpression_RefAndBounds] -> String -> String
showList :: [CastExpression_RefAndBounds] -> String -> String
Show)

_CastExpression_RefAndBounds :: Name
_CastExpression_RefAndBounds = (String -> Name
Core.Name String
"hydra/langs/java/syntax.CastExpression.RefAndBounds")

_CastExpression_RefAndBounds_type :: Name
_CastExpression_RefAndBounds_type = (String -> Name
Core.Name String
"type")

_CastExpression_RefAndBounds_bounds :: Name
_CastExpression_RefAndBounds_bounds = (String -> Name
Core.Name String
"bounds")

newtype ConstantExpression = 
  ConstantExpression {
    ConstantExpression -> Expression
unConstantExpression :: Expression}
  deriving (ConstantExpression -> ConstantExpression -> Bool
(ConstantExpression -> ConstantExpression -> Bool)
-> (ConstantExpression -> ConstantExpression -> Bool)
-> Eq ConstantExpression
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ConstantExpression -> ConstantExpression -> Bool
== :: ConstantExpression -> ConstantExpression -> Bool
$c/= :: ConstantExpression -> ConstantExpression -> Bool
/= :: ConstantExpression -> ConstantExpression -> Bool
Eq, Eq ConstantExpression
Eq ConstantExpression =>
(ConstantExpression -> ConstantExpression -> Ordering)
-> (ConstantExpression -> ConstantExpression -> Bool)
-> (ConstantExpression -> ConstantExpression -> Bool)
-> (ConstantExpression -> ConstantExpression -> Bool)
-> (ConstantExpression -> ConstantExpression -> Bool)
-> (ConstantExpression -> ConstantExpression -> ConstantExpression)
-> (ConstantExpression -> ConstantExpression -> ConstantExpression)
-> Ord 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
$ccompare :: ConstantExpression -> ConstantExpression -> Ordering
compare :: ConstantExpression -> ConstantExpression -> Ordering
$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
>= :: ConstantExpression -> ConstantExpression -> Bool
$cmax :: ConstantExpression -> ConstantExpression -> ConstantExpression
max :: ConstantExpression -> ConstantExpression -> ConstantExpression
$cmin :: ConstantExpression -> ConstantExpression -> ConstantExpression
min :: ConstantExpression -> ConstantExpression -> ConstantExpression
Ord, ReadPrec [ConstantExpression]
ReadPrec ConstantExpression
Int -> ReadS ConstantExpression
ReadS [ConstantExpression]
(Int -> ReadS ConstantExpression)
-> ReadS [ConstantExpression]
-> ReadPrec ConstantExpression
-> ReadPrec [ConstantExpression]
-> Read ConstantExpression
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ConstantExpression
readsPrec :: Int -> ReadS ConstantExpression
$creadList :: ReadS [ConstantExpression]
readList :: ReadS [ConstantExpression]
$creadPrec :: ReadPrec ConstantExpression
readPrec :: ReadPrec ConstantExpression
$creadListPrec :: ReadPrec [ConstantExpression]
readListPrec :: ReadPrec [ConstantExpression]
Read, Int -> ConstantExpression -> String -> String
[ConstantExpression] -> String -> String
ConstantExpression -> String
(Int -> ConstantExpression -> String -> String)
-> (ConstantExpression -> String)
-> ([ConstantExpression] -> String -> String)
-> Show ConstantExpression
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> ConstantExpression -> String -> String
showsPrec :: Int -> ConstantExpression -> String -> String
$cshow :: ConstantExpression -> String
show :: ConstantExpression -> String
$cshowList :: [ConstantExpression] -> String -> String
showList :: [ConstantExpression] -> String -> String
Show)

_ConstantExpression :: Name
_ConstantExpression = (String -> Name
Core.Name String
"hydra/langs/java/syntax.ConstantExpression")