module Hydra.Langs.Pegasus.Pdl where
import qualified Hydra.Core as Core
import qualified Hydra.Json as Json
import Data.Int
import Data.List as L
import Data.Map as M
import Data.Set as S
data Annotations =
Annotations {
Annotations -> Maybe String
annotationsDoc :: (Maybe String),
Annotations -> Bool
annotationsDeprecated :: Bool}
deriving (Annotations -> Annotations -> Bool
(Annotations -> Annotations -> Bool)
-> (Annotations -> Annotations -> Bool) -> Eq Annotations
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Annotations -> Annotations -> Bool
== :: Annotations -> Annotations -> Bool
$c/= :: Annotations -> Annotations -> Bool
/= :: Annotations -> Annotations -> Bool
Eq, Eq Annotations
Eq Annotations =>
(Annotations -> Annotations -> Ordering)
-> (Annotations -> Annotations -> Bool)
-> (Annotations -> Annotations -> Bool)
-> (Annotations -> Annotations -> Bool)
-> (Annotations -> Annotations -> Bool)
-> (Annotations -> Annotations -> Annotations)
-> (Annotations -> Annotations -> Annotations)
-> Ord Annotations
Annotations -> Annotations -> Bool
Annotations -> Annotations -> Ordering
Annotations -> Annotations -> Annotations
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Annotations -> Annotations -> Ordering
compare :: Annotations -> Annotations -> Ordering
$c< :: Annotations -> Annotations -> Bool
< :: Annotations -> Annotations -> Bool
$c<= :: Annotations -> Annotations -> Bool
<= :: Annotations -> Annotations -> Bool
$c> :: Annotations -> Annotations -> Bool
> :: Annotations -> Annotations -> Bool
$c>= :: Annotations -> Annotations -> Bool
>= :: Annotations -> Annotations -> Bool
$cmax :: Annotations -> Annotations -> Annotations
max :: Annotations -> Annotations -> Annotations
$cmin :: Annotations -> Annotations -> Annotations
min :: Annotations -> Annotations -> Annotations
Ord, ReadPrec [Annotations]
ReadPrec Annotations
Int -> ReadS Annotations
ReadS [Annotations]
(Int -> ReadS Annotations)
-> ReadS [Annotations]
-> ReadPrec Annotations
-> ReadPrec [Annotations]
-> Read Annotations
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Annotations
readsPrec :: Int -> ReadS Annotations
$creadList :: ReadS [Annotations]
readList :: ReadS [Annotations]
$creadPrec :: ReadPrec Annotations
readPrec :: ReadPrec Annotations
$creadListPrec :: ReadPrec [Annotations]
readListPrec :: ReadPrec [Annotations]
Read, Int -> Annotations -> ShowS
[Annotations] -> ShowS
Annotations -> String
(Int -> Annotations -> ShowS)
-> (Annotations -> String)
-> ([Annotations] -> ShowS)
-> Show Annotations
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Annotations -> ShowS
showsPrec :: Int -> Annotations -> ShowS
$cshow :: Annotations -> String
show :: Annotations -> String
$cshowList :: [Annotations] -> ShowS
showList :: [Annotations] -> ShowS
Show)
_Annotations :: Name
_Annotations = (String -> Name
Core.Name String
"hydra/langs/pegasus/pdl.Annotations")
_Annotations_doc :: Name
_Annotations_doc = (String -> Name
Core.Name String
"doc")
_Annotations_deprecated :: Name
_Annotations_deprecated = (String -> Name
Core.Name String
"deprecated")
data EnumField =
EnumField {
EnumField -> EnumFieldName
enumFieldName :: EnumFieldName,
EnumField -> Annotations
enumFieldAnnotations :: Annotations}
deriving (EnumField -> EnumField -> Bool
(EnumField -> EnumField -> Bool)
-> (EnumField -> EnumField -> Bool) -> Eq EnumField
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: EnumField -> EnumField -> Bool
== :: EnumField -> EnumField -> Bool
$c/= :: EnumField -> EnumField -> Bool
/= :: EnumField -> EnumField -> Bool
Eq, Eq EnumField
Eq EnumField =>
(EnumField -> EnumField -> Ordering)
-> (EnumField -> EnumField -> Bool)
-> (EnumField -> EnumField -> Bool)
-> (EnumField -> EnumField -> Bool)
-> (EnumField -> EnumField -> Bool)
-> (EnumField -> EnumField -> EnumField)
-> (EnumField -> EnumField -> EnumField)
-> Ord EnumField
EnumField -> EnumField -> Bool
EnumField -> EnumField -> Ordering
EnumField -> EnumField -> EnumField
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: EnumField -> EnumField -> Ordering
compare :: EnumField -> EnumField -> Ordering
$c< :: EnumField -> EnumField -> Bool
< :: EnumField -> EnumField -> Bool
$c<= :: EnumField -> EnumField -> Bool
<= :: EnumField -> EnumField -> Bool
$c> :: EnumField -> EnumField -> Bool
> :: EnumField -> EnumField -> Bool
$c>= :: EnumField -> EnumField -> Bool
>= :: EnumField -> EnumField -> Bool
$cmax :: EnumField -> EnumField -> EnumField
max :: EnumField -> EnumField -> EnumField
$cmin :: EnumField -> EnumField -> EnumField
min :: EnumField -> EnumField -> EnumField
Ord, ReadPrec [EnumField]
ReadPrec EnumField
Int -> ReadS EnumField
ReadS [EnumField]
(Int -> ReadS EnumField)
-> ReadS [EnumField]
-> ReadPrec EnumField
-> ReadPrec [EnumField]
-> Read EnumField
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS EnumField
readsPrec :: Int -> ReadS EnumField
$creadList :: ReadS [EnumField]
readList :: ReadS [EnumField]
$creadPrec :: ReadPrec EnumField
readPrec :: ReadPrec EnumField
$creadListPrec :: ReadPrec [EnumField]
readListPrec :: ReadPrec [EnumField]
Read, Int -> EnumField -> ShowS
[EnumField] -> ShowS
EnumField -> String
(Int -> EnumField -> ShowS)
-> (EnumField -> String)
-> ([EnumField] -> ShowS)
-> Show EnumField
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> EnumField -> ShowS
showsPrec :: Int -> EnumField -> ShowS
$cshow :: EnumField -> String
show :: EnumField -> String
$cshowList :: [EnumField] -> ShowS
showList :: [EnumField] -> ShowS
Show)
_EnumField :: Name
_EnumField = (String -> Name
Core.Name String
"hydra/langs/pegasus/pdl.EnumField")
_EnumField_name :: Name
_EnumField_name = (String -> Name
Core.Name String
"name")
_EnumField_annotations :: Name
_EnumField_annotations = (String -> Name
Core.Name String
"annotations")
newtype EnumFieldName =
EnumFieldName {
EnumFieldName -> String
unEnumFieldName :: String}
deriving (EnumFieldName -> EnumFieldName -> Bool
(EnumFieldName -> EnumFieldName -> Bool)
-> (EnumFieldName -> EnumFieldName -> Bool) -> Eq EnumFieldName
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: EnumFieldName -> EnumFieldName -> Bool
== :: EnumFieldName -> EnumFieldName -> Bool
$c/= :: EnumFieldName -> EnumFieldName -> Bool
/= :: EnumFieldName -> EnumFieldName -> Bool
Eq, Eq EnumFieldName
Eq EnumFieldName =>
(EnumFieldName -> EnumFieldName -> Ordering)
-> (EnumFieldName -> EnumFieldName -> Bool)
-> (EnumFieldName -> EnumFieldName -> Bool)
-> (EnumFieldName -> EnumFieldName -> Bool)
-> (EnumFieldName -> EnumFieldName -> Bool)
-> (EnumFieldName -> EnumFieldName -> EnumFieldName)
-> (EnumFieldName -> EnumFieldName -> EnumFieldName)
-> Ord EnumFieldName
EnumFieldName -> EnumFieldName -> Bool
EnumFieldName -> EnumFieldName -> Ordering
EnumFieldName -> EnumFieldName -> EnumFieldName
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: EnumFieldName -> EnumFieldName -> Ordering
compare :: EnumFieldName -> EnumFieldName -> Ordering
$c< :: EnumFieldName -> EnumFieldName -> Bool
< :: EnumFieldName -> EnumFieldName -> Bool
$c<= :: EnumFieldName -> EnumFieldName -> Bool
<= :: EnumFieldName -> EnumFieldName -> Bool
$c> :: EnumFieldName -> EnumFieldName -> Bool
> :: EnumFieldName -> EnumFieldName -> Bool
$c>= :: EnumFieldName -> EnumFieldName -> Bool
>= :: EnumFieldName -> EnumFieldName -> Bool
$cmax :: EnumFieldName -> EnumFieldName -> EnumFieldName
max :: EnumFieldName -> EnumFieldName -> EnumFieldName
$cmin :: EnumFieldName -> EnumFieldName -> EnumFieldName
min :: EnumFieldName -> EnumFieldName -> EnumFieldName
Ord, ReadPrec [EnumFieldName]
ReadPrec EnumFieldName
Int -> ReadS EnumFieldName
ReadS [EnumFieldName]
(Int -> ReadS EnumFieldName)
-> ReadS [EnumFieldName]
-> ReadPrec EnumFieldName
-> ReadPrec [EnumFieldName]
-> Read EnumFieldName
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS EnumFieldName
readsPrec :: Int -> ReadS EnumFieldName
$creadList :: ReadS [EnumFieldName]
readList :: ReadS [EnumFieldName]
$creadPrec :: ReadPrec EnumFieldName
readPrec :: ReadPrec EnumFieldName
$creadListPrec :: ReadPrec [EnumFieldName]
readListPrec :: ReadPrec [EnumFieldName]
Read, Int -> EnumFieldName -> ShowS
[EnumFieldName] -> ShowS
EnumFieldName -> String
(Int -> EnumFieldName -> ShowS)
-> (EnumFieldName -> String)
-> ([EnumFieldName] -> ShowS)
-> Show EnumFieldName
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> EnumFieldName -> ShowS
showsPrec :: Int -> EnumFieldName -> ShowS
$cshow :: EnumFieldName -> String
show :: EnumFieldName -> String
$cshowList :: [EnumFieldName] -> ShowS
showList :: [EnumFieldName] -> ShowS
Show)
_EnumFieldName :: Name
_EnumFieldName = (String -> Name
Core.Name String
"hydra/langs/pegasus/pdl.EnumFieldName")
data EnumSchema =
EnumSchema {
EnumSchema -> [EnumField]
enumSchemaFields :: [EnumField]}
deriving (EnumSchema -> EnumSchema -> Bool
(EnumSchema -> EnumSchema -> Bool)
-> (EnumSchema -> EnumSchema -> Bool) -> Eq EnumSchema
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: EnumSchema -> EnumSchema -> Bool
== :: EnumSchema -> EnumSchema -> Bool
$c/= :: EnumSchema -> EnumSchema -> Bool
/= :: EnumSchema -> EnumSchema -> Bool
Eq, Eq EnumSchema
Eq EnumSchema =>
(EnumSchema -> EnumSchema -> Ordering)
-> (EnumSchema -> EnumSchema -> Bool)
-> (EnumSchema -> EnumSchema -> Bool)
-> (EnumSchema -> EnumSchema -> Bool)
-> (EnumSchema -> EnumSchema -> Bool)
-> (EnumSchema -> EnumSchema -> EnumSchema)
-> (EnumSchema -> EnumSchema -> EnumSchema)
-> Ord EnumSchema
EnumSchema -> EnumSchema -> Bool
EnumSchema -> EnumSchema -> Ordering
EnumSchema -> EnumSchema -> EnumSchema
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: EnumSchema -> EnumSchema -> Ordering
compare :: EnumSchema -> EnumSchema -> Ordering
$c< :: EnumSchema -> EnumSchema -> Bool
< :: EnumSchema -> EnumSchema -> Bool
$c<= :: EnumSchema -> EnumSchema -> Bool
<= :: EnumSchema -> EnumSchema -> Bool
$c> :: EnumSchema -> EnumSchema -> Bool
> :: EnumSchema -> EnumSchema -> Bool
$c>= :: EnumSchema -> EnumSchema -> Bool
>= :: EnumSchema -> EnumSchema -> Bool
$cmax :: EnumSchema -> EnumSchema -> EnumSchema
max :: EnumSchema -> EnumSchema -> EnumSchema
$cmin :: EnumSchema -> EnumSchema -> EnumSchema
min :: EnumSchema -> EnumSchema -> EnumSchema
Ord, ReadPrec [EnumSchema]
ReadPrec EnumSchema
Int -> ReadS EnumSchema
ReadS [EnumSchema]
(Int -> ReadS EnumSchema)
-> ReadS [EnumSchema]
-> ReadPrec EnumSchema
-> ReadPrec [EnumSchema]
-> Read EnumSchema
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS EnumSchema
readsPrec :: Int -> ReadS EnumSchema
$creadList :: ReadS [EnumSchema]
readList :: ReadS [EnumSchema]
$creadPrec :: ReadPrec EnumSchema
readPrec :: ReadPrec EnumSchema
$creadListPrec :: ReadPrec [EnumSchema]
readListPrec :: ReadPrec [EnumSchema]
Read, Int -> EnumSchema -> ShowS
[EnumSchema] -> ShowS
EnumSchema -> String
(Int -> EnumSchema -> ShowS)
-> (EnumSchema -> String)
-> ([EnumSchema] -> ShowS)
-> Show EnumSchema
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> EnumSchema -> ShowS
showsPrec :: Int -> EnumSchema -> ShowS
$cshow :: EnumSchema -> String
show :: EnumSchema -> String
$cshowList :: [EnumSchema] -> ShowS
showList :: [EnumSchema] -> ShowS
Show)
_EnumSchema :: Name
_EnumSchema = (String -> Name
Core.Name String
"hydra/langs/pegasus/pdl.EnumSchema")
_EnumSchema_fields :: Name
_EnumSchema_fields = (String -> Name
Core.Name String
"fields")
newtype FieldName =
FieldName {
FieldName -> String
unFieldName :: String}
deriving (FieldName -> FieldName -> Bool
(FieldName -> FieldName -> Bool)
-> (FieldName -> FieldName -> Bool) -> Eq FieldName
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FieldName -> FieldName -> Bool
== :: FieldName -> FieldName -> Bool
$c/= :: FieldName -> FieldName -> Bool
/= :: FieldName -> FieldName -> Bool
Eq, Eq FieldName
Eq FieldName =>
(FieldName -> FieldName -> Ordering)
-> (FieldName -> FieldName -> Bool)
-> (FieldName -> FieldName -> Bool)
-> (FieldName -> FieldName -> Bool)
-> (FieldName -> FieldName -> Bool)
-> (FieldName -> FieldName -> FieldName)
-> (FieldName -> FieldName -> FieldName)
-> Ord FieldName
FieldName -> FieldName -> Bool
FieldName -> FieldName -> Ordering
FieldName -> FieldName -> FieldName
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: FieldName -> FieldName -> Ordering
compare :: FieldName -> FieldName -> Ordering
$c< :: FieldName -> FieldName -> Bool
< :: FieldName -> FieldName -> Bool
$c<= :: FieldName -> FieldName -> Bool
<= :: FieldName -> FieldName -> Bool
$c> :: FieldName -> FieldName -> Bool
> :: FieldName -> FieldName -> Bool
$c>= :: FieldName -> FieldName -> Bool
>= :: FieldName -> FieldName -> Bool
$cmax :: FieldName -> FieldName -> FieldName
max :: FieldName -> FieldName -> FieldName
$cmin :: FieldName -> FieldName -> FieldName
min :: FieldName -> FieldName -> FieldName
Ord, ReadPrec [FieldName]
ReadPrec FieldName
Int -> ReadS FieldName
ReadS [FieldName]
(Int -> ReadS FieldName)
-> ReadS [FieldName]
-> ReadPrec FieldName
-> ReadPrec [FieldName]
-> Read FieldName
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS FieldName
readsPrec :: Int -> ReadS FieldName
$creadList :: ReadS [FieldName]
readList :: ReadS [FieldName]
$creadPrec :: ReadPrec FieldName
readPrec :: ReadPrec FieldName
$creadListPrec :: ReadPrec [FieldName]
readListPrec :: ReadPrec [FieldName]
Read, Int -> FieldName -> ShowS
[FieldName] -> ShowS
FieldName -> String
(Int -> FieldName -> ShowS)
-> (FieldName -> String)
-> ([FieldName] -> ShowS)
-> Show FieldName
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FieldName -> ShowS
showsPrec :: Int -> FieldName -> ShowS
$cshow :: FieldName -> String
show :: FieldName -> String
$cshowList :: [FieldName] -> ShowS
showList :: [FieldName] -> ShowS
Show)
_FieldName :: Name
_FieldName = (String -> Name
Core.Name String
"hydra/langs/pegasus/pdl.FieldName")
data NamedSchema =
NamedSchema {
NamedSchema -> QualifiedName
namedSchemaQualifiedName :: QualifiedName,
NamedSchema -> NamedSchema_Type
namedSchemaType :: NamedSchema_Type,
NamedSchema -> Annotations
namedSchemaAnnotations :: Annotations}
deriving (NamedSchema -> NamedSchema -> Bool
(NamedSchema -> NamedSchema -> Bool)
-> (NamedSchema -> NamedSchema -> Bool) -> Eq NamedSchema
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: NamedSchema -> NamedSchema -> Bool
== :: NamedSchema -> NamedSchema -> Bool
$c/= :: NamedSchema -> NamedSchema -> Bool
/= :: NamedSchema -> NamedSchema -> Bool
Eq, Eq NamedSchema
Eq NamedSchema =>
(NamedSchema -> NamedSchema -> Ordering)
-> (NamedSchema -> NamedSchema -> Bool)
-> (NamedSchema -> NamedSchema -> Bool)
-> (NamedSchema -> NamedSchema -> Bool)
-> (NamedSchema -> NamedSchema -> Bool)
-> (NamedSchema -> NamedSchema -> NamedSchema)
-> (NamedSchema -> NamedSchema -> NamedSchema)
-> Ord NamedSchema
NamedSchema -> NamedSchema -> Bool
NamedSchema -> NamedSchema -> Ordering
NamedSchema -> NamedSchema -> NamedSchema
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: NamedSchema -> NamedSchema -> Ordering
compare :: NamedSchema -> NamedSchema -> Ordering
$c< :: NamedSchema -> NamedSchema -> Bool
< :: NamedSchema -> NamedSchema -> Bool
$c<= :: NamedSchema -> NamedSchema -> Bool
<= :: NamedSchema -> NamedSchema -> Bool
$c> :: NamedSchema -> NamedSchema -> Bool
> :: NamedSchema -> NamedSchema -> Bool
$c>= :: NamedSchema -> NamedSchema -> Bool
>= :: NamedSchema -> NamedSchema -> Bool
$cmax :: NamedSchema -> NamedSchema -> NamedSchema
max :: NamedSchema -> NamedSchema -> NamedSchema
$cmin :: NamedSchema -> NamedSchema -> NamedSchema
min :: NamedSchema -> NamedSchema -> NamedSchema
Ord, ReadPrec [NamedSchema]
ReadPrec NamedSchema
Int -> ReadS NamedSchema
ReadS [NamedSchema]
(Int -> ReadS NamedSchema)
-> ReadS [NamedSchema]
-> ReadPrec NamedSchema
-> ReadPrec [NamedSchema]
-> Read NamedSchema
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS NamedSchema
readsPrec :: Int -> ReadS NamedSchema
$creadList :: ReadS [NamedSchema]
readList :: ReadS [NamedSchema]
$creadPrec :: ReadPrec NamedSchema
readPrec :: ReadPrec NamedSchema
$creadListPrec :: ReadPrec [NamedSchema]
readListPrec :: ReadPrec [NamedSchema]
Read, Int -> NamedSchema -> ShowS
[NamedSchema] -> ShowS
NamedSchema -> String
(Int -> NamedSchema -> ShowS)
-> (NamedSchema -> String)
-> ([NamedSchema] -> ShowS)
-> Show NamedSchema
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> NamedSchema -> ShowS
showsPrec :: Int -> NamedSchema -> ShowS
$cshow :: NamedSchema -> String
show :: NamedSchema -> String
$cshowList :: [NamedSchema] -> ShowS
showList :: [NamedSchema] -> ShowS
Show)
_NamedSchema :: Name
_NamedSchema = (String -> Name
Core.Name String
"hydra/langs/pegasus/pdl.NamedSchema")
_NamedSchema_qualifiedName :: Name
_NamedSchema_qualifiedName = (String -> Name
Core.Name String
"qualifiedName")
_NamedSchema_type :: Name
_NamedSchema_type = (String -> Name
Core.Name String
"type")
_NamedSchema_annotations :: Name
_NamedSchema_annotations = (String -> Name
Core.Name String
"annotations")
data NamedSchema_Type =
NamedSchema_TypeRecord RecordSchema |
NamedSchema_TypeEnum EnumSchema |
NamedSchema_TypeTyperef Schema
deriving (NamedSchema_Type -> NamedSchema_Type -> Bool
(NamedSchema_Type -> NamedSchema_Type -> Bool)
-> (NamedSchema_Type -> NamedSchema_Type -> Bool)
-> Eq NamedSchema_Type
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: NamedSchema_Type -> NamedSchema_Type -> Bool
== :: NamedSchema_Type -> NamedSchema_Type -> Bool
$c/= :: NamedSchema_Type -> NamedSchema_Type -> Bool
/= :: NamedSchema_Type -> NamedSchema_Type -> Bool
Eq, Eq NamedSchema_Type
Eq NamedSchema_Type =>
(NamedSchema_Type -> NamedSchema_Type -> Ordering)
-> (NamedSchema_Type -> NamedSchema_Type -> Bool)
-> (NamedSchema_Type -> NamedSchema_Type -> Bool)
-> (NamedSchema_Type -> NamedSchema_Type -> Bool)
-> (NamedSchema_Type -> NamedSchema_Type -> Bool)
-> (NamedSchema_Type -> NamedSchema_Type -> NamedSchema_Type)
-> (NamedSchema_Type -> NamedSchema_Type -> NamedSchema_Type)
-> Ord NamedSchema_Type
NamedSchema_Type -> NamedSchema_Type -> Bool
NamedSchema_Type -> NamedSchema_Type -> Ordering
NamedSchema_Type -> NamedSchema_Type -> NamedSchema_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 :: NamedSchema_Type -> NamedSchema_Type -> Ordering
compare :: NamedSchema_Type -> NamedSchema_Type -> Ordering
$c< :: NamedSchema_Type -> NamedSchema_Type -> Bool
< :: NamedSchema_Type -> NamedSchema_Type -> Bool
$c<= :: NamedSchema_Type -> NamedSchema_Type -> Bool
<= :: NamedSchema_Type -> NamedSchema_Type -> Bool
$c> :: NamedSchema_Type -> NamedSchema_Type -> Bool
> :: NamedSchema_Type -> NamedSchema_Type -> Bool
$c>= :: NamedSchema_Type -> NamedSchema_Type -> Bool
>= :: NamedSchema_Type -> NamedSchema_Type -> Bool
$cmax :: NamedSchema_Type -> NamedSchema_Type -> NamedSchema_Type
max :: NamedSchema_Type -> NamedSchema_Type -> NamedSchema_Type
$cmin :: NamedSchema_Type -> NamedSchema_Type -> NamedSchema_Type
min :: NamedSchema_Type -> NamedSchema_Type -> NamedSchema_Type
Ord, ReadPrec [NamedSchema_Type]
ReadPrec NamedSchema_Type
Int -> ReadS NamedSchema_Type
ReadS [NamedSchema_Type]
(Int -> ReadS NamedSchema_Type)
-> ReadS [NamedSchema_Type]
-> ReadPrec NamedSchema_Type
-> ReadPrec [NamedSchema_Type]
-> Read NamedSchema_Type
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS NamedSchema_Type
readsPrec :: Int -> ReadS NamedSchema_Type
$creadList :: ReadS [NamedSchema_Type]
readList :: ReadS [NamedSchema_Type]
$creadPrec :: ReadPrec NamedSchema_Type
readPrec :: ReadPrec NamedSchema_Type
$creadListPrec :: ReadPrec [NamedSchema_Type]
readListPrec :: ReadPrec [NamedSchema_Type]
Read, Int -> NamedSchema_Type -> ShowS
[NamedSchema_Type] -> ShowS
NamedSchema_Type -> String
(Int -> NamedSchema_Type -> ShowS)
-> (NamedSchema_Type -> String)
-> ([NamedSchema_Type] -> ShowS)
-> Show NamedSchema_Type
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> NamedSchema_Type -> ShowS
showsPrec :: Int -> NamedSchema_Type -> ShowS
$cshow :: NamedSchema_Type -> String
show :: NamedSchema_Type -> String
$cshowList :: [NamedSchema_Type] -> ShowS
showList :: [NamedSchema_Type] -> ShowS
Show)
_NamedSchema_Type :: Name
_NamedSchema_Type = (String -> Name
Core.Name String
"hydra/langs/pegasus/pdl.NamedSchema.Type")
_NamedSchema_Type_record :: Name
_NamedSchema_Type_record = (String -> Name
Core.Name String
"record")
_NamedSchema_Type_enum :: Name
_NamedSchema_Type_enum = (String -> Name
Core.Name String
"enum")
_NamedSchema_Type_typeref :: Name
_NamedSchema_Type_typeref = (String -> Name
Core.Name String
"typeref")
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
Core.Name String
"hydra/langs/pegasus/pdl.Name")
newtype Namespace =
Namespace {
Namespace -> String
unNamespace :: String}
deriving (Namespace -> Namespace -> Bool
(Namespace -> Namespace -> Bool)
-> (Namespace -> Namespace -> Bool) -> Eq Namespace
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Namespace -> Namespace -> Bool
== :: Namespace -> Namespace -> Bool
$c/= :: Namespace -> Namespace -> Bool
/= :: Namespace -> Namespace -> Bool
Eq, Eq Namespace
Eq Namespace =>
(Namespace -> Namespace -> Ordering)
-> (Namespace -> Namespace -> Bool)
-> (Namespace -> Namespace -> Bool)
-> (Namespace -> Namespace -> Bool)
-> (Namespace -> Namespace -> Bool)
-> (Namespace -> Namespace -> Namespace)
-> (Namespace -> Namespace -> Namespace)
-> Ord Namespace
Namespace -> Namespace -> Bool
Namespace -> Namespace -> Ordering
Namespace -> Namespace -> Namespace
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Namespace -> Namespace -> Ordering
compare :: Namespace -> Namespace -> Ordering
$c< :: Namespace -> Namespace -> Bool
< :: Namespace -> Namespace -> Bool
$c<= :: Namespace -> Namespace -> Bool
<= :: Namespace -> Namespace -> Bool
$c> :: Namespace -> Namespace -> Bool
> :: Namespace -> Namespace -> Bool
$c>= :: Namespace -> Namespace -> Bool
>= :: Namespace -> Namespace -> Bool
$cmax :: Namespace -> Namespace -> Namespace
max :: Namespace -> Namespace -> Namespace
$cmin :: Namespace -> Namespace -> Namespace
min :: Namespace -> Namespace -> Namespace
Ord, ReadPrec [Namespace]
ReadPrec Namespace
Int -> ReadS Namespace
ReadS [Namespace]
(Int -> ReadS Namespace)
-> ReadS [Namespace]
-> ReadPrec Namespace
-> ReadPrec [Namespace]
-> Read Namespace
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Namespace
readsPrec :: Int -> ReadS Namespace
$creadList :: ReadS [Namespace]
readList :: ReadS [Namespace]
$creadPrec :: ReadPrec Namespace
readPrec :: ReadPrec Namespace
$creadListPrec :: ReadPrec [Namespace]
readListPrec :: ReadPrec [Namespace]
Read, Int -> Namespace -> ShowS
[Namespace] -> ShowS
Namespace -> String
(Int -> Namespace -> ShowS)
-> (Namespace -> String)
-> ([Namespace] -> ShowS)
-> Show Namespace
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Namespace -> ShowS
showsPrec :: Int -> Namespace -> ShowS
$cshow :: Namespace -> String
show :: Namespace -> String
$cshowList :: [Namespace] -> ShowS
showList :: [Namespace] -> ShowS
Show)
_Namespace :: Name
_Namespace = (String -> Name
Core.Name String
"hydra/langs/pegasus/pdl.Namespace")
newtype Package =
Package {
Package -> String
unPackage :: String}
deriving (Package -> Package -> Bool
(Package -> Package -> Bool)
-> (Package -> Package -> Bool) -> Eq Package
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Package -> Package -> Bool
== :: Package -> Package -> Bool
$c/= :: Package -> Package -> Bool
/= :: Package -> Package -> Bool
Eq, Eq Package
Eq Package =>
(Package -> Package -> Ordering)
-> (Package -> Package -> Bool)
-> (Package -> Package -> Bool)
-> (Package -> Package -> Bool)
-> (Package -> Package -> Bool)
-> (Package -> Package -> Package)
-> (Package -> Package -> Package)
-> Ord Package
Package -> Package -> Bool
Package -> Package -> Ordering
Package -> Package -> Package
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Package -> Package -> Ordering
compare :: Package -> Package -> Ordering
$c< :: Package -> Package -> Bool
< :: Package -> Package -> Bool
$c<= :: Package -> Package -> Bool
<= :: Package -> Package -> Bool
$c> :: Package -> Package -> Bool
> :: Package -> Package -> Bool
$c>= :: Package -> Package -> Bool
>= :: Package -> Package -> Bool
$cmax :: Package -> Package -> Package
max :: Package -> Package -> Package
$cmin :: Package -> Package -> Package
min :: Package -> Package -> Package
Ord, ReadPrec [Package]
ReadPrec Package
Int -> ReadS Package
ReadS [Package]
(Int -> ReadS Package)
-> ReadS [Package]
-> ReadPrec Package
-> ReadPrec [Package]
-> Read Package
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Package
readsPrec :: Int -> ReadS Package
$creadList :: ReadS [Package]
readList :: ReadS [Package]
$creadPrec :: ReadPrec Package
readPrec :: ReadPrec Package
$creadListPrec :: ReadPrec [Package]
readListPrec :: ReadPrec [Package]
Read, Int -> Package -> ShowS
[Package] -> ShowS
Package -> String
(Int -> Package -> ShowS)
-> (Package -> String) -> ([Package] -> ShowS) -> Show Package
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Package -> ShowS
showsPrec :: Int -> Package -> ShowS
$cshow :: Package -> String
show :: Package -> String
$cshowList :: [Package] -> ShowS
showList :: [Package] -> ShowS
Show)
_Package :: Name
_Package = (String -> Name
Core.Name String
"hydra/langs/pegasus/pdl.Package")
data PrimitiveType =
PrimitiveTypeBoolean |
PrimitiveTypeBytes |
PrimitiveTypeDouble |
PrimitiveTypeFloat |
PrimitiveTypeInt |
PrimitiveTypeLong |
PrimitiveTypeString
deriving (PrimitiveType -> PrimitiveType -> Bool
(PrimitiveType -> PrimitiveType -> Bool)
-> (PrimitiveType -> PrimitiveType -> Bool) -> Eq PrimitiveType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PrimitiveType -> PrimitiveType -> Bool
== :: PrimitiveType -> PrimitiveType -> Bool
$c/= :: PrimitiveType -> PrimitiveType -> Bool
/= :: PrimitiveType -> PrimitiveType -> Bool
Eq, Eq PrimitiveType
Eq PrimitiveType =>
(PrimitiveType -> PrimitiveType -> Ordering)
-> (PrimitiveType -> PrimitiveType -> Bool)
-> (PrimitiveType -> PrimitiveType -> Bool)
-> (PrimitiveType -> PrimitiveType -> Bool)
-> (PrimitiveType -> PrimitiveType -> Bool)
-> (PrimitiveType -> PrimitiveType -> PrimitiveType)
-> (PrimitiveType -> PrimitiveType -> PrimitiveType)
-> Ord PrimitiveType
PrimitiveType -> PrimitiveType -> Bool
PrimitiveType -> PrimitiveType -> Ordering
PrimitiveType -> PrimitiveType -> PrimitiveType
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: PrimitiveType -> PrimitiveType -> Ordering
compare :: PrimitiveType -> PrimitiveType -> Ordering
$c< :: PrimitiveType -> PrimitiveType -> Bool
< :: PrimitiveType -> PrimitiveType -> Bool
$c<= :: PrimitiveType -> PrimitiveType -> Bool
<= :: PrimitiveType -> PrimitiveType -> Bool
$c> :: PrimitiveType -> PrimitiveType -> Bool
> :: PrimitiveType -> PrimitiveType -> Bool
$c>= :: PrimitiveType -> PrimitiveType -> Bool
>= :: PrimitiveType -> PrimitiveType -> Bool
$cmax :: PrimitiveType -> PrimitiveType -> PrimitiveType
max :: PrimitiveType -> PrimitiveType -> PrimitiveType
$cmin :: PrimitiveType -> PrimitiveType -> PrimitiveType
min :: PrimitiveType -> PrimitiveType -> PrimitiveType
Ord, ReadPrec [PrimitiveType]
ReadPrec PrimitiveType
Int -> ReadS PrimitiveType
ReadS [PrimitiveType]
(Int -> ReadS PrimitiveType)
-> ReadS [PrimitiveType]
-> ReadPrec PrimitiveType
-> ReadPrec [PrimitiveType]
-> Read PrimitiveType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS PrimitiveType
readsPrec :: Int -> ReadS PrimitiveType
$creadList :: ReadS [PrimitiveType]
readList :: ReadS [PrimitiveType]
$creadPrec :: ReadPrec PrimitiveType
readPrec :: ReadPrec PrimitiveType
$creadListPrec :: ReadPrec [PrimitiveType]
readListPrec :: ReadPrec [PrimitiveType]
Read, Int -> PrimitiveType -> ShowS
[PrimitiveType] -> ShowS
PrimitiveType -> String
(Int -> PrimitiveType -> ShowS)
-> (PrimitiveType -> String)
-> ([PrimitiveType] -> ShowS)
-> Show PrimitiveType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PrimitiveType -> ShowS
showsPrec :: Int -> PrimitiveType -> ShowS
$cshow :: PrimitiveType -> String
show :: PrimitiveType -> String
$cshowList :: [PrimitiveType] -> ShowS
showList :: [PrimitiveType] -> ShowS
Show)
_PrimitiveType :: Name
_PrimitiveType = (String -> Name
Core.Name String
"hydra/langs/pegasus/pdl.PrimitiveType")
_PrimitiveType_boolean :: Name
_PrimitiveType_boolean = (String -> Name
Core.Name String
"boolean")
_PrimitiveType_bytes :: Name
_PrimitiveType_bytes = (String -> Name
Core.Name String
"bytes")
_PrimitiveType_double :: Name
_PrimitiveType_double = (String -> Name
Core.Name String
"double")
_PrimitiveType_float :: Name
_PrimitiveType_float = (String -> Name
Core.Name String
"float")
_PrimitiveType_int :: Name
_PrimitiveType_int = (String -> Name
Core.Name String
"int")
_PrimitiveType_long :: Name
_PrimitiveType_long = (String -> Name
Core.Name String
"long")
_PrimitiveType_string :: Name
_PrimitiveType_string = (String -> Name
Core.Name String
"string")
newtype PropertyKey =
PropertyKey {
PropertyKey -> String
unPropertyKey :: String}
deriving (PropertyKey -> PropertyKey -> Bool
(PropertyKey -> PropertyKey -> Bool)
-> (PropertyKey -> PropertyKey -> Bool) -> Eq PropertyKey
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PropertyKey -> PropertyKey -> Bool
== :: PropertyKey -> PropertyKey -> Bool
$c/= :: PropertyKey -> PropertyKey -> Bool
/= :: PropertyKey -> PropertyKey -> Bool
Eq, Eq PropertyKey
Eq PropertyKey =>
(PropertyKey -> PropertyKey -> Ordering)
-> (PropertyKey -> PropertyKey -> Bool)
-> (PropertyKey -> PropertyKey -> Bool)
-> (PropertyKey -> PropertyKey -> Bool)
-> (PropertyKey -> PropertyKey -> Bool)
-> (PropertyKey -> PropertyKey -> PropertyKey)
-> (PropertyKey -> PropertyKey -> PropertyKey)
-> Ord PropertyKey
PropertyKey -> PropertyKey -> Bool
PropertyKey -> PropertyKey -> Ordering
PropertyKey -> PropertyKey -> PropertyKey
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: PropertyKey -> PropertyKey -> Ordering
compare :: PropertyKey -> PropertyKey -> Ordering
$c< :: PropertyKey -> PropertyKey -> Bool
< :: PropertyKey -> PropertyKey -> Bool
$c<= :: PropertyKey -> PropertyKey -> Bool
<= :: PropertyKey -> PropertyKey -> Bool
$c> :: PropertyKey -> PropertyKey -> Bool
> :: PropertyKey -> PropertyKey -> Bool
$c>= :: PropertyKey -> PropertyKey -> Bool
>= :: PropertyKey -> PropertyKey -> Bool
$cmax :: PropertyKey -> PropertyKey -> PropertyKey
max :: PropertyKey -> PropertyKey -> PropertyKey
$cmin :: PropertyKey -> PropertyKey -> PropertyKey
min :: PropertyKey -> PropertyKey -> PropertyKey
Ord, ReadPrec [PropertyKey]
ReadPrec PropertyKey
Int -> ReadS PropertyKey
ReadS [PropertyKey]
(Int -> ReadS PropertyKey)
-> ReadS [PropertyKey]
-> ReadPrec PropertyKey
-> ReadPrec [PropertyKey]
-> Read PropertyKey
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS PropertyKey
readsPrec :: Int -> ReadS PropertyKey
$creadList :: ReadS [PropertyKey]
readList :: ReadS [PropertyKey]
$creadPrec :: ReadPrec PropertyKey
readPrec :: ReadPrec PropertyKey
$creadListPrec :: ReadPrec [PropertyKey]
readListPrec :: ReadPrec [PropertyKey]
Read, Int -> PropertyKey -> ShowS
[PropertyKey] -> ShowS
PropertyKey -> String
(Int -> PropertyKey -> ShowS)
-> (PropertyKey -> String)
-> ([PropertyKey] -> ShowS)
-> Show PropertyKey
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PropertyKey -> ShowS
showsPrec :: Int -> PropertyKey -> ShowS
$cshow :: PropertyKey -> String
show :: PropertyKey -> String
$cshowList :: [PropertyKey] -> ShowS
showList :: [PropertyKey] -> ShowS
Show)
_PropertyKey :: Name
_PropertyKey = (String -> Name
Core.Name String
"hydra/langs/pegasus/pdl.PropertyKey")
data Property =
Property {
Property -> PropertyKey
propertyKey :: PropertyKey,
Property -> Maybe Value
propertyValue :: (Maybe Json.Value)}
deriving (Property -> Property -> Bool
(Property -> Property -> Bool)
-> (Property -> Property -> Bool) -> Eq Property
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Property -> Property -> Bool
== :: Property -> Property -> Bool
$c/= :: Property -> Property -> Bool
/= :: Property -> Property -> Bool
Eq, Eq Property
Eq Property =>
(Property -> Property -> Ordering)
-> (Property -> Property -> Bool)
-> (Property -> Property -> Bool)
-> (Property -> Property -> Bool)
-> (Property -> Property -> Bool)
-> (Property -> Property -> Property)
-> (Property -> Property -> Property)
-> Ord Property
Property -> Property -> Bool
Property -> Property -> Ordering
Property -> Property -> Property
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Property -> Property -> Ordering
compare :: Property -> Property -> Ordering
$c< :: Property -> Property -> Bool
< :: Property -> Property -> Bool
$c<= :: Property -> Property -> Bool
<= :: Property -> Property -> Bool
$c> :: Property -> Property -> Bool
> :: Property -> Property -> Bool
$c>= :: Property -> Property -> Bool
>= :: Property -> Property -> Bool
$cmax :: Property -> Property -> Property
max :: Property -> Property -> Property
$cmin :: Property -> Property -> Property
min :: Property -> Property -> Property
Ord, ReadPrec [Property]
ReadPrec Property
Int -> ReadS Property
ReadS [Property]
(Int -> ReadS Property)
-> ReadS [Property]
-> ReadPrec Property
-> ReadPrec [Property]
-> Read Property
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Property
readsPrec :: Int -> ReadS Property
$creadList :: ReadS [Property]
readList :: ReadS [Property]
$creadPrec :: ReadPrec Property
readPrec :: ReadPrec Property
$creadListPrec :: ReadPrec [Property]
readListPrec :: ReadPrec [Property]
Read, Int -> Property -> ShowS
[Property] -> ShowS
Property -> String
(Int -> Property -> ShowS)
-> (Property -> String) -> ([Property] -> ShowS) -> Show Property
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Property -> ShowS
showsPrec :: Int -> Property -> ShowS
$cshow :: Property -> String
show :: Property -> String
$cshowList :: [Property] -> ShowS
showList :: [Property] -> ShowS
Show)
_Property :: Name
_Property = (String -> Name
Core.Name String
"hydra/langs/pegasus/pdl.Property")
_Property_key :: Name
_Property_key = (String -> Name
Core.Name String
"key")
_Property_value :: Name
_Property_value = (String -> Name
Core.Name String
"value")
data QualifiedName =
QualifiedName {
QualifiedName -> Name
qualifiedNameName :: Name,
QualifiedName -> Maybe Namespace
qualifiedNameNamespace :: (Maybe Namespace)}
deriving (QualifiedName -> QualifiedName -> Bool
(QualifiedName -> QualifiedName -> Bool)
-> (QualifiedName -> QualifiedName -> Bool) -> Eq QualifiedName
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: QualifiedName -> QualifiedName -> Bool
== :: QualifiedName -> QualifiedName -> Bool
$c/= :: QualifiedName -> QualifiedName -> Bool
/= :: QualifiedName -> QualifiedName -> Bool
Eq, Eq QualifiedName
Eq QualifiedName =>
(QualifiedName -> QualifiedName -> Ordering)
-> (QualifiedName -> QualifiedName -> Bool)
-> (QualifiedName -> QualifiedName -> Bool)
-> (QualifiedName -> QualifiedName -> Bool)
-> (QualifiedName -> QualifiedName -> Bool)
-> (QualifiedName -> QualifiedName -> QualifiedName)
-> (QualifiedName -> QualifiedName -> QualifiedName)
-> Ord QualifiedName
QualifiedName -> QualifiedName -> Bool
QualifiedName -> QualifiedName -> Ordering
QualifiedName -> QualifiedName -> QualifiedName
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: QualifiedName -> QualifiedName -> Ordering
compare :: QualifiedName -> QualifiedName -> Ordering
$c< :: QualifiedName -> QualifiedName -> Bool
< :: QualifiedName -> QualifiedName -> Bool
$c<= :: QualifiedName -> QualifiedName -> Bool
<= :: QualifiedName -> QualifiedName -> Bool
$c> :: QualifiedName -> QualifiedName -> Bool
> :: QualifiedName -> QualifiedName -> Bool
$c>= :: QualifiedName -> QualifiedName -> Bool
>= :: QualifiedName -> QualifiedName -> Bool
$cmax :: QualifiedName -> QualifiedName -> QualifiedName
max :: QualifiedName -> QualifiedName -> QualifiedName
$cmin :: QualifiedName -> QualifiedName -> QualifiedName
min :: QualifiedName -> QualifiedName -> QualifiedName
Ord, ReadPrec [QualifiedName]
ReadPrec QualifiedName
Int -> ReadS QualifiedName
ReadS [QualifiedName]
(Int -> ReadS QualifiedName)
-> ReadS [QualifiedName]
-> ReadPrec QualifiedName
-> ReadPrec [QualifiedName]
-> Read QualifiedName
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS QualifiedName
readsPrec :: Int -> ReadS QualifiedName
$creadList :: ReadS [QualifiedName]
readList :: ReadS [QualifiedName]
$creadPrec :: ReadPrec QualifiedName
readPrec :: ReadPrec QualifiedName
$creadListPrec :: ReadPrec [QualifiedName]
readListPrec :: ReadPrec [QualifiedName]
Read, Int -> QualifiedName -> ShowS
[QualifiedName] -> ShowS
QualifiedName -> String
(Int -> QualifiedName -> ShowS)
-> (QualifiedName -> String)
-> ([QualifiedName] -> ShowS)
-> Show QualifiedName
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> QualifiedName -> ShowS
showsPrec :: Int -> QualifiedName -> ShowS
$cshow :: QualifiedName -> String
show :: QualifiedName -> String
$cshowList :: [QualifiedName] -> ShowS
showList :: [QualifiedName] -> ShowS
Show)
_QualifiedName :: Name
_QualifiedName = (String -> Name
Core.Name String
"hydra/langs/pegasus/pdl.QualifiedName")
_QualifiedName_name :: Name
_QualifiedName_name = (String -> Name
Core.Name String
"name")
_QualifiedName_namespace :: Name
_QualifiedName_namespace = (String -> Name
Core.Name String
"namespace")
data RecordField =
RecordField {
RecordField -> FieldName
recordFieldName :: FieldName,
RecordField -> Schema
recordFieldValue :: Schema,
RecordField -> Bool
recordFieldOptional :: Bool,
RecordField -> Maybe Value
recordFieldDefault :: (Maybe Json.Value),
RecordField -> Annotations
recordFieldAnnotations :: Annotations}
deriving (RecordField -> RecordField -> Bool
(RecordField -> RecordField -> Bool)
-> (RecordField -> RecordField -> Bool) -> Eq RecordField
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RecordField -> RecordField -> Bool
== :: RecordField -> RecordField -> Bool
$c/= :: RecordField -> RecordField -> Bool
/= :: RecordField -> RecordField -> Bool
Eq, Eq RecordField
Eq RecordField =>
(RecordField -> RecordField -> Ordering)
-> (RecordField -> RecordField -> Bool)
-> (RecordField -> RecordField -> Bool)
-> (RecordField -> RecordField -> Bool)
-> (RecordField -> RecordField -> Bool)
-> (RecordField -> RecordField -> RecordField)
-> (RecordField -> RecordField -> RecordField)
-> Ord RecordField
RecordField -> RecordField -> Bool
RecordField -> RecordField -> Ordering
RecordField -> RecordField -> RecordField
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: RecordField -> RecordField -> Ordering
compare :: RecordField -> RecordField -> Ordering
$c< :: RecordField -> RecordField -> Bool
< :: RecordField -> RecordField -> Bool
$c<= :: RecordField -> RecordField -> Bool
<= :: RecordField -> RecordField -> Bool
$c> :: RecordField -> RecordField -> Bool
> :: RecordField -> RecordField -> Bool
$c>= :: RecordField -> RecordField -> Bool
>= :: RecordField -> RecordField -> Bool
$cmax :: RecordField -> RecordField -> RecordField
max :: RecordField -> RecordField -> RecordField
$cmin :: RecordField -> RecordField -> RecordField
min :: RecordField -> RecordField -> RecordField
Ord, ReadPrec [RecordField]
ReadPrec RecordField
Int -> ReadS RecordField
ReadS [RecordField]
(Int -> ReadS RecordField)
-> ReadS [RecordField]
-> ReadPrec RecordField
-> ReadPrec [RecordField]
-> Read RecordField
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS RecordField
readsPrec :: Int -> ReadS RecordField
$creadList :: ReadS [RecordField]
readList :: ReadS [RecordField]
$creadPrec :: ReadPrec RecordField
readPrec :: ReadPrec RecordField
$creadListPrec :: ReadPrec [RecordField]
readListPrec :: ReadPrec [RecordField]
Read, Int -> RecordField -> ShowS
[RecordField] -> ShowS
RecordField -> String
(Int -> RecordField -> ShowS)
-> (RecordField -> String)
-> ([RecordField] -> ShowS)
-> Show RecordField
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RecordField -> ShowS
showsPrec :: Int -> RecordField -> ShowS
$cshow :: RecordField -> String
show :: RecordField -> String
$cshowList :: [RecordField] -> ShowS
showList :: [RecordField] -> ShowS
Show)
_RecordField :: Name
_RecordField = (String -> Name
Core.Name String
"hydra/langs/pegasus/pdl.RecordField")
_RecordField_name :: Name
_RecordField_name = (String -> Name
Core.Name String
"name")
_RecordField_value :: Name
_RecordField_value = (String -> Name
Core.Name String
"value")
_RecordField_optional :: Name
_RecordField_optional = (String -> Name
Core.Name String
"optional")
_RecordField_default :: Name
_RecordField_default = (String -> Name
Core.Name String
"default")
_RecordField_annotations :: Name
_RecordField_annotations = (String -> Name
Core.Name String
"annotations")
data RecordSchema =
RecordSchema {
RecordSchema -> [RecordField]
recordSchemaFields :: [RecordField],
RecordSchema -> [NamedSchema]
recordSchemaIncludes :: [NamedSchema]}
deriving (RecordSchema -> RecordSchema -> Bool
(RecordSchema -> RecordSchema -> Bool)
-> (RecordSchema -> RecordSchema -> Bool) -> Eq RecordSchema
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RecordSchema -> RecordSchema -> Bool
== :: RecordSchema -> RecordSchema -> Bool
$c/= :: RecordSchema -> RecordSchema -> Bool
/= :: RecordSchema -> RecordSchema -> Bool
Eq, Eq RecordSchema
Eq RecordSchema =>
(RecordSchema -> RecordSchema -> Ordering)
-> (RecordSchema -> RecordSchema -> Bool)
-> (RecordSchema -> RecordSchema -> Bool)
-> (RecordSchema -> RecordSchema -> Bool)
-> (RecordSchema -> RecordSchema -> Bool)
-> (RecordSchema -> RecordSchema -> RecordSchema)
-> (RecordSchema -> RecordSchema -> RecordSchema)
-> Ord RecordSchema
RecordSchema -> RecordSchema -> Bool
RecordSchema -> RecordSchema -> Ordering
RecordSchema -> RecordSchema -> RecordSchema
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: RecordSchema -> RecordSchema -> Ordering
compare :: RecordSchema -> RecordSchema -> Ordering
$c< :: RecordSchema -> RecordSchema -> Bool
< :: RecordSchema -> RecordSchema -> Bool
$c<= :: RecordSchema -> RecordSchema -> Bool
<= :: RecordSchema -> RecordSchema -> Bool
$c> :: RecordSchema -> RecordSchema -> Bool
> :: RecordSchema -> RecordSchema -> Bool
$c>= :: RecordSchema -> RecordSchema -> Bool
>= :: RecordSchema -> RecordSchema -> Bool
$cmax :: RecordSchema -> RecordSchema -> RecordSchema
max :: RecordSchema -> RecordSchema -> RecordSchema
$cmin :: RecordSchema -> RecordSchema -> RecordSchema
min :: RecordSchema -> RecordSchema -> RecordSchema
Ord, ReadPrec [RecordSchema]
ReadPrec RecordSchema
Int -> ReadS RecordSchema
ReadS [RecordSchema]
(Int -> ReadS RecordSchema)
-> ReadS [RecordSchema]
-> ReadPrec RecordSchema
-> ReadPrec [RecordSchema]
-> Read RecordSchema
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS RecordSchema
readsPrec :: Int -> ReadS RecordSchema
$creadList :: ReadS [RecordSchema]
readList :: ReadS [RecordSchema]
$creadPrec :: ReadPrec RecordSchema
readPrec :: ReadPrec RecordSchema
$creadListPrec :: ReadPrec [RecordSchema]
readListPrec :: ReadPrec [RecordSchema]
Read, Int -> RecordSchema -> ShowS
[RecordSchema] -> ShowS
RecordSchema -> String
(Int -> RecordSchema -> ShowS)
-> (RecordSchema -> String)
-> ([RecordSchema] -> ShowS)
-> Show RecordSchema
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RecordSchema -> ShowS
showsPrec :: Int -> RecordSchema -> ShowS
$cshow :: RecordSchema -> String
show :: RecordSchema -> String
$cshowList :: [RecordSchema] -> ShowS
showList :: [RecordSchema] -> ShowS
Show)
_RecordSchema :: Name
_RecordSchema = (String -> Name
Core.Name String
"hydra/langs/pegasus/pdl.RecordSchema")
_RecordSchema_fields :: Name
_RecordSchema_fields = (String -> Name
Core.Name String
"fields")
_RecordSchema_includes :: Name
_RecordSchema_includes = (String -> Name
Core.Name String
"includes")
data Schema =
SchemaArray Schema |
SchemaFixed Int |
SchemaInline NamedSchema |
SchemaMap Schema |
SchemaNamed QualifiedName |
SchemaNull |
SchemaPrimitive PrimitiveType |
SchemaUnion UnionSchema
deriving (Schema -> Schema -> Bool
(Schema -> Schema -> Bool)
-> (Schema -> Schema -> Bool) -> Eq Schema
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Schema -> Schema -> Bool
== :: Schema -> Schema -> Bool
$c/= :: Schema -> Schema -> Bool
/= :: Schema -> Schema -> Bool
Eq, Eq Schema
Eq Schema =>
(Schema -> Schema -> Ordering)
-> (Schema -> Schema -> Bool)
-> (Schema -> Schema -> Bool)
-> (Schema -> Schema -> Bool)
-> (Schema -> Schema -> Bool)
-> (Schema -> Schema -> Schema)
-> (Schema -> Schema -> Schema)
-> Ord Schema
Schema -> Schema -> Bool
Schema -> Schema -> Ordering
Schema -> Schema -> Schema
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Schema -> Schema -> Ordering
compare :: Schema -> Schema -> Ordering
$c< :: Schema -> Schema -> Bool
< :: Schema -> Schema -> Bool
$c<= :: Schema -> Schema -> Bool
<= :: Schema -> Schema -> Bool
$c> :: Schema -> Schema -> Bool
> :: Schema -> Schema -> Bool
$c>= :: Schema -> Schema -> Bool
>= :: Schema -> Schema -> Bool
$cmax :: Schema -> Schema -> Schema
max :: Schema -> Schema -> Schema
$cmin :: Schema -> Schema -> Schema
min :: Schema -> Schema -> Schema
Ord, ReadPrec [Schema]
ReadPrec Schema
Int -> ReadS Schema
ReadS [Schema]
(Int -> ReadS Schema)
-> ReadS [Schema]
-> ReadPrec Schema
-> ReadPrec [Schema]
-> Read Schema
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Schema
readsPrec :: Int -> ReadS Schema
$creadList :: ReadS [Schema]
readList :: ReadS [Schema]
$creadPrec :: ReadPrec Schema
readPrec :: ReadPrec Schema
$creadListPrec :: ReadPrec [Schema]
readListPrec :: ReadPrec [Schema]
Read, Int -> Schema -> ShowS
[Schema] -> ShowS
Schema -> String
(Int -> Schema -> ShowS)
-> (Schema -> String) -> ([Schema] -> ShowS) -> Show Schema
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Schema -> ShowS
showsPrec :: Int -> Schema -> ShowS
$cshow :: Schema -> String
show :: Schema -> String
$cshowList :: [Schema] -> ShowS
showList :: [Schema] -> ShowS
Show)
_Schema :: Name
_Schema = (String -> Name
Core.Name String
"hydra/langs/pegasus/pdl.Schema")
_Schema_array :: Name
_Schema_array = (String -> Name
Core.Name String
"array")
_Schema_fixed :: Name
_Schema_fixed = (String -> Name
Core.Name String
"fixed")
_Schema_inline :: Name
_Schema_inline = (String -> Name
Core.Name String
"inline")
_Schema_map :: Name
_Schema_map = (String -> Name
Core.Name String
"map")
_Schema_named :: Name
_Schema_named = (String -> Name
Core.Name String
"named")
_Schema_null :: Name
_Schema_null = (String -> Name
Core.Name String
"null")
_Schema_primitive :: Name
_Schema_primitive = (String -> Name
Core.Name String
"primitive")
_Schema_union :: Name
_Schema_union = (String -> Name
Core.Name String
"union")
data SchemaFile =
SchemaFile {
SchemaFile -> Namespace
schemaFileNamespace :: Namespace,
SchemaFile -> Maybe Package
schemaFilePackage :: (Maybe Package),
SchemaFile -> [QualifiedName]
schemaFileImports :: [QualifiedName],
SchemaFile -> [NamedSchema]
schemaFileSchemas :: [NamedSchema]}
deriving (SchemaFile -> SchemaFile -> Bool
(SchemaFile -> SchemaFile -> Bool)
-> (SchemaFile -> SchemaFile -> Bool) -> Eq SchemaFile
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SchemaFile -> SchemaFile -> Bool
== :: SchemaFile -> SchemaFile -> Bool
$c/= :: SchemaFile -> SchemaFile -> Bool
/= :: SchemaFile -> SchemaFile -> Bool
Eq, Eq SchemaFile
Eq SchemaFile =>
(SchemaFile -> SchemaFile -> Ordering)
-> (SchemaFile -> SchemaFile -> Bool)
-> (SchemaFile -> SchemaFile -> Bool)
-> (SchemaFile -> SchemaFile -> Bool)
-> (SchemaFile -> SchemaFile -> Bool)
-> (SchemaFile -> SchemaFile -> SchemaFile)
-> (SchemaFile -> SchemaFile -> SchemaFile)
-> Ord SchemaFile
SchemaFile -> SchemaFile -> Bool
SchemaFile -> SchemaFile -> Ordering
SchemaFile -> SchemaFile -> SchemaFile
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: SchemaFile -> SchemaFile -> Ordering
compare :: SchemaFile -> SchemaFile -> Ordering
$c< :: SchemaFile -> SchemaFile -> Bool
< :: SchemaFile -> SchemaFile -> Bool
$c<= :: SchemaFile -> SchemaFile -> Bool
<= :: SchemaFile -> SchemaFile -> Bool
$c> :: SchemaFile -> SchemaFile -> Bool
> :: SchemaFile -> SchemaFile -> Bool
$c>= :: SchemaFile -> SchemaFile -> Bool
>= :: SchemaFile -> SchemaFile -> Bool
$cmax :: SchemaFile -> SchemaFile -> SchemaFile
max :: SchemaFile -> SchemaFile -> SchemaFile
$cmin :: SchemaFile -> SchemaFile -> SchemaFile
min :: SchemaFile -> SchemaFile -> SchemaFile
Ord, ReadPrec [SchemaFile]
ReadPrec SchemaFile
Int -> ReadS SchemaFile
ReadS [SchemaFile]
(Int -> ReadS SchemaFile)
-> ReadS [SchemaFile]
-> ReadPrec SchemaFile
-> ReadPrec [SchemaFile]
-> Read SchemaFile
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS SchemaFile
readsPrec :: Int -> ReadS SchemaFile
$creadList :: ReadS [SchemaFile]
readList :: ReadS [SchemaFile]
$creadPrec :: ReadPrec SchemaFile
readPrec :: ReadPrec SchemaFile
$creadListPrec :: ReadPrec [SchemaFile]
readListPrec :: ReadPrec [SchemaFile]
Read, Int -> SchemaFile -> ShowS
[SchemaFile] -> ShowS
SchemaFile -> String
(Int -> SchemaFile -> ShowS)
-> (SchemaFile -> String)
-> ([SchemaFile] -> ShowS)
-> Show SchemaFile
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SchemaFile -> ShowS
showsPrec :: Int -> SchemaFile -> ShowS
$cshow :: SchemaFile -> String
show :: SchemaFile -> String
$cshowList :: [SchemaFile] -> ShowS
showList :: [SchemaFile] -> ShowS
Show)
_SchemaFile :: Name
_SchemaFile = (String -> Name
Core.Name String
"hydra/langs/pegasus/pdl.SchemaFile")
_SchemaFile_namespace :: Name
_SchemaFile_namespace = (String -> Name
Core.Name String
"namespace")
_SchemaFile_package :: Name
_SchemaFile_package = (String -> Name
Core.Name String
"package")
_SchemaFile_imports :: Name
_SchemaFile_imports = (String -> Name
Core.Name String
"imports")
_SchemaFile_schemas :: Name
_SchemaFile_schemas = (String -> Name
Core.Name String
"schemas")
data UnionMember =
UnionMember {
UnionMember -> Maybe FieldName
unionMemberAlias :: (Maybe FieldName),
UnionMember -> Schema
unionMemberValue :: Schema,
UnionMember -> Annotations
unionMemberAnnotations :: Annotations}
deriving (UnionMember -> UnionMember -> Bool
(UnionMember -> UnionMember -> Bool)
-> (UnionMember -> UnionMember -> Bool) -> Eq UnionMember
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: UnionMember -> UnionMember -> Bool
== :: UnionMember -> UnionMember -> Bool
$c/= :: UnionMember -> UnionMember -> Bool
/= :: UnionMember -> UnionMember -> Bool
Eq, Eq UnionMember
Eq UnionMember =>
(UnionMember -> UnionMember -> Ordering)
-> (UnionMember -> UnionMember -> Bool)
-> (UnionMember -> UnionMember -> Bool)
-> (UnionMember -> UnionMember -> Bool)
-> (UnionMember -> UnionMember -> Bool)
-> (UnionMember -> UnionMember -> UnionMember)
-> (UnionMember -> UnionMember -> UnionMember)
-> Ord UnionMember
UnionMember -> UnionMember -> Bool
UnionMember -> UnionMember -> Ordering
UnionMember -> UnionMember -> UnionMember
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: UnionMember -> UnionMember -> Ordering
compare :: UnionMember -> UnionMember -> Ordering
$c< :: UnionMember -> UnionMember -> Bool
< :: UnionMember -> UnionMember -> Bool
$c<= :: UnionMember -> UnionMember -> Bool
<= :: UnionMember -> UnionMember -> Bool
$c> :: UnionMember -> UnionMember -> Bool
> :: UnionMember -> UnionMember -> Bool
$c>= :: UnionMember -> UnionMember -> Bool
>= :: UnionMember -> UnionMember -> Bool
$cmax :: UnionMember -> UnionMember -> UnionMember
max :: UnionMember -> UnionMember -> UnionMember
$cmin :: UnionMember -> UnionMember -> UnionMember
min :: UnionMember -> UnionMember -> UnionMember
Ord, ReadPrec [UnionMember]
ReadPrec UnionMember
Int -> ReadS UnionMember
ReadS [UnionMember]
(Int -> ReadS UnionMember)
-> ReadS [UnionMember]
-> ReadPrec UnionMember
-> ReadPrec [UnionMember]
-> Read UnionMember
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS UnionMember
readsPrec :: Int -> ReadS UnionMember
$creadList :: ReadS [UnionMember]
readList :: ReadS [UnionMember]
$creadPrec :: ReadPrec UnionMember
readPrec :: ReadPrec UnionMember
$creadListPrec :: ReadPrec [UnionMember]
readListPrec :: ReadPrec [UnionMember]
Read, Int -> UnionMember -> ShowS
[UnionMember] -> ShowS
UnionMember -> String
(Int -> UnionMember -> ShowS)
-> (UnionMember -> String)
-> ([UnionMember] -> ShowS)
-> Show UnionMember
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> UnionMember -> ShowS
showsPrec :: Int -> UnionMember -> ShowS
$cshow :: UnionMember -> String
show :: UnionMember -> String
$cshowList :: [UnionMember] -> ShowS
showList :: [UnionMember] -> ShowS
Show)
_UnionMember :: Name
_UnionMember = (String -> Name
Core.Name String
"hydra/langs/pegasus/pdl.UnionMember")
_UnionMember_alias :: Name
_UnionMember_alias = (String -> Name
Core.Name String
"alias")
_UnionMember_value :: Name
_UnionMember_value = (String -> Name
Core.Name String
"value")
_UnionMember_annotations :: Name
_UnionMember_annotations = (String -> Name
Core.Name String
"annotations")
newtype UnionSchema =
UnionSchema {
UnionSchema -> [UnionMember]
unUnionSchema :: [UnionMember]}
deriving (UnionSchema -> UnionSchema -> Bool
(UnionSchema -> UnionSchema -> Bool)
-> (UnionSchema -> UnionSchema -> Bool) -> Eq UnionSchema
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: UnionSchema -> UnionSchema -> Bool
== :: UnionSchema -> UnionSchema -> Bool
$c/= :: UnionSchema -> UnionSchema -> Bool
/= :: UnionSchema -> UnionSchema -> Bool
Eq, Eq UnionSchema
Eq UnionSchema =>
(UnionSchema -> UnionSchema -> Ordering)
-> (UnionSchema -> UnionSchema -> Bool)
-> (UnionSchema -> UnionSchema -> Bool)
-> (UnionSchema -> UnionSchema -> Bool)
-> (UnionSchema -> UnionSchema -> Bool)
-> (UnionSchema -> UnionSchema -> UnionSchema)
-> (UnionSchema -> UnionSchema -> UnionSchema)
-> Ord UnionSchema
UnionSchema -> UnionSchema -> Bool
UnionSchema -> UnionSchema -> Ordering
UnionSchema -> UnionSchema -> UnionSchema
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: UnionSchema -> UnionSchema -> Ordering
compare :: UnionSchema -> UnionSchema -> Ordering
$c< :: UnionSchema -> UnionSchema -> Bool
< :: UnionSchema -> UnionSchema -> Bool
$c<= :: UnionSchema -> UnionSchema -> Bool
<= :: UnionSchema -> UnionSchema -> Bool
$c> :: UnionSchema -> UnionSchema -> Bool
> :: UnionSchema -> UnionSchema -> Bool
$c>= :: UnionSchema -> UnionSchema -> Bool
>= :: UnionSchema -> UnionSchema -> Bool
$cmax :: UnionSchema -> UnionSchema -> UnionSchema
max :: UnionSchema -> UnionSchema -> UnionSchema
$cmin :: UnionSchema -> UnionSchema -> UnionSchema
min :: UnionSchema -> UnionSchema -> UnionSchema
Ord, ReadPrec [UnionSchema]
ReadPrec UnionSchema
Int -> ReadS UnionSchema
ReadS [UnionSchema]
(Int -> ReadS UnionSchema)
-> ReadS [UnionSchema]
-> ReadPrec UnionSchema
-> ReadPrec [UnionSchema]
-> Read UnionSchema
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS UnionSchema
readsPrec :: Int -> ReadS UnionSchema
$creadList :: ReadS [UnionSchema]
readList :: ReadS [UnionSchema]
$creadPrec :: ReadPrec UnionSchema
readPrec :: ReadPrec UnionSchema
$creadListPrec :: ReadPrec [UnionSchema]
readListPrec :: ReadPrec [UnionSchema]
Read, Int -> UnionSchema -> ShowS
[UnionSchema] -> ShowS
UnionSchema -> String
(Int -> UnionSchema -> ShowS)
-> (UnionSchema -> String)
-> ([UnionSchema] -> ShowS)
-> Show UnionSchema
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> UnionSchema -> ShowS
showsPrec :: Int -> UnionSchema -> ShowS
$cshow :: UnionSchema -> String
show :: UnionSchema -> String
$cshowList :: [UnionSchema] -> ShowS
showList :: [UnionSchema] -> ShowS
Show)
_UnionSchema :: Name
_UnionSchema = (String -> Name
Core.Name String
"hydra/langs/pegasus/pdl.UnionSchema")