module Hydra.Core where
import Data.Int
import Data.List as L
import Data.Map as M
import Data.Set as S
data AnnotatedTerm =
AnnotatedTerm {
AnnotatedTerm -> Term
annotatedTermSubject :: Term,
AnnotatedTerm -> Map String Term
annotatedTermAnnotation :: (Map String Term)}
deriving (AnnotatedTerm -> AnnotatedTerm -> Bool
(AnnotatedTerm -> AnnotatedTerm -> Bool)
-> (AnnotatedTerm -> AnnotatedTerm -> Bool) -> Eq AnnotatedTerm
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AnnotatedTerm -> AnnotatedTerm -> Bool
== :: AnnotatedTerm -> AnnotatedTerm -> Bool
$c/= :: AnnotatedTerm -> AnnotatedTerm -> Bool
/= :: AnnotatedTerm -> AnnotatedTerm -> Bool
Eq, Eq AnnotatedTerm
Eq AnnotatedTerm =>
(AnnotatedTerm -> AnnotatedTerm -> Ordering)
-> (AnnotatedTerm -> AnnotatedTerm -> Bool)
-> (AnnotatedTerm -> AnnotatedTerm -> Bool)
-> (AnnotatedTerm -> AnnotatedTerm -> Bool)
-> (AnnotatedTerm -> AnnotatedTerm -> Bool)
-> (AnnotatedTerm -> AnnotatedTerm -> AnnotatedTerm)
-> (AnnotatedTerm -> AnnotatedTerm -> AnnotatedTerm)
-> Ord AnnotatedTerm
AnnotatedTerm -> AnnotatedTerm -> Bool
AnnotatedTerm -> AnnotatedTerm -> Ordering
AnnotatedTerm -> AnnotatedTerm -> AnnotatedTerm
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: AnnotatedTerm -> AnnotatedTerm -> Ordering
compare :: AnnotatedTerm -> AnnotatedTerm -> Ordering
$c< :: AnnotatedTerm -> AnnotatedTerm -> Bool
< :: AnnotatedTerm -> AnnotatedTerm -> Bool
$c<= :: AnnotatedTerm -> AnnotatedTerm -> Bool
<= :: AnnotatedTerm -> AnnotatedTerm -> Bool
$c> :: AnnotatedTerm -> AnnotatedTerm -> Bool
> :: AnnotatedTerm -> AnnotatedTerm -> Bool
$c>= :: AnnotatedTerm -> AnnotatedTerm -> Bool
>= :: AnnotatedTerm -> AnnotatedTerm -> Bool
$cmax :: AnnotatedTerm -> AnnotatedTerm -> AnnotatedTerm
max :: AnnotatedTerm -> AnnotatedTerm -> AnnotatedTerm
$cmin :: AnnotatedTerm -> AnnotatedTerm -> AnnotatedTerm
min :: AnnotatedTerm -> AnnotatedTerm -> AnnotatedTerm
Ord, ReadPrec [AnnotatedTerm]
ReadPrec AnnotatedTerm
Int -> ReadS AnnotatedTerm
ReadS [AnnotatedTerm]
(Int -> ReadS AnnotatedTerm)
-> ReadS [AnnotatedTerm]
-> ReadPrec AnnotatedTerm
-> ReadPrec [AnnotatedTerm]
-> Read AnnotatedTerm
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS AnnotatedTerm
readsPrec :: Int -> ReadS AnnotatedTerm
$creadList :: ReadS [AnnotatedTerm]
readList :: ReadS [AnnotatedTerm]
$creadPrec :: ReadPrec AnnotatedTerm
readPrec :: ReadPrec AnnotatedTerm
$creadListPrec :: ReadPrec [AnnotatedTerm]
readListPrec :: ReadPrec [AnnotatedTerm]
Read, Int -> AnnotatedTerm -> ShowS
[AnnotatedTerm] -> ShowS
AnnotatedTerm -> String
(Int -> AnnotatedTerm -> ShowS)
-> (AnnotatedTerm -> String)
-> ([AnnotatedTerm] -> ShowS)
-> Show AnnotatedTerm
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> AnnotatedTerm -> ShowS
showsPrec :: Int -> AnnotatedTerm -> ShowS
$cshow :: AnnotatedTerm -> String
show :: AnnotatedTerm -> String
$cshowList :: [AnnotatedTerm] -> ShowS
showList :: [AnnotatedTerm] -> ShowS
Show)
_AnnotatedTerm :: Name
_AnnotatedTerm = (String -> Name
Name String
"hydra/core.AnnotatedTerm")
_AnnotatedTerm_subject :: Name
_AnnotatedTerm_subject = (String -> Name
Name String
"subject")
_AnnotatedTerm_annotation :: Name
_AnnotatedTerm_annotation = (String -> Name
Name String
"annotation")
data AnnotatedType =
AnnotatedType {
AnnotatedType -> Type
annotatedTypeSubject :: Type,
AnnotatedType -> Map String Term
annotatedTypeAnnotation :: (Map String Term)}
deriving (AnnotatedType -> AnnotatedType -> Bool
(AnnotatedType -> AnnotatedType -> Bool)
-> (AnnotatedType -> AnnotatedType -> Bool) -> Eq AnnotatedType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AnnotatedType -> AnnotatedType -> Bool
== :: AnnotatedType -> AnnotatedType -> Bool
$c/= :: AnnotatedType -> AnnotatedType -> Bool
/= :: AnnotatedType -> AnnotatedType -> Bool
Eq, Eq AnnotatedType
Eq AnnotatedType =>
(AnnotatedType -> AnnotatedType -> Ordering)
-> (AnnotatedType -> AnnotatedType -> Bool)
-> (AnnotatedType -> AnnotatedType -> Bool)
-> (AnnotatedType -> AnnotatedType -> Bool)
-> (AnnotatedType -> AnnotatedType -> Bool)
-> (AnnotatedType -> AnnotatedType -> AnnotatedType)
-> (AnnotatedType -> AnnotatedType -> AnnotatedType)
-> Ord AnnotatedType
AnnotatedType -> AnnotatedType -> Bool
AnnotatedType -> AnnotatedType -> Ordering
AnnotatedType -> AnnotatedType -> AnnotatedType
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: AnnotatedType -> AnnotatedType -> Ordering
compare :: AnnotatedType -> AnnotatedType -> Ordering
$c< :: AnnotatedType -> AnnotatedType -> Bool
< :: AnnotatedType -> AnnotatedType -> Bool
$c<= :: AnnotatedType -> AnnotatedType -> Bool
<= :: AnnotatedType -> AnnotatedType -> Bool
$c> :: AnnotatedType -> AnnotatedType -> Bool
> :: AnnotatedType -> AnnotatedType -> Bool
$c>= :: AnnotatedType -> AnnotatedType -> Bool
>= :: AnnotatedType -> AnnotatedType -> Bool
$cmax :: AnnotatedType -> AnnotatedType -> AnnotatedType
max :: AnnotatedType -> AnnotatedType -> AnnotatedType
$cmin :: AnnotatedType -> AnnotatedType -> AnnotatedType
min :: AnnotatedType -> AnnotatedType -> AnnotatedType
Ord, ReadPrec [AnnotatedType]
ReadPrec AnnotatedType
Int -> ReadS AnnotatedType
ReadS [AnnotatedType]
(Int -> ReadS AnnotatedType)
-> ReadS [AnnotatedType]
-> ReadPrec AnnotatedType
-> ReadPrec [AnnotatedType]
-> Read AnnotatedType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS AnnotatedType
readsPrec :: Int -> ReadS AnnotatedType
$creadList :: ReadS [AnnotatedType]
readList :: ReadS [AnnotatedType]
$creadPrec :: ReadPrec AnnotatedType
readPrec :: ReadPrec AnnotatedType
$creadListPrec :: ReadPrec [AnnotatedType]
readListPrec :: ReadPrec [AnnotatedType]
Read, Int -> AnnotatedType -> ShowS
[AnnotatedType] -> ShowS
AnnotatedType -> String
(Int -> AnnotatedType -> ShowS)
-> (AnnotatedType -> String)
-> ([AnnotatedType] -> ShowS)
-> Show AnnotatedType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> AnnotatedType -> ShowS
showsPrec :: Int -> AnnotatedType -> ShowS
$cshow :: AnnotatedType -> String
show :: AnnotatedType -> String
$cshowList :: [AnnotatedType] -> ShowS
showList :: [AnnotatedType] -> ShowS
Show)
_AnnotatedType :: Name
_AnnotatedType = (String -> Name
Name String
"hydra/core.AnnotatedType")
_AnnotatedType_subject :: Name
_AnnotatedType_subject = (String -> Name
Name String
"subject")
_AnnotatedType_annotation :: Name
_AnnotatedType_annotation = (String -> Name
Name String
"annotation")
data Application =
Application {
Application -> Term
applicationFunction :: Term,
Application -> Term
applicationArgument :: Term}
deriving (Application -> Application -> Bool
(Application -> Application -> Bool)
-> (Application -> Application -> Bool) -> Eq Application
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Application -> Application -> Bool
== :: Application -> Application -> Bool
$c/= :: Application -> Application -> Bool
/= :: Application -> Application -> Bool
Eq, Eq Application
Eq Application =>
(Application -> Application -> Ordering)
-> (Application -> Application -> Bool)
-> (Application -> Application -> Bool)
-> (Application -> Application -> Bool)
-> (Application -> Application -> Bool)
-> (Application -> Application -> Application)
-> (Application -> Application -> Application)
-> Ord Application
Application -> Application -> Bool
Application -> Application -> Ordering
Application -> Application -> Application
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Application -> Application -> Ordering
compare :: Application -> Application -> Ordering
$c< :: Application -> Application -> Bool
< :: Application -> Application -> Bool
$c<= :: Application -> Application -> Bool
<= :: Application -> Application -> Bool
$c> :: Application -> Application -> Bool
> :: Application -> Application -> Bool
$c>= :: Application -> Application -> Bool
>= :: Application -> Application -> Bool
$cmax :: Application -> Application -> Application
max :: Application -> Application -> Application
$cmin :: Application -> Application -> Application
min :: Application -> Application -> Application
Ord, ReadPrec [Application]
ReadPrec Application
Int -> ReadS Application
ReadS [Application]
(Int -> ReadS Application)
-> ReadS [Application]
-> ReadPrec Application
-> ReadPrec [Application]
-> Read Application
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Application
readsPrec :: Int -> ReadS Application
$creadList :: ReadS [Application]
readList :: ReadS [Application]
$creadPrec :: ReadPrec Application
readPrec :: ReadPrec Application
$creadListPrec :: ReadPrec [Application]
readListPrec :: ReadPrec [Application]
Read, Int -> Application -> ShowS
[Application] -> ShowS
Application -> String
(Int -> Application -> ShowS)
-> (Application -> String)
-> ([Application] -> ShowS)
-> Show Application
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Application -> ShowS
showsPrec :: Int -> Application -> ShowS
$cshow :: Application -> String
show :: Application -> String
$cshowList :: [Application] -> ShowS
showList :: [Application] -> ShowS
Show)
_Application :: Name
_Application = (String -> Name
Name String
"hydra/core.Application")
_Application_function :: Name
_Application_function = (String -> Name
Name String
"function")
_Application_argument :: Name
_Application_argument = (String -> Name
Name String
"argument")
data ApplicationType =
ApplicationType {
ApplicationType -> Type
applicationTypeFunction :: Type,
ApplicationType -> Type
applicationTypeArgument :: Type}
deriving (ApplicationType -> ApplicationType -> Bool
(ApplicationType -> ApplicationType -> Bool)
-> (ApplicationType -> ApplicationType -> Bool)
-> Eq ApplicationType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ApplicationType -> ApplicationType -> Bool
== :: ApplicationType -> ApplicationType -> Bool
$c/= :: ApplicationType -> ApplicationType -> Bool
/= :: ApplicationType -> ApplicationType -> Bool
Eq, Eq ApplicationType
Eq ApplicationType =>
(ApplicationType -> ApplicationType -> Ordering)
-> (ApplicationType -> ApplicationType -> Bool)
-> (ApplicationType -> ApplicationType -> Bool)
-> (ApplicationType -> ApplicationType -> Bool)
-> (ApplicationType -> ApplicationType -> Bool)
-> (ApplicationType -> ApplicationType -> ApplicationType)
-> (ApplicationType -> ApplicationType -> ApplicationType)
-> Ord ApplicationType
ApplicationType -> ApplicationType -> Bool
ApplicationType -> ApplicationType -> Ordering
ApplicationType -> ApplicationType -> ApplicationType
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ApplicationType -> ApplicationType -> Ordering
compare :: ApplicationType -> ApplicationType -> Ordering
$c< :: ApplicationType -> ApplicationType -> Bool
< :: ApplicationType -> ApplicationType -> Bool
$c<= :: ApplicationType -> ApplicationType -> Bool
<= :: ApplicationType -> ApplicationType -> Bool
$c> :: ApplicationType -> ApplicationType -> Bool
> :: ApplicationType -> ApplicationType -> Bool
$c>= :: ApplicationType -> ApplicationType -> Bool
>= :: ApplicationType -> ApplicationType -> Bool
$cmax :: ApplicationType -> ApplicationType -> ApplicationType
max :: ApplicationType -> ApplicationType -> ApplicationType
$cmin :: ApplicationType -> ApplicationType -> ApplicationType
min :: ApplicationType -> ApplicationType -> ApplicationType
Ord, ReadPrec [ApplicationType]
ReadPrec ApplicationType
Int -> ReadS ApplicationType
ReadS [ApplicationType]
(Int -> ReadS ApplicationType)
-> ReadS [ApplicationType]
-> ReadPrec ApplicationType
-> ReadPrec [ApplicationType]
-> Read ApplicationType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ApplicationType
readsPrec :: Int -> ReadS ApplicationType
$creadList :: ReadS [ApplicationType]
readList :: ReadS [ApplicationType]
$creadPrec :: ReadPrec ApplicationType
readPrec :: ReadPrec ApplicationType
$creadListPrec :: ReadPrec [ApplicationType]
readListPrec :: ReadPrec [ApplicationType]
Read, Int -> ApplicationType -> ShowS
[ApplicationType] -> ShowS
ApplicationType -> String
(Int -> ApplicationType -> ShowS)
-> (ApplicationType -> String)
-> ([ApplicationType] -> ShowS)
-> Show ApplicationType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ApplicationType -> ShowS
showsPrec :: Int -> ApplicationType -> ShowS
$cshow :: ApplicationType -> String
show :: ApplicationType -> String
$cshowList :: [ApplicationType] -> ShowS
showList :: [ApplicationType] -> ShowS
Show)
_ApplicationType :: Name
_ApplicationType = (String -> Name
Name String
"hydra/core.ApplicationType")
_ApplicationType_function :: Name
_ApplicationType_function = (String -> Name
Name String
"function")
_ApplicationType_argument :: Name
_ApplicationType_argument = (String -> Name
Name String
"argument")
data CaseStatement =
CaseStatement {
CaseStatement -> Name
caseStatementTypeName :: Name,
CaseStatement -> Maybe Term
caseStatementDefault :: (Maybe Term),
CaseStatement -> [Field]
caseStatementCases :: [Field]}
deriving (CaseStatement -> CaseStatement -> Bool
(CaseStatement -> CaseStatement -> Bool)
-> (CaseStatement -> CaseStatement -> Bool) -> Eq CaseStatement
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CaseStatement -> CaseStatement -> Bool
== :: CaseStatement -> CaseStatement -> Bool
$c/= :: CaseStatement -> CaseStatement -> Bool
/= :: CaseStatement -> CaseStatement -> Bool
Eq, Eq CaseStatement
Eq CaseStatement =>
(CaseStatement -> CaseStatement -> Ordering)
-> (CaseStatement -> CaseStatement -> Bool)
-> (CaseStatement -> CaseStatement -> Bool)
-> (CaseStatement -> CaseStatement -> Bool)
-> (CaseStatement -> CaseStatement -> Bool)
-> (CaseStatement -> CaseStatement -> CaseStatement)
-> (CaseStatement -> CaseStatement -> CaseStatement)
-> Ord CaseStatement
CaseStatement -> CaseStatement -> Bool
CaseStatement -> CaseStatement -> Ordering
CaseStatement -> CaseStatement -> CaseStatement
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: CaseStatement -> CaseStatement -> Ordering
compare :: CaseStatement -> CaseStatement -> Ordering
$c< :: CaseStatement -> CaseStatement -> Bool
< :: CaseStatement -> CaseStatement -> Bool
$c<= :: CaseStatement -> CaseStatement -> Bool
<= :: CaseStatement -> CaseStatement -> Bool
$c> :: CaseStatement -> CaseStatement -> Bool
> :: CaseStatement -> CaseStatement -> Bool
$c>= :: CaseStatement -> CaseStatement -> Bool
>= :: CaseStatement -> CaseStatement -> Bool
$cmax :: CaseStatement -> CaseStatement -> CaseStatement
max :: CaseStatement -> CaseStatement -> CaseStatement
$cmin :: CaseStatement -> CaseStatement -> CaseStatement
min :: CaseStatement -> CaseStatement -> CaseStatement
Ord, ReadPrec [CaseStatement]
ReadPrec CaseStatement
Int -> ReadS CaseStatement
ReadS [CaseStatement]
(Int -> ReadS CaseStatement)
-> ReadS [CaseStatement]
-> ReadPrec CaseStatement
-> ReadPrec [CaseStatement]
-> Read CaseStatement
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS CaseStatement
readsPrec :: Int -> ReadS CaseStatement
$creadList :: ReadS [CaseStatement]
readList :: ReadS [CaseStatement]
$creadPrec :: ReadPrec CaseStatement
readPrec :: ReadPrec CaseStatement
$creadListPrec :: ReadPrec [CaseStatement]
readListPrec :: ReadPrec [CaseStatement]
Read, Int -> CaseStatement -> ShowS
[CaseStatement] -> ShowS
CaseStatement -> String
(Int -> CaseStatement -> ShowS)
-> (CaseStatement -> String)
-> ([CaseStatement] -> ShowS)
-> Show CaseStatement
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CaseStatement -> ShowS
showsPrec :: Int -> CaseStatement -> ShowS
$cshow :: CaseStatement -> String
show :: CaseStatement -> String
$cshowList :: [CaseStatement] -> ShowS
showList :: [CaseStatement] -> ShowS
Show)
_CaseStatement :: Name
_CaseStatement = (String -> Name
Name String
"hydra/core.CaseStatement")
_CaseStatement_typeName :: Name
_CaseStatement_typeName = (String -> Name
Name String
"typeName")
_CaseStatement_default :: Name
_CaseStatement_default = (String -> Name
Name String
"default")
_CaseStatement_cases :: Name
_CaseStatement_cases = (String -> Name
Name String
"cases")
data Elimination =
EliminationList Term |
EliminationOptional OptionalCases |
EliminationProduct TupleProjection |
EliminationRecord Projection |
EliminationUnion CaseStatement |
EliminationWrap Name
deriving (Elimination -> Elimination -> Bool
(Elimination -> Elimination -> Bool)
-> (Elimination -> Elimination -> Bool) -> Eq Elimination
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Elimination -> Elimination -> Bool
== :: Elimination -> Elimination -> Bool
$c/= :: Elimination -> Elimination -> Bool
/= :: Elimination -> Elimination -> Bool
Eq, Eq Elimination
Eq Elimination =>
(Elimination -> Elimination -> Ordering)
-> (Elimination -> Elimination -> Bool)
-> (Elimination -> Elimination -> Bool)
-> (Elimination -> Elimination -> Bool)
-> (Elimination -> Elimination -> Bool)
-> (Elimination -> Elimination -> Elimination)
-> (Elimination -> Elimination -> Elimination)
-> Ord Elimination
Elimination -> Elimination -> Bool
Elimination -> Elimination -> Ordering
Elimination -> Elimination -> Elimination
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Elimination -> Elimination -> Ordering
compare :: Elimination -> Elimination -> Ordering
$c< :: Elimination -> Elimination -> Bool
< :: Elimination -> Elimination -> Bool
$c<= :: Elimination -> Elimination -> Bool
<= :: Elimination -> Elimination -> Bool
$c> :: Elimination -> Elimination -> Bool
> :: Elimination -> Elimination -> Bool
$c>= :: Elimination -> Elimination -> Bool
>= :: Elimination -> Elimination -> Bool
$cmax :: Elimination -> Elimination -> Elimination
max :: Elimination -> Elimination -> Elimination
$cmin :: Elimination -> Elimination -> Elimination
min :: Elimination -> Elimination -> Elimination
Ord, ReadPrec [Elimination]
ReadPrec Elimination
Int -> ReadS Elimination
ReadS [Elimination]
(Int -> ReadS Elimination)
-> ReadS [Elimination]
-> ReadPrec Elimination
-> ReadPrec [Elimination]
-> Read Elimination
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Elimination
readsPrec :: Int -> ReadS Elimination
$creadList :: ReadS [Elimination]
readList :: ReadS [Elimination]
$creadPrec :: ReadPrec Elimination
readPrec :: ReadPrec Elimination
$creadListPrec :: ReadPrec [Elimination]
readListPrec :: ReadPrec [Elimination]
Read, Int -> Elimination -> ShowS
[Elimination] -> ShowS
Elimination -> String
(Int -> Elimination -> ShowS)
-> (Elimination -> String)
-> ([Elimination] -> ShowS)
-> Show Elimination
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Elimination -> ShowS
showsPrec :: Int -> Elimination -> ShowS
$cshow :: Elimination -> String
show :: Elimination -> String
$cshowList :: [Elimination] -> ShowS
showList :: [Elimination] -> ShowS
Show)
_Elimination :: Name
_Elimination = (String -> Name
Name String
"hydra/core.Elimination")
_Elimination_list :: Name
_Elimination_list = (String -> Name
Name String
"list")
_Elimination_optional :: Name
_Elimination_optional = (String -> Name
Name String
"optional")
_Elimination_product :: Name
_Elimination_product = (String -> Name
Name String
"product")
_Elimination_record :: Name
_Elimination_record = (String -> Name
Name String
"record")
_Elimination_union :: Name
_Elimination_union = (String -> Name
Name String
"union")
_Elimination_wrap :: Name
_Elimination_wrap = (String -> Name
Name String
"wrap")
data Field =
Field {
Field -> Name
fieldName :: Name,
Field -> Term
fieldTerm :: Term}
deriving (Field -> Field -> Bool
(Field -> Field -> Bool) -> (Field -> Field -> Bool) -> Eq Field
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Field -> Field -> Bool
== :: Field -> Field -> Bool
$c/= :: Field -> Field -> Bool
/= :: Field -> Field -> Bool
Eq, Eq Field
Eq Field =>
(Field -> Field -> Ordering)
-> (Field -> Field -> Bool)
-> (Field -> Field -> Bool)
-> (Field -> Field -> Bool)
-> (Field -> Field -> Bool)
-> (Field -> Field -> Field)
-> (Field -> Field -> Field)
-> Ord Field
Field -> Field -> Bool
Field -> Field -> Ordering
Field -> Field -> Field
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Field -> Field -> Ordering
compare :: Field -> Field -> Ordering
$c< :: Field -> Field -> Bool
< :: Field -> Field -> Bool
$c<= :: Field -> Field -> Bool
<= :: Field -> Field -> Bool
$c> :: Field -> Field -> Bool
> :: Field -> Field -> Bool
$c>= :: Field -> Field -> Bool
>= :: Field -> Field -> Bool
$cmax :: Field -> Field -> Field
max :: Field -> Field -> Field
$cmin :: Field -> Field -> Field
min :: Field -> Field -> Field
Ord, ReadPrec [Field]
ReadPrec Field
Int -> ReadS Field
ReadS [Field]
(Int -> ReadS Field)
-> ReadS [Field]
-> ReadPrec Field
-> ReadPrec [Field]
-> Read Field
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Field
readsPrec :: Int -> ReadS Field
$creadList :: ReadS [Field]
readList :: ReadS [Field]
$creadPrec :: ReadPrec Field
readPrec :: ReadPrec Field
$creadListPrec :: ReadPrec [Field]
readListPrec :: ReadPrec [Field]
Read, Int -> Field -> ShowS
[Field] -> ShowS
Field -> String
(Int -> Field -> ShowS)
-> (Field -> String) -> ([Field] -> ShowS) -> Show Field
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Field -> ShowS
showsPrec :: Int -> Field -> ShowS
$cshow :: Field -> String
show :: Field -> String
$cshowList :: [Field] -> ShowS
showList :: [Field] -> ShowS
Show)
_Field :: Name
_Field = (String -> Name
Name String
"hydra/core.Field")
_Field_name :: Name
_Field_name = (String -> Name
Name String
"name")
_Field_term :: Name
_Field_term = (String -> Name
Name String
"term")
data FieldType =
FieldType {
FieldType -> Name
fieldTypeName :: Name,
FieldType -> Type
fieldTypeType :: Type}
deriving (FieldType -> FieldType -> Bool
(FieldType -> FieldType -> Bool)
-> (FieldType -> FieldType -> Bool) -> Eq FieldType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FieldType -> FieldType -> Bool
== :: FieldType -> FieldType -> Bool
$c/= :: FieldType -> FieldType -> Bool
/= :: FieldType -> FieldType -> Bool
Eq, Eq FieldType
Eq FieldType =>
(FieldType -> FieldType -> Ordering)
-> (FieldType -> FieldType -> Bool)
-> (FieldType -> FieldType -> Bool)
-> (FieldType -> FieldType -> Bool)
-> (FieldType -> FieldType -> Bool)
-> (FieldType -> FieldType -> FieldType)
-> (FieldType -> FieldType -> FieldType)
-> Ord FieldType
FieldType -> FieldType -> Bool
FieldType -> FieldType -> Ordering
FieldType -> FieldType -> FieldType
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: FieldType -> FieldType -> Ordering
compare :: FieldType -> FieldType -> Ordering
$c< :: FieldType -> FieldType -> Bool
< :: FieldType -> FieldType -> Bool
$c<= :: FieldType -> FieldType -> Bool
<= :: FieldType -> FieldType -> Bool
$c> :: FieldType -> FieldType -> Bool
> :: FieldType -> FieldType -> Bool
$c>= :: FieldType -> FieldType -> Bool
>= :: FieldType -> FieldType -> Bool
$cmax :: FieldType -> FieldType -> FieldType
max :: FieldType -> FieldType -> FieldType
$cmin :: FieldType -> FieldType -> FieldType
min :: FieldType -> FieldType -> FieldType
Ord, ReadPrec [FieldType]
ReadPrec FieldType
Int -> ReadS FieldType
ReadS [FieldType]
(Int -> ReadS FieldType)
-> ReadS [FieldType]
-> ReadPrec FieldType
-> ReadPrec [FieldType]
-> Read FieldType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS FieldType
readsPrec :: Int -> ReadS FieldType
$creadList :: ReadS [FieldType]
readList :: ReadS [FieldType]
$creadPrec :: ReadPrec FieldType
readPrec :: ReadPrec FieldType
$creadListPrec :: ReadPrec [FieldType]
readListPrec :: ReadPrec [FieldType]
Read, Int -> FieldType -> ShowS
[FieldType] -> ShowS
FieldType -> String
(Int -> FieldType -> ShowS)
-> (FieldType -> String)
-> ([FieldType] -> ShowS)
-> Show FieldType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FieldType -> ShowS
showsPrec :: Int -> FieldType -> ShowS
$cshow :: FieldType -> String
show :: FieldType -> String
$cshowList :: [FieldType] -> ShowS
showList :: [FieldType] -> ShowS
Show)
_FieldType :: Name
_FieldType = (String -> Name
Name String
"hydra/core.FieldType")
_FieldType_name :: Name
_FieldType_name = (String -> Name
Name String
"name")
_FieldType_type :: Name
_FieldType_type = (String -> Name
Name String
"type")
data FloatType =
FloatTypeBigfloat |
FloatTypeFloat32 |
FloatTypeFloat64
deriving (FloatType -> FloatType -> Bool
(FloatType -> FloatType -> Bool)
-> (FloatType -> FloatType -> Bool) -> Eq FloatType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FloatType -> FloatType -> Bool
== :: FloatType -> FloatType -> Bool
$c/= :: FloatType -> FloatType -> Bool
/= :: FloatType -> FloatType -> Bool
Eq, Eq FloatType
Eq FloatType =>
(FloatType -> FloatType -> Ordering)
-> (FloatType -> FloatType -> Bool)
-> (FloatType -> FloatType -> Bool)
-> (FloatType -> FloatType -> Bool)
-> (FloatType -> FloatType -> Bool)
-> (FloatType -> FloatType -> FloatType)
-> (FloatType -> FloatType -> FloatType)
-> Ord FloatType
FloatType -> FloatType -> Bool
FloatType -> FloatType -> Ordering
FloatType -> FloatType -> FloatType
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: FloatType -> FloatType -> Ordering
compare :: FloatType -> FloatType -> Ordering
$c< :: FloatType -> FloatType -> Bool
< :: FloatType -> FloatType -> Bool
$c<= :: FloatType -> FloatType -> Bool
<= :: FloatType -> FloatType -> Bool
$c> :: FloatType -> FloatType -> Bool
> :: FloatType -> FloatType -> Bool
$c>= :: FloatType -> FloatType -> Bool
>= :: FloatType -> FloatType -> Bool
$cmax :: FloatType -> FloatType -> FloatType
max :: FloatType -> FloatType -> FloatType
$cmin :: FloatType -> FloatType -> FloatType
min :: FloatType -> FloatType -> FloatType
Ord, ReadPrec [FloatType]
ReadPrec FloatType
Int -> ReadS FloatType
ReadS [FloatType]
(Int -> ReadS FloatType)
-> ReadS [FloatType]
-> ReadPrec FloatType
-> ReadPrec [FloatType]
-> Read FloatType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS FloatType
readsPrec :: Int -> ReadS FloatType
$creadList :: ReadS [FloatType]
readList :: ReadS [FloatType]
$creadPrec :: ReadPrec FloatType
readPrec :: ReadPrec FloatType
$creadListPrec :: ReadPrec [FloatType]
readListPrec :: ReadPrec [FloatType]
Read, Int -> FloatType -> ShowS
[FloatType] -> ShowS
FloatType -> String
(Int -> FloatType -> ShowS)
-> (FloatType -> String)
-> ([FloatType] -> ShowS)
-> Show FloatType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FloatType -> ShowS
showsPrec :: Int -> FloatType -> ShowS
$cshow :: FloatType -> String
show :: FloatType -> String
$cshowList :: [FloatType] -> ShowS
showList :: [FloatType] -> ShowS
Show)
_FloatType :: Name
_FloatType = (String -> Name
Name String
"hydra/core.FloatType")
_FloatType_bigfloat :: Name
_FloatType_bigfloat = (String -> Name
Name String
"bigfloat")
_FloatType_float32 :: Name
_FloatType_float32 = (String -> Name
Name String
"float32")
_FloatType_float64 :: Name
_FloatType_float64 = (String -> Name
Name String
"float64")
data FloatValue =
FloatValueBigfloat Double |
FloatValueFloat32 Float |
FloatValueFloat64 Double
deriving (FloatValue -> FloatValue -> Bool
(FloatValue -> FloatValue -> Bool)
-> (FloatValue -> FloatValue -> Bool) -> Eq FloatValue
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FloatValue -> FloatValue -> Bool
== :: FloatValue -> FloatValue -> Bool
$c/= :: FloatValue -> FloatValue -> Bool
/= :: FloatValue -> FloatValue -> Bool
Eq, Eq FloatValue
Eq FloatValue =>
(FloatValue -> FloatValue -> Ordering)
-> (FloatValue -> FloatValue -> Bool)
-> (FloatValue -> FloatValue -> Bool)
-> (FloatValue -> FloatValue -> Bool)
-> (FloatValue -> FloatValue -> Bool)
-> (FloatValue -> FloatValue -> FloatValue)
-> (FloatValue -> FloatValue -> FloatValue)
-> Ord FloatValue
FloatValue -> FloatValue -> Bool
FloatValue -> FloatValue -> Ordering
FloatValue -> FloatValue -> FloatValue
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: FloatValue -> FloatValue -> Ordering
compare :: FloatValue -> FloatValue -> Ordering
$c< :: FloatValue -> FloatValue -> Bool
< :: FloatValue -> FloatValue -> Bool
$c<= :: FloatValue -> FloatValue -> Bool
<= :: FloatValue -> FloatValue -> Bool
$c> :: FloatValue -> FloatValue -> Bool
> :: FloatValue -> FloatValue -> Bool
$c>= :: FloatValue -> FloatValue -> Bool
>= :: FloatValue -> FloatValue -> Bool
$cmax :: FloatValue -> FloatValue -> FloatValue
max :: FloatValue -> FloatValue -> FloatValue
$cmin :: FloatValue -> FloatValue -> FloatValue
min :: FloatValue -> FloatValue -> FloatValue
Ord, ReadPrec [FloatValue]
ReadPrec FloatValue
Int -> ReadS FloatValue
ReadS [FloatValue]
(Int -> ReadS FloatValue)
-> ReadS [FloatValue]
-> ReadPrec FloatValue
-> ReadPrec [FloatValue]
-> Read FloatValue
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS FloatValue
readsPrec :: Int -> ReadS FloatValue
$creadList :: ReadS [FloatValue]
readList :: ReadS [FloatValue]
$creadPrec :: ReadPrec FloatValue
readPrec :: ReadPrec FloatValue
$creadListPrec :: ReadPrec [FloatValue]
readListPrec :: ReadPrec [FloatValue]
Read, Int -> FloatValue -> ShowS
[FloatValue] -> ShowS
FloatValue -> String
(Int -> FloatValue -> ShowS)
-> (FloatValue -> String)
-> ([FloatValue] -> ShowS)
-> Show FloatValue
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FloatValue -> ShowS
showsPrec :: Int -> FloatValue -> ShowS
$cshow :: FloatValue -> String
show :: FloatValue -> String
$cshowList :: [FloatValue] -> ShowS
showList :: [FloatValue] -> ShowS
Show)
_FloatValue :: Name
_FloatValue = (String -> Name
Name String
"hydra/core.FloatValue")
_FloatValue_bigfloat :: Name
_FloatValue_bigfloat = (String -> Name
Name String
"bigfloat")
_FloatValue_float32 :: Name
_FloatValue_float32 = (String -> Name
Name String
"float32")
_FloatValue_float64 :: Name
_FloatValue_float64 = (String -> Name
Name String
"float64")
data Function =
FunctionElimination Elimination |
FunctionLambda Lambda |
FunctionPrimitive Name
deriving (Function -> Function -> Bool
(Function -> Function -> Bool)
-> (Function -> Function -> Bool) -> Eq Function
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Function -> Function -> Bool
== :: Function -> Function -> Bool
$c/= :: Function -> Function -> Bool
/= :: Function -> Function -> Bool
Eq, Eq Function
Eq Function =>
(Function -> Function -> Ordering)
-> (Function -> Function -> Bool)
-> (Function -> Function -> Bool)
-> (Function -> Function -> Bool)
-> (Function -> Function -> Bool)
-> (Function -> Function -> Function)
-> (Function -> Function -> Function)
-> Ord Function
Function -> Function -> Bool
Function -> Function -> Ordering
Function -> Function -> 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
$ccompare :: Function -> Function -> Ordering
compare :: Function -> Function -> Ordering
$c< :: Function -> Function -> Bool
< :: Function -> Function -> Bool
$c<= :: Function -> Function -> Bool
<= :: Function -> Function -> Bool
$c> :: Function -> Function -> Bool
> :: Function -> Function -> Bool
$c>= :: Function -> Function -> Bool
>= :: Function -> Function -> Bool
$cmax :: Function -> Function -> Function
max :: Function -> Function -> Function
$cmin :: Function -> Function -> Function
min :: Function -> Function -> Function
Ord, ReadPrec [Function]
ReadPrec Function
Int -> ReadS Function
ReadS [Function]
(Int -> ReadS Function)
-> ReadS [Function]
-> ReadPrec Function
-> ReadPrec [Function]
-> Read Function
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Function
readsPrec :: Int -> ReadS Function
$creadList :: ReadS [Function]
readList :: ReadS [Function]
$creadPrec :: ReadPrec Function
readPrec :: ReadPrec Function
$creadListPrec :: ReadPrec [Function]
readListPrec :: ReadPrec [Function]
Read, Int -> Function -> ShowS
[Function] -> ShowS
Function -> String
(Int -> Function -> ShowS)
-> (Function -> String) -> ([Function] -> ShowS) -> Show Function
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Function -> ShowS
showsPrec :: Int -> Function -> ShowS
$cshow :: Function -> String
show :: Function -> String
$cshowList :: [Function] -> ShowS
showList :: [Function] -> ShowS
Show)
_Function :: Name
_Function = (String -> Name
Name String
"hydra/core.Function")
_Function_elimination :: Name
_Function_elimination = (String -> Name
Name String
"elimination")
_Function_lambda :: Name
_Function_lambda = (String -> Name
Name String
"lambda")
_Function_primitive :: Name
_Function_primitive = (String -> Name
Name String
"primitive")
data FunctionType =
FunctionType {
FunctionType -> Type
functionTypeDomain :: Type,
FunctionType -> Type
functionTypeCodomain :: Type}
deriving (FunctionType -> FunctionType -> Bool
(FunctionType -> FunctionType -> Bool)
-> (FunctionType -> FunctionType -> Bool) -> Eq FunctionType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FunctionType -> FunctionType -> Bool
== :: FunctionType -> FunctionType -> Bool
$c/= :: FunctionType -> FunctionType -> Bool
/= :: FunctionType -> FunctionType -> Bool
Eq, Eq FunctionType
Eq FunctionType =>
(FunctionType -> FunctionType -> Ordering)
-> (FunctionType -> FunctionType -> Bool)
-> (FunctionType -> FunctionType -> Bool)
-> (FunctionType -> FunctionType -> Bool)
-> (FunctionType -> FunctionType -> Bool)
-> (FunctionType -> FunctionType -> FunctionType)
-> (FunctionType -> FunctionType -> FunctionType)
-> Ord FunctionType
FunctionType -> FunctionType -> Bool
FunctionType -> FunctionType -> Ordering
FunctionType -> FunctionType -> 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
$ccompare :: FunctionType -> FunctionType -> Ordering
compare :: FunctionType -> FunctionType -> Ordering
$c< :: FunctionType -> FunctionType -> Bool
< :: FunctionType -> FunctionType -> Bool
$c<= :: FunctionType -> FunctionType -> Bool
<= :: FunctionType -> FunctionType -> Bool
$c> :: FunctionType -> FunctionType -> Bool
> :: FunctionType -> FunctionType -> Bool
$c>= :: FunctionType -> FunctionType -> Bool
>= :: FunctionType -> FunctionType -> Bool
$cmax :: FunctionType -> FunctionType -> FunctionType
max :: FunctionType -> FunctionType -> FunctionType
$cmin :: FunctionType -> FunctionType -> FunctionType
min :: FunctionType -> FunctionType -> FunctionType
Ord, ReadPrec [FunctionType]
ReadPrec FunctionType
Int -> ReadS FunctionType
ReadS [FunctionType]
(Int -> ReadS FunctionType)
-> ReadS [FunctionType]
-> ReadPrec FunctionType
-> ReadPrec [FunctionType]
-> Read FunctionType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS FunctionType
readsPrec :: Int -> ReadS FunctionType
$creadList :: ReadS [FunctionType]
readList :: ReadS [FunctionType]
$creadPrec :: ReadPrec FunctionType
readPrec :: ReadPrec FunctionType
$creadListPrec :: ReadPrec [FunctionType]
readListPrec :: ReadPrec [FunctionType]
Read, Int -> FunctionType -> ShowS
[FunctionType] -> ShowS
FunctionType -> String
(Int -> FunctionType -> ShowS)
-> (FunctionType -> String)
-> ([FunctionType] -> ShowS)
-> Show FunctionType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FunctionType -> ShowS
showsPrec :: Int -> FunctionType -> ShowS
$cshow :: FunctionType -> String
show :: FunctionType -> String
$cshowList :: [FunctionType] -> ShowS
showList :: [FunctionType] -> ShowS
Show)
_FunctionType :: Name
_FunctionType = (String -> Name
Name String
"hydra/core.FunctionType")
_FunctionType_domain :: Name
_FunctionType_domain = (String -> Name
Name String
"domain")
_FunctionType_codomain :: Name
_FunctionType_codomain = (String -> Name
Name String
"codomain")
data Injection =
Injection {
Injection -> Name
injectionTypeName :: Name,
Injection -> Field
injectionField :: Field}
deriving (Injection -> Injection -> Bool
(Injection -> Injection -> Bool)
-> (Injection -> Injection -> Bool) -> Eq Injection
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Injection -> Injection -> Bool
== :: Injection -> Injection -> Bool
$c/= :: Injection -> Injection -> Bool
/= :: Injection -> Injection -> Bool
Eq, Eq Injection
Eq Injection =>
(Injection -> Injection -> Ordering)
-> (Injection -> Injection -> Bool)
-> (Injection -> Injection -> Bool)
-> (Injection -> Injection -> Bool)
-> (Injection -> Injection -> Bool)
-> (Injection -> Injection -> Injection)
-> (Injection -> Injection -> Injection)
-> Ord Injection
Injection -> Injection -> Bool
Injection -> Injection -> Ordering
Injection -> Injection -> Injection
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Injection -> Injection -> Ordering
compare :: Injection -> Injection -> Ordering
$c< :: Injection -> Injection -> Bool
< :: Injection -> Injection -> Bool
$c<= :: Injection -> Injection -> Bool
<= :: Injection -> Injection -> Bool
$c> :: Injection -> Injection -> Bool
> :: Injection -> Injection -> Bool
$c>= :: Injection -> Injection -> Bool
>= :: Injection -> Injection -> Bool
$cmax :: Injection -> Injection -> Injection
max :: Injection -> Injection -> Injection
$cmin :: Injection -> Injection -> Injection
min :: Injection -> Injection -> Injection
Ord, ReadPrec [Injection]
ReadPrec Injection
Int -> ReadS Injection
ReadS [Injection]
(Int -> ReadS Injection)
-> ReadS [Injection]
-> ReadPrec Injection
-> ReadPrec [Injection]
-> Read Injection
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Injection
readsPrec :: Int -> ReadS Injection
$creadList :: ReadS [Injection]
readList :: ReadS [Injection]
$creadPrec :: ReadPrec Injection
readPrec :: ReadPrec Injection
$creadListPrec :: ReadPrec [Injection]
readListPrec :: ReadPrec [Injection]
Read, Int -> Injection -> ShowS
[Injection] -> ShowS
Injection -> String
(Int -> Injection -> ShowS)
-> (Injection -> String)
-> ([Injection] -> ShowS)
-> Show Injection
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Injection -> ShowS
showsPrec :: Int -> Injection -> ShowS
$cshow :: Injection -> String
show :: Injection -> String
$cshowList :: [Injection] -> ShowS
showList :: [Injection] -> ShowS
Show)
_Injection :: Name
_Injection = (String -> Name
Name String
"hydra/core.Injection")
_Injection_typeName :: Name
_Injection_typeName = (String -> Name
Name String
"typeName")
_Injection_field :: Name
_Injection_field = (String -> Name
Name String
"field")
data IntegerType =
IntegerTypeBigint |
IntegerTypeInt8 |
IntegerTypeInt16 |
IntegerTypeInt32 |
IntegerTypeInt64 |
IntegerTypeUint8 |
IntegerTypeUint16 |
IntegerTypeUint32 |
IntegerTypeUint64
deriving (IntegerType -> IntegerType -> Bool
(IntegerType -> IntegerType -> Bool)
-> (IntegerType -> IntegerType -> Bool) -> Eq IntegerType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: IntegerType -> IntegerType -> Bool
== :: IntegerType -> IntegerType -> Bool
$c/= :: IntegerType -> IntegerType -> Bool
/= :: IntegerType -> IntegerType -> Bool
Eq, Eq IntegerType
Eq IntegerType =>
(IntegerType -> IntegerType -> Ordering)
-> (IntegerType -> IntegerType -> Bool)
-> (IntegerType -> IntegerType -> Bool)
-> (IntegerType -> IntegerType -> Bool)
-> (IntegerType -> IntegerType -> Bool)
-> (IntegerType -> IntegerType -> IntegerType)
-> (IntegerType -> IntegerType -> IntegerType)
-> Ord IntegerType
IntegerType -> IntegerType -> Bool
IntegerType -> IntegerType -> Ordering
IntegerType -> IntegerType -> IntegerType
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: IntegerType -> IntegerType -> Ordering
compare :: IntegerType -> IntegerType -> Ordering
$c< :: IntegerType -> IntegerType -> Bool
< :: IntegerType -> IntegerType -> Bool
$c<= :: IntegerType -> IntegerType -> Bool
<= :: IntegerType -> IntegerType -> Bool
$c> :: IntegerType -> IntegerType -> Bool
> :: IntegerType -> IntegerType -> Bool
$c>= :: IntegerType -> IntegerType -> Bool
>= :: IntegerType -> IntegerType -> Bool
$cmax :: IntegerType -> IntegerType -> IntegerType
max :: IntegerType -> IntegerType -> IntegerType
$cmin :: IntegerType -> IntegerType -> IntegerType
min :: IntegerType -> IntegerType -> IntegerType
Ord, ReadPrec [IntegerType]
ReadPrec IntegerType
Int -> ReadS IntegerType
ReadS [IntegerType]
(Int -> ReadS IntegerType)
-> ReadS [IntegerType]
-> ReadPrec IntegerType
-> ReadPrec [IntegerType]
-> Read IntegerType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS IntegerType
readsPrec :: Int -> ReadS IntegerType
$creadList :: ReadS [IntegerType]
readList :: ReadS [IntegerType]
$creadPrec :: ReadPrec IntegerType
readPrec :: ReadPrec IntegerType
$creadListPrec :: ReadPrec [IntegerType]
readListPrec :: ReadPrec [IntegerType]
Read, Int -> IntegerType -> ShowS
[IntegerType] -> ShowS
IntegerType -> String
(Int -> IntegerType -> ShowS)
-> (IntegerType -> String)
-> ([IntegerType] -> ShowS)
-> Show IntegerType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> IntegerType -> ShowS
showsPrec :: Int -> IntegerType -> ShowS
$cshow :: IntegerType -> String
show :: IntegerType -> String
$cshowList :: [IntegerType] -> ShowS
showList :: [IntegerType] -> ShowS
Show)
_IntegerType :: Name
_IntegerType = (String -> Name
Name String
"hydra/core.IntegerType")
_IntegerType_bigint :: Name
_IntegerType_bigint = (String -> Name
Name String
"bigint")
_IntegerType_int8 :: Name
_IntegerType_int8 = (String -> Name
Name String
"int8")
_IntegerType_int16 :: Name
_IntegerType_int16 = (String -> Name
Name String
"int16")
_IntegerType_int32 :: Name
_IntegerType_int32 = (String -> Name
Name String
"int32")
_IntegerType_int64 :: Name
_IntegerType_int64 = (String -> Name
Name String
"int64")
_IntegerType_uint8 :: Name
_IntegerType_uint8 = (String -> Name
Name String
"uint8")
_IntegerType_uint16 :: Name
_IntegerType_uint16 = (String -> Name
Name String
"uint16")
_IntegerType_uint32 :: Name
_IntegerType_uint32 = (String -> Name
Name String
"uint32")
_IntegerType_uint64 :: Name
_IntegerType_uint64 = (String -> Name
Name String
"uint64")
data IntegerValue =
IntegerValueBigint Integer |
IntegerValueInt8 Int8 |
IntegerValueInt16 Int16 |
IntegerValueInt32 Int |
IntegerValueInt64 Int64 |
IntegerValueUint8 Int16 |
IntegerValueUint16 Int |
IntegerValueUint32 Int64 |
IntegerValueUint64 Integer
deriving (IntegerValue -> IntegerValue -> Bool
(IntegerValue -> IntegerValue -> Bool)
-> (IntegerValue -> IntegerValue -> Bool) -> Eq IntegerValue
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: IntegerValue -> IntegerValue -> Bool
== :: IntegerValue -> IntegerValue -> Bool
$c/= :: IntegerValue -> IntegerValue -> Bool
/= :: IntegerValue -> IntegerValue -> Bool
Eq, Eq IntegerValue
Eq IntegerValue =>
(IntegerValue -> IntegerValue -> Ordering)
-> (IntegerValue -> IntegerValue -> Bool)
-> (IntegerValue -> IntegerValue -> Bool)
-> (IntegerValue -> IntegerValue -> Bool)
-> (IntegerValue -> IntegerValue -> Bool)
-> (IntegerValue -> IntegerValue -> IntegerValue)
-> (IntegerValue -> IntegerValue -> IntegerValue)
-> Ord IntegerValue
IntegerValue -> IntegerValue -> Bool
IntegerValue -> IntegerValue -> Ordering
IntegerValue -> IntegerValue -> IntegerValue
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: IntegerValue -> IntegerValue -> Ordering
compare :: IntegerValue -> IntegerValue -> Ordering
$c< :: IntegerValue -> IntegerValue -> Bool
< :: IntegerValue -> IntegerValue -> Bool
$c<= :: IntegerValue -> IntegerValue -> Bool
<= :: IntegerValue -> IntegerValue -> Bool
$c> :: IntegerValue -> IntegerValue -> Bool
> :: IntegerValue -> IntegerValue -> Bool
$c>= :: IntegerValue -> IntegerValue -> Bool
>= :: IntegerValue -> IntegerValue -> Bool
$cmax :: IntegerValue -> IntegerValue -> IntegerValue
max :: IntegerValue -> IntegerValue -> IntegerValue
$cmin :: IntegerValue -> IntegerValue -> IntegerValue
min :: IntegerValue -> IntegerValue -> IntegerValue
Ord, ReadPrec [IntegerValue]
ReadPrec IntegerValue
Int -> ReadS IntegerValue
ReadS [IntegerValue]
(Int -> ReadS IntegerValue)
-> ReadS [IntegerValue]
-> ReadPrec IntegerValue
-> ReadPrec [IntegerValue]
-> Read IntegerValue
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS IntegerValue
readsPrec :: Int -> ReadS IntegerValue
$creadList :: ReadS [IntegerValue]
readList :: ReadS [IntegerValue]
$creadPrec :: ReadPrec IntegerValue
readPrec :: ReadPrec IntegerValue
$creadListPrec :: ReadPrec [IntegerValue]
readListPrec :: ReadPrec [IntegerValue]
Read, Int -> IntegerValue -> ShowS
[IntegerValue] -> ShowS
IntegerValue -> String
(Int -> IntegerValue -> ShowS)
-> (IntegerValue -> String)
-> ([IntegerValue] -> ShowS)
-> Show IntegerValue
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> IntegerValue -> ShowS
showsPrec :: Int -> IntegerValue -> ShowS
$cshow :: IntegerValue -> String
show :: IntegerValue -> String
$cshowList :: [IntegerValue] -> ShowS
showList :: [IntegerValue] -> ShowS
Show)
_IntegerValue :: Name
_IntegerValue = (String -> Name
Name String
"hydra/core.IntegerValue")
_IntegerValue_bigint :: Name
_IntegerValue_bigint = (String -> Name
Name String
"bigint")
_IntegerValue_int8 :: Name
_IntegerValue_int8 = (String -> Name
Name String
"int8")
_IntegerValue_int16 :: Name
_IntegerValue_int16 = (String -> Name
Name String
"int16")
_IntegerValue_int32 :: Name
_IntegerValue_int32 = (String -> Name
Name String
"int32")
_IntegerValue_int64 :: Name
_IntegerValue_int64 = (String -> Name
Name String
"int64")
_IntegerValue_uint8 :: Name
_IntegerValue_uint8 = (String -> Name
Name String
"uint8")
_IntegerValue_uint16 :: Name
_IntegerValue_uint16 = (String -> Name
Name String
"uint16")
_IntegerValue_uint32 :: Name
_IntegerValue_uint32 = (String -> Name
Name String
"uint32")
_IntegerValue_uint64 :: Name
_IntegerValue_uint64 = (String -> Name
Name String
"uint64")
data Lambda =
Lambda {
Lambda -> Name
lambdaParameter :: Name,
Lambda -> Term
lambdaBody :: Term}
deriving (Lambda -> Lambda -> Bool
(Lambda -> Lambda -> Bool)
-> (Lambda -> Lambda -> Bool) -> Eq Lambda
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Lambda -> Lambda -> Bool
== :: Lambda -> Lambda -> Bool
$c/= :: Lambda -> Lambda -> Bool
/= :: Lambda -> Lambda -> Bool
Eq, Eq Lambda
Eq Lambda =>
(Lambda -> Lambda -> Ordering)
-> (Lambda -> Lambda -> Bool)
-> (Lambda -> Lambda -> Bool)
-> (Lambda -> Lambda -> Bool)
-> (Lambda -> Lambda -> Bool)
-> (Lambda -> Lambda -> Lambda)
-> (Lambda -> Lambda -> Lambda)
-> Ord Lambda
Lambda -> Lambda -> Bool
Lambda -> Lambda -> Ordering
Lambda -> Lambda -> Lambda
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Lambda -> Lambda -> Ordering
compare :: Lambda -> Lambda -> Ordering
$c< :: Lambda -> Lambda -> Bool
< :: Lambda -> Lambda -> Bool
$c<= :: Lambda -> Lambda -> Bool
<= :: Lambda -> Lambda -> Bool
$c> :: Lambda -> Lambda -> Bool
> :: Lambda -> Lambda -> Bool
$c>= :: Lambda -> Lambda -> Bool
>= :: Lambda -> Lambda -> Bool
$cmax :: Lambda -> Lambda -> Lambda
max :: Lambda -> Lambda -> Lambda
$cmin :: Lambda -> Lambda -> Lambda
min :: Lambda -> Lambda -> Lambda
Ord, ReadPrec [Lambda]
ReadPrec Lambda
Int -> ReadS Lambda
ReadS [Lambda]
(Int -> ReadS Lambda)
-> ReadS [Lambda]
-> ReadPrec Lambda
-> ReadPrec [Lambda]
-> Read Lambda
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Lambda
readsPrec :: Int -> ReadS Lambda
$creadList :: ReadS [Lambda]
readList :: ReadS [Lambda]
$creadPrec :: ReadPrec Lambda
readPrec :: ReadPrec Lambda
$creadListPrec :: ReadPrec [Lambda]
readListPrec :: ReadPrec [Lambda]
Read, Int -> Lambda -> ShowS
[Lambda] -> ShowS
Lambda -> String
(Int -> Lambda -> ShowS)
-> (Lambda -> String) -> ([Lambda] -> ShowS) -> Show Lambda
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Lambda -> ShowS
showsPrec :: Int -> Lambda -> ShowS
$cshow :: Lambda -> String
show :: Lambda -> String
$cshowList :: [Lambda] -> ShowS
showList :: [Lambda] -> ShowS
Show)
_Lambda :: Name
_Lambda = (String -> Name
Name String
"hydra/core.Lambda")
_Lambda_parameter :: Name
_Lambda_parameter = (String -> Name
Name String
"parameter")
_Lambda_body :: Name
_Lambda_body = (String -> Name
Name String
"body")
data LambdaType =
LambdaType {
LambdaType -> Name
lambdaTypeParameter :: Name,
LambdaType -> Type
lambdaTypeBody :: Type}
deriving (LambdaType -> LambdaType -> Bool
(LambdaType -> LambdaType -> Bool)
-> (LambdaType -> LambdaType -> Bool) -> Eq LambdaType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: LambdaType -> LambdaType -> Bool
== :: LambdaType -> LambdaType -> Bool
$c/= :: LambdaType -> LambdaType -> Bool
/= :: LambdaType -> LambdaType -> Bool
Eq, Eq LambdaType
Eq LambdaType =>
(LambdaType -> LambdaType -> Ordering)
-> (LambdaType -> LambdaType -> Bool)
-> (LambdaType -> LambdaType -> Bool)
-> (LambdaType -> LambdaType -> Bool)
-> (LambdaType -> LambdaType -> Bool)
-> (LambdaType -> LambdaType -> LambdaType)
-> (LambdaType -> LambdaType -> LambdaType)
-> Ord LambdaType
LambdaType -> LambdaType -> Bool
LambdaType -> LambdaType -> Ordering
LambdaType -> LambdaType -> LambdaType
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: LambdaType -> LambdaType -> Ordering
compare :: LambdaType -> LambdaType -> Ordering
$c< :: LambdaType -> LambdaType -> Bool
< :: LambdaType -> LambdaType -> Bool
$c<= :: LambdaType -> LambdaType -> Bool
<= :: LambdaType -> LambdaType -> Bool
$c> :: LambdaType -> LambdaType -> Bool
> :: LambdaType -> LambdaType -> Bool
$c>= :: LambdaType -> LambdaType -> Bool
>= :: LambdaType -> LambdaType -> Bool
$cmax :: LambdaType -> LambdaType -> LambdaType
max :: LambdaType -> LambdaType -> LambdaType
$cmin :: LambdaType -> LambdaType -> LambdaType
min :: LambdaType -> LambdaType -> LambdaType
Ord, ReadPrec [LambdaType]
ReadPrec LambdaType
Int -> ReadS LambdaType
ReadS [LambdaType]
(Int -> ReadS LambdaType)
-> ReadS [LambdaType]
-> ReadPrec LambdaType
-> ReadPrec [LambdaType]
-> Read LambdaType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS LambdaType
readsPrec :: Int -> ReadS LambdaType
$creadList :: ReadS [LambdaType]
readList :: ReadS [LambdaType]
$creadPrec :: ReadPrec LambdaType
readPrec :: ReadPrec LambdaType
$creadListPrec :: ReadPrec [LambdaType]
readListPrec :: ReadPrec [LambdaType]
Read, Int -> LambdaType -> ShowS
[LambdaType] -> ShowS
LambdaType -> String
(Int -> LambdaType -> ShowS)
-> (LambdaType -> String)
-> ([LambdaType] -> ShowS)
-> Show LambdaType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> LambdaType -> ShowS
showsPrec :: Int -> LambdaType -> ShowS
$cshow :: LambdaType -> String
show :: LambdaType -> String
$cshowList :: [LambdaType] -> ShowS
showList :: [LambdaType] -> ShowS
Show)
_LambdaType :: Name
_LambdaType = (String -> Name
Name String
"hydra/core.LambdaType")
_LambdaType_parameter :: Name
_LambdaType_parameter = (String -> Name
Name String
"parameter")
_LambdaType_body :: Name
_LambdaType_body = (String -> Name
Name String
"body")
data Let =
Let {
Let -> [LetBinding]
letBindings :: [LetBinding],
Let -> Term
letEnvironment :: Term}
deriving (Let -> Let -> Bool
(Let -> Let -> Bool) -> (Let -> Let -> Bool) -> Eq Let
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Let -> Let -> Bool
== :: Let -> Let -> Bool
$c/= :: Let -> Let -> Bool
/= :: Let -> Let -> Bool
Eq, Eq Let
Eq Let =>
(Let -> Let -> Ordering)
-> (Let -> Let -> Bool)
-> (Let -> Let -> Bool)
-> (Let -> Let -> Bool)
-> (Let -> Let -> Bool)
-> (Let -> Let -> Let)
-> (Let -> Let -> Let)
-> Ord Let
Let -> Let -> Bool
Let -> Let -> Ordering
Let -> Let -> Let
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Let -> Let -> Ordering
compare :: Let -> Let -> Ordering
$c< :: Let -> Let -> Bool
< :: Let -> Let -> Bool
$c<= :: Let -> Let -> Bool
<= :: Let -> Let -> Bool
$c> :: Let -> Let -> Bool
> :: Let -> Let -> Bool
$c>= :: Let -> Let -> Bool
>= :: Let -> Let -> Bool
$cmax :: Let -> Let -> Let
max :: Let -> Let -> Let
$cmin :: Let -> Let -> Let
min :: Let -> Let -> Let
Ord, ReadPrec [Let]
ReadPrec Let
Int -> ReadS Let
ReadS [Let]
(Int -> ReadS Let)
-> ReadS [Let] -> ReadPrec Let -> ReadPrec [Let] -> Read Let
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Let
readsPrec :: Int -> ReadS Let
$creadList :: ReadS [Let]
readList :: ReadS [Let]
$creadPrec :: ReadPrec Let
readPrec :: ReadPrec Let
$creadListPrec :: ReadPrec [Let]
readListPrec :: ReadPrec [Let]
Read, Int -> Let -> ShowS
[Let] -> ShowS
Let -> String
(Int -> Let -> ShowS)
-> (Let -> String) -> ([Let] -> ShowS) -> Show Let
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Let -> ShowS
showsPrec :: Int -> Let -> ShowS
$cshow :: Let -> String
show :: Let -> String
$cshowList :: [Let] -> ShowS
showList :: [Let] -> ShowS
Show)
_Let :: Name
_Let = (String -> Name
Name String
"hydra/core.Let")
_Let_bindings :: Name
_Let_bindings = (String -> Name
Name String
"bindings")
_Let_environment :: Name
_Let_environment = (String -> Name
Name String
"environment")
data LetBinding =
LetBinding {
LetBinding -> Name
letBindingName :: Name,
LetBinding -> Term
letBindingTerm :: Term,
LetBinding -> Maybe TypeScheme
letBindingType :: (Maybe TypeScheme)}
deriving (LetBinding -> LetBinding -> Bool
(LetBinding -> LetBinding -> Bool)
-> (LetBinding -> LetBinding -> Bool) -> Eq LetBinding
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: LetBinding -> LetBinding -> Bool
== :: LetBinding -> LetBinding -> Bool
$c/= :: LetBinding -> LetBinding -> Bool
/= :: LetBinding -> LetBinding -> Bool
Eq, Eq LetBinding
Eq LetBinding =>
(LetBinding -> LetBinding -> Ordering)
-> (LetBinding -> LetBinding -> Bool)
-> (LetBinding -> LetBinding -> Bool)
-> (LetBinding -> LetBinding -> Bool)
-> (LetBinding -> LetBinding -> Bool)
-> (LetBinding -> LetBinding -> LetBinding)
-> (LetBinding -> LetBinding -> LetBinding)
-> Ord LetBinding
LetBinding -> LetBinding -> Bool
LetBinding -> LetBinding -> Ordering
LetBinding -> LetBinding -> LetBinding
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: LetBinding -> LetBinding -> Ordering
compare :: LetBinding -> LetBinding -> Ordering
$c< :: LetBinding -> LetBinding -> Bool
< :: LetBinding -> LetBinding -> Bool
$c<= :: LetBinding -> LetBinding -> Bool
<= :: LetBinding -> LetBinding -> Bool
$c> :: LetBinding -> LetBinding -> Bool
> :: LetBinding -> LetBinding -> Bool
$c>= :: LetBinding -> LetBinding -> Bool
>= :: LetBinding -> LetBinding -> Bool
$cmax :: LetBinding -> LetBinding -> LetBinding
max :: LetBinding -> LetBinding -> LetBinding
$cmin :: LetBinding -> LetBinding -> LetBinding
min :: LetBinding -> LetBinding -> LetBinding
Ord, ReadPrec [LetBinding]
ReadPrec LetBinding
Int -> ReadS LetBinding
ReadS [LetBinding]
(Int -> ReadS LetBinding)
-> ReadS [LetBinding]
-> ReadPrec LetBinding
-> ReadPrec [LetBinding]
-> Read LetBinding
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS LetBinding
readsPrec :: Int -> ReadS LetBinding
$creadList :: ReadS [LetBinding]
readList :: ReadS [LetBinding]
$creadPrec :: ReadPrec LetBinding
readPrec :: ReadPrec LetBinding
$creadListPrec :: ReadPrec [LetBinding]
readListPrec :: ReadPrec [LetBinding]
Read, Int -> LetBinding -> ShowS
[LetBinding] -> ShowS
LetBinding -> String
(Int -> LetBinding -> ShowS)
-> (LetBinding -> String)
-> ([LetBinding] -> ShowS)
-> Show LetBinding
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> LetBinding -> ShowS
showsPrec :: Int -> LetBinding -> ShowS
$cshow :: LetBinding -> String
show :: LetBinding -> String
$cshowList :: [LetBinding] -> ShowS
showList :: [LetBinding] -> ShowS
Show)
_LetBinding :: Name
_LetBinding = (String -> Name
Name String
"hydra/core.LetBinding")
_LetBinding_name :: Name
_LetBinding_name = (String -> Name
Name String
"name")
_LetBinding_term :: Name
_LetBinding_term = (String -> Name
Name String
"term")
_LetBinding_type :: Name
_LetBinding_type = (String -> Name
Name String
"type")
data Literal =
LiteralBinary String |
LiteralBoolean Bool |
LiteralFloat FloatValue |
LiteralInteger IntegerValue |
LiteralString String
deriving (Literal -> Literal -> Bool
(Literal -> Literal -> Bool)
-> (Literal -> Literal -> Bool) -> Eq Literal
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Literal -> Literal -> Bool
== :: Literal -> Literal -> Bool
$c/= :: Literal -> Literal -> Bool
/= :: Literal -> Literal -> Bool
Eq, Eq Literal
Eq Literal =>
(Literal -> Literal -> Ordering)
-> (Literal -> Literal -> Bool)
-> (Literal -> Literal -> Bool)
-> (Literal -> Literal -> Bool)
-> (Literal -> Literal -> Bool)
-> (Literal -> Literal -> Literal)
-> (Literal -> Literal -> Literal)
-> Ord Literal
Literal -> Literal -> Bool
Literal -> Literal -> Ordering
Literal -> Literal -> Literal
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Literal -> Literal -> Ordering
compare :: Literal -> Literal -> Ordering
$c< :: Literal -> Literal -> Bool
< :: Literal -> Literal -> Bool
$c<= :: Literal -> Literal -> Bool
<= :: Literal -> Literal -> Bool
$c> :: Literal -> Literal -> Bool
> :: Literal -> Literal -> Bool
$c>= :: Literal -> Literal -> Bool
>= :: Literal -> Literal -> Bool
$cmax :: Literal -> Literal -> Literal
max :: Literal -> Literal -> Literal
$cmin :: Literal -> Literal -> Literal
min :: Literal -> Literal -> Literal
Ord, ReadPrec [Literal]
ReadPrec Literal
Int -> ReadS Literal
ReadS [Literal]
(Int -> ReadS Literal)
-> ReadS [Literal]
-> ReadPrec Literal
-> ReadPrec [Literal]
-> Read Literal
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Literal
readsPrec :: Int -> ReadS Literal
$creadList :: ReadS [Literal]
readList :: ReadS [Literal]
$creadPrec :: ReadPrec Literal
readPrec :: ReadPrec Literal
$creadListPrec :: ReadPrec [Literal]
readListPrec :: ReadPrec [Literal]
Read, Int -> Literal -> ShowS
[Literal] -> ShowS
Literal -> String
(Int -> Literal -> ShowS)
-> (Literal -> String) -> ([Literal] -> ShowS) -> Show Literal
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Literal -> ShowS
showsPrec :: Int -> Literal -> ShowS
$cshow :: Literal -> String
show :: Literal -> String
$cshowList :: [Literal] -> ShowS
showList :: [Literal] -> ShowS
Show)
_Literal :: Name
_Literal = (String -> Name
Name String
"hydra/core.Literal")
_Literal_binary :: Name
_Literal_binary = (String -> Name
Name String
"binary")
_Literal_boolean :: Name
_Literal_boolean = (String -> Name
Name String
"boolean")
_Literal_float :: Name
_Literal_float = (String -> Name
Name String
"float")
_Literal_integer :: Name
_Literal_integer = (String -> Name
Name String
"integer")
_Literal_string :: Name
_Literal_string = (String -> Name
Name String
"string")
data LiteralType =
LiteralTypeBinary |
LiteralTypeBoolean |
LiteralTypeFloat FloatType |
LiteralTypeInteger IntegerType |
LiteralTypeString
deriving (LiteralType -> LiteralType -> Bool
(LiteralType -> LiteralType -> Bool)
-> (LiteralType -> LiteralType -> Bool) -> Eq LiteralType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: LiteralType -> LiteralType -> Bool
== :: LiteralType -> LiteralType -> Bool
$c/= :: LiteralType -> LiteralType -> Bool
/= :: LiteralType -> LiteralType -> Bool
Eq, Eq LiteralType
Eq LiteralType =>
(LiteralType -> LiteralType -> Ordering)
-> (LiteralType -> LiteralType -> Bool)
-> (LiteralType -> LiteralType -> Bool)
-> (LiteralType -> LiteralType -> Bool)
-> (LiteralType -> LiteralType -> Bool)
-> (LiteralType -> LiteralType -> LiteralType)
-> (LiteralType -> LiteralType -> LiteralType)
-> Ord LiteralType
LiteralType -> LiteralType -> Bool
LiteralType -> LiteralType -> Ordering
LiteralType -> LiteralType -> LiteralType
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: LiteralType -> LiteralType -> Ordering
compare :: LiteralType -> LiteralType -> Ordering
$c< :: LiteralType -> LiteralType -> Bool
< :: LiteralType -> LiteralType -> Bool
$c<= :: LiteralType -> LiteralType -> Bool
<= :: LiteralType -> LiteralType -> Bool
$c> :: LiteralType -> LiteralType -> Bool
> :: LiteralType -> LiteralType -> Bool
$c>= :: LiteralType -> LiteralType -> Bool
>= :: LiteralType -> LiteralType -> Bool
$cmax :: LiteralType -> LiteralType -> LiteralType
max :: LiteralType -> LiteralType -> LiteralType
$cmin :: LiteralType -> LiteralType -> LiteralType
min :: LiteralType -> LiteralType -> LiteralType
Ord, ReadPrec [LiteralType]
ReadPrec LiteralType
Int -> ReadS LiteralType
ReadS [LiteralType]
(Int -> ReadS LiteralType)
-> ReadS [LiteralType]
-> ReadPrec LiteralType
-> ReadPrec [LiteralType]
-> Read LiteralType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS LiteralType
readsPrec :: Int -> ReadS LiteralType
$creadList :: ReadS [LiteralType]
readList :: ReadS [LiteralType]
$creadPrec :: ReadPrec LiteralType
readPrec :: ReadPrec LiteralType
$creadListPrec :: ReadPrec [LiteralType]
readListPrec :: ReadPrec [LiteralType]
Read, Int -> LiteralType -> ShowS
[LiteralType] -> ShowS
LiteralType -> String
(Int -> LiteralType -> ShowS)
-> (LiteralType -> String)
-> ([LiteralType] -> ShowS)
-> Show LiteralType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> LiteralType -> ShowS
showsPrec :: Int -> LiteralType -> ShowS
$cshow :: LiteralType -> String
show :: LiteralType -> String
$cshowList :: [LiteralType] -> ShowS
showList :: [LiteralType] -> ShowS
Show)
_LiteralType :: Name
_LiteralType = (String -> Name
Name String
"hydra/core.LiteralType")
_LiteralType_binary :: Name
_LiteralType_binary = (String -> Name
Name String
"binary")
_LiteralType_boolean :: Name
_LiteralType_boolean = (String -> Name
Name String
"boolean")
_LiteralType_float :: Name
_LiteralType_float = (String -> Name
Name String
"float")
_LiteralType_integer :: Name
_LiteralType_integer = (String -> Name
Name String
"integer")
_LiteralType_string :: Name
_LiteralType_string = (String -> Name
Name String
"string")
data MapType =
MapType {
MapType -> Type
mapTypeKeys :: Type,
MapType -> Type
mapTypeValues :: Type}
deriving (MapType -> MapType -> Bool
(MapType -> MapType -> Bool)
-> (MapType -> MapType -> Bool) -> Eq MapType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: MapType -> MapType -> Bool
== :: MapType -> MapType -> Bool
$c/= :: MapType -> MapType -> Bool
/= :: MapType -> MapType -> Bool
Eq, Eq MapType
Eq MapType =>
(MapType -> MapType -> Ordering)
-> (MapType -> MapType -> Bool)
-> (MapType -> MapType -> Bool)
-> (MapType -> MapType -> Bool)
-> (MapType -> MapType -> Bool)
-> (MapType -> MapType -> MapType)
-> (MapType -> MapType -> MapType)
-> Ord MapType
MapType -> MapType -> Bool
MapType -> MapType -> Ordering
MapType -> MapType -> MapType
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: MapType -> MapType -> Ordering
compare :: MapType -> MapType -> Ordering
$c< :: MapType -> MapType -> Bool
< :: MapType -> MapType -> Bool
$c<= :: MapType -> MapType -> Bool
<= :: MapType -> MapType -> Bool
$c> :: MapType -> MapType -> Bool
> :: MapType -> MapType -> Bool
$c>= :: MapType -> MapType -> Bool
>= :: MapType -> MapType -> Bool
$cmax :: MapType -> MapType -> MapType
max :: MapType -> MapType -> MapType
$cmin :: MapType -> MapType -> MapType
min :: MapType -> MapType -> MapType
Ord, ReadPrec [MapType]
ReadPrec MapType
Int -> ReadS MapType
ReadS [MapType]
(Int -> ReadS MapType)
-> ReadS [MapType]
-> ReadPrec MapType
-> ReadPrec [MapType]
-> Read MapType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS MapType
readsPrec :: Int -> ReadS MapType
$creadList :: ReadS [MapType]
readList :: ReadS [MapType]
$creadPrec :: ReadPrec MapType
readPrec :: ReadPrec MapType
$creadListPrec :: ReadPrec [MapType]
readListPrec :: ReadPrec [MapType]
Read, Int -> MapType -> ShowS
[MapType] -> ShowS
MapType -> String
(Int -> MapType -> ShowS)
-> (MapType -> String) -> ([MapType] -> ShowS) -> Show MapType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> MapType -> ShowS
showsPrec :: Int -> MapType -> ShowS
$cshow :: MapType -> String
show :: MapType -> String
$cshowList :: [MapType] -> ShowS
showList :: [MapType] -> ShowS
Show)
_MapType :: Name
_MapType = (String -> Name
Name String
"hydra/core.MapType")
_MapType_keys :: Name
_MapType_keys = (String -> Name
Name String
"keys")
_MapType_values :: Name
_MapType_values = (String -> Name
Name String
"values")
newtype Name =
Name {
Name -> String
unName :: String}
deriving (Name -> Name -> Bool
(Name -> Name -> Bool) -> (Name -> Name -> Bool) -> Eq Name
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Name -> Name -> Bool
== :: Name -> Name -> Bool
$c/= :: Name -> Name -> Bool
/= :: Name -> Name -> Bool
Eq, Eq Name
Eq Name =>
(Name -> Name -> Ordering)
-> (Name -> Name -> Bool)
-> (Name -> Name -> Bool)
-> (Name -> Name -> Bool)
-> (Name -> Name -> Bool)
-> (Name -> Name -> Name)
-> (Name -> Name -> Name)
-> Ord 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
$ccompare :: Name -> Name -> Ordering
compare :: Name -> Name -> Ordering
$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
>= :: Name -> Name -> Bool
$cmax :: Name -> Name -> Name
max :: Name -> Name -> Name
$cmin :: Name -> Name -> Name
min :: Name -> Name -> Name
Ord, ReadPrec [Name]
ReadPrec Name
Int -> ReadS Name
ReadS [Name]
(Int -> ReadS Name)
-> ReadS [Name] -> ReadPrec Name -> ReadPrec [Name] -> Read Name
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Name
readsPrec :: Int -> ReadS Name
$creadList :: ReadS [Name]
readList :: ReadS [Name]
$creadPrec :: ReadPrec Name
readPrec :: ReadPrec Name
$creadListPrec :: ReadPrec [Name]
readListPrec :: ReadPrec [Name]
Read, Int -> Name -> ShowS
[Name] -> ShowS
Name -> String
(Int -> Name -> ShowS)
-> (Name -> String) -> ([Name] -> ShowS) -> Show Name
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Name -> ShowS
showsPrec :: Int -> Name -> ShowS
$cshow :: Name -> String
show :: Name -> String
$cshowList :: [Name] -> ShowS
showList :: [Name] -> ShowS
Show)
_Name :: Name
_Name = (String -> Name
Name String
"hydra/core.Name")
data WrappedTerm =
WrappedTerm {
WrappedTerm -> Name
wrappedTermTypeName :: Name,
WrappedTerm -> Term
wrappedTermObject :: Term}
deriving (WrappedTerm -> WrappedTerm -> Bool
(WrappedTerm -> WrappedTerm -> Bool)
-> (WrappedTerm -> WrappedTerm -> Bool) -> Eq WrappedTerm
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: WrappedTerm -> WrappedTerm -> Bool
== :: WrappedTerm -> WrappedTerm -> Bool
$c/= :: WrappedTerm -> WrappedTerm -> Bool
/= :: WrappedTerm -> WrappedTerm -> Bool
Eq, Eq WrappedTerm
Eq WrappedTerm =>
(WrappedTerm -> WrappedTerm -> Ordering)
-> (WrappedTerm -> WrappedTerm -> Bool)
-> (WrappedTerm -> WrappedTerm -> Bool)
-> (WrappedTerm -> WrappedTerm -> Bool)
-> (WrappedTerm -> WrappedTerm -> Bool)
-> (WrappedTerm -> WrappedTerm -> WrappedTerm)
-> (WrappedTerm -> WrappedTerm -> WrappedTerm)
-> Ord WrappedTerm
WrappedTerm -> WrappedTerm -> Bool
WrappedTerm -> WrappedTerm -> Ordering
WrappedTerm -> WrappedTerm -> WrappedTerm
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: WrappedTerm -> WrappedTerm -> Ordering
compare :: WrappedTerm -> WrappedTerm -> Ordering
$c< :: WrappedTerm -> WrappedTerm -> Bool
< :: WrappedTerm -> WrappedTerm -> Bool
$c<= :: WrappedTerm -> WrappedTerm -> Bool
<= :: WrappedTerm -> WrappedTerm -> Bool
$c> :: WrappedTerm -> WrappedTerm -> Bool
> :: WrappedTerm -> WrappedTerm -> Bool
$c>= :: WrappedTerm -> WrappedTerm -> Bool
>= :: WrappedTerm -> WrappedTerm -> Bool
$cmax :: WrappedTerm -> WrappedTerm -> WrappedTerm
max :: WrappedTerm -> WrappedTerm -> WrappedTerm
$cmin :: WrappedTerm -> WrappedTerm -> WrappedTerm
min :: WrappedTerm -> WrappedTerm -> WrappedTerm
Ord, ReadPrec [WrappedTerm]
ReadPrec WrappedTerm
Int -> ReadS WrappedTerm
ReadS [WrappedTerm]
(Int -> ReadS WrappedTerm)
-> ReadS [WrappedTerm]
-> ReadPrec WrappedTerm
-> ReadPrec [WrappedTerm]
-> Read WrappedTerm
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS WrappedTerm
readsPrec :: Int -> ReadS WrappedTerm
$creadList :: ReadS [WrappedTerm]
readList :: ReadS [WrappedTerm]
$creadPrec :: ReadPrec WrappedTerm
readPrec :: ReadPrec WrappedTerm
$creadListPrec :: ReadPrec [WrappedTerm]
readListPrec :: ReadPrec [WrappedTerm]
Read, Int -> WrappedTerm -> ShowS
[WrappedTerm] -> ShowS
WrappedTerm -> String
(Int -> WrappedTerm -> ShowS)
-> (WrappedTerm -> String)
-> ([WrappedTerm] -> ShowS)
-> Show WrappedTerm
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> WrappedTerm -> ShowS
showsPrec :: Int -> WrappedTerm -> ShowS
$cshow :: WrappedTerm -> String
show :: WrappedTerm -> String
$cshowList :: [WrappedTerm] -> ShowS
showList :: [WrappedTerm] -> ShowS
Show)
_WrappedTerm :: Name
_WrappedTerm = (String -> Name
Name String
"hydra/core.WrappedTerm")
_WrappedTerm_typeName :: Name
_WrappedTerm_typeName = (String -> Name
Name String
"typeName")
_WrappedTerm_object :: Name
_WrappedTerm_object = (String -> Name
Name String
"object")
data WrappedType =
WrappedType {
WrappedType -> Name
wrappedTypeTypeName :: Name,
WrappedType -> Type
wrappedTypeObject :: Type}
deriving (WrappedType -> WrappedType -> Bool
(WrappedType -> WrappedType -> Bool)
-> (WrappedType -> WrappedType -> Bool) -> Eq WrappedType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: WrappedType -> WrappedType -> Bool
== :: WrappedType -> WrappedType -> Bool
$c/= :: WrappedType -> WrappedType -> Bool
/= :: WrappedType -> WrappedType -> Bool
Eq, Eq WrappedType
Eq WrappedType =>
(WrappedType -> WrappedType -> Ordering)
-> (WrappedType -> WrappedType -> Bool)
-> (WrappedType -> WrappedType -> Bool)
-> (WrappedType -> WrappedType -> Bool)
-> (WrappedType -> WrappedType -> Bool)
-> (WrappedType -> WrappedType -> WrappedType)
-> (WrappedType -> WrappedType -> WrappedType)
-> Ord WrappedType
WrappedType -> WrappedType -> Bool
WrappedType -> WrappedType -> Ordering
WrappedType -> WrappedType -> WrappedType
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: WrappedType -> WrappedType -> Ordering
compare :: WrappedType -> WrappedType -> Ordering
$c< :: WrappedType -> WrappedType -> Bool
< :: WrappedType -> WrappedType -> Bool
$c<= :: WrappedType -> WrappedType -> Bool
<= :: WrappedType -> WrappedType -> Bool
$c> :: WrappedType -> WrappedType -> Bool
> :: WrappedType -> WrappedType -> Bool
$c>= :: WrappedType -> WrappedType -> Bool
>= :: WrappedType -> WrappedType -> Bool
$cmax :: WrappedType -> WrappedType -> WrappedType
max :: WrappedType -> WrappedType -> WrappedType
$cmin :: WrappedType -> WrappedType -> WrappedType
min :: WrappedType -> WrappedType -> WrappedType
Ord, ReadPrec [WrappedType]
ReadPrec WrappedType
Int -> ReadS WrappedType
ReadS [WrappedType]
(Int -> ReadS WrappedType)
-> ReadS [WrappedType]
-> ReadPrec WrappedType
-> ReadPrec [WrappedType]
-> Read WrappedType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS WrappedType
readsPrec :: Int -> ReadS WrappedType
$creadList :: ReadS [WrappedType]
readList :: ReadS [WrappedType]
$creadPrec :: ReadPrec WrappedType
readPrec :: ReadPrec WrappedType
$creadListPrec :: ReadPrec [WrappedType]
readListPrec :: ReadPrec [WrappedType]
Read, Int -> WrappedType -> ShowS
[WrappedType] -> ShowS
WrappedType -> String
(Int -> WrappedType -> ShowS)
-> (WrappedType -> String)
-> ([WrappedType] -> ShowS)
-> Show WrappedType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> WrappedType -> ShowS
showsPrec :: Int -> WrappedType -> ShowS
$cshow :: WrappedType -> String
show :: WrappedType -> String
$cshowList :: [WrappedType] -> ShowS
showList :: [WrappedType] -> ShowS
Show)
_WrappedType :: Name
_WrappedType = (String -> Name
Name String
"hydra/core.WrappedType")
_WrappedType_typeName :: Name
_WrappedType_typeName = (String -> Name
Name String
"typeName")
_WrappedType_object :: Name
_WrappedType_object = (String -> Name
Name String
"object")
data OptionalCases =
OptionalCases {
OptionalCases -> Term
optionalCasesNothing :: Term,
OptionalCases -> Term
optionalCasesJust :: Term}
deriving (OptionalCases -> OptionalCases -> Bool
(OptionalCases -> OptionalCases -> Bool)
-> (OptionalCases -> OptionalCases -> Bool) -> Eq OptionalCases
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: OptionalCases -> OptionalCases -> Bool
== :: OptionalCases -> OptionalCases -> Bool
$c/= :: OptionalCases -> OptionalCases -> Bool
/= :: OptionalCases -> OptionalCases -> Bool
Eq, Eq OptionalCases
Eq OptionalCases =>
(OptionalCases -> OptionalCases -> Ordering)
-> (OptionalCases -> OptionalCases -> Bool)
-> (OptionalCases -> OptionalCases -> Bool)
-> (OptionalCases -> OptionalCases -> Bool)
-> (OptionalCases -> OptionalCases -> Bool)
-> (OptionalCases -> OptionalCases -> OptionalCases)
-> (OptionalCases -> OptionalCases -> OptionalCases)
-> Ord OptionalCases
OptionalCases -> OptionalCases -> Bool
OptionalCases -> OptionalCases -> Ordering
OptionalCases -> OptionalCases -> OptionalCases
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: OptionalCases -> OptionalCases -> Ordering
compare :: OptionalCases -> OptionalCases -> Ordering
$c< :: OptionalCases -> OptionalCases -> Bool
< :: OptionalCases -> OptionalCases -> Bool
$c<= :: OptionalCases -> OptionalCases -> Bool
<= :: OptionalCases -> OptionalCases -> Bool
$c> :: OptionalCases -> OptionalCases -> Bool
> :: OptionalCases -> OptionalCases -> Bool
$c>= :: OptionalCases -> OptionalCases -> Bool
>= :: OptionalCases -> OptionalCases -> Bool
$cmax :: OptionalCases -> OptionalCases -> OptionalCases
max :: OptionalCases -> OptionalCases -> OptionalCases
$cmin :: OptionalCases -> OptionalCases -> OptionalCases
min :: OptionalCases -> OptionalCases -> OptionalCases
Ord, ReadPrec [OptionalCases]
ReadPrec OptionalCases
Int -> ReadS OptionalCases
ReadS [OptionalCases]
(Int -> ReadS OptionalCases)
-> ReadS [OptionalCases]
-> ReadPrec OptionalCases
-> ReadPrec [OptionalCases]
-> Read OptionalCases
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS OptionalCases
readsPrec :: Int -> ReadS OptionalCases
$creadList :: ReadS [OptionalCases]
readList :: ReadS [OptionalCases]
$creadPrec :: ReadPrec OptionalCases
readPrec :: ReadPrec OptionalCases
$creadListPrec :: ReadPrec [OptionalCases]
readListPrec :: ReadPrec [OptionalCases]
Read, Int -> OptionalCases -> ShowS
[OptionalCases] -> ShowS
OptionalCases -> String
(Int -> OptionalCases -> ShowS)
-> (OptionalCases -> String)
-> ([OptionalCases] -> ShowS)
-> Show OptionalCases
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> OptionalCases -> ShowS
showsPrec :: Int -> OptionalCases -> ShowS
$cshow :: OptionalCases -> String
show :: OptionalCases -> String
$cshowList :: [OptionalCases] -> ShowS
showList :: [OptionalCases] -> ShowS
Show)
_OptionalCases :: Name
_OptionalCases = (String -> Name
Name String
"hydra/core.OptionalCases")
_OptionalCases_nothing :: Name
_OptionalCases_nothing = (String -> Name
Name String
"nothing")
_OptionalCases_just :: Name
_OptionalCases_just = (String -> Name
Name String
"just")
data Projection =
Projection {
Projection -> Name
projectionTypeName :: Name,
Projection -> Name
projectionField :: Name}
deriving (Projection -> Projection -> Bool
(Projection -> Projection -> Bool)
-> (Projection -> Projection -> Bool) -> Eq Projection
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Projection -> Projection -> Bool
== :: Projection -> Projection -> Bool
$c/= :: Projection -> Projection -> Bool
/= :: Projection -> Projection -> Bool
Eq, Eq Projection
Eq Projection =>
(Projection -> Projection -> Ordering)
-> (Projection -> Projection -> Bool)
-> (Projection -> Projection -> Bool)
-> (Projection -> Projection -> Bool)
-> (Projection -> Projection -> Bool)
-> (Projection -> Projection -> Projection)
-> (Projection -> Projection -> Projection)
-> Ord Projection
Projection -> Projection -> Bool
Projection -> Projection -> Ordering
Projection -> Projection -> Projection
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Projection -> Projection -> Ordering
compare :: Projection -> Projection -> Ordering
$c< :: Projection -> Projection -> Bool
< :: Projection -> Projection -> Bool
$c<= :: Projection -> Projection -> Bool
<= :: Projection -> Projection -> Bool
$c> :: Projection -> Projection -> Bool
> :: Projection -> Projection -> Bool
$c>= :: Projection -> Projection -> Bool
>= :: Projection -> Projection -> Bool
$cmax :: Projection -> Projection -> Projection
max :: Projection -> Projection -> Projection
$cmin :: Projection -> Projection -> Projection
min :: Projection -> Projection -> Projection
Ord, ReadPrec [Projection]
ReadPrec Projection
Int -> ReadS Projection
ReadS [Projection]
(Int -> ReadS Projection)
-> ReadS [Projection]
-> ReadPrec Projection
-> ReadPrec [Projection]
-> Read Projection
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Projection
readsPrec :: Int -> ReadS Projection
$creadList :: ReadS [Projection]
readList :: ReadS [Projection]
$creadPrec :: ReadPrec Projection
readPrec :: ReadPrec Projection
$creadListPrec :: ReadPrec [Projection]
readListPrec :: ReadPrec [Projection]
Read, Int -> Projection -> ShowS
[Projection] -> ShowS
Projection -> String
(Int -> Projection -> ShowS)
-> (Projection -> String)
-> ([Projection] -> ShowS)
-> Show Projection
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Projection -> ShowS
showsPrec :: Int -> Projection -> ShowS
$cshow :: Projection -> String
show :: Projection -> String
$cshowList :: [Projection] -> ShowS
showList :: [Projection] -> ShowS
Show)
_Projection :: Name
_Projection = (String -> Name
Name String
"hydra/core.Projection")
_Projection_typeName :: Name
_Projection_typeName = (String -> Name
Name String
"typeName")
_Projection_field :: Name
_Projection_field = (String -> Name
Name String
"field")
data Record =
Record {
Record -> Name
recordTypeName :: Name,
Record -> [Field]
recordFields :: [Field]}
deriving (Record -> Record -> Bool
(Record -> Record -> Bool)
-> (Record -> Record -> Bool) -> Eq Record
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Record -> Record -> Bool
== :: Record -> Record -> Bool
$c/= :: Record -> Record -> Bool
/= :: Record -> Record -> Bool
Eq, Eq Record
Eq Record =>
(Record -> Record -> Ordering)
-> (Record -> Record -> Bool)
-> (Record -> Record -> Bool)
-> (Record -> Record -> Bool)
-> (Record -> Record -> Bool)
-> (Record -> Record -> Record)
-> (Record -> Record -> Record)
-> Ord Record
Record -> Record -> Bool
Record -> Record -> Ordering
Record -> Record -> Record
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Record -> Record -> Ordering
compare :: Record -> Record -> Ordering
$c< :: Record -> Record -> Bool
< :: Record -> Record -> Bool
$c<= :: Record -> Record -> Bool
<= :: Record -> Record -> Bool
$c> :: Record -> Record -> Bool
> :: Record -> Record -> Bool
$c>= :: Record -> Record -> Bool
>= :: Record -> Record -> Bool
$cmax :: Record -> Record -> Record
max :: Record -> Record -> Record
$cmin :: Record -> Record -> Record
min :: Record -> Record -> Record
Ord, ReadPrec [Record]
ReadPrec Record
Int -> ReadS Record
ReadS [Record]
(Int -> ReadS Record)
-> ReadS [Record]
-> ReadPrec Record
-> ReadPrec [Record]
-> Read Record
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Record
readsPrec :: Int -> ReadS Record
$creadList :: ReadS [Record]
readList :: ReadS [Record]
$creadPrec :: ReadPrec Record
readPrec :: ReadPrec Record
$creadListPrec :: ReadPrec [Record]
readListPrec :: ReadPrec [Record]
Read, Int -> Record -> ShowS
[Record] -> ShowS
Record -> String
(Int -> Record -> ShowS)
-> (Record -> String) -> ([Record] -> ShowS) -> Show Record
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Record -> ShowS
showsPrec :: Int -> Record -> ShowS
$cshow :: Record -> String
show :: Record -> String
$cshowList :: [Record] -> ShowS
showList :: [Record] -> ShowS
Show)
_Record :: Name
_Record = (String -> Name
Name String
"hydra/core.Record")
_Record_typeName :: Name
_Record_typeName = (String -> Name
Name String
"typeName")
_Record_fields :: Name
_Record_fields = (String -> Name
Name String
"fields")
data RowType =
RowType {
RowType -> Name
rowTypeTypeName :: Name,
RowType -> Maybe Name
rowTypeExtends :: (Maybe Name),
RowType -> [FieldType]
rowTypeFields :: [FieldType]}
deriving (RowType -> RowType -> Bool
(RowType -> RowType -> Bool)
-> (RowType -> RowType -> Bool) -> Eq RowType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RowType -> RowType -> Bool
== :: RowType -> RowType -> Bool
$c/= :: RowType -> RowType -> Bool
/= :: RowType -> RowType -> Bool
Eq, Eq RowType
Eq RowType =>
(RowType -> RowType -> Ordering)
-> (RowType -> RowType -> Bool)
-> (RowType -> RowType -> Bool)
-> (RowType -> RowType -> Bool)
-> (RowType -> RowType -> Bool)
-> (RowType -> RowType -> RowType)
-> (RowType -> RowType -> RowType)
-> Ord RowType
RowType -> RowType -> Bool
RowType -> RowType -> Ordering
RowType -> RowType -> RowType
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: RowType -> RowType -> Ordering
compare :: RowType -> RowType -> Ordering
$c< :: RowType -> RowType -> Bool
< :: RowType -> RowType -> Bool
$c<= :: RowType -> RowType -> Bool
<= :: RowType -> RowType -> Bool
$c> :: RowType -> RowType -> Bool
> :: RowType -> RowType -> Bool
$c>= :: RowType -> RowType -> Bool
>= :: RowType -> RowType -> Bool
$cmax :: RowType -> RowType -> RowType
max :: RowType -> RowType -> RowType
$cmin :: RowType -> RowType -> RowType
min :: RowType -> RowType -> RowType
Ord, ReadPrec [RowType]
ReadPrec RowType
Int -> ReadS RowType
ReadS [RowType]
(Int -> ReadS RowType)
-> ReadS [RowType]
-> ReadPrec RowType
-> ReadPrec [RowType]
-> Read RowType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS RowType
readsPrec :: Int -> ReadS RowType
$creadList :: ReadS [RowType]
readList :: ReadS [RowType]
$creadPrec :: ReadPrec RowType
readPrec :: ReadPrec RowType
$creadListPrec :: ReadPrec [RowType]
readListPrec :: ReadPrec [RowType]
Read, Int -> RowType -> ShowS
[RowType] -> ShowS
RowType -> String
(Int -> RowType -> ShowS)
-> (RowType -> String) -> ([RowType] -> ShowS) -> Show RowType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RowType -> ShowS
showsPrec :: Int -> RowType -> ShowS
$cshow :: RowType -> String
show :: RowType -> String
$cshowList :: [RowType] -> ShowS
showList :: [RowType] -> ShowS
Show)
_RowType :: Name
_RowType = (String -> Name
Name String
"hydra/core.RowType")
_RowType_typeName :: Name
_RowType_typeName = (String -> Name
Name String
"typeName")
_RowType_extends :: Name
_RowType_extends = (String -> Name
Name String
"extends")
_RowType_fields :: Name
_RowType_fields = (String -> Name
Name String
"fields")
data Sum =
Sum {
Sum -> Int
sumIndex :: Int,
Sum -> Int
sumSize :: Int,
Sum -> Term
sumTerm :: Term}
deriving (Sum -> Sum -> Bool
(Sum -> Sum -> Bool) -> (Sum -> Sum -> Bool) -> Eq Sum
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Sum -> Sum -> Bool
== :: Sum -> Sum -> Bool
$c/= :: Sum -> Sum -> Bool
/= :: Sum -> Sum -> Bool
Eq, Eq Sum
Eq Sum =>
(Sum -> Sum -> Ordering)
-> (Sum -> Sum -> Bool)
-> (Sum -> Sum -> Bool)
-> (Sum -> Sum -> Bool)
-> (Sum -> Sum -> Bool)
-> (Sum -> Sum -> Sum)
-> (Sum -> Sum -> Sum)
-> Ord Sum
Sum -> Sum -> Bool
Sum -> Sum -> Ordering
Sum -> Sum -> Sum
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Sum -> Sum -> Ordering
compare :: Sum -> Sum -> Ordering
$c< :: Sum -> Sum -> Bool
< :: Sum -> Sum -> Bool
$c<= :: Sum -> Sum -> Bool
<= :: Sum -> Sum -> Bool
$c> :: Sum -> Sum -> Bool
> :: Sum -> Sum -> Bool
$c>= :: Sum -> Sum -> Bool
>= :: Sum -> Sum -> Bool
$cmax :: Sum -> Sum -> Sum
max :: Sum -> Sum -> Sum
$cmin :: Sum -> Sum -> Sum
min :: Sum -> Sum -> Sum
Ord, ReadPrec [Sum]
ReadPrec Sum
Int -> ReadS Sum
ReadS [Sum]
(Int -> ReadS Sum)
-> ReadS [Sum] -> ReadPrec Sum -> ReadPrec [Sum] -> Read Sum
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Sum
readsPrec :: Int -> ReadS Sum
$creadList :: ReadS [Sum]
readList :: ReadS [Sum]
$creadPrec :: ReadPrec Sum
readPrec :: ReadPrec Sum
$creadListPrec :: ReadPrec [Sum]
readListPrec :: ReadPrec [Sum]
Read, Int -> Sum -> ShowS
[Sum] -> ShowS
Sum -> String
(Int -> Sum -> ShowS)
-> (Sum -> String) -> ([Sum] -> ShowS) -> Show Sum
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Sum -> ShowS
showsPrec :: Int -> Sum -> ShowS
$cshow :: Sum -> String
show :: Sum -> String
$cshowList :: [Sum] -> ShowS
showList :: [Sum] -> ShowS
Show)
_Sum :: Name
_Sum = (String -> Name
Name String
"hydra/core.Sum")
_Sum_index :: Name
_Sum_index = (String -> Name
Name String
"index")
_Sum_size :: Name
_Sum_size = (String -> Name
Name String
"size")
_Sum_term :: Name
_Sum_term = (String -> Name
Name String
"term")
data Term =
TermAnnotated AnnotatedTerm |
TermApplication Application |
TermFunction Function |
TermLet Let |
TermList [Term] |
TermLiteral Literal |
TermMap (Map Term Term) |
TermOptional (Maybe Term) |
TermProduct [Term] |
TermRecord Record |
TermSet (Set Term) |
TermSum Sum |
TermTyped TypedTerm |
TermUnion Injection |
TermVariable Name |
TermWrap WrappedTerm
deriving (Term -> Term -> Bool
(Term -> Term -> Bool) -> (Term -> Term -> Bool) -> Eq Term
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Term -> Term -> Bool
== :: Term -> Term -> Bool
$c/= :: Term -> Term -> Bool
/= :: Term -> Term -> Bool
Eq, Eq Term
Eq Term =>
(Term -> Term -> Ordering)
-> (Term -> Term -> Bool)
-> (Term -> Term -> Bool)
-> (Term -> Term -> Bool)
-> (Term -> Term -> Bool)
-> (Term -> Term -> Term)
-> (Term -> Term -> Term)
-> Ord Term
Term -> Term -> Bool
Term -> Term -> Ordering
Term -> Term -> Term
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Term -> Term -> Ordering
compare :: Term -> Term -> Ordering
$c< :: Term -> Term -> Bool
< :: Term -> Term -> Bool
$c<= :: Term -> Term -> Bool
<= :: Term -> Term -> Bool
$c> :: Term -> Term -> Bool
> :: Term -> Term -> Bool
$c>= :: Term -> Term -> Bool
>= :: Term -> Term -> Bool
$cmax :: Term -> Term -> Term
max :: Term -> Term -> Term
$cmin :: Term -> Term -> Term
min :: Term -> Term -> Term
Ord, ReadPrec [Term]
ReadPrec Term
Int -> ReadS Term
ReadS [Term]
(Int -> ReadS Term)
-> ReadS [Term] -> ReadPrec Term -> ReadPrec [Term] -> Read Term
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Term
readsPrec :: Int -> ReadS Term
$creadList :: ReadS [Term]
readList :: ReadS [Term]
$creadPrec :: ReadPrec Term
readPrec :: ReadPrec Term
$creadListPrec :: ReadPrec [Term]
readListPrec :: ReadPrec [Term]
Read, Int -> Term -> ShowS
[Term] -> ShowS
Term -> String
(Int -> Term -> ShowS)
-> (Term -> String) -> ([Term] -> ShowS) -> Show Term
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Term -> ShowS
showsPrec :: Int -> Term -> ShowS
$cshow :: Term -> String
show :: Term -> String
$cshowList :: [Term] -> ShowS
showList :: [Term] -> ShowS
Show)
_Term :: Name
_Term = (String -> Name
Name String
"hydra/core.Term")
_Term_annotated :: Name
_Term_annotated = (String -> Name
Name String
"annotated")
_Term_application :: Name
_Term_application = (String -> Name
Name String
"application")
_Term_function :: Name
_Term_function = (String -> Name
Name String
"function")
_Term_let :: Name
_Term_let = (String -> Name
Name String
"let")
_Term_list :: Name
_Term_list = (String -> Name
Name String
"list")
_Term_literal :: Name
_Term_literal = (String -> Name
Name String
"literal")
_Term_map :: Name
_Term_map = (String -> Name
Name String
"map")
_Term_optional :: Name
_Term_optional = (String -> Name
Name String
"optional")
_Term_product :: Name
_Term_product = (String -> Name
Name String
"product")
_Term_record :: Name
_Term_record = (String -> Name
Name String
"record")
_Term_set :: Name
_Term_set = (String -> Name
Name String
"set")
_Term_sum :: Name
_Term_sum = (String -> Name
Name String
"sum")
_Term_typed :: Name
_Term_typed = (String -> Name
Name String
"typed")
_Term_union :: Name
_Term_union = (String -> Name
Name String
"union")
_Term_variable :: Name
_Term_variable = (String -> Name
Name String
"variable")
_Term_wrap :: Name
_Term_wrap = (String -> Name
Name String
"wrap")
data TupleProjection =
TupleProjection {
TupleProjection -> Int
tupleProjectionArity :: Int,
TupleProjection -> Int
tupleProjectionIndex :: Int}
deriving (TupleProjection -> TupleProjection -> Bool
(TupleProjection -> TupleProjection -> Bool)
-> (TupleProjection -> TupleProjection -> Bool)
-> Eq TupleProjection
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TupleProjection -> TupleProjection -> Bool
== :: TupleProjection -> TupleProjection -> Bool
$c/= :: TupleProjection -> TupleProjection -> Bool
/= :: TupleProjection -> TupleProjection -> Bool
Eq, Eq TupleProjection
Eq TupleProjection =>
(TupleProjection -> TupleProjection -> Ordering)
-> (TupleProjection -> TupleProjection -> Bool)
-> (TupleProjection -> TupleProjection -> Bool)
-> (TupleProjection -> TupleProjection -> Bool)
-> (TupleProjection -> TupleProjection -> Bool)
-> (TupleProjection -> TupleProjection -> TupleProjection)
-> (TupleProjection -> TupleProjection -> TupleProjection)
-> Ord TupleProjection
TupleProjection -> TupleProjection -> Bool
TupleProjection -> TupleProjection -> Ordering
TupleProjection -> TupleProjection -> TupleProjection
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: TupleProjection -> TupleProjection -> Ordering
compare :: TupleProjection -> TupleProjection -> Ordering
$c< :: TupleProjection -> TupleProjection -> Bool
< :: TupleProjection -> TupleProjection -> Bool
$c<= :: TupleProjection -> TupleProjection -> Bool
<= :: TupleProjection -> TupleProjection -> Bool
$c> :: TupleProjection -> TupleProjection -> Bool
> :: TupleProjection -> TupleProjection -> Bool
$c>= :: TupleProjection -> TupleProjection -> Bool
>= :: TupleProjection -> TupleProjection -> Bool
$cmax :: TupleProjection -> TupleProjection -> TupleProjection
max :: TupleProjection -> TupleProjection -> TupleProjection
$cmin :: TupleProjection -> TupleProjection -> TupleProjection
min :: TupleProjection -> TupleProjection -> TupleProjection
Ord, ReadPrec [TupleProjection]
ReadPrec TupleProjection
Int -> ReadS TupleProjection
ReadS [TupleProjection]
(Int -> ReadS TupleProjection)
-> ReadS [TupleProjection]
-> ReadPrec TupleProjection
-> ReadPrec [TupleProjection]
-> Read TupleProjection
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS TupleProjection
readsPrec :: Int -> ReadS TupleProjection
$creadList :: ReadS [TupleProjection]
readList :: ReadS [TupleProjection]
$creadPrec :: ReadPrec TupleProjection
readPrec :: ReadPrec TupleProjection
$creadListPrec :: ReadPrec [TupleProjection]
readListPrec :: ReadPrec [TupleProjection]
Read, Int -> TupleProjection -> ShowS
[TupleProjection] -> ShowS
TupleProjection -> String
(Int -> TupleProjection -> ShowS)
-> (TupleProjection -> String)
-> ([TupleProjection] -> ShowS)
-> Show TupleProjection
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TupleProjection -> ShowS
showsPrec :: Int -> TupleProjection -> ShowS
$cshow :: TupleProjection -> String
show :: TupleProjection -> String
$cshowList :: [TupleProjection] -> ShowS
showList :: [TupleProjection] -> ShowS
Show)
_TupleProjection :: Name
_TupleProjection = (String -> Name
Name String
"hydra/core.TupleProjection")
_TupleProjection_arity :: Name
_TupleProjection_arity = (String -> Name
Name String
"arity")
_TupleProjection_index :: Name
_TupleProjection_index = (String -> Name
Name String
"index")
data Type =
TypeAnnotated AnnotatedType |
TypeApplication ApplicationType |
TypeFunction FunctionType |
TypeLambda LambdaType |
TypeList Type |
TypeLiteral LiteralType |
TypeMap MapType |
TypeOptional Type |
TypeProduct [Type] |
TypeRecord RowType |
TypeSet Type |
TypeSum [Type] |
TypeUnion RowType |
TypeVariable Name |
TypeWrap WrappedType
deriving (Type -> Type -> Bool
(Type -> Type -> Bool) -> (Type -> Type -> Bool) -> Eq Type
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Type -> Type -> Bool
== :: Type -> Type -> Bool
$c/= :: Type -> Type -> Bool
/= :: Type -> Type -> Bool
Eq, Eq Type
Eq Type =>
(Type -> Type -> Ordering)
-> (Type -> Type -> Bool)
-> (Type -> Type -> Bool)
-> (Type -> Type -> Bool)
-> (Type -> Type -> Bool)
-> (Type -> Type -> Type)
-> (Type -> Type -> Type)
-> Ord Type
Type -> Type -> Bool
Type -> Type -> Ordering
Type -> Type -> Type
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Type -> Type -> Ordering
compare :: Type -> Type -> Ordering
$c< :: Type -> Type -> Bool
< :: Type -> Type -> Bool
$c<= :: Type -> Type -> Bool
<= :: Type -> Type -> Bool
$c> :: Type -> Type -> Bool
> :: Type -> Type -> Bool
$c>= :: Type -> Type -> Bool
>= :: Type -> Type -> Bool
$cmax :: Type -> Type -> Type
max :: Type -> Type -> Type
$cmin :: Type -> Type -> Type
min :: Type -> Type -> Type
Ord, ReadPrec [Type]
ReadPrec Type
Int -> ReadS Type
ReadS [Type]
(Int -> ReadS Type)
-> ReadS [Type] -> ReadPrec Type -> ReadPrec [Type] -> Read Type
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Type
readsPrec :: Int -> ReadS Type
$creadList :: ReadS [Type]
readList :: ReadS [Type]
$creadPrec :: ReadPrec Type
readPrec :: ReadPrec Type
$creadListPrec :: ReadPrec [Type]
readListPrec :: ReadPrec [Type]
Read, Int -> Type -> ShowS
[Type] -> ShowS
Type -> String
(Int -> Type -> ShowS)
-> (Type -> String) -> ([Type] -> ShowS) -> Show Type
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Type -> ShowS
showsPrec :: Int -> Type -> ShowS
$cshow :: Type -> String
show :: Type -> String
$cshowList :: [Type] -> ShowS
showList :: [Type] -> ShowS
Show)
_Type :: Name
_Type = (String -> Name
Name String
"hydra/core.Type")
_Type_annotated :: Name
_Type_annotated = (String -> Name
Name String
"annotated")
_Type_application :: Name
_Type_application = (String -> Name
Name String
"application")
_Type_function :: Name
_Type_function = (String -> Name
Name String
"function")
_Type_lambda :: Name
_Type_lambda = (String -> Name
Name String
"lambda")
_Type_list :: Name
_Type_list = (String -> Name
Name String
"list")
_Type_literal :: Name
_Type_literal = (String -> Name
Name String
"literal")
_Type_map :: Name
_Type_map = (String -> Name
Name String
"map")
_Type_optional :: Name
_Type_optional = (String -> Name
Name String
"optional")
_Type_product :: Name
_Type_product = (String -> Name
Name String
"product")
_Type_record :: Name
_Type_record = (String -> Name
Name String
"record")
_Type_set :: Name
_Type_set = (String -> Name
Name String
"set")
_Type_sum :: Name
_Type_sum = (String -> Name
Name String
"sum")
_Type_union :: Name
_Type_union = (String -> Name
Name String
"union")
_Type_variable :: Name
_Type_variable = (String -> Name
Name String
"variable")
_Type_wrap :: Name
_Type_wrap = (String -> Name
Name String
"wrap")
data TypeScheme =
TypeScheme {
TypeScheme -> [Name]
typeSchemeVariables :: [Name],
TypeScheme -> Type
typeSchemeType :: Type}
deriving (TypeScheme -> TypeScheme -> Bool
(TypeScheme -> TypeScheme -> Bool)
-> (TypeScheme -> TypeScheme -> Bool) -> Eq TypeScheme
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TypeScheme -> TypeScheme -> Bool
== :: TypeScheme -> TypeScheme -> Bool
$c/= :: TypeScheme -> TypeScheme -> Bool
/= :: TypeScheme -> TypeScheme -> Bool
Eq, Eq TypeScheme
Eq TypeScheme =>
(TypeScheme -> TypeScheme -> Ordering)
-> (TypeScheme -> TypeScheme -> Bool)
-> (TypeScheme -> TypeScheme -> Bool)
-> (TypeScheme -> TypeScheme -> Bool)
-> (TypeScheme -> TypeScheme -> Bool)
-> (TypeScheme -> TypeScheme -> TypeScheme)
-> (TypeScheme -> TypeScheme -> TypeScheme)
-> Ord TypeScheme
TypeScheme -> TypeScheme -> Bool
TypeScheme -> TypeScheme -> Ordering
TypeScheme -> TypeScheme -> TypeScheme
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: TypeScheme -> TypeScheme -> Ordering
compare :: TypeScheme -> TypeScheme -> Ordering
$c< :: TypeScheme -> TypeScheme -> Bool
< :: TypeScheme -> TypeScheme -> Bool
$c<= :: TypeScheme -> TypeScheme -> Bool
<= :: TypeScheme -> TypeScheme -> Bool
$c> :: TypeScheme -> TypeScheme -> Bool
> :: TypeScheme -> TypeScheme -> Bool
$c>= :: TypeScheme -> TypeScheme -> Bool
>= :: TypeScheme -> TypeScheme -> Bool
$cmax :: TypeScheme -> TypeScheme -> TypeScheme
max :: TypeScheme -> TypeScheme -> TypeScheme
$cmin :: TypeScheme -> TypeScheme -> TypeScheme
min :: TypeScheme -> TypeScheme -> TypeScheme
Ord, ReadPrec [TypeScheme]
ReadPrec TypeScheme
Int -> ReadS TypeScheme
ReadS [TypeScheme]
(Int -> ReadS TypeScheme)
-> ReadS [TypeScheme]
-> ReadPrec TypeScheme
-> ReadPrec [TypeScheme]
-> Read TypeScheme
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS TypeScheme
readsPrec :: Int -> ReadS TypeScheme
$creadList :: ReadS [TypeScheme]
readList :: ReadS [TypeScheme]
$creadPrec :: ReadPrec TypeScheme
readPrec :: ReadPrec TypeScheme
$creadListPrec :: ReadPrec [TypeScheme]
readListPrec :: ReadPrec [TypeScheme]
Read, Int -> TypeScheme -> ShowS
[TypeScheme] -> ShowS
TypeScheme -> String
(Int -> TypeScheme -> ShowS)
-> (TypeScheme -> String)
-> ([TypeScheme] -> ShowS)
-> Show TypeScheme
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TypeScheme -> ShowS
showsPrec :: Int -> TypeScheme -> ShowS
$cshow :: TypeScheme -> String
show :: TypeScheme -> String
$cshowList :: [TypeScheme] -> ShowS
showList :: [TypeScheme] -> ShowS
Show)
_TypeScheme :: Name
_TypeScheme = (String -> Name
Name String
"hydra/core.TypeScheme")
_TypeScheme_variables :: Name
_TypeScheme_variables = (String -> Name
Name String
"variables")
_TypeScheme_type :: Name
_TypeScheme_type = (String -> Name
Name String
"type")
data TypedTerm =
TypedTerm {
TypedTerm -> Term
typedTermTerm :: Term,
TypedTerm -> Type
typedTermType :: Type}
deriving (TypedTerm -> TypedTerm -> Bool
(TypedTerm -> TypedTerm -> Bool)
-> (TypedTerm -> TypedTerm -> Bool) -> Eq TypedTerm
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TypedTerm -> TypedTerm -> Bool
== :: TypedTerm -> TypedTerm -> Bool
$c/= :: TypedTerm -> TypedTerm -> Bool
/= :: TypedTerm -> TypedTerm -> Bool
Eq, Eq TypedTerm
Eq TypedTerm =>
(TypedTerm -> TypedTerm -> Ordering)
-> (TypedTerm -> TypedTerm -> Bool)
-> (TypedTerm -> TypedTerm -> Bool)
-> (TypedTerm -> TypedTerm -> Bool)
-> (TypedTerm -> TypedTerm -> Bool)
-> (TypedTerm -> TypedTerm -> TypedTerm)
-> (TypedTerm -> TypedTerm -> TypedTerm)
-> Ord TypedTerm
TypedTerm -> TypedTerm -> Bool
TypedTerm -> TypedTerm -> Ordering
TypedTerm -> TypedTerm -> TypedTerm
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: TypedTerm -> TypedTerm -> Ordering
compare :: TypedTerm -> TypedTerm -> Ordering
$c< :: TypedTerm -> TypedTerm -> Bool
< :: TypedTerm -> TypedTerm -> Bool
$c<= :: TypedTerm -> TypedTerm -> Bool
<= :: TypedTerm -> TypedTerm -> Bool
$c> :: TypedTerm -> TypedTerm -> Bool
> :: TypedTerm -> TypedTerm -> Bool
$c>= :: TypedTerm -> TypedTerm -> Bool
>= :: TypedTerm -> TypedTerm -> Bool
$cmax :: TypedTerm -> TypedTerm -> TypedTerm
max :: TypedTerm -> TypedTerm -> TypedTerm
$cmin :: TypedTerm -> TypedTerm -> TypedTerm
min :: TypedTerm -> TypedTerm -> TypedTerm
Ord, ReadPrec [TypedTerm]
ReadPrec TypedTerm
Int -> ReadS TypedTerm
ReadS [TypedTerm]
(Int -> ReadS TypedTerm)
-> ReadS [TypedTerm]
-> ReadPrec TypedTerm
-> ReadPrec [TypedTerm]
-> Read TypedTerm
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS TypedTerm
readsPrec :: Int -> ReadS TypedTerm
$creadList :: ReadS [TypedTerm]
readList :: ReadS [TypedTerm]
$creadPrec :: ReadPrec TypedTerm
readPrec :: ReadPrec TypedTerm
$creadListPrec :: ReadPrec [TypedTerm]
readListPrec :: ReadPrec [TypedTerm]
Read, Int -> TypedTerm -> ShowS
[TypedTerm] -> ShowS
TypedTerm -> String
(Int -> TypedTerm -> ShowS)
-> (TypedTerm -> String)
-> ([TypedTerm] -> ShowS)
-> Show TypedTerm
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TypedTerm -> ShowS
showsPrec :: Int -> TypedTerm -> ShowS
$cshow :: TypedTerm -> String
show :: TypedTerm -> String
$cshowList :: [TypedTerm] -> ShowS
showList :: [TypedTerm] -> ShowS
Show)
_TypedTerm :: Name
_TypedTerm = (String -> Name
Name String
"hydra/core.TypedTerm")
_TypedTerm_term :: Name
_TypedTerm_term = (String -> Name
Name String
"term")
_TypedTerm_type :: Name
_TypedTerm_type = (String -> Name
Name String
"type")
data Unit =
Unit {}
deriving (Unit -> Unit -> Bool
(Unit -> Unit -> Bool) -> (Unit -> Unit -> Bool) -> Eq Unit
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Unit -> Unit -> Bool
== :: Unit -> Unit -> Bool
$c/= :: Unit -> Unit -> Bool
/= :: Unit -> Unit -> Bool
Eq, Eq Unit
Eq Unit =>
(Unit -> Unit -> Ordering)
-> (Unit -> Unit -> Bool)
-> (Unit -> Unit -> Bool)
-> (Unit -> Unit -> Bool)
-> (Unit -> Unit -> Bool)
-> (Unit -> Unit -> Unit)
-> (Unit -> Unit -> Unit)
-> Ord Unit
Unit -> Unit -> Bool
Unit -> Unit -> Ordering
Unit -> Unit -> Unit
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Unit -> Unit -> Ordering
compare :: Unit -> Unit -> Ordering
$c< :: Unit -> Unit -> Bool
< :: Unit -> Unit -> Bool
$c<= :: Unit -> Unit -> Bool
<= :: Unit -> Unit -> Bool
$c> :: Unit -> Unit -> Bool
> :: Unit -> Unit -> Bool
$c>= :: Unit -> Unit -> Bool
>= :: Unit -> Unit -> Bool
$cmax :: Unit -> Unit -> Unit
max :: Unit -> Unit -> Unit
$cmin :: Unit -> Unit -> Unit
min :: Unit -> Unit -> Unit
Ord, ReadPrec [Unit]
ReadPrec Unit
Int -> ReadS Unit
ReadS [Unit]
(Int -> ReadS Unit)
-> ReadS [Unit] -> ReadPrec Unit -> ReadPrec [Unit] -> Read Unit
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Unit
readsPrec :: Int -> ReadS Unit
$creadList :: ReadS [Unit]
readList :: ReadS [Unit]
$creadPrec :: ReadPrec Unit
readPrec :: ReadPrec Unit
$creadListPrec :: ReadPrec [Unit]
readListPrec :: ReadPrec [Unit]
Read, Int -> Unit -> ShowS
[Unit] -> ShowS
Unit -> String
(Int -> Unit -> ShowS)
-> (Unit -> String) -> ([Unit] -> ShowS) -> Show Unit
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Unit -> ShowS
showsPrec :: Int -> Unit -> ShowS
$cshow :: Unit -> String
show :: Unit -> String
$cshowList :: [Unit] -> ShowS
showList :: [Unit] -> ShowS
Show)
_Unit :: Name
_Unit = (String -> Name
Name String
"hydra/core.Unit")