-- | A Scala syntax model based on Scalameta (https://scalameta.org)

module Hydra.Ext.Scala.Meta where

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

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

_PredefString :: Name
_PredefString = (String -> Name
Core.Name String
"hydra/ext/scala/meta.PredefString")

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

_ScalaSymbol :: Name
_ScalaSymbol = (String -> Name
Core.Name String
"hydra/ext/scala/meta.ScalaSymbol")

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

data Tree = 
  TreeRef Ref |
  TreeStat Stat |
  TreeType Type |
  TreeBounds Type_Bounds |
  TreePat Pat |
  TreeMember Member |
  TreeCtor Ctor |
  TreeTemplate Template |
  TreeMod Mod |
  TreeEnumerator Enumerator |
  TreeImporter Importer |
  TreeImportee Importee |
  TreeCaseTree CaseTree |
  TreeSource Source |
  TreeQuasi Quasi
  deriving (Tree -> Tree -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Tree -> Tree -> Bool
$c/= :: Tree -> Tree -> Bool
== :: Tree -> Tree -> Bool
$c== :: Tree -> Tree -> Bool
Eq, Eq Tree
Tree -> Tree -> Bool
Tree -> Tree -> Ordering
Tree -> Tree -> Tree
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Tree -> Tree -> Tree
$cmin :: Tree -> Tree -> Tree
max :: Tree -> Tree -> Tree
$cmax :: Tree -> Tree -> Tree
>= :: Tree -> Tree -> Bool
$c>= :: Tree -> Tree -> Bool
> :: Tree -> Tree -> Bool
$c> :: Tree -> Tree -> Bool
<= :: Tree -> Tree -> Bool
$c<= :: Tree -> Tree -> Bool
< :: Tree -> Tree -> Bool
$c< :: Tree -> Tree -> Bool
compare :: Tree -> Tree -> Ordering
$ccompare :: Tree -> Tree -> Ordering
Ord, ReadPrec [Tree]
ReadPrec Tree
Int -> ReadS Tree
ReadS [Tree]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Tree]
$creadListPrec :: ReadPrec [Tree]
readPrec :: ReadPrec Tree
$creadPrec :: ReadPrec Tree
readList :: ReadS [Tree]
$creadList :: ReadS [Tree]
readsPrec :: Int -> ReadS Tree
$creadsPrec :: Int -> ReadS Tree
Read, Int -> Tree -> String -> String
[Tree] -> String -> String
Tree -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [Tree] -> String -> String
$cshowList :: [Tree] -> String -> String
show :: Tree -> String
$cshow :: Tree -> String
showsPrec :: Int -> Tree -> String -> String
$cshowsPrec :: Int -> Tree -> String -> String
Show)

_Tree :: Name
_Tree = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Tree")

_Tree_ref :: FieldName
_Tree_ref = (String -> FieldName
Core.FieldName String
"ref")

_Tree_stat :: FieldName
_Tree_stat = (String -> FieldName
Core.FieldName String
"stat")

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

_Tree_bounds :: FieldName
_Tree_bounds = (String -> FieldName
Core.FieldName String
"bounds")

_Tree_pat :: FieldName
_Tree_pat = (String -> FieldName
Core.FieldName String
"pat")

_Tree_member :: FieldName
_Tree_member = (String -> FieldName
Core.FieldName String
"member")

_Tree_ctor :: FieldName
_Tree_ctor = (String -> FieldName
Core.FieldName String
"ctor")

_Tree_template :: FieldName
_Tree_template = (String -> FieldName
Core.FieldName String
"template")

_Tree_mod :: FieldName
_Tree_mod = (String -> FieldName
Core.FieldName String
"mod")

_Tree_enumerator :: FieldName
_Tree_enumerator = (String -> FieldName
Core.FieldName String
"enumerator")

_Tree_importer :: FieldName
_Tree_importer = (String -> FieldName
Core.FieldName String
"importer")

_Tree_importee :: FieldName
_Tree_importee = (String -> FieldName
Core.FieldName String
"importee")

_Tree_caseTree :: FieldName
_Tree_caseTree = (String -> FieldName
Core.FieldName String
"caseTree")

_Tree_source :: FieldName
_Tree_source = (String -> FieldName
Core.FieldName String
"source")

_Tree_quasi :: FieldName
_Tree_quasi = (String -> FieldName
Core.FieldName String
"quasi")

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

_Ref :: Name
_Ref = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Ref")

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

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

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

_Stat :: Name
_Stat = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Stat")

_Stat_term :: FieldName
_Stat_term = (String -> FieldName
Core.FieldName String
"term")

_Stat_decl :: FieldName
_Stat_decl = (String -> FieldName
Core.FieldName String
"decl")

_Stat_defn :: FieldName
_Stat_defn = (String -> FieldName
Core.FieldName String
"defn")

_Stat_importExport :: FieldName
_Stat_importExport = (String -> FieldName
Core.FieldName String
"importExport")

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

_Name :: Name
_Name = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Name")

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

_Name_anonymous :: FieldName
_Name_anonymous = (String -> FieldName
Core.FieldName String
"anonymous")

_Name_indeterminate :: FieldName
_Name_indeterminate = (String -> FieldName
Core.FieldName String
"indeterminate")

data Lit = 
  LitNull  |
  LitInt Int |
  LitDouble Double |
  LitFloat Float |
  LitByte Int |
  LitShort Int |
  LitChar Int |
  LitLong Integer |
  LitBoolean Bool |
  LitUnit  |
  LitString String |
  LitSymbol ScalaSymbol
  deriving (Lit -> Lit -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Lit -> Lit -> Bool
$c/= :: Lit -> Lit -> Bool
== :: Lit -> Lit -> Bool
$c== :: Lit -> Lit -> Bool
Eq, Eq Lit
Lit -> Lit -> Bool
Lit -> Lit -> Ordering
Lit -> Lit -> Lit
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Lit -> Lit -> Lit
$cmin :: Lit -> Lit -> Lit
max :: Lit -> Lit -> Lit
$cmax :: Lit -> Lit -> Lit
>= :: Lit -> Lit -> Bool
$c>= :: Lit -> Lit -> Bool
> :: Lit -> Lit -> Bool
$c> :: Lit -> Lit -> Bool
<= :: Lit -> Lit -> Bool
$c<= :: Lit -> Lit -> Bool
< :: Lit -> Lit -> Bool
$c< :: Lit -> Lit -> Bool
compare :: Lit -> Lit -> Ordering
$ccompare :: Lit -> Lit -> Ordering
Ord, ReadPrec [Lit]
ReadPrec Lit
Int -> ReadS Lit
ReadS [Lit]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Lit]
$creadListPrec :: ReadPrec [Lit]
readPrec :: ReadPrec Lit
$creadPrec :: ReadPrec Lit
readList :: ReadS [Lit]
$creadList :: ReadS [Lit]
readsPrec :: Int -> ReadS Lit
$creadsPrec :: Int -> ReadS Lit
Read, Int -> Lit -> String -> String
[Lit] -> String -> String
Lit -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [Lit] -> String -> String
$cshowList :: [Lit] -> String -> String
show :: Lit -> String
$cshow :: Lit -> String
showsPrec :: Int -> Lit -> String -> String
$cshowsPrec :: Int -> Lit -> String -> String
Show)

_Lit :: Name
_Lit = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Lit")

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

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

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

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

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

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

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

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

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

_Lit_unit :: FieldName
_Lit_unit = (String -> FieldName
Core.FieldName String
"unit")

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

_Lit_symbol :: FieldName
_Lit_symbol = (String -> FieldName
Core.FieldName String
"symbol")

data Data = 
  DataLit Lit |
  DataRef Data_Ref |
  DataInterpolate Data_Interpolate |
  DataXml Data_Xml |
  DataApply Data_Apply |
  DataApplyUsing Data_ApplyUsing |
  DataApplyType Data_ApplyType |
  DataAssign Data_Assign |
  DataReturn Data_Return |
  DataThrow Data_Throw |
  DataAscribe Data_Ascribe |
  DataAnnotate Data_Annotate |
  DataTuple Data_Tuple |
  DataBlock Data_Block |
  DataEndMarker Data_EndMarker |
  DataIf Data_If |
  DataQuotedMacroExpr Data_QuotedMacroExpr |
  DataQuotedMacroType Data_QuotedMacroType |
  DataSplicedMacroExpr Data_SplicedMacroExpr |
  DataMatch Data_Match |
  DataTry Data_Try |
  DataTryWithHandler Data_TryWithHandler |
  DataFunctionData Data_FunctionData |
  DataPolyFunction Data_PolyFunction |
  DataPartialFunction Data_PartialFunction |
  DataWhile Data_While |
  DataDo Data_Do |
  DataFor Data_For |
  DataForYield Data_ForYield |
  DataNew Data_New |
  DataNewAnonymous Data_NewAnonymous |
  DataPlaceholder Data_Placeholder |
  DataEta Data_Eta |
  DataRepeated Data_Repeated |
  DataParam Data_Param
  deriving (Data -> Data -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Data -> Data -> Bool
$c/= :: Data -> Data -> Bool
== :: Data -> Data -> Bool
$c== :: Data -> Data -> Bool
Eq, Eq Data
Data -> Data -> Bool
Data -> Data -> Ordering
Data -> Data -> Data
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Data -> Data -> Data
$cmin :: Data -> Data -> Data
max :: Data -> Data -> Data
$cmax :: Data -> Data -> Data
>= :: Data -> Data -> Bool
$c>= :: Data -> Data -> Bool
> :: Data -> Data -> Bool
$c> :: Data -> Data -> Bool
<= :: Data -> Data -> Bool
$c<= :: Data -> Data -> Bool
< :: Data -> Data -> Bool
$c< :: Data -> Data -> Bool
compare :: Data -> Data -> Ordering
$ccompare :: Data -> Data -> Ordering
Ord, ReadPrec [Data]
ReadPrec Data
Int -> ReadS Data
ReadS [Data]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Data]
$creadListPrec :: ReadPrec [Data]
readPrec :: ReadPrec Data
$creadPrec :: ReadPrec Data
readList :: ReadS [Data]
$creadList :: ReadS [Data]
readsPrec :: Int -> ReadS Data
$creadsPrec :: Int -> ReadS Data
Read, Int -> Data -> String -> String
[Data] -> String -> String
Data -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [Data] -> String -> String
$cshowList :: [Data] -> String -> String
show :: Data -> String
$cshow :: Data -> String
showsPrec :: Int -> Data -> String -> String
$cshowsPrec :: Int -> Data -> String -> String
Show)

_Data :: Name
_Data = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Data")

_Data_lit :: FieldName
_Data_lit = (String -> FieldName
Core.FieldName String
"lit")

_Data_ref :: FieldName
_Data_ref = (String -> FieldName
Core.FieldName String
"ref")

_Data_interpolate :: FieldName
_Data_interpolate = (String -> FieldName
Core.FieldName String
"interpolate")

_Data_xml :: FieldName
_Data_xml = (String -> FieldName
Core.FieldName String
"xml")

_Data_apply :: FieldName
_Data_apply = (String -> FieldName
Core.FieldName String
"apply")

_Data_applyUsing :: FieldName
_Data_applyUsing = (String -> FieldName
Core.FieldName String
"applyUsing")

_Data_applyType :: FieldName
_Data_applyType = (String -> FieldName
Core.FieldName String
"applyType")

_Data_assign :: FieldName
_Data_assign = (String -> FieldName
Core.FieldName String
"assign")

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

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

_Data_ascribe :: FieldName
_Data_ascribe = (String -> FieldName
Core.FieldName String
"ascribe")

_Data_annotate :: FieldName
_Data_annotate = (String -> FieldName
Core.FieldName String
"annotate")

_Data_tuple :: FieldName
_Data_tuple = (String -> FieldName
Core.FieldName String
"tuple")

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

_Data_endMarker :: FieldName
_Data_endMarker = (String -> FieldName
Core.FieldName String
"endMarker")

_Data_if :: FieldName
_Data_if = (String -> FieldName
Core.FieldName String
"if")

_Data_quotedMacroExpr :: FieldName
_Data_quotedMacroExpr = (String -> FieldName
Core.FieldName String
"quotedMacroExpr")

_Data_quotedMacroType :: FieldName
_Data_quotedMacroType = (String -> FieldName
Core.FieldName String
"quotedMacroType")

_Data_splicedMacroExpr :: FieldName
_Data_splicedMacroExpr = (String -> FieldName
Core.FieldName String
"splicedMacroExpr")

_Data_match :: FieldName
_Data_match = (String -> FieldName
Core.FieldName String
"match")

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

_Data_tryWithHandler :: FieldName
_Data_tryWithHandler = (String -> FieldName
Core.FieldName String
"tryWithHandler")

_Data_functionData :: FieldName
_Data_functionData = (String -> FieldName
Core.FieldName String
"functionData")

_Data_polyFunction :: FieldName
_Data_polyFunction = (String -> FieldName
Core.FieldName String
"polyFunction")

_Data_partialFunction :: FieldName
_Data_partialFunction = (String -> FieldName
Core.FieldName String
"partialFunction")

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

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

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

_Data_forYield :: FieldName
_Data_forYield = (String -> FieldName
Core.FieldName String
"forYield")

_Data_new :: FieldName
_Data_new = (String -> FieldName
Core.FieldName String
"new")

_Data_newAnonymous :: FieldName
_Data_newAnonymous = (String -> FieldName
Core.FieldName String
"newAnonymous")

_Data_placeholder :: FieldName
_Data_placeholder = (String -> FieldName
Core.FieldName String
"placeholder")

_Data_eta :: FieldName
_Data_eta = (String -> FieldName
Core.FieldName String
"eta")

_Data_repeated :: FieldName
_Data_repeated = (String -> FieldName
Core.FieldName String
"repeated")

_Data_param :: FieldName
_Data_param = (String -> FieldName
Core.FieldName String
"param")

data Data_Ref = 
  Data_RefThis Data_This |
  Data_RefSuper Data_Super |
  Data_RefName Data_Name |
  Data_RefAnonymous Data_Anonymous |
  Data_RefSelect Data_Select |
  Data_RefApplyUnary Data_ApplyUnary
  deriving (Data_Ref -> Data_Ref -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Data_Ref -> Data_Ref -> Bool
$c/= :: Data_Ref -> Data_Ref -> Bool
== :: Data_Ref -> Data_Ref -> Bool
$c== :: Data_Ref -> Data_Ref -> Bool
Eq, Eq Data_Ref
Data_Ref -> Data_Ref -> Bool
Data_Ref -> Data_Ref -> Ordering
Data_Ref -> Data_Ref -> Data_Ref
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Data_Ref -> Data_Ref -> Data_Ref
$cmin :: Data_Ref -> Data_Ref -> Data_Ref
max :: Data_Ref -> Data_Ref -> Data_Ref
$cmax :: Data_Ref -> Data_Ref -> Data_Ref
>= :: Data_Ref -> Data_Ref -> Bool
$c>= :: Data_Ref -> Data_Ref -> Bool
> :: Data_Ref -> Data_Ref -> Bool
$c> :: Data_Ref -> Data_Ref -> Bool
<= :: Data_Ref -> Data_Ref -> Bool
$c<= :: Data_Ref -> Data_Ref -> Bool
< :: Data_Ref -> Data_Ref -> Bool
$c< :: Data_Ref -> Data_Ref -> Bool
compare :: Data_Ref -> Data_Ref -> Ordering
$ccompare :: Data_Ref -> Data_Ref -> Ordering
Ord, ReadPrec [Data_Ref]
ReadPrec Data_Ref
Int -> ReadS Data_Ref
ReadS [Data_Ref]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Data_Ref]
$creadListPrec :: ReadPrec [Data_Ref]
readPrec :: ReadPrec Data_Ref
$creadPrec :: ReadPrec Data_Ref
readList :: ReadS [Data_Ref]
$creadList :: ReadS [Data_Ref]
readsPrec :: Int -> ReadS Data_Ref
$creadsPrec :: Int -> ReadS Data_Ref
Read, Int -> Data_Ref -> String -> String
[Data_Ref] -> String -> String
Data_Ref -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [Data_Ref] -> String -> String
$cshowList :: [Data_Ref] -> String -> String
show :: Data_Ref -> String
$cshow :: Data_Ref -> String
showsPrec :: Int -> Data_Ref -> String -> String
$cshowsPrec :: Int -> Data_Ref -> String -> String
Show)

_Data_Ref :: Name
_Data_Ref = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Data.Ref")

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

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

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

_Data_Ref_anonymous :: FieldName
_Data_Ref_anonymous = (String -> FieldName
Core.FieldName String
"anonymous")

_Data_Ref_select :: FieldName
_Data_Ref_select = (String -> FieldName
Core.FieldName String
"select")

_Data_Ref_applyUnary :: FieldName
_Data_Ref_applyUnary = (String -> FieldName
Core.FieldName String
"applyUnary")

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

_Data_This :: Name
_Data_This = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Data.This")

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

_Data_Super :: Name
_Data_Super = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Data.Super")

_Data_Super_thisp :: FieldName
_Data_Super_thisp = (String -> FieldName
Core.FieldName String
"thisp")

_Data_Super_superp :: FieldName
_Data_Super_superp = (String -> FieldName
Core.FieldName String
"superp")

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

_Data_Name :: Name
_Data_Name = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Data.Name")

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

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

_Data_Anonymous :: Name
_Data_Anonymous = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Data.Anonymous")

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

_Data_Select :: Name
_Data_Select = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Data.Select")

_Data_Select_qual :: FieldName
_Data_Select_qual = (String -> FieldName
Core.FieldName String
"qual")

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

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

_Data_Interpolate :: Name
_Data_Interpolate = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Data.Interpolate")

_Data_Interpolate_prefix :: FieldName
_Data_Interpolate_prefix = (String -> FieldName
Core.FieldName String
"prefix")

_Data_Interpolate_parts :: FieldName
_Data_Interpolate_parts = (String -> FieldName
Core.FieldName String
"parts")

_Data_Interpolate_args :: FieldName
_Data_Interpolate_args = (String -> FieldName
Core.FieldName String
"args")

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

_Data_Xml :: Name
_Data_Xml = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Data.Xml")

_Data_Xml_parts :: FieldName
_Data_Xml_parts = (String -> FieldName
Core.FieldName String
"parts")

_Data_Xml_args :: FieldName
_Data_Xml_args = (String -> FieldName
Core.FieldName String
"args")

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

_Data_Apply :: Name
_Data_Apply = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Data.Apply")

_Data_Apply_fun :: FieldName
_Data_Apply_fun = (String -> FieldName
Core.FieldName String
"fun")

_Data_Apply_args :: FieldName
_Data_Apply_args = (String -> FieldName
Core.FieldName String
"args")

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

_Data_ApplyUsing :: Name
_Data_ApplyUsing = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Data.ApplyUsing")

_Data_ApplyUsing_fun :: FieldName
_Data_ApplyUsing_fun = (String -> FieldName
Core.FieldName String
"fun")

_Data_ApplyUsing_targs :: FieldName
_Data_ApplyUsing_targs = (String -> FieldName
Core.FieldName String
"targs")

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

_Data_ApplyType :: Name
_Data_ApplyType = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Data.ApplyType")

_Data_ApplyType_lhs :: FieldName
_Data_ApplyType_lhs = (String -> FieldName
Core.FieldName String
"lhs")

_Data_ApplyType_op :: FieldName
_Data_ApplyType_op = (String -> FieldName
Core.FieldName String
"op")

_Data_ApplyType_targs :: FieldName
_Data_ApplyType_targs = (String -> FieldName
Core.FieldName String
"targs")

_Data_ApplyType_args :: FieldName
_Data_ApplyType_args = (String -> FieldName
Core.FieldName String
"args")

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

_Data_ApplyInfix :: Name
_Data_ApplyInfix = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Data.ApplyInfix")

_Data_ApplyInfix_lhs :: FieldName
_Data_ApplyInfix_lhs = (String -> FieldName
Core.FieldName String
"lhs")

_Data_ApplyInfix_op :: FieldName
_Data_ApplyInfix_op = (String -> FieldName
Core.FieldName String
"op")

_Data_ApplyInfix_targs :: FieldName
_Data_ApplyInfix_targs = (String -> FieldName
Core.FieldName String
"targs")

_Data_ApplyInfix_args :: FieldName
_Data_ApplyInfix_args = (String -> FieldName
Core.FieldName String
"args")

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

_Data_ApplyUnary :: Name
_Data_ApplyUnary = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Data.ApplyUnary")

_Data_ApplyUnary_op :: FieldName
_Data_ApplyUnary_op = (String -> FieldName
Core.FieldName String
"op")

_Data_ApplyUnary_arg :: FieldName
_Data_ApplyUnary_arg = (String -> FieldName
Core.FieldName String
"arg")

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

_Data_Assign :: Name
_Data_Assign = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Data.Assign")

_Data_Assign_lhs :: FieldName
_Data_Assign_lhs = (String -> FieldName
Core.FieldName String
"lhs")

_Data_Assign_rhs :: FieldName
_Data_Assign_rhs = (String -> FieldName
Core.FieldName String
"rhs")

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

_Data_Return :: Name
_Data_Return = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Data.Return")

_Data_Return_expr :: FieldName
_Data_Return_expr = (String -> FieldName
Core.FieldName String
"expr")

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

_Data_Throw :: Name
_Data_Throw = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Data.Throw")

_Data_Throw_expr :: FieldName
_Data_Throw_expr = (String -> FieldName
Core.FieldName String
"expr")

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

_Data_Ascribe :: Name
_Data_Ascribe = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Data.Ascribe")

_Data_Ascribe_expr :: FieldName
_Data_Ascribe_expr = (String -> FieldName
Core.FieldName String
"expr")

_Data_Ascribe_tpe :: FieldName
_Data_Ascribe_tpe = (String -> FieldName
Core.FieldName String
"tpe")

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

_Data_Annotate :: Name
_Data_Annotate = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Data.Annotate")

_Data_Annotate_expr :: FieldName
_Data_Annotate_expr = (String -> FieldName
Core.FieldName String
"expr")

_Data_Annotate_annots :: FieldName
_Data_Annotate_annots = (String -> FieldName
Core.FieldName String
"annots")

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

_Data_Tuple :: Name
_Data_Tuple = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Data.Tuple")

_Data_Tuple_args :: FieldName
_Data_Tuple_args = (String -> FieldName
Core.FieldName String
"args")

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

_Data_Block :: Name
_Data_Block = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Data.Block")

_Data_Block_stats :: FieldName
_Data_Block_stats = (String -> FieldName
Core.FieldName String
"stats")

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

_Data_EndMarker :: Name
_Data_EndMarker = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Data.EndMarker")

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

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

_Data_If :: Name
_Data_If = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Data.If")

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

_Data_If_thenp :: FieldName
_Data_If_thenp = (String -> FieldName
Core.FieldName String
"thenp")

_Data_If_elsep :: FieldName
_Data_If_elsep = (String -> FieldName
Core.FieldName String
"elsep")

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

_Data_QuotedMacroExpr :: Name
_Data_QuotedMacroExpr = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Data.QuotedMacroExpr")

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

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

_Data_QuotedMacroType :: Name
_Data_QuotedMacroType = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Data.QuotedMacroType")

_Data_QuotedMacroType_tpe :: FieldName
_Data_QuotedMacroType_tpe = (String -> FieldName
Core.FieldName String
"tpe")

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

_Data_SplicedMacroExpr :: Name
_Data_SplicedMacroExpr = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Data.SplicedMacroExpr")

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

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

_Data_Match :: Name
_Data_Match = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Data.Match")

_Data_Match_expr :: FieldName
_Data_Match_expr = (String -> FieldName
Core.FieldName String
"expr")

_Data_Match_cases :: FieldName
_Data_Match_cases = (String -> FieldName
Core.FieldName String
"cases")

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

_Data_Try :: Name
_Data_Try = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Data.Try")

_Data_Try_expr :: FieldName
_Data_Try_expr = (String -> FieldName
Core.FieldName String
"expr")

_Data_Try_catchp :: FieldName
_Data_Try_catchp = (String -> FieldName
Core.FieldName String
"catchp")

_Data_Try_finallyp :: FieldName
_Data_Try_finallyp = (String -> FieldName
Core.FieldName String
"finallyp")

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

_Data_TryWithHandler :: Name
_Data_TryWithHandler = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Data.TryWithHandler")

_Data_TryWithHandler_expr :: FieldName
_Data_TryWithHandler_expr = (String -> FieldName
Core.FieldName String
"expr")

_Data_TryWithHandler_catchp :: FieldName
_Data_TryWithHandler_catchp = (String -> FieldName
Core.FieldName String
"catchp")

_Data_TryWithHandler_finallyp :: FieldName
_Data_TryWithHandler_finallyp = (String -> FieldName
Core.FieldName String
"finallyp")

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

_Data_FunctionData :: Name
_Data_FunctionData = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Data.FunctionData")

_Data_FunctionData_contextFunction :: FieldName
_Data_FunctionData_contextFunction = (String -> FieldName
Core.FieldName String
"contextFunction")

_Data_FunctionData_function :: FieldName
_Data_FunctionData_function = (String -> FieldName
Core.FieldName String
"function")

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

_Data_ContextFunction :: Name
_Data_ContextFunction = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Data.ContextFunction")

_Data_ContextFunction_params :: FieldName
_Data_ContextFunction_params = (String -> FieldName
Core.FieldName String
"params")

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

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

_Data_Function :: Name
_Data_Function = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Data.Function")

_Data_Function_params :: FieldName
_Data_Function_params = (String -> FieldName
Core.FieldName String
"params")

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

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

_Data_PolyFunction :: Name
_Data_PolyFunction = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Data.PolyFunction")

_Data_PolyFunction_tparams :: FieldName
_Data_PolyFunction_tparams = (String -> FieldName
Core.FieldName String
"tparams")

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

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

_Data_PartialFunction :: Name
_Data_PartialFunction = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Data.PartialFunction")

_Data_PartialFunction_cases :: FieldName
_Data_PartialFunction_cases = (String -> FieldName
Core.FieldName String
"cases")

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

_Data_While :: Name
_Data_While = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Data.While")

_Data_While_expr :: FieldName
_Data_While_expr = (String -> FieldName
Core.FieldName String
"expr")

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

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

_Data_Do :: Name
_Data_Do = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Data.Do")

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

_Data_Do_expr :: FieldName
_Data_Do_expr = (String -> FieldName
Core.FieldName String
"expr")

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

_Data_For :: Name
_Data_For = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Data.For")

_Data_For_enums :: FieldName
_Data_For_enums = (String -> FieldName
Core.FieldName String
"enums")

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

_Data_ForYield :: Name
_Data_ForYield = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Data.ForYield")

_Data_ForYield_enums :: FieldName
_Data_ForYield_enums = (String -> FieldName
Core.FieldName String
"enums")

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

_Data_New :: Name
_Data_New = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Data.New")

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

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

_Data_NewAnonymous :: Name
_Data_NewAnonymous = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Data.NewAnonymous")

_Data_NewAnonymous_templ :: FieldName
_Data_NewAnonymous_templ = (String -> FieldName
Core.FieldName String
"templ")

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

_Data_Placeholder :: Name
_Data_Placeholder = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Data.Placeholder")

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

_Data_Eta :: Name
_Data_Eta = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Data.Eta")

_Data_Eta_expr :: FieldName
_Data_Eta_expr = (String -> FieldName
Core.FieldName String
"expr")

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

_Data_Repeated :: Name
_Data_Repeated = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Data.Repeated")

_Data_Repeated_expr :: FieldName
_Data_Repeated_expr = (String -> FieldName
Core.FieldName String
"expr")

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

_Data_Param :: Name
_Data_Param = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Data.Param")

_Data_Param_mods :: FieldName
_Data_Param_mods = (String -> FieldName
Core.FieldName String
"mods")

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

_Data_Param_decltpe :: FieldName
_Data_Param_decltpe = (String -> FieldName
Core.FieldName String
"decltpe")

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

data Type = 
  TypeRef Type_Ref |
  TypeAnonymousName Type_AnonymousName |
  TypeApply Type_Apply |
  TypeApplyInfix Type_ApplyInfix |
  TypeFunctionType Type_FunctionType |
  TypePolyFunction Type_PolyFunction |
  TypeImplicitFunction Type_ImplicitFunction |
  TypeTuple Type_Tuple |
  TypeWith Type_With |
  TypeAnd Type_And |
  TypeOr Type_Or |
  TypeRefine Type_Refine |
  TypeExistential Type_Existential |
  TypeAnnotate Type_Annotate |
  TypeLambda Type_Lambda |
  TypeMacro Type_Macro |
  TypeMethod Type_Method |
  TypePlaceholder Type_Placeholder |
  TypeByName Type_ByName |
  TypeRepeated Type_Repeated |
  TypeVar Type_Var |
  TypeTypedParam Type_TypedParam |
  TypeMatch Type_Match
  deriving (Type -> Type -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Type -> Type -> Bool
$c/= :: Type -> Type -> Bool
== :: Type -> Type -> Bool
$c== :: Type -> Type -> Bool
Eq, Eq Type
Type -> Type -> Bool
Type -> Type -> Ordering
Type -> Type -> Type
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Type -> Type -> Type
$cmin :: Type -> Type -> Type
max :: Type -> Type -> Type
$cmax :: Type -> Type -> Type
>= :: Type -> Type -> Bool
$c>= :: Type -> Type -> Bool
> :: Type -> Type -> Bool
$c> :: Type -> Type -> Bool
<= :: Type -> Type -> Bool
$c<= :: Type -> Type -> Bool
< :: Type -> Type -> Bool
$c< :: Type -> Type -> Bool
compare :: Type -> Type -> Ordering
$ccompare :: Type -> Type -> Ordering
Ord, ReadPrec [Type]
ReadPrec Type
Int -> ReadS Type
ReadS [Type]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Type]
$creadListPrec :: ReadPrec [Type]
readPrec :: ReadPrec Type
$creadPrec :: ReadPrec Type
readList :: ReadS [Type]
$creadList :: ReadS [Type]
readsPrec :: Int -> ReadS Type
$creadsPrec :: Int -> ReadS Type
Read, Int -> Type -> String -> String
[Type] -> String -> String
Type -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [Type] -> String -> String
$cshowList :: [Type] -> String -> String
show :: Type -> String
$cshow :: Type -> String
showsPrec :: Int -> Type -> String -> String
$cshowsPrec :: Int -> Type -> String -> String
Show)

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

_Type_ref :: FieldName
_Type_ref = (String -> FieldName
Core.FieldName String
"ref")

_Type_anonymousName :: FieldName
_Type_anonymousName = (String -> FieldName
Core.FieldName String
"anonymousName")

_Type_apply :: FieldName
_Type_apply = (String -> FieldName
Core.FieldName String
"apply")

_Type_applyInfix :: FieldName
_Type_applyInfix = (String -> FieldName
Core.FieldName String
"applyInfix")

_Type_functionType :: FieldName
_Type_functionType = (String -> FieldName
Core.FieldName String
"functionType")

_Type_polyFunction :: FieldName
_Type_polyFunction = (String -> FieldName
Core.FieldName String
"polyFunction")

_Type_implicitFunction :: FieldName
_Type_implicitFunction = (String -> FieldName
Core.FieldName String
"implicitFunction")

_Type_tuple :: FieldName
_Type_tuple = (String -> FieldName
Core.FieldName String
"tuple")

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

_Type_and :: FieldName
_Type_and = (String -> FieldName
Core.FieldName String
"and")

_Type_or :: FieldName
_Type_or = (String -> FieldName
Core.FieldName String
"or")

_Type_refine :: FieldName
_Type_refine = (String -> FieldName
Core.FieldName String
"refine")

_Type_existential :: FieldName
_Type_existential = (String -> FieldName
Core.FieldName String
"existential")

_Type_annotate :: FieldName
_Type_annotate = (String -> FieldName
Core.FieldName String
"annotate")

_Type_lambda :: FieldName
_Type_lambda = (String -> FieldName
Core.FieldName String
"lambda")

_Type_macro :: FieldName
_Type_macro = (String -> FieldName
Core.FieldName String
"macro")

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

_Type_placeholder :: FieldName
_Type_placeholder = (String -> FieldName
Core.FieldName String
"placeholder")

_Type_byName :: FieldName
_Type_byName = (String -> FieldName
Core.FieldName String
"byName")

_Type_repeated :: FieldName
_Type_repeated = (String -> FieldName
Core.FieldName String
"repeated")

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

_Type_typedParam :: FieldName
_Type_typedParam = (String -> FieldName
Core.FieldName String
"typedParam")

_Type_match :: FieldName
_Type_match = (String -> FieldName
Core.FieldName String
"match")

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

_Type_Ref :: Name
_Type_Ref = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Type.Ref")

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

_Type_Ref_select :: FieldName
_Type_Ref_select = (String -> FieldName
Core.FieldName String
"select")

_Type_Ref_project :: FieldName
_Type_Ref_project = (String -> FieldName
Core.FieldName String
"project")

_Type_Ref_singleton :: FieldName
_Type_Ref_singleton = (String -> FieldName
Core.FieldName String
"singleton")

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

_Type_Name :: Name
_Type_Name = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Type.Name")

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

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

_Type_AnonymousName :: Name
_Type_AnonymousName = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Type.AnonymousName")

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

_Type_Select :: Name
_Type_Select = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Type.Select")

_Type_Select_qual :: FieldName
_Type_Select_qual = (String -> FieldName
Core.FieldName String
"qual")

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

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

_Type_Project :: Name
_Type_Project = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Type.Project")

_Type_Project_qual :: FieldName
_Type_Project_qual = (String -> FieldName
Core.FieldName String
"qual")

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

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

_Type_Singleton :: Name
_Type_Singleton = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Type.Singleton")

_Type_Singleton_ref :: FieldName
_Type_Singleton_ref = (String -> FieldName
Core.FieldName String
"ref")

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

_Type_Apply :: Name
_Type_Apply = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Type.Apply")

_Type_Apply_tpe :: FieldName
_Type_Apply_tpe = (String -> FieldName
Core.FieldName String
"tpe")

_Type_Apply_args :: FieldName
_Type_Apply_args = (String -> FieldName
Core.FieldName String
"args")

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

_Type_ApplyInfix :: Name
_Type_ApplyInfix = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Type.ApplyInfix")

_Type_ApplyInfix_lhs :: FieldName
_Type_ApplyInfix_lhs = (String -> FieldName
Core.FieldName String
"lhs")

_Type_ApplyInfix_op :: FieldName
_Type_ApplyInfix_op = (String -> FieldName
Core.FieldName String
"op")

_Type_ApplyInfix_rhs :: FieldName
_Type_ApplyInfix_rhs = (String -> FieldName
Core.FieldName String
"rhs")

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

_Type_FunctionType :: Name
_Type_FunctionType = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Type.FunctionType")

_Type_FunctionType_function :: FieldName
_Type_FunctionType_function = (String -> FieldName
Core.FieldName String
"function")

_Type_FunctionType_contextFunction :: FieldName
_Type_FunctionType_contextFunction = (String -> FieldName
Core.FieldName String
"contextFunction")

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

_Type_Function :: Name
_Type_Function = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Type.Function")

_Type_Function_params :: FieldName
_Type_Function_params = (String -> FieldName
Core.FieldName String
"params")

_Type_Function_res :: FieldName
_Type_Function_res = (String -> FieldName
Core.FieldName String
"res")

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

_Type_PolyFunction :: Name
_Type_PolyFunction = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Type.PolyFunction")

_Type_PolyFunction_tparams :: FieldName
_Type_PolyFunction_tparams = (String -> FieldName
Core.FieldName String
"tparams")

_Type_PolyFunction_tpe :: FieldName
_Type_PolyFunction_tpe = (String -> FieldName
Core.FieldName String
"tpe")

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

_Type_ContextFunction :: Name
_Type_ContextFunction = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Type.ContextFunction")

_Type_ContextFunction_params :: FieldName
_Type_ContextFunction_params = (String -> FieldName
Core.FieldName String
"params")

_Type_ContextFunction_res :: FieldName
_Type_ContextFunction_res = (String -> FieldName
Core.FieldName String
"res")

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

_Type_ImplicitFunction :: Name
_Type_ImplicitFunction = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Type.ImplicitFunction")

_Type_ImplicitFunction_params :: FieldName
_Type_ImplicitFunction_params = (String -> FieldName
Core.FieldName String
"params")

_Type_ImplicitFunction_res :: FieldName
_Type_ImplicitFunction_res = (String -> FieldName
Core.FieldName String
"res")

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

_Type_Tuple :: Name
_Type_Tuple = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Type.Tuple")

_Type_Tuple_args :: FieldName
_Type_Tuple_args = (String -> FieldName
Core.FieldName String
"args")

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

_Type_With :: Name
_Type_With = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Type.With")

_Type_With_lhs :: FieldName
_Type_With_lhs = (String -> FieldName
Core.FieldName String
"lhs")

_Type_With_rhs :: FieldName
_Type_With_rhs = (String -> FieldName
Core.FieldName String
"rhs")

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

_Type_And :: Name
_Type_And = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Type.And")

_Type_And_lhs :: FieldName
_Type_And_lhs = (String -> FieldName
Core.FieldName String
"lhs")

_Type_And_rhs :: FieldName
_Type_And_rhs = (String -> FieldName
Core.FieldName String
"rhs")

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

_Type_Or :: Name
_Type_Or = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Type.Or")

_Type_Or_lhs :: FieldName
_Type_Or_lhs = (String -> FieldName
Core.FieldName String
"lhs")

_Type_Or_rhs :: FieldName
_Type_Or_rhs = (String -> FieldName
Core.FieldName String
"rhs")

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

_Type_Refine :: Name
_Type_Refine = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Type.Refine")

_Type_Refine_tpe :: FieldName
_Type_Refine_tpe = (String -> FieldName
Core.FieldName String
"tpe")

_Type_Refine_stats :: FieldName
_Type_Refine_stats = (String -> FieldName
Core.FieldName String
"stats")

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

_Type_Existential :: Name
_Type_Existential = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Type.Existential")

_Type_Existential_tpe :: FieldName
_Type_Existential_tpe = (String -> FieldName
Core.FieldName String
"tpe")

_Type_Existential_stats :: FieldName
_Type_Existential_stats = (String -> FieldName
Core.FieldName String
"stats")

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

_Type_Annotate :: Name
_Type_Annotate = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Type.Annotate")

_Type_Annotate_tpe :: FieldName
_Type_Annotate_tpe = (String -> FieldName
Core.FieldName String
"tpe")

_Type_Annotate_annots :: FieldName
_Type_Annotate_annots = (String -> FieldName
Core.FieldName String
"annots")

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

_Type_Lambda :: Name
_Type_Lambda = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Type.Lambda")

_Type_Lambda_tparams :: FieldName
_Type_Lambda_tparams = (String -> FieldName
Core.FieldName String
"tparams")

_Type_Lambda_tpe :: FieldName
_Type_Lambda_tpe = (String -> FieldName
Core.FieldName String
"tpe")

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

_Type_Macro :: Name
_Type_Macro = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Type.Macro")

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

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

_Type_Method :: Name
_Type_Method = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Type.Method")

_Type_Method_paramss :: FieldName
_Type_Method_paramss = (String -> FieldName
Core.FieldName String
"paramss")

_Type_Method_tpe :: FieldName
_Type_Method_tpe = (String -> FieldName
Core.FieldName String
"tpe")

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

_Type_Placeholder :: Name
_Type_Placeholder = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Type.Placeholder")

_Type_Placeholder_bounds :: FieldName
_Type_Placeholder_bounds = (String -> FieldName
Core.FieldName String
"bounds")

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

_Type_Bounds :: Name
_Type_Bounds = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Type.Bounds")

_Type_Bounds_lo :: FieldName
_Type_Bounds_lo = (String -> FieldName
Core.FieldName String
"lo")

_Type_Bounds_hi :: FieldName
_Type_Bounds_hi = (String -> FieldName
Core.FieldName String
"hi")

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

_Type_ByName :: Name
_Type_ByName = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Type.ByName")

_Type_ByName_tpe :: FieldName
_Type_ByName_tpe = (String -> FieldName
Core.FieldName String
"tpe")

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

_Type_Repeated :: Name
_Type_Repeated = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Type.Repeated")

_Type_Repeated_tpe :: FieldName
_Type_Repeated_tpe = (String -> FieldName
Core.FieldName String
"tpe")

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

_Type_Var :: Name
_Type_Var = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Type.Var")

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

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

_Type_TypedParam :: Name
_Type_TypedParam = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Type.TypedParam")

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

_Type_TypedParam_typ :: FieldName
_Type_TypedParam_typ = (String -> FieldName
Core.FieldName String
"typ")

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

_Type_Param :: Name
_Type_Param = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Type.Param")

_Type_Param_mods :: FieldName
_Type_Param_mods = (String -> FieldName
Core.FieldName String
"mods")

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

_Type_Param_tparams :: FieldName
_Type_Param_tparams = (String -> FieldName
Core.FieldName String
"tparams")

_Type_Param_tbounds :: FieldName
_Type_Param_tbounds = (String -> FieldName
Core.FieldName String
"tbounds")

_Type_Param_vbounds :: FieldName
_Type_Param_vbounds = (String -> FieldName
Core.FieldName String
"vbounds")

_Type_Param_cbounds :: FieldName
_Type_Param_cbounds = (String -> FieldName
Core.FieldName String
"cbounds")

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

_Type_Match :: Name
_Type_Match = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Type.Match")

_Type_Match_tpe :: FieldName
_Type_Match_tpe = (String -> FieldName
Core.FieldName String
"tpe")

_Type_Match_cases :: FieldName
_Type_Match_cases = (String -> FieldName
Core.FieldName String
"cases")

data Pat = 
  PatVar Pat_Var |
  PatWildcard  |
  PatSeqWildcard  |
  PatBind Pat_Bind |
  PatAlternative Pat_Alternative |
  PatTuple Pat_Tuple |
  PatRepeated Pat_Repeated |
  PatExtract Pat_Extract |
  PatExtractInfix Pat_ExtractInfix |
  PatInterpolate Pat_Interpolate |
  PatXml Pat_Xml |
  PatTyped Pat_Typed |
  PatMacro Pat_Macro |
  PatGiven Pat_Given
  deriving (Pat -> Pat -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Pat -> Pat -> Bool
$c/= :: Pat -> Pat -> Bool
== :: Pat -> Pat -> Bool
$c== :: Pat -> Pat -> Bool
Eq, Eq Pat
Pat -> Pat -> Bool
Pat -> Pat -> Ordering
Pat -> Pat -> Pat
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Pat -> Pat -> Pat
$cmin :: Pat -> Pat -> Pat
max :: Pat -> Pat -> Pat
$cmax :: Pat -> Pat -> Pat
>= :: Pat -> Pat -> Bool
$c>= :: Pat -> Pat -> Bool
> :: Pat -> Pat -> Bool
$c> :: Pat -> Pat -> Bool
<= :: Pat -> Pat -> Bool
$c<= :: Pat -> Pat -> Bool
< :: Pat -> Pat -> Bool
$c< :: Pat -> Pat -> Bool
compare :: Pat -> Pat -> Ordering
$ccompare :: Pat -> Pat -> Ordering
Ord, ReadPrec [Pat]
ReadPrec Pat
Int -> ReadS Pat
ReadS [Pat]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Pat]
$creadListPrec :: ReadPrec [Pat]
readPrec :: ReadPrec Pat
$creadPrec :: ReadPrec Pat
readList :: ReadS [Pat]
$creadList :: ReadS [Pat]
readsPrec :: Int -> ReadS Pat
$creadsPrec :: Int -> ReadS Pat
Read, Int -> Pat -> String -> String
[Pat] -> String -> String
Pat -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [Pat] -> String -> String
$cshowList :: [Pat] -> String -> String
show :: Pat -> String
$cshow :: Pat -> String
showsPrec :: Int -> Pat -> String -> String
$cshowsPrec :: Int -> Pat -> String -> String
Show)

_Pat :: Name
_Pat = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Pat")

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

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

_Pat_seqWildcard :: FieldName
_Pat_seqWildcard = (String -> FieldName
Core.FieldName String
"seqWildcard")

_Pat_bind :: FieldName
_Pat_bind = (String -> FieldName
Core.FieldName String
"bind")

_Pat_alternative :: FieldName
_Pat_alternative = (String -> FieldName
Core.FieldName String
"alternative")

_Pat_tuple :: FieldName
_Pat_tuple = (String -> FieldName
Core.FieldName String
"tuple")

_Pat_repeated :: FieldName
_Pat_repeated = (String -> FieldName
Core.FieldName String
"repeated")

_Pat_extract :: FieldName
_Pat_extract = (String -> FieldName
Core.FieldName String
"extract")

_Pat_extractInfix :: FieldName
_Pat_extractInfix = (String -> FieldName
Core.FieldName String
"extractInfix")

_Pat_interpolate :: FieldName
_Pat_interpolate = (String -> FieldName
Core.FieldName String
"interpolate")

_Pat_xml :: FieldName
_Pat_xml = (String -> FieldName
Core.FieldName String
"xml")

_Pat_typed :: FieldName
_Pat_typed = (String -> FieldName
Core.FieldName String
"typed")

_Pat_macro :: FieldName
_Pat_macro = (String -> FieldName
Core.FieldName String
"macro")

_Pat_given :: FieldName
_Pat_given = (String -> FieldName
Core.FieldName String
"given")

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

_Pat_Var :: Name
_Pat_Var = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Pat.Var")

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

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

_Pat_Bind :: Name
_Pat_Bind = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Pat.Bind")

_Pat_Bind_lhs :: FieldName
_Pat_Bind_lhs = (String -> FieldName
Core.FieldName String
"lhs")

_Pat_Bind_rhs :: FieldName
_Pat_Bind_rhs = (String -> FieldName
Core.FieldName String
"rhs")

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

_Pat_Alternative :: Name
_Pat_Alternative = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Pat.Alternative")

_Pat_Alternative_lhs :: FieldName
_Pat_Alternative_lhs = (String -> FieldName
Core.FieldName String
"lhs")

_Pat_Alternative_rhs :: FieldName
_Pat_Alternative_rhs = (String -> FieldName
Core.FieldName String
"rhs")

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

_Pat_Tuple :: Name
_Pat_Tuple = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Pat.Tuple")

_Pat_Tuple_args :: FieldName
_Pat_Tuple_args = (String -> FieldName
Core.FieldName String
"args")

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

_Pat_Repeated :: Name
_Pat_Repeated = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Pat.Repeated")

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

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

_Pat_Extract :: Name
_Pat_Extract = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Pat.Extract")

_Pat_Extract_fun :: FieldName
_Pat_Extract_fun = (String -> FieldName
Core.FieldName String
"fun")

_Pat_Extract_args :: FieldName
_Pat_Extract_args = (String -> FieldName
Core.FieldName String
"args")

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

_Pat_ExtractInfix :: Name
_Pat_ExtractInfix = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Pat.ExtractInfix")

_Pat_ExtractInfix_lhs :: FieldName
_Pat_ExtractInfix_lhs = (String -> FieldName
Core.FieldName String
"lhs")

_Pat_ExtractInfix_op :: FieldName
_Pat_ExtractInfix_op = (String -> FieldName
Core.FieldName String
"op")

_Pat_ExtractInfix_rhs :: FieldName
_Pat_ExtractInfix_rhs = (String -> FieldName
Core.FieldName String
"rhs")

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

_Pat_Interpolate :: Name
_Pat_Interpolate = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Pat.Interpolate")

_Pat_Interpolate_prefix :: FieldName
_Pat_Interpolate_prefix = (String -> FieldName
Core.FieldName String
"prefix")

_Pat_Interpolate_parts :: FieldName
_Pat_Interpolate_parts = (String -> FieldName
Core.FieldName String
"parts")

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

_Pat_Xml :: Name
_Pat_Xml = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Pat.Xml")

_Pat_Xml_parts :: FieldName
_Pat_Xml_parts = (String -> FieldName
Core.FieldName String
"parts")

_Pat_Xml_args :: FieldName
_Pat_Xml_args = (String -> FieldName
Core.FieldName String
"args")

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

_Pat_Typed :: Name
_Pat_Typed = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Pat.Typed")

_Pat_Typed_lhs :: FieldName
_Pat_Typed_lhs = (String -> FieldName
Core.FieldName String
"lhs")

_Pat_Typed_rhs :: FieldName
_Pat_Typed_rhs = (String -> FieldName
Core.FieldName String
"rhs")

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

_Pat_Macro :: Name
_Pat_Macro = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Pat.Macro")

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

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

_Pat_Given :: Name
_Pat_Given = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Pat.Given")

_Pat_Given_tpe :: FieldName
_Pat_Given_tpe = (String -> FieldName
Core.FieldName String
"tpe")

data Member = 
  MemberTerm Member_Data |
  MemberType Member_Type |
  MemberTermParam Data_Param |
  MemberTypeParam Type_Param |
  MemberSelf Self
  deriving (Member -> Member -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Member -> Member -> Bool
$c/= :: Member -> Member -> Bool
== :: Member -> Member -> Bool
$c== :: Member -> Member -> Bool
Eq, Eq Member
Member -> Member -> Bool
Member -> Member -> Ordering
Member -> Member -> Member
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Member -> Member -> Member
$cmin :: Member -> Member -> Member
max :: Member -> Member -> Member
$cmax :: Member -> Member -> Member
>= :: Member -> Member -> Bool
$c>= :: Member -> Member -> Bool
> :: Member -> Member -> Bool
$c> :: Member -> Member -> Bool
<= :: Member -> Member -> Bool
$c<= :: Member -> Member -> Bool
< :: Member -> Member -> Bool
$c< :: Member -> Member -> Bool
compare :: Member -> Member -> Ordering
$ccompare :: Member -> Member -> Ordering
Ord, ReadPrec [Member]
ReadPrec Member
Int -> ReadS Member
ReadS [Member]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Member]
$creadListPrec :: ReadPrec [Member]
readPrec :: ReadPrec Member
$creadPrec :: ReadPrec Member
readList :: ReadS [Member]
$creadList :: ReadS [Member]
readsPrec :: Int -> ReadS Member
$creadsPrec :: Int -> ReadS Member
Read, Int -> Member -> String -> String
[Member] -> String -> String
Member -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [Member] -> String -> String
$cshowList :: [Member] -> String -> String
show :: Member -> String
$cshow :: Member -> String
showsPrec :: Int -> Member -> String -> String
$cshowsPrec :: Int -> Member -> String -> String
Show)

_Member :: Name
_Member = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Member")

_Member_term :: FieldName
_Member_term = (String -> FieldName
Core.FieldName String
"term")

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

_Member_termParam :: FieldName
_Member_termParam = (String -> FieldName
Core.FieldName String
"termParam")

_Member_typeParam :: FieldName
_Member_typeParam = (String -> FieldName
Core.FieldName String
"typeParam")

_Member_self :: FieldName
_Member_self = (String -> FieldName
Core.FieldName String
"self")

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

_Member_Data :: Name
_Member_Data = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Member.Data")

_Member_Data_pkg :: FieldName
_Member_Data_pkg = (String -> FieldName
Core.FieldName String
"pkg")

_Member_Data_object :: FieldName
_Member_Data_object = (String -> FieldName
Core.FieldName String
"object")

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

_Member_Type :: Name
_Member_Type = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Member.Type")

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

data Decl = 
  DeclVal Decl_Val |
  DeclVar Decl_Var |
  DeclDef Decl_Def |
  DeclType Decl_Type |
  DeclGiven Decl_Given
  deriving (Decl -> Decl -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Decl -> Decl -> Bool
$c/= :: Decl -> Decl -> Bool
== :: Decl -> Decl -> Bool
$c== :: Decl -> Decl -> Bool
Eq, Eq Decl
Decl -> Decl -> Bool
Decl -> Decl -> Ordering
Decl -> Decl -> Decl
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Decl -> Decl -> Decl
$cmin :: Decl -> Decl -> Decl
max :: Decl -> Decl -> Decl
$cmax :: Decl -> Decl -> Decl
>= :: Decl -> Decl -> Bool
$c>= :: Decl -> Decl -> Bool
> :: Decl -> Decl -> Bool
$c> :: Decl -> Decl -> Bool
<= :: Decl -> Decl -> Bool
$c<= :: Decl -> Decl -> Bool
< :: Decl -> Decl -> Bool
$c< :: Decl -> Decl -> Bool
compare :: Decl -> Decl -> Ordering
$ccompare :: Decl -> Decl -> Ordering
Ord, ReadPrec [Decl]
ReadPrec Decl
Int -> ReadS Decl
ReadS [Decl]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Decl]
$creadListPrec :: ReadPrec [Decl]
readPrec :: ReadPrec Decl
$creadPrec :: ReadPrec Decl
readList :: ReadS [Decl]
$creadList :: ReadS [Decl]
readsPrec :: Int -> ReadS Decl
$creadsPrec :: Int -> ReadS Decl
Read, Int -> Decl -> String -> String
[Decl] -> String -> String
Decl -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [Decl] -> String -> String
$cshowList :: [Decl] -> String -> String
show :: Decl -> String
$cshow :: Decl -> String
showsPrec :: Int -> Decl -> String -> String
$cshowsPrec :: Int -> Decl -> String -> String
Show)

_Decl :: Name
_Decl = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Decl")

_Decl_val :: FieldName
_Decl_val = (String -> FieldName
Core.FieldName String
"val")

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

_Decl_def :: FieldName
_Decl_def = (String -> FieldName
Core.FieldName String
"def")

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

_Decl_given :: FieldName
_Decl_given = (String -> FieldName
Core.FieldName String
"given")

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

_Decl_Val :: Name
_Decl_Val = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Decl.Val")

_Decl_Val_mods :: FieldName
_Decl_Val_mods = (String -> FieldName
Core.FieldName String
"mods")

_Decl_Val_pats :: FieldName
_Decl_Val_pats = (String -> FieldName
Core.FieldName String
"pats")

_Decl_Val_decltpe :: FieldName
_Decl_Val_decltpe = (String -> FieldName
Core.FieldName String
"decltpe")

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

_Decl_Var :: Name
_Decl_Var = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Decl.Var")

_Decl_Var_mods :: FieldName
_Decl_Var_mods = (String -> FieldName
Core.FieldName String
"mods")

_Decl_Var_pats :: FieldName
_Decl_Var_pats = (String -> FieldName
Core.FieldName String
"pats")

_Decl_Var_decltpe :: FieldName
_Decl_Var_decltpe = (String -> FieldName
Core.FieldName String
"decltpe")

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

_Decl_Def :: Name
_Decl_Def = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Decl.Def")

_Decl_Def_mods :: FieldName
_Decl_Def_mods = (String -> FieldName
Core.FieldName String
"mods")

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

_Decl_Def_tparams :: FieldName
_Decl_Def_tparams = (String -> FieldName
Core.FieldName String
"tparams")

_Decl_Def_paramss :: FieldName
_Decl_Def_paramss = (String -> FieldName
Core.FieldName String
"paramss")

_Decl_Def_decltpe :: FieldName
_Decl_Def_decltpe = (String -> FieldName
Core.FieldName String
"decltpe")

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

_Decl_Type :: Name
_Decl_Type = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Decl.Type")

_Decl_Type_mods :: FieldName
_Decl_Type_mods = (String -> FieldName
Core.FieldName String
"mods")

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

_Decl_Type_tparams :: FieldName
_Decl_Type_tparams = (String -> FieldName
Core.FieldName String
"tparams")

_Decl_Type_bounds :: FieldName
_Decl_Type_bounds = (String -> FieldName
Core.FieldName String
"bounds")

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

_Decl_Given :: Name
_Decl_Given = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Decl.Given")

_Decl_Given_mods :: FieldName
_Decl_Given_mods = (String -> FieldName
Core.FieldName String
"mods")

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

_Decl_Given_tparams :: FieldName
_Decl_Given_tparams = (String -> FieldName
Core.FieldName String
"tparams")

_Decl_Given_sparams :: FieldName
_Decl_Given_sparams = (String -> FieldName
Core.FieldName String
"sparams")

_Decl_Given_decltpe :: FieldName
_Decl_Given_decltpe = (String -> FieldName
Core.FieldName String
"decltpe")

data Defn = 
  DefnVal Defn_Val |
  DefnVar Defn_Var |
  DefnGiven Defn_Given |
  DefnEnum Defn_Enum |
  DefnEnumCase Defn_EnumCase |
  DefnRepeatedEnumCase Defn_RepeatedEnumCase |
  DefnGivenAlias Defn_GivenAlias |
  DefnExtensionGroup Defn_ExtensionGroup |
  DefnDef Defn_Def |
  DefnMacro Defn_Macro |
  DefnType Defn_Type |
  DefnClass Defn_Class |
  DefnTrait Defn_Trait |
  DefnObject Defn_Object
  deriving (Defn -> Defn -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Defn -> Defn -> Bool
$c/= :: Defn -> Defn -> Bool
== :: Defn -> Defn -> Bool
$c== :: Defn -> Defn -> Bool
Eq, Eq Defn
Defn -> Defn -> Bool
Defn -> Defn -> Ordering
Defn -> Defn -> Defn
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Defn -> Defn -> Defn
$cmin :: Defn -> Defn -> Defn
max :: Defn -> Defn -> Defn
$cmax :: Defn -> Defn -> Defn
>= :: Defn -> Defn -> Bool
$c>= :: Defn -> Defn -> Bool
> :: Defn -> Defn -> Bool
$c> :: Defn -> Defn -> Bool
<= :: Defn -> Defn -> Bool
$c<= :: Defn -> Defn -> Bool
< :: Defn -> Defn -> Bool
$c< :: Defn -> Defn -> Bool
compare :: Defn -> Defn -> Ordering
$ccompare :: Defn -> Defn -> Ordering
Ord, ReadPrec [Defn]
ReadPrec Defn
Int -> ReadS Defn
ReadS [Defn]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Defn]
$creadListPrec :: ReadPrec [Defn]
readPrec :: ReadPrec Defn
$creadPrec :: ReadPrec Defn
readList :: ReadS [Defn]
$creadList :: ReadS [Defn]
readsPrec :: Int -> ReadS Defn
$creadsPrec :: Int -> ReadS Defn
Read, Int -> Defn -> String -> String
[Defn] -> String -> String
Defn -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [Defn] -> String -> String
$cshowList :: [Defn] -> String -> String
show :: Defn -> String
$cshow :: Defn -> String
showsPrec :: Int -> Defn -> String -> String
$cshowsPrec :: Int -> Defn -> String -> String
Show)

_Defn :: Name
_Defn = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Defn")

_Defn_val :: FieldName
_Defn_val = (String -> FieldName
Core.FieldName String
"val")

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

_Defn_given :: FieldName
_Defn_given = (String -> FieldName
Core.FieldName String
"given")

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

_Defn_enumCase :: FieldName
_Defn_enumCase = (String -> FieldName
Core.FieldName String
"enumCase")

_Defn_repeatedEnumCase :: FieldName
_Defn_repeatedEnumCase = (String -> FieldName
Core.FieldName String
"repeatedEnumCase")

_Defn_givenAlias :: FieldName
_Defn_givenAlias = (String -> FieldName
Core.FieldName String
"givenAlias")

_Defn_extensionGroup :: FieldName
_Defn_extensionGroup = (String -> FieldName
Core.FieldName String
"extensionGroup")

_Defn_def :: FieldName
_Defn_def = (String -> FieldName
Core.FieldName String
"def")

_Defn_macro :: FieldName
_Defn_macro = (String -> FieldName
Core.FieldName String
"macro")

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

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

_Defn_trait :: FieldName
_Defn_trait = (String -> FieldName
Core.FieldName String
"trait")

_Defn_object :: FieldName
_Defn_object = (String -> FieldName
Core.FieldName String
"object")

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

_Defn_Val :: Name
_Defn_Val = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Defn.Val")

_Defn_Val_mods :: FieldName
_Defn_Val_mods = (String -> FieldName
Core.FieldName String
"mods")

_Defn_Val_pats :: FieldName
_Defn_Val_pats = (String -> FieldName
Core.FieldName String
"pats")

_Defn_Val_decltpe :: FieldName
_Defn_Val_decltpe = (String -> FieldName
Core.FieldName String
"decltpe")

_Defn_Val_rhs :: FieldName
_Defn_Val_rhs = (String -> FieldName
Core.FieldName String
"rhs")

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

_Defn_Var :: Name
_Defn_Var = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Defn.Var")

_Defn_Var_mods :: FieldName
_Defn_Var_mods = (String -> FieldName
Core.FieldName String
"mods")

_Defn_Var_pats :: FieldName
_Defn_Var_pats = (String -> FieldName
Core.FieldName String
"pats")

_Defn_Var_decltpe :: FieldName
_Defn_Var_decltpe = (String -> FieldName
Core.FieldName String
"decltpe")

_Defn_Var_rhs :: FieldName
_Defn_Var_rhs = (String -> FieldName
Core.FieldName String
"rhs")

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

_Defn_Given :: Name
_Defn_Given = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Defn.Given")

_Defn_Given_mods :: FieldName
_Defn_Given_mods = (String -> FieldName
Core.FieldName String
"mods")

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

_Defn_Given_tparams :: FieldName
_Defn_Given_tparams = (String -> FieldName
Core.FieldName String
"tparams")

_Defn_Given_sparams :: FieldName
_Defn_Given_sparams = (String -> FieldName
Core.FieldName String
"sparams")

_Defn_Given_templ :: FieldName
_Defn_Given_templ = (String -> FieldName
Core.FieldName String
"templ")

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

_Defn_Enum :: Name
_Defn_Enum = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Defn.Enum")

_Defn_Enum_mods :: FieldName
_Defn_Enum_mods = (String -> FieldName
Core.FieldName String
"mods")

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

_Defn_Enum_tparams :: FieldName
_Defn_Enum_tparams = (String -> FieldName
Core.FieldName String
"tparams")

_Defn_Enum_ctor :: FieldName
_Defn_Enum_ctor = (String -> FieldName
Core.FieldName String
"ctor")

_Defn_Enum_template :: FieldName
_Defn_Enum_template = (String -> FieldName
Core.FieldName String
"template")

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

_Defn_EnumCase :: Name
_Defn_EnumCase = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Defn.EnumCase")

_Defn_EnumCase_mods :: FieldName
_Defn_EnumCase_mods = (String -> FieldName
Core.FieldName String
"mods")

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

_Defn_EnumCase_tparams :: FieldName
_Defn_EnumCase_tparams = (String -> FieldName
Core.FieldName String
"tparams")

_Defn_EnumCase_ctor :: FieldName
_Defn_EnumCase_ctor = (String -> FieldName
Core.FieldName String
"ctor")

_Defn_EnumCase_inits :: FieldName
_Defn_EnumCase_inits = (String -> FieldName
Core.FieldName String
"inits")

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

_Defn_RepeatedEnumCase :: Name
_Defn_RepeatedEnumCase = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Defn.RepeatedEnumCase")

_Defn_RepeatedEnumCase_mods :: FieldName
_Defn_RepeatedEnumCase_mods = (String -> FieldName
Core.FieldName String
"mods")

_Defn_RepeatedEnumCase_cases :: FieldName
_Defn_RepeatedEnumCase_cases = (String -> FieldName
Core.FieldName String
"cases")

data Defn_GivenAlias = 
  Defn_GivenAlias {
    Defn_GivenAlias -> [Mod]
defn_GivenAliasMods :: [Mod],
    Defn_GivenAlias -> Name
defn_GivenAliasName :: Name,
    Defn_GivenAlias -> [[Type_Param]]
defn_GivenAliasTparams :: [[Type_Param]],
    Defn_GivenAlias -> [[Data_Param]]
defn_GivenAliasSparams :: [[Data_Param]],
    Defn_GivenAlias -> Type
defn_GivenAliasDecltpe :: Type,
    Defn_GivenAlias -> Data
defn_GivenAliasBody :: Data}
  deriving (Defn_GivenAlias -> Defn_GivenAlias -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Defn_GivenAlias -> Defn_GivenAlias -> Bool
$c/= :: Defn_GivenAlias -> Defn_GivenAlias -> Bool
== :: Defn_GivenAlias -> Defn_GivenAlias -> Bool
$c== :: Defn_GivenAlias -> Defn_GivenAlias -> Bool
Eq, Eq Defn_GivenAlias
Defn_GivenAlias -> Defn_GivenAlias -> Bool
Defn_GivenAlias -> Defn_GivenAlias -> Ordering
Defn_GivenAlias -> Defn_GivenAlias -> Defn_GivenAlias
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Defn_GivenAlias -> Defn_GivenAlias -> Defn_GivenAlias
$cmin :: Defn_GivenAlias -> Defn_GivenAlias -> Defn_GivenAlias
max :: Defn_GivenAlias -> Defn_GivenAlias -> Defn_GivenAlias
$cmax :: Defn_GivenAlias -> Defn_GivenAlias -> Defn_GivenAlias
>= :: Defn_GivenAlias -> Defn_GivenAlias -> Bool
$c>= :: Defn_GivenAlias -> Defn_GivenAlias -> Bool
> :: Defn_GivenAlias -> Defn_GivenAlias -> Bool
$c> :: Defn_GivenAlias -> Defn_GivenAlias -> Bool
<= :: Defn_GivenAlias -> Defn_GivenAlias -> Bool
$c<= :: Defn_GivenAlias -> Defn_GivenAlias -> Bool
< :: Defn_GivenAlias -> Defn_GivenAlias -> Bool
$c< :: Defn_GivenAlias -> Defn_GivenAlias -> Bool
compare :: Defn_GivenAlias -> Defn_GivenAlias -> Ordering
$ccompare :: Defn_GivenAlias -> Defn_GivenAlias -> Ordering
Ord, ReadPrec [Defn_GivenAlias]
ReadPrec Defn_GivenAlias
Int -> ReadS Defn_GivenAlias
ReadS [Defn_GivenAlias]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Defn_GivenAlias]
$creadListPrec :: ReadPrec [Defn_GivenAlias]
readPrec :: ReadPrec Defn_GivenAlias
$creadPrec :: ReadPrec Defn_GivenAlias
readList :: ReadS [Defn_GivenAlias]
$creadList :: ReadS [Defn_GivenAlias]
readsPrec :: Int -> ReadS Defn_GivenAlias
$creadsPrec :: Int -> ReadS Defn_GivenAlias
Read, Int -> Defn_GivenAlias -> String -> String
[Defn_GivenAlias] -> String -> String
Defn_GivenAlias -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [Defn_GivenAlias] -> String -> String
$cshowList :: [Defn_GivenAlias] -> String -> String
show :: Defn_GivenAlias -> String
$cshow :: Defn_GivenAlias -> String
showsPrec :: Int -> Defn_GivenAlias -> String -> String
$cshowsPrec :: Int -> Defn_GivenAlias -> String -> String
Show)

_Defn_GivenAlias :: Name
_Defn_GivenAlias = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Defn.GivenAlias")

_Defn_GivenAlias_mods :: FieldName
_Defn_GivenAlias_mods = (String -> FieldName
Core.FieldName String
"mods")

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

_Defn_GivenAlias_tparams :: FieldName
_Defn_GivenAlias_tparams = (String -> FieldName
Core.FieldName String
"tparams")

_Defn_GivenAlias_sparams :: FieldName
_Defn_GivenAlias_sparams = (String -> FieldName
Core.FieldName String
"sparams")

_Defn_GivenAlias_decltpe :: FieldName
_Defn_GivenAlias_decltpe = (String -> FieldName
Core.FieldName String
"decltpe")

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

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

_Defn_ExtensionGroup :: Name
_Defn_ExtensionGroup = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Defn.ExtensionGroup")

_Defn_ExtensionGroup_tparams :: FieldName
_Defn_ExtensionGroup_tparams = (String -> FieldName
Core.FieldName String
"tparams")

_Defn_ExtensionGroup_parmss :: FieldName
_Defn_ExtensionGroup_parmss = (String -> FieldName
Core.FieldName String
"parmss")

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

data Defn_Def = 
  Defn_Def {
    Defn_Def -> [Mod]
defn_DefMods :: [Mod],
    Defn_Def -> Data_Name
defn_DefName :: Data_Name,
    Defn_Def -> [Type_Param]
defn_DefTparams :: [Type_Param],
    Defn_Def -> [[Data_Param]]
defn_DefParamss :: [[Data_Param]],
    Defn_Def -> Maybe Type
defn_DefDecltpe :: (Maybe Type),
    Defn_Def -> Data
defn_DefBody :: Data}
  deriving (Defn_Def -> Defn_Def -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Defn_Def -> Defn_Def -> Bool
$c/= :: Defn_Def -> Defn_Def -> Bool
== :: Defn_Def -> Defn_Def -> Bool
$c== :: Defn_Def -> Defn_Def -> Bool
Eq, Eq Defn_Def
Defn_Def -> Defn_Def -> Bool
Defn_Def -> Defn_Def -> Ordering
Defn_Def -> Defn_Def -> Defn_Def
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Defn_Def -> Defn_Def -> Defn_Def
$cmin :: Defn_Def -> Defn_Def -> Defn_Def
max :: Defn_Def -> Defn_Def -> Defn_Def
$cmax :: Defn_Def -> Defn_Def -> Defn_Def
>= :: Defn_Def -> Defn_Def -> Bool
$c>= :: Defn_Def -> Defn_Def -> Bool
> :: Defn_Def -> Defn_Def -> Bool
$c> :: Defn_Def -> Defn_Def -> Bool
<= :: Defn_Def -> Defn_Def -> Bool
$c<= :: Defn_Def -> Defn_Def -> Bool
< :: Defn_Def -> Defn_Def -> Bool
$c< :: Defn_Def -> Defn_Def -> Bool
compare :: Defn_Def -> Defn_Def -> Ordering
$ccompare :: Defn_Def -> Defn_Def -> Ordering
Ord, ReadPrec [Defn_Def]
ReadPrec Defn_Def
Int -> ReadS Defn_Def
ReadS [Defn_Def]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Defn_Def]
$creadListPrec :: ReadPrec [Defn_Def]
readPrec :: ReadPrec Defn_Def
$creadPrec :: ReadPrec Defn_Def
readList :: ReadS [Defn_Def]
$creadList :: ReadS [Defn_Def]
readsPrec :: Int -> ReadS Defn_Def
$creadsPrec :: Int -> ReadS Defn_Def
Read, Int -> Defn_Def -> String -> String
[Defn_Def] -> String -> String
Defn_Def -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [Defn_Def] -> String -> String
$cshowList :: [Defn_Def] -> String -> String
show :: Defn_Def -> String
$cshow :: Defn_Def -> String
showsPrec :: Int -> Defn_Def -> String -> String
$cshowsPrec :: Int -> Defn_Def -> String -> String
Show)

_Defn_Def :: Name
_Defn_Def = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Defn.Def")

_Defn_Def_mods :: FieldName
_Defn_Def_mods = (String -> FieldName
Core.FieldName String
"mods")

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

_Defn_Def_tparams :: FieldName
_Defn_Def_tparams = (String -> FieldName
Core.FieldName String
"tparams")

_Defn_Def_paramss :: FieldName
_Defn_Def_paramss = (String -> FieldName
Core.FieldName String
"paramss")

_Defn_Def_decltpe :: FieldName
_Defn_Def_decltpe = (String -> FieldName
Core.FieldName String
"decltpe")

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

data Defn_Macro = 
  Defn_Macro {
    Defn_Macro -> [Mod]
defn_MacroMods :: [Mod],
    Defn_Macro -> Data_Name
defn_MacroName :: Data_Name,
    Defn_Macro -> [Type_Param]
defn_MacroTparams :: [Type_Param],
    Defn_Macro -> [[Data_Param]]
defn_MacroParamss :: [[Data_Param]],
    Defn_Macro -> Maybe Type
defn_MacroDecltpe :: (Maybe Type),
    Defn_Macro -> Data
defn_MacroBody :: Data}
  deriving (Defn_Macro -> Defn_Macro -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Defn_Macro -> Defn_Macro -> Bool
$c/= :: Defn_Macro -> Defn_Macro -> Bool
== :: Defn_Macro -> Defn_Macro -> Bool
$c== :: Defn_Macro -> Defn_Macro -> Bool
Eq, Eq Defn_Macro
Defn_Macro -> Defn_Macro -> Bool
Defn_Macro -> Defn_Macro -> Ordering
Defn_Macro -> Defn_Macro -> Defn_Macro
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Defn_Macro -> Defn_Macro -> Defn_Macro
$cmin :: Defn_Macro -> Defn_Macro -> Defn_Macro
max :: Defn_Macro -> Defn_Macro -> Defn_Macro
$cmax :: Defn_Macro -> Defn_Macro -> Defn_Macro
>= :: Defn_Macro -> Defn_Macro -> Bool
$c>= :: Defn_Macro -> Defn_Macro -> Bool
> :: Defn_Macro -> Defn_Macro -> Bool
$c> :: Defn_Macro -> Defn_Macro -> Bool
<= :: Defn_Macro -> Defn_Macro -> Bool
$c<= :: Defn_Macro -> Defn_Macro -> Bool
< :: Defn_Macro -> Defn_Macro -> Bool
$c< :: Defn_Macro -> Defn_Macro -> Bool
compare :: Defn_Macro -> Defn_Macro -> Ordering
$ccompare :: Defn_Macro -> Defn_Macro -> Ordering
Ord, ReadPrec [Defn_Macro]
ReadPrec Defn_Macro
Int -> ReadS Defn_Macro
ReadS [Defn_Macro]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Defn_Macro]
$creadListPrec :: ReadPrec [Defn_Macro]
readPrec :: ReadPrec Defn_Macro
$creadPrec :: ReadPrec Defn_Macro
readList :: ReadS [Defn_Macro]
$creadList :: ReadS [Defn_Macro]
readsPrec :: Int -> ReadS Defn_Macro
$creadsPrec :: Int -> ReadS Defn_Macro
Read, Int -> Defn_Macro -> String -> String
[Defn_Macro] -> String -> String
Defn_Macro -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [Defn_Macro] -> String -> String
$cshowList :: [Defn_Macro] -> String -> String
show :: Defn_Macro -> String
$cshow :: Defn_Macro -> String
showsPrec :: Int -> Defn_Macro -> String -> String
$cshowsPrec :: Int -> Defn_Macro -> String -> String
Show)

_Defn_Macro :: Name
_Defn_Macro = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Defn.Macro")

_Defn_Macro_mods :: FieldName
_Defn_Macro_mods = (String -> FieldName
Core.FieldName String
"mods")

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

_Defn_Macro_tparams :: FieldName
_Defn_Macro_tparams = (String -> FieldName
Core.FieldName String
"tparams")

_Defn_Macro_paramss :: FieldName
_Defn_Macro_paramss = (String -> FieldName
Core.FieldName String
"paramss")

_Defn_Macro_decltpe :: FieldName
_Defn_Macro_decltpe = (String -> FieldName
Core.FieldName String
"decltpe")

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

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

_Defn_Type :: Name
_Defn_Type = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Defn.Type")

_Defn_Type_mods :: FieldName
_Defn_Type_mods = (String -> FieldName
Core.FieldName String
"mods")

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

_Defn_Type_tparams :: FieldName
_Defn_Type_tparams = (String -> FieldName
Core.FieldName String
"tparams")

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

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

_Defn_Class :: Name
_Defn_Class = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Defn.Class")

_Defn_Class_mods :: FieldName
_Defn_Class_mods = (String -> FieldName
Core.FieldName String
"mods")

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

_Defn_Class_tparams :: FieldName
_Defn_Class_tparams = (String -> FieldName
Core.FieldName String
"tparams")

_Defn_Class_ctor :: FieldName
_Defn_Class_ctor = (String -> FieldName
Core.FieldName String
"ctor")

_Defn_Class_template :: FieldName
_Defn_Class_template = (String -> FieldName
Core.FieldName String
"template")

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

_Defn_Trait :: Name
_Defn_Trait = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Defn.Trait")

_Defn_Trait_mods :: FieldName
_Defn_Trait_mods = (String -> FieldName
Core.FieldName String
"mods")

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

_Defn_Trait_tparams :: FieldName
_Defn_Trait_tparams = (String -> FieldName
Core.FieldName String
"tparams")

_Defn_Trait_ctor :: FieldName
_Defn_Trait_ctor = (String -> FieldName
Core.FieldName String
"ctor")

_Defn_Trait_template :: FieldName
_Defn_Trait_template = (String -> FieldName
Core.FieldName String
"template")

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

_Defn_Object :: Name
_Defn_Object = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Defn.Object")

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

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

_Pkg :: Name
_Pkg = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Pkg")

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

_Pkg_ref :: FieldName
_Pkg_ref = (String -> FieldName
Core.FieldName String
"ref")

_Pkg_stats :: FieldName
_Pkg_stats = (String -> FieldName
Core.FieldName String
"stats")

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

_Pkg_Object :: Name
_Pkg_Object = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Pkg.Object")

_Pkg_Object_mods :: FieldName
_Pkg_Object_mods = (String -> FieldName
Core.FieldName String
"mods")

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

_Pkg_Object_template :: FieldName
_Pkg_Object_template = (String -> FieldName
Core.FieldName String
"template")

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

_Ctor :: Name
_Ctor = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Ctor")

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

_Ctor_secondary :: FieldName
_Ctor_secondary = (String -> FieldName
Core.FieldName String
"secondary")

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

_Ctor_Primary :: Name
_Ctor_Primary = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Ctor.Primary")

_Ctor_Primary_mods :: FieldName
_Ctor_Primary_mods = (String -> FieldName
Core.FieldName String
"mods")

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

_Ctor_Primary_paramss :: FieldName
_Ctor_Primary_paramss = (String -> FieldName
Core.FieldName String
"paramss")

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

_Ctor_Secondary :: Name
_Ctor_Secondary = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Ctor.Secondary")

_Ctor_Secondary_mods :: FieldName
_Ctor_Secondary_mods = (String -> FieldName
Core.FieldName String
"mods")

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

_Ctor_Secondary_paramss :: FieldName
_Ctor_Secondary_paramss = (String -> FieldName
Core.FieldName String
"paramss")

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

_Ctor_Secondary_stats :: FieldName
_Ctor_Secondary_stats = (String -> FieldName
Core.FieldName String
"stats")

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

_Init :: Name
_Init = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Init")

_Init_tpe :: FieldName
_Init_tpe = (String -> FieldName
Core.FieldName String
"tpe")

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

_Init_argss :: FieldName
_Init_argss = (String -> FieldName
Core.FieldName String
"argss")

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

_Self :: Name
_Self = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Self")

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

_Template :: Name
_Template = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Template")

_Template_early :: FieldName
_Template_early = (String -> FieldName
Core.FieldName String
"early")

_Template_inits :: FieldName
_Template_inits = (String -> FieldName
Core.FieldName String
"inits")

_Template_self :: FieldName
_Template_self = (String -> FieldName
Core.FieldName String
"self")

_Template_stats :: FieldName
_Template_stats = (String -> FieldName
Core.FieldName String
"stats")

data Mod = 
  ModAnnot Mod_Annot |
  ModPrivate Mod_Private |
  ModProtected Mod_Protected |
  ModImplicit  |
  ModFinal  |
  ModSealed  |
  ModOpen  |
  ModSuper  |
  ModOverride  |
  ModCase  |
  ModAbstract  |
  ModCovariant  |
  ModContravariant  |
  ModLazy  |
  ModValParam  |
  ModVarParam  |
  ModInfix  |
  ModInline  |
  ModUsing  |
  ModOpaque  |
  ModTransparent 
  deriving (Mod -> Mod -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Mod -> Mod -> Bool
$c/= :: Mod -> Mod -> Bool
== :: Mod -> Mod -> Bool
$c== :: Mod -> Mod -> Bool
Eq, Eq Mod
Mod -> Mod -> Bool
Mod -> Mod -> Ordering
Mod -> Mod -> Mod
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Mod -> Mod -> Mod
$cmin :: Mod -> Mod -> Mod
max :: Mod -> Mod -> Mod
$cmax :: Mod -> Mod -> Mod
>= :: Mod -> Mod -> Bool
$c>= :: Mod -> Mod -> Bool
> :: Mod -> Mod -> Bool
$c> :: Mod -> Mod -> Bool
<= :: Mod -> Mod -> Bool
$c<= :: Mod -> Mod -> Bool
< :: Mod -> Mod -> Bool
$c< :: Mod -> Mod -> Bool
compare :: Mod -> Mod -> Ordering
$ccompare :: Mod -> Mod -> Ordering
Ord, ReadPrec [Mod]
ReadPrec Mod
Int -> ReadS Mod
ReadS [Mod]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Mod]
$creadListPrec :: ReadPrec [Mod]
readPrec :: ReadPrec Mod
$creadPrec :: ReadPrec Mod
readList :: ReadS [Mod]
$creadList :: ReadS [Mod]
readsPrec :: Int -> ReadS Mod
$creadsPrec :: Int -> ReadS Mod
Read, Int -> Mod -> String -> String
[Mod] -> String -> String
Mod -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [Mod] -> String -> String
$cshowList :: [Mod] -> String -> String
show :: Mod -> String
$cshow :: Mod -> String
showsPrec :: Int -> Mod -> String -> String
$cshowsPrec :: Int -> Mod -> String -> String
Show)

_Mod :: Name
_Mod = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Mod")

_Mod_annot :: FieldName
_Mod_annot = (String -> FieldName
Core.FieldName String
"annot")

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

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

_Mod_implicit :: FieldName
_Mod_implicit = (String -> FieldName
Core.FieldName String
"implicit")

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

_Mod_sealed :: FieldName
_Mod_sealed = (String -> FieldName
Core.FieldName String
"sealed")

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

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

_Mod_override :: FieldName
_Mod_override = (String -> FieldName
Core.FieldName String
"override")

_Mod_case :: FieldName
_Mod_case = (String -> FieldName
Core.FieldName String
"case")

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

_Mod_covariant :: FieldName
_Mod_covariant = (String -> FieldName
Core.FieldName String
"covariant")

_Mod_contravariant :: FieldName
_Mod_contravariant = (String -> FieldName
Core.FieldName String
"contravariant")

_Mod_lazy :: FieldName
_Mod_lazy = (String -> FieldName
Core.FieldName String
"lazy")

_Mod_valParam :: FieldName
_Mod_valParam = (String -> FieldName
Core.FieldName String
"valParam")

_Mod_varParam :: FieldName
_Mod_varParam = (String -> FieldName
Core.FieldName String
"varParam")

_Mod_infix :: FieldName
_Mod_infix = (String -> FieldName
Core.FieldName String
"infix")

_Mod_inline :: FieldName
_Mod_inline = (String -> FieldName
Core.FieldName String
"inline")

_Mod_using :: FieldName
_Mod_using = (String -> FieldName
Core.FieldName String
"using")

_Mod_opaque :: FieldName
_Mod_opaque = (String -> FieldName
Core.FieldName String
"opaque")

_Mod_transparent :: FieldName
_Mod_transparent = (String -> FieldName
Core.FieldName String
"transparent")

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

_Mod_Annot :: Name
_Mod_Annot = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Mod.Annot")

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

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

_Mod_Private :: Name
_Mod_Private = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Mod.Private")

_Mod_Private_within :: FieldName
_Mod_Private_within = (String -> FieldName
Core.FieldName String
"within")

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

_Mod_Protected :: Name
_Mod_Protected = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Mod.Protected")

_Mod_Protected_within :: FieldName
_Mod_Protected_within = (String -> FieldName
Core.FieldName String
"within")

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

_Enumerator :: Name
_Enumerator = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Enumerator")

_Enumerator_generator :: FieldName
_Enumerator_generator = (String -> FieldName
Core.FieldName String
"generator")

_Enumerator_caseGenerator :: FieldName
_Enumerator_caseGenerator = (String -> FieldName
Core.FieldName String
"caseGenerator")

_Enumerator_val :: FieldName
_Enumerator_val = (String -> FieldName
Core.FieldName String
"val")

_Enumerator_guard :: FieldName
_Enumerator_guard = (String -> FieldName
Core.FieldName String
"guard")

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

_Enumerator_Generator :: Name
_Enumerator_Generator = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Enumerator.Generator")

_Enumerator_Generator_pat :: FieldName
_Enumerator_Generator_pat = (String -> FieldName
Core.FieldName String
"pat")

_Enumerator_Generator_rhs :: FieldName
_Enumerator_Generator_rhs = (String -> FieldName
Core.FieldName String
"rhs")

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

_Enumerator_CaseGenerator :: Name
_Enumerator_CaseGenerator = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Enumerator.CaseGenerator")

_Enumerator_CaseGenerator_pat :: FieldName
_Enumerator_CaseGenerator_pat = (String -> FieldName
Core.FieldName String
"pat")

_Enumerator_CaseGenerator_rhs :: FieldName
_Enumerator_CaseGenerator_rhs = (String -> FieldName
Core.FieldName String
"rhs")

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

_Enumerator_Val :: Name
_Enumerator_Val = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Enumerator.Val")

_Enumerator_Val_pat :: FieldName
_Enumerator_Val_pat = (String -> FieldName
Core.FieldName String
"pat")

_Enumerator_Val_rhs :: FieldName
_Enumerator_Val_rhs = (String -> FieldName
Core.FieldName String
"rhs")

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

_Enumerator_Guard :: Name
_Enumerator_Guard = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Enumerator.Guard")

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

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

_ImportExportStat :: Name
_ImportExportStat = (String -> Name
Core.Name String
"hydra/ext/scala/meta.ImportExportStat")

_ImportExportStat_import :: FieldName
_ImportExportStat_import = (String -> FieldName
Core.FieldName String
"import")

_ImportExportStat_export :: FieldName
_ImportExportStat_export = (String -> FieldName
Core.FieldName String
"export")

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

_Import :: Name
_Import = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Import")

_Import_importers :: FieldName
_Import_importers = (String -> FieldName
Core.FieldName String
"importers")

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

_Export :: Name
_Export = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Export")

_Export_importers :: FieldName
_Export_importers = (String -> FieldName
Core.FieldName String
"importers")

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

_Importer :: Name
_Importer = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Importer")

_Importer_ref :: FieldName
_Importer_ref = (String -> FieldName
Core.FieldName String
"ref")

_Importer_importees :: FieldName
_Importer_importees = (String -> FieldName
Core.FieldName String
"importees")

data Importee = 
  ImporteeWildcard  |
  ImporteeGiven Importee_Given |
  ImporteeGivenAll  |
  ImporteeName Importee_Name |
  ImporteeRename Importee_Rename |
  ImporteeUnimport Importee_Unimport
  deriving (Importee -> Importee -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Importee -> Importee -> Bool
$c/= :: Importee -> Importee -> Bool
== :: Importee -> Importee -> Bool
$c== :: Importee -> Importee -> Bool
Eq, Eq Importee
Importee -> Importee -> Bool
Importee -> Importee -> Ordering
Importee -> Importee -> Importee
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Importee -> Importee -> Importee
$cmin :: Importee -> Importee -> Importee
max :: Importee -> Importee -> Importee
$cmax :: Importee -> Importee -> Importee
>= :: Importee -> Importee -> Bool
$c>= :: Importee -> Importee -> Bool
> :: Importee -> Importee -> Bool
$c> :: Importee -> Importee -> Bool
<= :: Importee -> Importee -> Bool
$c<= :: Importee -> Importee -> Bool
< :: Importee -> Importee -> Bool
$c< :: Importee -> Importee -> Bool
compare :: Importee -> Importee -> Ordering
$ccompare :: Importee -> Importee -> Ordering
Ord, ReadPrec [Importee]
ReadPrec Importee
Int -> ReadS Importee
ReadS [Importee]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Importee]
$creadListPrec :: ReadPrec [Importee]
readPrec :: ReadPrec Importee
$creadPrec :: ReadPrec Importee
readList :: ReadS [Importee]
$creadList :: ReadS [Importee]
readsPrec :: Int -> ReadS Importee
$creadsPrec :: Int -> ReadS Importee
Read, Int -> Importee -> String -> String
[Importee] -> String -> String
Importee -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [Importee] -> String -> String
$cshowList :: [Importee] -> String -> String
show :: Importee -> String
$cshow :: Importee -> String
showsPrec :: Int -> Importee -> String -> String
$cshowsPrec :: Int -> Importee -> String -> String
Show)

_Importee :: Name
_Importee = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Importee")

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

_Importee_given :: FieldName
_Importee_given = (String -> FieldName
Core.FieldName String
"given")

_Importee_givenAll :: FieldName
_Importee_givenAll = (String -> FieldName
Core.FieldName String
"givenAll")

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

_Importee_rename :: FieldName
_Importee_rename = (String -> FieldName
Core.FieldName String
"rename")

_Importee_unimport :: FieldName
_Importee_unimport = (String -> FieldName
Core.FieldName String
"unimport")

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

_Importee_Given :: Name
_Importee_Given = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Importee.Given")

_Importee_Given_tpe :: FieldName
_Importee_Given_tpe = (String -> FieldName
Core.FieldName String
"tpe")

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

_Importee_Name :: Name
_Importee_Name = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Importee.Name")

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

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

_Importee_Rename :: Name
_Importee_Rename = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Importee.Rename")

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

_Importee_Rename_rename :: FieldName
_Importee_Rename_rename = (String -> FieldName
Core.FieldName String
"rename")

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

_Importee_Unimport :: Name
_Importee_Unimport = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Importee.Unimport")

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

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

_CaseTree :: Name
_CaseTree = (String -> Name
Core.Name String
"hydra/ext/scala/meta.CaseTree")

_CaseTree_case :: FieldName
_CaseTree_case = (String -> FieldName
Core.FieldName String
"case")

_CaseTree_typeCase :: FieldName
_CaseTree_typeCase = (String -> FieldName
Core.FieldName String
"typeCase")

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

_Case :: Name
_Case = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Case")

_Case_pat :: FieldName
_Case_pat = (String -> FieldName
Core.FieldName String
"pat")

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

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

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

_TypeCase :: Name
_TypeCase = (String -> Name
Core.Name String
"hydra/ext/scala/meta.TypeCase")

_TypeCase_pat :: FieldName
_TypeCase_pat = (String -> FieldName
Core.FieldName String
"pat")

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

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

_Source :: Name
_Source = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Source")

_Source_stats :: FieldName
_Source_stats = (String -> FieldName
Core.FieldName String
"stats")

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

_Quasi :: Name
_Quasi = (String -> Name
Core.Name String
"hydra/ext/scala/meta.Quasi")