-- | A Shex model. Based on the BNF at:
-- |   https://github.com/shexSpec/grammar/blob/master/bnf

module Hydra.Langs.Shex.Syntax where

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

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

_ShexDoc :: Name
_ShexDoc = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.ShexDoc")

_ShexDoc_listOfDirective :: Name
_ShexDoc_listOfDirective = (String -> Name
Core.Name String
"listOfDirective")

_ShexDoc_sequence :: Name
_ShexDoc_sequence = (String -> Name
Core.Name String
"sequence")

_ShexDoc_prefixDecl :: Name
_ShexDoc_prefixDecl = (String -> Name
Core.Name String
"prefixDecl")

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

_ShexDoc_Sequence_Option :: Name
_ShexDoc_Sequence_Option = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.ShexDoc.Sequence.Option")

_ShexDoc_Sequence_Option_alts :: Name
_ShexDoc_Sequence_Option_alts = (String -> Name
Core.Name String
"alts")

_ShexDoc_Sequence_Option_listOfStatement :: Name
_ShexDoc_Sequence_Option_listOfStatement = (String -> Name
Core.Name String
"listOfStatement")

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

_ShexDoc_Sequence_Option_Alts :: Name
_ShexDoc_Sequence_Option_Alts = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.ShexDoc.Sequence.Option.Alts")

_ShexDoc_Sequence_Option_Alts_notStartAction :: Name
_ShexDoc_Sequence_Option_Alts_notStartAction = (String -> Name
Core.Name String
"notStartAction")

_ShexDoc_Sequence_Option_Alts_startActions :: Name
_ShexDoc_Sequence_Option_Alts_startActions = (String -> Name
Core.Name String
"startActions")

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

_Directive :: Name
_Directive = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.Directive")

_Directive_baseDecl :: Name
_Directive_baseDecl = (String -> Name
Core.Name String
"baseDecl")

_Directive_prefixDecl :: Name
_Directive_prefixDecl = (String -> Name
Core.Name String
"prefixDecl")

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

_BaseDecl :: Name
_BaseDecl = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.BaseDecl")

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

_PrefixDecl :: Name
_PrefixDecl = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.PrefixDecl")

_PrefixDecl_pnameNs :: Name
_PrefixDecl_pnameNs = (String -> Name
Core.Name String
"pnameNs")

_PrefixDecl_iriRef :: Name
_PrefixDecl_iriRef = (String -> Name
Core.Name String
"iriRef")

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

_NotStartAction :: Name
_NotStartAction = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.NotStartAction")

_NotStartAction_start :: Name
_NotStartAction_start = (String -> Name
Core.Name String
"start")

_NotStartAction_shapeExprDecl :: Name
_NotStartAction_shapeExprDecl = (String -> Name
Core.Name String
"shapeExprDecl")

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

_NotStartAction_ShapeExprDecl :: Name
_NotStartAction_ShapeExprDecl = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.NotStartAction.ShapeExprDecl")

_NotStartAction_ShapeExprDecl_shapeExprLabel :: Name
_NotStartAction_ShapeExprDecl_shapeExprLabel = (String -> Name
Core.Name String
"shapeExprLabel")

_NotStartAction_ShapeExprDecl_alts :: Name
_NotStartAction_ShapeExprDecl_alts = (String -> Name
Core.Name String
"alts")

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

_NotStartAction_ShapeExprDecl_Alts :: Name
_NotStartAction_ShapeExprDecl_Alts = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.NotStartAction.ShapeExprDecl.Alts")

_NotStartAction_ShapeExprDecl_Alts_shapeExpression :: Name
_NotStartAction_ShapeExprDecl_Alts_shapeExpression = (String -> Name
Core.Name String
"shapeExpression")

_NotStartAction_ShapeExprDecl_Alts_eXTERNAL :: Name
_NotStartAction_ShapeExprDecl_Alts_eXTERNAL = (String -> Name
Core.Name String
"eXTERNAL")

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

_StartActions :: Name
_StartActions = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.StartActions")

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

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

_Statement_directive :: Name
_Statement_directive = (String -> Name
Core.Name String
"directive")

_Statement_notStartAction :: Name
_Statement_notStartAction = (String -> Name
Core.Name String
"notStartAction")

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

_ShapeExpression :: Name
_ShapeExpression = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.ShapeExpression")

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

_InlineShapeExpression :: Name
_InlineShapeExpression = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.InlineShapeExpression")

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

_ShapeOr :: Name
_ShapeOr = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.ShapeOr")

_ShapeOr_shapeAnd :: Name
_ShapeOr_shapeAnd = (String -> Name
Core.Name String
"shapeAnd")

_ShapeOr_listOfSequence :: Name
_ShapeOr_listOfSequence = (String -> Name
Core.Name String
"listOfSequence")

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

_InlineShapeOr :: Name
_InlineShapeOr = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.InlineShapeOr")

_InlineShapeOr_shapeAnd :: Name
_InlineShapeOr_shapeAnd = (String -> Name
Core.Name String
"shapeAnd")

_InlineShapeOr_listOfSequence :: Name
_InlineShapeOr_listOfSequence = (String -> Name
Core.Name String
"listOfSequence")

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

_ShapeAnd :: Name
_ShapeAnd = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.ShapeAnd")

_ShapeAnd_shapeNot :: Name
_ShapeAnd_shapeNot = (String -> Name
Core.Name String
"shapeNot")

_ShapeAnd_listOfSequence :: Name
_ShapeAnd_listOfSequence = (String -> Name
Core.Name String
"listOfSequence")

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

_InlineShapeAnd :: Name
_InlineShapeAnd = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.InlineShapeAnd")

_InlineShapeAnd_inlineShapeNot :: Name
_InlineShapeAnd_inlineShapeNot = (String -> Name
Core.Name String
"inlineShapeNot")

_InlineShapeAnd_listOfSequence :: Name
_InlineShapeAnd_listOfSequence = (String -> Name
Core.Name String
"listOfSequence")

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

_ShapeNot :: Name
_ShapeNot = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.ShapeNot")

_ShapeNot_nOT :: Name
_ShapeNot_nOT = (String -> Name
Core.Name String
"nOT")

_ShapeNot_shapeAtom :: Name
_ShapeNot_shapeAtom = (String -> Name
Core.Name String
"shapeAtom")

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

_InlineShapeNot :: Name
_InlineShapeNot = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.InlineShapeNot")

_InlineShapeNot_nOT :: Name
_InlineShapeNot_nOT = (String -> Name
Core.Name String
"nOT")

_InlineShapeNot_inlineShapeAtom :: Name
_InlineShapeNot_inlineShapeAtom = (String -> Name
Core.Name String
"inlineShapeAtom")

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

_ShapeAtom :: Name
_ShapeAtom = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.ShapeAtom")

_ShapeAtom_sequence :: Name
_ShapeAtom_sequence = (String -> Name
Core.Name String
"sequence")

_ShapeAtom_shapeOrRef :: Name
_ShapeAtom_shapeOrRef = (String -> Name
Core.Name String
"shapeOrRef")

_ShapeAtom_sequence2 :: Name
_ShapeAtom_sequence2 = (String -> Name
Core.Name String
"sequence2")

_ShapeAtom_period :: Name
_ShapeAtom_period = (String -> Name
Core.Name String
"period")

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

_ShapeAtom_Sequence :: Name
_ShapeAtom_Sequence = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.ShapeAtom.Sequence")

_ShapeAtom_Sequence_nodeConstraint :: Name
_ShapeAtom_Sequence_nodeConstraint = (String -> Name
Core.Name String
"nodeConstraint")

_ShapeAtom_Sequence_shapeOrRef :: Name
_ShapeAtom_Sequence_shapeOrRef = (String -> Name
Core.Name String
"shapeOrRef")

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

_InlineShapeAtom :: Name
_InlineShapeAtom = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.InlineShapeAtom")

_InlineShapeAtom_sequence :: Name
_InlineShapeAtom_sequence = (String -> Name
Core.Name String
"sequence")

_InlineShapeAtom_sequence2 :: Name
_InlineShapeAtom_sequence2 = (String -> Name
Core.Name String
"sequence2")

_InlineShapeAtom_sequence3 :: Name
_InlineShapeAtom_sequence3 = (String -> Name
Core.Name String
"sequence3")

_InlineShapeAtom_period :: Name
_InlineShapeAtom_period = (String -> Name
Core.Name String
"period")

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

_InlineShapeAtom_Sequence :: Name
_InlineShapeAtom_Sequence = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.InlineShapeAtom.Sequence")

_InlineShapeAtom_Sequence_nodeConstraint :: Name
_InlineShapeAtom_Sequence_nodeConstraint = (String -> Name
Core.Name String
"nodeConstraint")

_InlineShapeAtom_Sequence_inlineShapeOrRef :: Name
_InlineShapeAtom_Sequence_inlineShapeOrRef = (String -> Name
Core.Name String
"inlineShapeOrRef")

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

_InlineShapeAtom_Sequence2 :: Name
_InlineShapeAtom_Sequence2 = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.InlineShapeAtom.Sequence2")

_InlineShapeAtom_Sequence2_inlineShapeOrRef :: Name
_InlineShapeAtom_Sequence2_inlineShapeOrRef = (String -> Name
Core.Name String
"inlineShapeOrRef")

_InlineShapeAtom_Sequence2_nodeConstraint :: Name
_InlineShapeAtom_Sequence2_nodeConstraint = (String -> Name
Core.Name String
"nodeConstraint")

data ShapeOrRef = 
  ShapeOrRefShapeDefinition ShapeDefinition |
  ShapeOrRefAtpNameLn AtpNameLn |
  ShapeOrRefAtpNameNs AtpNameNs |
  ShapeOrRefSequence ShapeExprLabel
  deriving (ShapeOrRef -> ShapeOrRef -> Bool
(ShapeOrRef -> ShapeOrRef -> Bool)
-> (ShapeOrRef -> ShapeOrRef -> Bool) -> Eq ShapeOrRef
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ShapeOrRef -> ShapeOrRef -> Bool
== :: ShapeOrRef -> ShapeOrRef -> Bool
$c/= :: ShapeOrRef -> ShapeOrRef -> Bool
/= :: ShapeOrRef -> ShapeOrRef -> Bool
Eq, Eq ShapeOrRef
Eq ShapeOrRef =>
(ShapeOrRef -> ShapeOrRef -> Ordering)
-> (ShapeOrRef -> ShapeOrRef -> Bool)
-> (ShapeOrRef -> ShapeOrRef -> Bool)
-> (ShapeOrRef -> ShapeOrRef -> Bool)
-> (ShapeOrRef -> ShapeOrRef -> Bool)
-> (ShapeOrRef -> ShapeOrRef -> ShapeOrRef)
-> (ShapeOrRef -> ShapeOrRef -> ShapeOrRef)
-> Ord ShapeOrRef
ShapeOrRef -> ShapeOrRef -> Bool
ShapeOrRef -> ShapeOrRef -> Ordering
ShapeOrRef -> ShapeOrRef -> ShapeOrRef
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ShapeOrRef -> ShapeOrRef -> Ordering
compare :: ShapeOrRef -> ShapeOrRef -> Ordering
$c< :: ShapeOrRef -> ShapeOrRef -> Bool
< :: ShapeOrRef -> ShapeOrRef -> Bool
$c<= :: ShapeOrRef -> ShapeOrRef -> Bool
<= :: ShapeOrRef -> ShapeOrRef -> Bool
$c> :: ShapeOrRef -> ShapeOrRef -> Bool
> :: ShapeOrRef -> ShapeOrRef -> Bool
$c>= :: ShapeOrRef -> ShapeOrRef -> Bool
>= :: ShapeOrRef -> ShapeOrRef -> Bool
$cmax :: ShapeOrRef -> ShapeOrRef -> ShapeOrRef
max :: ShapeOrRef -> ShapeOrRef -> ShapeOrRef
$cmin :: ShapeOrRef -> ShapeOrRef -> ShapeOrRef
min :: ShapeOrRef -> ShapeOrRef -> ShapeOrRef
Ord, ReadPrec [ShapeOrRef]
ReadPrec ShapeOrRef
Int -> ReadS ShapeOrRef
ReadS [ShapeOrRef]
(Int -> ReadS ShapeOrRef)
-> ReadS [ShapeOrRef]
-> ReadPrec ShapeOrRef
-> ReadPrec [ShapeOrRef]
-> Read ShapeOrRef
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ShapeOrRef
readsPrec :: Int -> ReadS ShapeOrRef
$creadList :: ReadS [ShapeOrRef]
readList :: ReadS [ShapeOrRef]
$creadPrec :: ReadPrec ShapeOrRef
readPrec :: ReadPrec ShapeOrRef
$creadListPrec :: ReadPrec [ShapeOrRef]
readListPrec :: ReadPrec [ShapeOrRef]
Read, Int -> ShapeOrRef -> ShowS
[ShapeOrRef] -> ShowS
ShapeOrRef -> String
(Int -> ShapeOrRef -> ShowS)
-> (ShapeOrRef -> String)
-> ([ShapeOrRef] -> ShowS)
-> Show ShapeOrRef
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ShapeOrRef -> ShowS
showsPrec :: Int -> ShapeOrRef -> ShowS
$cshow :: ShapeOrRef -> String
show :: ShapeOrRef -> String
$cshowList :: [ShapeOrRef] -> ShowS
showList :: [ShapeOrRef] -> ShowS
Show)

_ShapeOrRef :: Name
_ShapeOrRef = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.ShapeOrRef")

_ShapeOrRef_shapeDefinition :: Name
_ShapeOrRef_shapeDefinition = (String -> Name
Core.Name String
"shapeDefinition")

_ShapeOrRef_atpNameLn :: Name
_ShapeOrRef_atpNameLn = (String -> Name
Core.Name String
"atpNameLn")

_ShapeOrRef_atpNameNs :: Name
_ShapeOrRef_atpNameNs = (String -> Name
Core.Name String
"atpNameNs")

_ShapeOrRef_sequence :: Name
_ShapeOrRef_sequence = (String -> Name
Core.Name String
"sequence")

data InlineShapeOrRef = 
  InlineShapeOrRefInlineShapeDefinition InlineShapeDefinition |
  InlineShapeOrRefAtpNameLn AtpNameLn |
  InlineShapeOrRefAtpNameNs AtpNameNs |
  InlineShapeOrRefSequence ShapeExprLabel
  deriving (InlineShapeOrRef -> InlineShapeOrRef -> Bool
(InlineShapeOrRef -> InlineShapeOrRef -> Bool)
-> (InlineShapeOrRef -> InlineShapeOrRef -> Bool)
-> Eq InlineShapeOrRef
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: InlineShapeOrRef -> InlineShapeOrRef -> Bool
== :: InlineShapeOrRef -> InlineShapeOrRef -> Bool
$c/= :: InlineShapeOrRef -> InlineShapeOrRef -> Bool
/= :: InlineShapeOrRef -> InlineShapeOrRef -> Bool
Eq, Eq InlineShapeOrRef
Eq InlineShapeOrRef =>
(InlineShapeOrRef -> InlineShapeOrRef -> Ordering)
-> (InlineShapeOrRef -> InlineShapeOrRef -> Bool)
-> (InlineShapeOrRef -> InlineShapeOrRef -> Bool)
-> (InlineShapeOrRef -> InlineShapeOrRef -> Bool)
-> (InlineShapeOrRef -> InlineShapeOrRef -> Bool)
-> (InlineShapeOrRef -> InlineShapeOrRef -> InlineShapeOrRef)
-> (InlineShapeOrRef -> InlineShapeOrRef -> InlineShapeOrRef)
-> Ord InlineShapeOrRef
InlineShapeOrRef -> InlineShapeOrRef -> Bool
InlineShapeOrRef -> InlineShapeOrRef -> Ordering
InlineShapeOrRef -> InlineShapeOrRef -> InlineShapeOrRef
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: InlineShapeOrRef -> InlineShapeOrRef -> Ordering
compare :: InlineShapeOrRef -> InlineShapeOrRef -> Ordering
$c< :: InlineShapeOrRef -> InlineShapeOrRef -> Bool
< :: InlineShapeOrRef -> InlineShapeOrRef -> Bool
$c<= :: InlineShapeOrRef -> InlineShapeOrRef -> Bool
<= :: InlineShapeOrRef -> InlineShapeOrRef -> Bool
$c> :: InlineShapeOrRef -> InlineShapeOrRef -> Bool
> :: InlineShapeOrRef -> InlineShapeOrRef -> Bool
$c>= :: InlineShapeOrRef -> InlineShapeOrRef -> Bool
>= :: InlineShapeOrRef -> InlineShapeOrRef -> Bool
$cmax :: InlineShapeOrRef -> InlineShapeOrRef -> InlineShapeOrRef
max :: InlineShapeOrRef -> InlineShapeOrRef -> InlineShapeOrRef
$cmin :: InlineShapeOrRef -> InlineShapeOrRef -> InlineShapeOrRef
min :: InlineShapeOrRef -> InlineShapeOrRef -> InlineShapeOrRef
Ord, ReadPrec [InlineShapeOrRef]
ReadPrec InlineShapeOrRef
Int -> ReadS InlineShapeOrRef
ReadS [InlineShapeOrRef]
(Int -> ReadS InlineShapeOrRef)
-> ReadS [InlineShapeOrRef]
-> ReadPrec InlineShapeOrRef
-> ReadPrec [InlineShapeOrRef]
-> Read InlineShapeOrRef
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS InlineShapeOrRef
readsPrec :: Int -> ReadS InlineShapeOrRef
$creadList :: ReadS [InlineShapeOrRef]
readList :: ReadS [InlineShapeOrRef]
$creadPrec :: ReadPrec InlineShapeOrRef
readPrec :: ReadPrec InlineShapeOrRef
$creadListPrec :: ReadPrec [InlineShapeOrRef]
readListPrec :: ReadPrec [InlineShapeOrRef]
Read, Int -> InlineShapeOrRef -> ShowS
[InlineShapeOrRef] -> ShowS
InlineShapeOrRef -> String
(Int -> InlineShapeOrRef -> ShowS)
-> (InlineShapeOrRef -> String)
-> ([InlineShapeOrRef] -> ShowS)
-> Show InlineShapeOrRef
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> InlineShapeOrRef -> ShowS
showsPrec :: Int -> InlineShapeOrRef -> ShowS
$cshow :: InlineShapeOrRef -> String
show :: InlineShapeOrRef -> String
$cshowList :: [InlineShapeOrRef] -> ShowS
showList :: [InlineShapeOrRef] -> ShowS
Show)

_InlineShapeOrRef :: Name
_InlineShapeOrRef = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.InlineShapeOrRef")

_InlineShapeOrRef_inlineShapeDefinition :: Name
_InlineShapeOrRef_inlineShapeDefinition = (String -> Name
Core.Name String
"inlineShapeDefinition")

_InlineShapeOrRef_atpNameLn :: Name
_InlineShapeOrRef_atpNameLn = (String -> Name
Core.Name String
"atpNameLn")

_InlineShapeOrRef_atpNameNs :: Name
_InlineShapeOrRef_atpNameNs = (String -> Name
Core.Name String
"atpNameNs")

_InlineShapeOrRef_sequence :: Name
_InlineShapeOrRef_sequence = (String -> Name
Core.Name String
"sequence")

data NodeConstraint = 
  NodeConstraintSequence [XsFacet] |
  NodeConstraintSequence2 NodeConstraint_Sequence2 |
  NodeConstraintSequence3 NodeConstraint_Sequence3 |
  NodeConstraintSequence4 NodeConstraint_Sequence4 |
  NodeConstraintSequence5 NodeConstraint_Sequence5 |
  NodeConstraintListOfXsFacet [XsFacet]
  deriving (NodeConstraint -> NodeConstraint -> Bool
(NodeConstraint -> NodeConstraint -> Bool)
-> (NodeConstraint -> NodeConstraint -> Bool) -> Eq NodeConstraint
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: NodeConstraint -> NodeConstraint -> Bool
== :: NodeConstraint -> NodeConstraint -> Bool
$c/= :: NodeConstraint -> NodeConstraint -> Bool
/= :: NodeConstraint -> NodeConstraint -> Bool
Eq, Eq NodeConstraint
Eq NodeConstraint =>
(NodeConstraint -> NodeConstraint -> Ordering)
-> (NodeConstraint -> NodeConstraint -> Bool)
-> (NodeConstraint -> NodeConstraint -> Bool)
-> (NodeConstraint -> NodeConstraint -> Bool)
-> (NodeConstraint -> NodeConstraint -> Bool)
-> (NodeConstraint -> NodeConstraint -> NodeConstraint)
-> (NodeConstraint -> NodeConstraint -> NodeConstraint)
-> Ord NodeConstraint
NodeConstraint -> NodeConstraint -> Bool
NodeConstraint -> NodeConstraint -> Ordering
NodeConstraint -> NodeConstraint -> NodeConstraint
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: NodeConstraint -> NodeConstraint -> Ordering
compare :: NodeConstraint -> NodeConstraint -> Ordering
$c< :: NodeConstraint -> NodeConstraint -> Bool
< :: NodeConstraint -> NodeConstraint -> Bool
$c<= :: NodeConstraint -> NodeConstraint -> Bool
<= :: NodeConstraint -> NodeConstraint -> Bool
$c> :: NodeConstraint -> NodeConstraint -> Bool
> :: NodeConstraint -> NodeConstraint -> Bool
$c>= :: NodeConstraint -> NodeConstraint -> Bool
>= :: NodeConstraint -> NodeConstraint -> Bool
$cmax :: NodeConstraint -> NodeConstraint -> NodeConstraint
max :: NodeConstraint -> NodeConstraint -> NodeConstraint
$cmin :: NodeConstraint -> NodeConstraint -> NodeConstraint
min :: NodeConstraint -> NodeConstraint -> NodeConstraint
Ord, ReadPrec [NodeConstraint]
ReadPrec NodeConstraint
Int -> ReadS NodeConstraint
ReadS [NodeConstraint]
(Int -> ReadS NodeConstraint)
-> ReadS [NodeConstraint]
-> ReadPrec NodeConstraint
-> ReadPrec [NodeConstraint]
-> Read NodeConstraint
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS NodeConstraint
readsPrec :: Int -> ReadS NodeConstraint
$creadList :: ReadS [NodeConstraint]
readList :: ReadS [NodeConstraint]
$creadPrec :: ReadPrec NodeConstraint
readPrec :: ReadPrec NodeConstraint
$creadListPrec :: ReadPrec [NodeConstraint]
readListPrec :: ReadPrec [NodeConstraint]
Read, Int -> NodeConstraint -> ShowS
[NodeConstraint] -> ShowS
NodeConstraint -> String
(Int -> NodeConstraint -> ShowS)
-> (NodeConstraint -> String)
-> ([NodeConstraint] -> ShowS)
-> Show NodeConstraint
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> NodeConstraint -> ShowS
showsPrec :: Int -> NodeConstraint -> ShowS
$cshow :: NodeConstraint -> String
show :: NodeConstraint -> String
$cshowList :: [NodeConstraint] -> ShowS
showList :: [NodeConstraint] -> ShowS
Show)

_NodeConstraint :: Name
_NodeConstraint = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.NodeConstraint")

_NodeConstraint_sequence :: Name
_NodeConstraint_sequence = (String -> Name
Core.Name String
"sequence")

_NodeConstraint_sequence2 :: Name
_NodeConstraint_sequence2 = (String -> Name
Core.Name String
"sequence2")

_NodeConstraint_sequence3 :: Name
_NodeConstraint_sequence3 = (String -> Name
Core.Name String
"sequence3")

_NodeConstraint_sequence4 :: Name
_NodeConstraint_sequence4 = (String -> Name
Core.Name String
"sequence4")

_NodeConstraint_sequence5 :: Name
_NodeConstraint_sequence5 = (String -> Name
Core.Name String
"sequence5")

_NodeConstraint_listOfXsFacet :: Name
_NodeConstraint_listOfXsFacet = (String -> Name
Core.Name String
"listOfXsFacet")

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

_NodeConstraint_Sequence2 :: Name
_NodeConstraint_Sequence2 = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.NodeConstraint.Sequence2")

_NodeConstraint_Sequence2_nonLiteralKind :: Name
_NodeConstraint_Sequence2_nonLiteralKind = (String -> Name
Core.Name String
"nonLiteralKind")

_NodeConstraint_Sequence2_listOfStringFacet :: Name
_NodeConstraint_Sequence2_listOfStringFacet = (String -> Name
Core.Name String
"listOfStringFacet")

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

_NodeConstraint_Sequence3 :: Name
_NodeConstraint_Sequence3 = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.NodeConstraint.Sequence3")

_NodeConstraint_Sequence3_datatype :: Name
_NodeConstraint_Sequence3_datatype = (String -> Name
Core.Name String
"datatype")

_NodeConstraint_Sequence3_listOfXsFacet :: Name
_NodeConstraint_Sequence3_listOfXsFacet = (String -> Name
Core.Name String
"listOfXsFacet")

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

_NodeConstraint_Sequence4 :: Name
_NodeConstraint_Sequence4 = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.NodeConstraint.Sequence4")

_NodeConstraint_Sequence4_valueSet :: Name
_NodeConstraint_Sequence4_valueSet = (String -> Name
Core.Name String
"valueSet")

_NodeConstraint_Sequence4_listOfXsFacet :: Name
_NodeConstraint_Sequence4_listOfXsFacet = (String -> Name
Core.Name String
"listOfXsFacet")

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

_NodeConstraint_Sequence5 :: Name
_NodeConstraint_Sequence5 = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.NodeConstraint.Sequence5")

_NodeConstraint_Sequence5_valueSet :: Name
_NodeConstraint_Sequence5_valueSet = (String -> Name
Core.Name String
"valueSet")

_NodeConstraint_Sequence5_listOfXsFacet :: Name
_NodeConstraint_Sequence5_listOfXsFacet = (String -> Name
Core.Name String
"listOfXsFacet")

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

_NonLiteralKind :: Name
_NonLiteralKind = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.NonLiteralKind")

_NonLiteralKind_iRI :: Name
_NonLiteralKind_iRI = (String -> Name
Core.Name String
"iRI")

_NonLiteralKind_bNODE :: Name
_NonLiteralKind_bNODE = (String -> Name
Core.Name String
"bNODE")

_NonLiteralKind_nONLITERAL :: Name
_NonLiteralKind_nONLITERAL = (String -> Name
Core.Name String
"nONLITERAL")

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

_XsFacet :: Name
_XsFacet = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.XsFacet")

_XsFacet_stringFacet :: Name
_XsFacet_stringFacet = (String -> Name
Core.Name String
"stringFacet")

_XsFacet_numericFacet :: Name
_XsFacet_numericFacet = (String -> Name
Core.Name String
"numericFacet")

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

_StringFacet :: Name
_StringFacet = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.StringFacet")

_StringFacet_sequence :: Name
_StringFacet_sequence = (String -> Name
Core.Name String
"sequence")

_StringFacet_regexp :: Name
_StringFacet_regexp = (String -> Name
Core.Name String
"regexp")

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

_StringFacet_Sequence :: Name
_StringFacet_Sequence = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.StringFacet.Sequence")

_StringFacet_Sequence_stringLength :: Name
_StringFacet_Sequence_stringLength = (String -> Name
Core.Name String
"stringLength")

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

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

_StringLength :: Name
_StringLength = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.StringLength")

_StringLength_lENGTH :: Name
_StringLength_lENGTH = (String -> Name
Core.Name String
"lENGTH")

_StringLength_mINLENGTH :: Name
_StringLength_mINLENGTH = (String -> Name
Core.Name String
"mINLENGTH")

_StringLength_mAXLENGTH :: Name
_StringLength_mAXLENGTH = (String -> Name
Core.Name String
"mAXLENGTH")

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

_NumericFacet :: Name
_NumericFacet = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.NumericFacet")

_NumericFacet_sequence :: Name
_NumericFacet_sequence = (String -> Name
Core.Name String
"sequence")

_NumericFacet_sequence2 :: Name
_NumericFacet_sequence2 = (String -> Name
Core.Name String
"sequence2")

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

_NumericFacet_Sequence :: Name
_NumericFacet_Sequence = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.NumericFacet.Sequence")

_NumericFacet_Sequence_numericRange :: Name
_NumericFacet_Sequence_numericRange = (String -> Name
Core.Name String
"numericRange")

_NumericFacet_Sequence_numericLiteral :: Name
_NumericFacet_Sequence_numericLiteral = (String -> Name
Core.Name String
"numericLiteral")

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

_NumericFacet_Sequence2 :: Name
_NumericFacet_Sequence2 = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.NumericFacet.Sequence2")

_NumericFacet_Sequence2_numericLength :: Name
_NumericFacet_Sequence2_numericLength = (String -> Name
Core.Name String
"numericLength")

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

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

_NumericRange :: Name
_NumericRange = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.NumericRange")

_NumericRange_mININCLUSIVE :: Name
_NumericRange_mININCLUSIVE = (String -> Name
Core.Name String
"mININCLUSIVE")

_NumericRange_mINEXCLUSIVE :: Name
_NumericRange_mINEXCLUSIVE = (String -> Name
Core.Name String
"mINEXCLUSIVE")

_NumericRange_mAXINCLUSIVE :: Name
_NumericRange_mAXINCLUSIVE = (String -> Name
Core.Name String
"mAXINCLUSIVE")

_NumericRange_mAXEXCLUSIVE :: Name
_NumericRange_mAXEXCLUSIVE = (String -> Name
Core.Name String
"mAXEXCLUSIVE")

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

_NumericLength :: Name
_NumericLength = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.NumericLength")

_NumericLength_tOTALDIGITS :: Name
_NumericLength_tOTALDIGITS = (String -> Name
Core.Name String
"tOTALDIGITS")

_NumericLength_fRACTIONDIGITS :: Name
_NumericLength_fRACTIONDIGITS = (String -> Name
Core.Name String
"fRACTIONDIGITS")

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

_ShapeDefinition :: Name
_ShapeDefinition = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.ShapeDefinition")

_ShapeDefinition_listOfAlts :: Name
_ShapeDefinition_listOfAlts = (String -> Name
Core.Name String
"listOfAlts")

_ShapeDefinition_tripleExpression :: Name
_ShapeDefinition_tripleExpression = (String -> Name
Core.Name String
"tripleExpression")

_ShapeDefinition_listOfAnnotation :: Name
_ShapeDefinition_listOfAnnotation = (String -> Name
Core.Name String
"listOfAnnotation")

_ShapeDefinition_semanticActions :: Name
_ShapeDefinition_semanticActions = (String -> Name
Core.Name String
"semanticActions")

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

_ShapeDefinition_ListOfAlts_Elmt :: Name
_ShapeDefinition_ListOfAlts_Elmt = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.ShapeDefinition.ListOfAlts.Elmt")

_ShapeDefinition_ListOfAlts_Elmt_includeSet :: Name
_ShapeDefinition_ListOfAlts_Elmt_includeSet = (String -> Name
Core.Name String
"includeSet")

_ShapeDefinition_ListOfAlts_Elmt_extraPropertySet :: Name
_ShapeDefinition_ListOfAlts_Elmt_extraPropertySet = (String -> Name
Core.Name String
"extraPropertySet")

_ShapeDefinition_ListOfAlts_Elmt_cLOSED :: Name
_ShapeDefinition_ListOfAlts_Elmt_cLOSED = (String -> Name
Core.Name String
"cLOSED")

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

_InlineShapeDefinition :: Name
_InlineShapeDefinition = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.InlineShapeDefinition")

_InlineShapeDefinition_listOfAlts :: Name
_InlineShapeDefinition_listOfAlts = (String -> Name
Core.Name String
"listOfAlts")

_InlineShapeDefinition_tripleExpression :: Name
_InlineShapeDefinition_tripleExpression = (String -> Name
Core.Name String
"tripleExpression")

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

_InlineShapeDefinition_ListOfAlts_Elmt :: Name
_InlineShapeDefinition_ListOfAlts_Elmt = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.InlineShapeDefinition.ListOfAlts.Elmt")

_InlineShapeDefinition_ListOfAlts_Elmt_includeSet :: Name
_InlineShapeDefinition_ListOfAlts_Elmt_includeSet = (String -> Name
Core.Name String
"includeSet")

_InlineShapeDefinition_ListOfAlts_Elmt_extraPropertySet :: Name
_InlineShapeDefinition_ListOfAlts_Elmt_extraPropertySet = (String -> Name
Core.Name String
"extraPropertySet")

_InlineShapeDefinition_ListOfAlts_Elmt_cLOSED :: Name
_InlineShapeDefinition_ListOfAlts_Elmt_cLOSED = (String -> Name
Core.Name String
"cLOSED")

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

_ExtraPropertySet :: Name
_ExtraPropertySet = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.ExtraPropertySet")

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

_TripleExpression :: Name
_TripleExpression = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.TripleExpression")

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

_OneOfTripleExpr :: Name
_OneOfTripleExpr = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.OneOfTripleExpr")

_OneOfTripleExpr_groupTripleExpr :: Name
_OneOfTripleExpr_groupTripleExpr = (String -> Name
Core.Name String
"groupTripleExpr")

_OneOfTripleExpr_multiElementOneOf :: Name
_OneOfTripleExpr_multiElementOneOf = (String -> Name
Core.Name String
"multiElementOneOf")

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

_MultiElementOneOf :: Name
_MultiElementOneOf = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.MultiElementOneOf")

_MultiElementOneOf_groupTripleExpr :: Name
_MultiElementOneOf_groupTripleExpr = (String -> Name
Core.Name String
"groupTripleExpr")

_MultiElementOneOf_listOfSequence :: Name
_MultiElementOneOf_listOfSequence = (String -> Name
Core.Name String
"listOfSequence")

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

_InnerTripleExpr :: Name
_InnerTripleExpr = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.InnerTripleExpr")

_InnerTripleExpr_multiElementGroup :: Name
_InnerTripleExpr_multiElementGroup = (String -> Name
Core.Name String
"multiElementGroup")

_InnerTripleExpr_multiElementOneOf :: Name
_InnerTripleExpr_multiElementOneOf = (String -> Name
Core.Name String
"multiElementOneOf")

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

_GroupTripleExpr :: Name
_GroupTripleExpr = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.GroupTripleExpr")

_GroupTripleExpr_singleElementGroup :: Name
_GroupTripleExpr_singleElementGroup = (String -> Name
Core.Name String
"singleElementGroup")

_GroupTripleExpr_multiElementGroup :: Name
_GroupTripleExpr_multiElementGroup = (String -> Name
Core.Name String
"multiElementGroup")

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

_SingleElementGroup :: Name
_SingleElementGroup = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.SingleElementGroup")

_SingleElementGroup_unaryTripleExpr :: Name
_SingleElementGroup_unaryTripleExpr = (String -> Name
Core.Name String
"unaryTripleExpr")

_SingleElementGroup_semi :: Name
_SingleElementGroup_semi = (String -> Name
Core.Name String
"semi")

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

_MultiElementGroup :: Name
_MultiElementGroup = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.MultiElementGroup")

_MultiElementGroup_unaryTripleExpr :: Name
_MultiElementGroup_unaryTripleExpr = (String -> Name
Core.Name String
"unaryTripleExpr")

_MultiElementGroup_listOfSequence :: Name
_MultiElementGroup_listOfSequence = (String -> Name
Core.Name String
"listOfSequence")

_MultiElementGroup_semi :: Name
_MultiElementGroup_semi = (String -> Name
Core.Name String
"semi")

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

_UnaryTripleExpr :: Name
_UnaryTripleExpr = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.UnaryTripleExpr")

_UnaryTripleExpr_sequence :: Name
_UnaryTripleExpr_sequence = (String -> Name
Core.Name String
"sequence")

_UnaryTripleExpr_include :: Name
_UnaryTripleExpr_include = (String -> Name
Core.Name String
"include")

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

_UnaryTripleExpr_Sequence :: Name
_UnaryTripleExpr_Sequence = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.UnaryTripleExpr.Sequence")

_UnaryTripleExpr_Sequence_sequence :: Name
_UnaryTripleExpr_Sequence_sequence = (String -> Name
Core.Name String
"sequence")

_UnaryTripleExpr_Sequence_alts :: Name
_UnaryTripleExpr_Sequence_alts = (String -> Name
Core.Name String
"alts")

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

_UnaryTripleExpr_Sequence_Alts :: Name
_UnaryTripleExpr_Sequence_Alts = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.UnaryTripleExpr.Sequence.Alts")

_UnaryTripleExpr_Sequence_Alts_tripleConstraint :: Name
_UnaryTripleExpr_Sequence_Alts_tripleConstraint = (String -> Name
Core.Name String
"tripleConstraint")

_UnaryTripleExpr_Sequence_Alts_bracketedTripleExpr :: Name
_UnaryTripleExpr_Sequence_Alts_bracketedTripleExpr = (String -> Name
Core.Name String
"bracketedTripleExpr")

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

_BracketedTripleExpr :: Name
_BracketedTripleExpr = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.BracketedTripleExpr")

_BracketedTripleExpr_innerTripleExpr :: Name
_BracketedTripleExpr_innerTripleExpr = (String -> Name
Core.Name String
"innerTripleExpr")

_BracketedTripleExpr_cardinality :: Name
_BracketedTripleExpr_cardinality = (String -> Name
Core.Name String
"cardinality")

_BracketedTripleExpr_listOfAnnotation :: Name
_BracketedTripleExpr_listOfAnnotation = (String -> Name
Core.Name String
"listOfAnnotation")

_BracketedTripleExpr_semanticActions :: Name
_BracketedTripleExpr_semanticActions = (String -> Name
Core.Name String
"semanticActions")

data TripleConstraint = 
  TripleConstraint {
    TripleConstraint -> Maybe SenseFlags
tripleConstraintSenseFlags :: (Maybe SenseFlags),
    TripleConstraint -> Predicate
tripleConstraintPredicate :: Predicate,
    TripleConstraint -> InlineShapeExpression
tripleConstraintInlineShapeExpression :: InlineShapeExpression,
    TripleConstraint -> Maybe Cardinality
tripleConstraintCardinality :: (Maybe Cardinality),
    TripleConstraint -> [Annotation]
tripleConstraintListOfAnnotation :: [Annotation],
    TripleConstraint -> SemanticActions
tripleConstraintSemanticActions :: SemanticActions}
  deriving (TripleConstraint -> TripleConstraint -> Bool
(TripleConstraint -> TripleConstraint -> Bool)
-> (TripleConstraint -> TripleConstraint -> Bool)
-> Eq TripleConstraint
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TripleConstraint -> TripleConstraint -> Bool
== :: TripleConstraint -> TripleConstraint -> Bool
$c/= :: TripleConstraint -> TripleConstraint -> Bool
/= :: TripleConstraint -> TripleConstraint -> Bool
Eq, Eq TripleConstraint
Eq TripleConstraint =>
(TripleConstraint -> TripleConstraint -> Ordering)
-> (TripleConstraint -> TripleConstraint -> Bool)
-> (TripleConstraint -> TripleConstraint -> Bool)
-> (TripleConstraint -> TripleConstraint -> Bool)
-> (TripleConstraint -> TripleConstraint -> Bool)
-> (TripleConstraint -> TripleConstraint -> TripleConstraint)
-> (TripleConstraint -> TripleConstraint -> TripleConstraint)
-> Ord TripleConstraint
TripleConstraint -> TripleConstraint -> Bool
TripleConstraint -> TripleConstraint -> Ordering
TripleConstraint -> TripleConstraint -> TripleConstraint
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: TripleConstraint -> TripleConstraint -> Ordering
compare :: TripleConstraint -> TripleConstraint -> Ordering
$c< :: TripleConstraint -> TripleConstraint -> Bool
< :: TripleConstraint -> TripleConstraint -> Bool
$c<= :: TripleConstraint -> TripleConstraint -> Bool
<= :: TripleConstraint -> TripleConstraint -> Bool
$c> :: TripleConstraint -> TripleConstraint -> Bool
> :: TripleConstraint -> TripleConstraint -> Bool
$c>= :: TripleConstraint -> TripleConstraint -> Bool
>= :: TripleConstraint -> TripleConstraint -> Bool
$cmax :: TripleConstraint -> TripleConstraint -> TripleConstraint
max :: TripleConstraint -> TripleConstraint -> TripleConstraint
$cmin :: TripleConstraint -> TripleConstraint -> TripleConstraint
min :: TripleConstraint -> TripleConstraint -> TripleConstraint
Ord, ReadPrec [TripleConstraint]
ReadPrec TripleConstraint
Int -> ReadS TripleConstraint
ReadS [TripleConstraint]
(Int -> ReadS TripleConstraint)
-> ReadS [TripleConstraint]
-> ReadPrec TripleConstraint
-> ReadPrec [TripleConstraint]
-> Read TripleConstraint
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS TripleConstraint
readsPrec :: Int -> ReadS TripleConstraint
$creadList :: ReadS [TripleConstraint]
readList :: ReadS [TripleConstraint]
$creadPrec :: ReadPrec TripleConstraint
readPrec :: ReadPrec TripleConstraint
$creadListPrec :: ReadPrec [TripleConstraint]
readListPrec :: ReadPrec [TripleConstraint]
Read, Int -> TripleConstraint -> ShowS
[TripleConstraint] -> ShowS
TripleConstraint -> String
(Int -> TripleConstraint -> ShowS)
-> (TripleConstraint -> String)
-> ([TripleConstraint] -> ShowS)
-> Show TripleConstraint
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TripleConstraint -> ShowS
showsPrec :: Int -> TripleConstraint -> ShowS
$cshow :: TripleConstraint -> String
show :: TripleConstraint -> String
$cshowList :: [TripleConstraint] -> ShowS
showList :: [TripleConstraint] -> ShowS
Show)

_TripleConstraint :: Name
_TripleConstraint = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.TripleConstraint")

_TripleConstraint_senseFlags :: Name
_TripleConstraint_senseFlags = (String -> Name
Core.Name String
"senseFlags")

_TripleConstraint_predicate :: Name
_TripleConstraint_predicate = (String -> Name
Core.Name String
"predicate")

_TripleConstraint_inlineShapeExpression :: Name
_TripleConstraint_inlineShapeExpression = (String -> Name
Core.Name String
"inlineShapeExpression")

_TripleConstraint_cardinality :: Name
_TripleConstraint_cardinality = (String -> Name
Core.Name String
"cardinality")

_TripleConstraint_listOfAnnotation :: Name
_TripleConstraint_listOfAnnotation = (String -> Name
Core.Name String
"listOfAnnotation")

_TripleConstraint_semanticActions :: Name
_TripleConstraint_semanticActions = (String -> Name
Core.Name String
"semanticActions")

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

_Cardinality :: Name
_Cardinality = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.Cardinality")

_Cardinality_ast :: Name
_Cardinality_ast = (String -> Name
Core.Name String
"ast")

_Cardinality_plus :: Name
_Cardinality_plus = (String -> Name
Core.Name String
"plus")

_Cardinality_quest :: Name
_Cardinality_quest = (String -> Name
Core.Name String
"quest")

_Cardinality_repeatRange :: Name
_Cardinality_repeatRange = (String -> Name
Core.Name String
"repeatRange")

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

_SenseFlags :: Name
_SenseFlags = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.SenseFlags")

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

_ValueSet :: Name
_ValueSet = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.ValueSet")

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

_ValueSetValue :: Name
_ValueSetValue = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.ValueSetValue")

_ValueSetValue_iriRange :: Name
_ValueSetValue_iriRange = (String -> Name
Core.Name String
"iriRange")

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

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

_IriRange :: Name
_IriRange = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.IriRange")

_IriRange_sequence :: Name
_IriRange_sequence = (String -> Name
Core.Name String
"sequence")

_IriRange_sequence2 :: Name
_IriRange_sequence2 = (String -> Name
Core.Name String
"sequence2")

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

_IriRange_Sequence :: Name
_IriRange_Sequence = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.IriRange.Sequence")

_IriRange_Sequence_iri :: Name
_IriRange_Sequence_iri = (String -> Name
Core.Name String
"iri")

_IriRange_Sequence_sequence :: Name
_IriRange_Sequence_sequence = (String -> Name
Core.Name String
"sequence")

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

_Exclusion :: Name
_Exclusion = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.Exclusion")

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

_Include :: Name
_Include = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.Include")

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

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

_Annotation_predicate :: Name
_Annotation_predicate = (String -> Name
Core.Name String
"predicate")

_Annotation_alts :: Name
_Annotation_alts = (String -> Name
Core.Name String
"alts")

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

_Annotation_Alts :: Name
_Annotation_Alts = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.Annotation.Alts")

_Annotation_Alts_iri :: Name
_Annotation_Alts_iri = (String -> Name
Core.Name String
"iri")

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

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

_SemanticActions :: Name
_SemanticActions = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.SemanticActions")

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

_CodeDecl :: Name
_CodeDecl = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.CodeDecl")

_CodeDecl_iri :: Name
_CodeDecl_iri = (String -> Name
Core.Name String
"iri")

_CodeDecl_alts :: Name
_CodeDecl_alts = (String -> Name
Core.Name String
"alts")

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

_CodeDecl_Alts :: Name
_CodeDecl_Alts = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.CodeDecl.Alts")

_CodeDecl_Alts_code :: Name
_CodeDecl_Alts_code = (String -> Name
Core.Name String
"code")

_CodeDecl_Alts_percnt :: Name
_CodeDecl_Alts_percnt = (String -> Name
Core.Name String
"percnt")

data Literal = 
  LiteralRdfLiteral RdfLiteral |
  LiteralNumericLiteral NumericLiteral |
  LiteralBooleanLiteral BooleanLiteral
  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
Core.Name String
"hydra/langs/shex/syntax.Literal")

_Literal_rdfLiteral :: Name
_Literal_rdfLiteral = (String -> Name
Core.Name String
"rdfLiteral")

_Literal_numericLiteral :: Name
_Literal_numericLiteral = (String -> Name
Core.Name String
"numericLiteral")

_Literal_booleanLiteral :: Name
_Literal_booleanLiteral = (String -> Name
Core.Name String
"booleanLiteral")

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

_Predicate :: Name
_Predicate = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.Predicate")

_Predicate_iri :: Name
_Predicate_iri = (String -> Name
Core.Name String
"iri")

_Predicate_rdfType :: Name
_Predicate_rdfType = (String -> Name
Core.Name String
"rdfType")

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

_Datatype :: Name
_Datatype = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.Datatype")

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

_ShapeExprLabel :: Name
_ShapeExprLabel = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.ShapeExprLabel")

_ShapeExprLabel_iri :: Name
_ShapeExprLabel_iri = (String -> Name
Core.Name String
"iri")

_ShapeExprLabel_blankNode :: Name
_ShapeExprLabel_blankNode = (String -> Name
Core.Name String
"blankNode")

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

_TripleExprLabel :: Name
_TripleExprLabel = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.TripleExprLabel")

_TripleExprLabel_iri :: Name
_TripleExprLabel_iri = (String -> Name
Core.Name String
"iri")

_TripleExprLabel_blankNode :: Name
_TripleExprLabel_blankNode = (String -> Name
Core.Name String
"blankNode")

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

_NumericLiteral :: Name
_NumericLiteral = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.NumericLiteral")

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

_NumericLiteral_decimal :: Name
_NumericLiteral_decimal = (String -> Name
Core.Name String
"decimal")

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

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

_RdfLiteral :: Name
_RdfLiteral = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.RdfLiteral")

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

_RdfLiteral_alts :: Name
_RdfLiteral_alts = (String -> Name
Core.Name String
"alts")

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

_RdfLiteral_Alts_Option :: Name
_RdfLiteral_Alts_Option = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.RdfLiteral.Alts.Option")

_RdfLiteral_Alts_Option_langTag :: Name
_RdfLiteral_Alts_Option_langTag = (String -> Name
Core.Name String
"langTag")

_RdfLiteral_Alts_Option_sequence :: Name
_RdfLiteral_Alts_Option_sequence = (String -> Name
Core.Name String
"sequence")

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

_BooleanLiteral :: Name
_BooleanLiteral = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.BooleanLiteral")

_BooleanLiteral_true :: Name
_BooleanLiteral_true = (String -> Name
Core.Name String
"true")

_BooleanLiteral_false :: Name
_BooleanLiteral_false = (String -> Name
Core.Name String
"false")

data String_ = 
  StringStringLiteral1 StringLiteral1 |
  StringStringLiteralLong1 StringLiteralLong1 |
  StringStringLiteral2 StringLiteral2 |
  StringStringLiteralLong2 StringLiteralLong2
  deriving (String_ -> String_ -> Bool
(String_ -> String_ -> Bool)
-> (String_ -> String_ -> Bool) -> Eq String_
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: String_ -> String_ -> Bool
== :: String_ -> String_ -> Bool
$c/= :: String_ -> String_ -> Bool
/= :: String_ -> String_ -> Bool
Eq, Eq String_
Eq String_ =>
(String_ -> String_ -> Ordering)
-> (String_ -> String_ -> Bool)
-> (String_ -> String_ -> Bool)
-> (String_ -> String_ -> Bool)
-> (String_ -> String_ -> Bool)
-> (String_ -> String_ -> String_)
-> (String_ -> String_ -> String_)
-> Ord String_
String_ -> String_ -> Bool
String_ -> String_ -> Ordering
String_ -> String_ -> String_
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: String_ -> String_ -> Ordering
compare :: String_ -> String_ -> Ordering
$c< :: String_ -> String_ -> Bool
< :: String_ -> String_ -> Bool
$c<= :: String_ -> String_ -> Bool
<= :: String_ -> String_ -> Bool
$c> :: String_ -> String_ -> Bool
> :: String_ -> String_ -> Bool
$c>= :: String_ -> String_ -> Bool
>= :: String_ -> String_ -> Bool
$cmax :: String_ -> String_ -> String_
max :: String_ -> String_ -> String_
$cmin :: String_ -> String_ -> String_
min :: String_ -> String_ -> String_
Ord, ReadPrec [String_]
ReadPrec String_
Int -> ReadS String_
ReadS [String_]
(Int -> ReadS String_)
-> ReadS [String_]
-> ReadPrec String_
-> ReadPrec [String_]
-> Read String_
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS String_
readsPrec :: Int -> ReadS String_
$creadList :: ReadS [String_]
readList :: ReadS [String_]
$creadPrec :: ReadPrec String_
readPrec :: ReadPrec String_
$creadListPrec :: ReadPrec [String_]
readListPrec :: ReadPrec [String_]
Read, Int -> String_ -> ShowS
[String_] -> ShowS
String_ -> String
(Int -> String_ -> ShowS)
-> (String_ -> String) -> ([String_] -> ShowS) -> Show String_
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> String_ -> ShowS
showsPrec :: Int -> String_ -> ShowS
$cshow :: String_ -> String
show :: String_ -> String
$cshowList :: [String_] -> ShowS
showList :: [String_] -> ShowS
Show)

_String :: Name
_String = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.String")

_String_stringLiteral1 :: Name
_String_stringLiteral1 = (String -> Name
Core.Name String
"stringLiteral1")

_String_stringLiteralLong1 :: Name
_String_stringLiteralLong1 = (String -> Name
Core.Name String
"stringLiteralLong1")

_String_stringLiteral2 :: Name
_String_stringLiteral2 = (String -> Name
Core.Name String
"stringLiteral2")

_String_stringLiteralLong2 :: Name
_String_stringLiteralLong2 = (String -> Name
Core.Name String
"stringLiteralLong2")

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

_Iri :: Name
_Iri = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.Iri")

_Iri_iriRef :: Name
_Iri_iriRef = (String -> Name
Core.Name String
"iriRef")

_Iri_prefixedName :: Name
_Iri_prefixedName = (String -> Name
Core.Name String
"prefixedName")

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

_PrefixedName :: Name
_PrefixedName = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.PrefixedName")

_PrefixedName_pnameLn :: Name
_PrefixedName_pnameLn = (String -> Name
Core.Name String
"pnameLn")

_PrefixedName_pnameNs :: Name
_PrefixedName_pnameNs = (String -> Name
Core.Name String
"pnameNs")

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

_BlankNode :: Name
_BlankNode = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.BlankNode")

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

_IncludeSet :: Name
_IncludeSet = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.IncludeSet")

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

_Code :: Name
_Code = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.Code")

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

_Code_Elmt :: Name
_Code_Elmt = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.Code.Elmt")

_Code_Elmt_regex :: Name
_Code_Elmt_regex = (String -> Name
Core.Name String
"regex")

_Code_Elmt_sequence :: Name
_Code_Elmt_sequence = (String -> Name
Core.Name String
"sequence")

_Code_Elmt_uchar :: Name
_Code_Elmt_uchar = (String -> Name
Core.Name String
"uchar")

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

_RepeatRange :: Name
_RepeatRange = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.RepeatRange")

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

_RepeatRange_sequence :: Name
_RepeatRange_sequence = (String -> Name
Core.Name String
"sequence")

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

_RepeatRange_Sequence_Option_Option_Option :: Name
_RepeatRange_Sequence_Option_Option_Option = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.RepeatRange.Sequence.Option.Option.Option")

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

_RepeatRange_Sequence_Option_Option_Option_ast :: Name
_RepeatRange_Sequence_Option_Option_Option_ast = (String -> Name
Core.Name String
"ast")

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

_RdfType :: Name
_RdfType = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.RdfType")

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

_IriRef :: Name
_IriRef = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.IriRef")

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

_IriRef_Elmt :: Name
_IriRef_Elmt = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.IriRef.Elmt")

_IriRef_Elmt_regex :: Name
_IriRef_Elmt_regex = (String -> Name
Core.Name String
"regex")

_IriRef_Elmt_uchar :: Name
_IriRef_Elmt_uchar = (String -> Name
Core.Name String
"uchar")

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

_PnameNs :: Name
_PnameNs = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.PnameNs")

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

_PnameLn :: Name
_PnameLn = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.PnameLn")

_PnameLn_pnameNs :: Name
_PnameLn_pnameNs = (String -> Name
Core.Name String
"pnameNs")

_PnameLn_pnLocal :: Name
_PnameLn_pnLocal = (String -> Name
Core.Name String
"pnLocal")

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

_AtpNameNs :: Name
_AtpNameNs = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.AtpNameNs")

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

_AtpNameLn :: Name
_AtpNameLn = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.AtpNameLn")

_AtpNameLn_pnameNs :: Name
_AtpNameLn_pnameNs = (String -> Name
Core.Name String
"pnameNs")

_AtpNameLn_pnLocal :: Name
_AtpNameLn_pnLocal = (String -> Name
Core.Name String
"pnLocal")

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

_Regexp :: Name
_Regexp = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.Regexp")

_Regexp_listOfAlts :: Name
_Regexp_listOfAlts = (String -> Name
Core.Name String
"listOfAlts")

_Regexp_listOfRegex :: Name
_Regexp_listOfRegex = (String -> Name
Core.Name String
"listOfRegex")

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

_Regexp_ListOfAlts_Elmt :: Name
_Regexp_ListOfAlts_Elmt = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.Regexp.ListOfAlts.Elmt")

_Regexp_ListOfAlts_Elmt_regex :: Name
_Regexp_ListOfAlts_Elmt_regex = (String -> Name
Core.Name String
"regex")

_Regexp_ListOfAlts_Elmt_sequence :: Name
_Regexp_ListOfAlts_Elmt_sequence = (String -> Name
Core.Name String
"sequence")

_Regexp_ListOfAlts_Elmt_uchar :: Name
_Regexp_ListOfAlts_Elmt_uchar = (String -> Name
Core.Name String
"uchar")

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

_BlankNodeLabel :: Name
_BlankNodeLabel = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.BlankNodeLabel")

_BlankNodeLabel_alts :: Name
_BlankNodeLabel_alts = (String -> Name
Core.Name String
"alts")

_BlankNodeLabel_listOfAlts :: Name
_BlankNodeLabel_listOfAlts = (String -> Name
Core.Name String
"listOfAlts")

_BlankNodeLabel_pnChars :: Name
_BlankNodeLabel_pnChars = (String -> Name
Core.Name String
"pnChars")

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

_BlankNodeLabel_Alts :: Name
_BlankNodeLabel_Alts = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.BlankNodeLabel.Alts")

_BlankNodeLabel_Alts_pnCharsU :: Name
_BlankNodeLabel_Alts_pnCharsU = (String -> Name
Core.Name String
"pnCharsU")

_BlankNodeLabel_Alts_regex :: Name
_BlankNodeLabel_Alts_regex = (String -> Name
Core.Name String
"regex")

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

_BlankNodeLabel_ListOfAlts_Option_Elmt :: Name
_BlankNodeLabel_ListOfAlts_Option_Elmt = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.BlankNodeLabel.ListOfAlts.Option.Elmt")

_BlankNodeLabel_ListOfAlts_Option_Elmt_pnChars :: Name
_BlankNodeLabel_ListOfAlts_Option_Elmt_pnChars = (String -> Name
Core.Name String
"pnChars")

_BlankNodeLabel_ListOfAlts_Option_Elmt_period :: Name
_BlankNodeLabel_ListOfAlts_Option_Elmt_period = (String -> Name
Core.Name String
"period")

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

_LangTag :: Name
_LangTag = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.LangTag")

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

_Integer :: Name
_Integer = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.Integer")

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

_Decimal :: Name
_Decimal = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.Decimal")

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

_Double :: Name
_Double = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.Double")

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

_StringLiteral1 :: Name
_StringLiteral1 = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.StringLiteral1")

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

_StringLiteral1_Elmt :: Name
_StringLiteral1_Elmt = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.StringLiteral1.Elmt")

_StringLiteral1_Elmt_regex :: Name
_StringLiteral1_Elmt_regex = (String -> Name
Core.Name String
"regex")

_StringLiteral1_Elmt_echar :: Name
_StringLiteral1_Elmt_echar = (String -> Name
Core.Name String
"echar")

_StringLiteral1_Elmt_uchar :: Name
_StringLiteral1_Elmt_uchar = (String -> Name
Core.Name String
"uchar")

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

_StringLiteral2 :: Name
_StringLiteral2 = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.StringLiteral2")

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

_StringLiteral2_Elmt :: Name
_StringLiteral2_Elmt = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.StringLiteral2.Elmt")

_StringLiteral2_Elmt_regex :: Name
_StringLiteral2_Elmt_regex = (String -> Name
Core.Name String
"regex")

_StringLiteral2_Elmt_echar :: Name
_StringLiteral2_Elmt_echar = (String -> Name
Core.Name String
"echar")

_StringLiteral2_Elmt_uchar :: Name
_StringLiteral2_Elmt_uchar = (String -> Name
Core.Name String
"uchar")

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

_StringLiteralLong1 :: Name
_StringLiteralLong1 = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.StringLiteralLong1")

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

_StringLiteralLong1_Elmt :: Name
_StringLiteralLong1_Elmt = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.StringLiteralLong1.Elmt")

_StringLiteralLong1_Elmt_sequence :: Name
_StringLiteralLong1_Elmt_sequence = (String -> Name
Core.Name String
"sequence")

_StringLiteralLong1_Elmt_echar :: Name
_StringLiteralLong1_Elmt_echar = (String -> Name
Core.Name String
"echar")

_StringLiteralLong1_Elmt_uchar :: Name
_StringLiteralLong1_Elmt_uchar = (String -> Name
Core.Name String
"uchar")

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

_StringLiteralLong1_Elmt_Sequence :: Name
_StringLiteralLong1_Elmt_Sequence = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.StringLiteralLong1.Elmt.Sequence")

_StringLiteralLong1_Elmt_Sequence_alts :: Name
_StringLiteralLong1_Elmt_Sequence_alts = (String -> Name
Core.Name String
"alts")

_StringLiteralLong1_Elmt_Sequence_regex :: Name
_StringLiteralLong1_Elmt_Sequence_regex = (String -> Name
Core.Name String
"regex")

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

_StringLiteralLong1_Elmt_Sequence_Alts_Option :: Name
_StringLiteralLong1_Elmt_Sequence_Alts_Option = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.StringLiteralLong1.Elmt.Sequence.Alts.Option")

_StringLiteralLong1_Elmt_Sequence_Alts_Option_apos :: Name
_StringLiteralLong1_Elmt_Sequence_Alts_Option_apos = (String -> Name
Core.Name String
"apos")

_StringLiteralLong1_Elmt_Sequence_Alts_Option_sequence :: Name
_StringLiteralLong1_Elmt_Sequence_Alts_Option_sequence = (String -> Name
Core.Name String
"sequence")

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

_StringLiteralLong1_Elmt_Sequence_Alts_Option_Sequence :: Name
_StringLiteralLong1_Elmt_Sequence_Alts_Option_Sequence = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.StringLiteralLong1.Elmt.Sequence.Alts.Option.Sequence")

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

_StringLiteralLong2 :: Name
_StringLiteralLong2 = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.StringLiteralLong2")

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

_StringLiteralLong2_Elmt :: Name
_StringLiteralLong2_Elmt = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.StringLiteralLong2.Elmt")

_StringLiteralLong2_Elmt_sequence :: Name
_StringLiteralLong2_Elmt_sequence = (String -> Name
Core.Name String
"sequence")

_StringLiteralLong2_Elmt_echar :: Name
_StringLiteralLong2_Elmt_echar = (String -> Name
Core.Name String
"echar")

_StringLiteralLong2_Elmt_uchar :: Name
_StringLiteralLong2_Elmt_uchar = (String -> Name
Core.Name String
"uchar")

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

_StringLiteralLong2_Elmt_Sequence :: Name
_StringLiteralLong2_Elmt_Sequence = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.StringLiteralLong2.Elmt.Sequence")

_StringLiteralLong2_Elmt_Sequence_alts :: Name
_StringLiteralLong2_Elmt_Sequence_alts = (String -> Name
Core.Name String
"alts")

_StringLiteralLong2_Elmt_Sequence_regex :: Name
_StringLiteralLong2_Elmt_Sequence_regex = (String -> Name
Core.Name String
"regex")

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

_StringLiteralLong2_Elmt_Sequence_Alts_Option :: Name
_StringLiteralLong2_Elmt_Sequence_Alts_Option = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.StringLiteralLong2.Elmt.Sequence.Alts.Option")

_StringLiteralLong2_Elmt_Sequence_Alts_Option_quot :: Name
_StringLiteralLong2_Elmt_Sequence_Alts_Option_quot = (String -> Name
Core.Name String
"quot")

_StringLiteralLong2_Elmt_Sequence_Alts_Option_sequence :: Name
_StringLiteralLong2_Elmt_Sequence_Alts_Option_sequence = (String -> Name
Core.Name String
"sequence")

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

_StringLiteralLong2_Elmt_Sequence_Alts_Option_Sequence :: Name
_StringLiteralLong2_Elmt_Sequence_Alts_Option_Sequence = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.StringLiteralLong2.Elmt.Sequence.Alts.Option.Sequence")

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

_Uchar :: Name
_Uchar = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.Uchar")

_Uchar_sequence :: Name
_Uchar_sequence = (String -> Name
Core.Name String
"sequence")

_Uchar_sequence2 :: Name
_Uchar_sequence2 = (String -> Name
Core.Name String
"sequence2")

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

_Uchar_Sequence :: Name
_Uchar_Sequence = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.Uchar.Sequence")

_Uchar_Sequence_hex :: Name
_Uchar_Sequence_hex = (String -> Name
Core.Name String
"hex")

_Uchar_Sequence_hex2 :: Name
_Uchar_Sequence_hex2 = (String -> Name
Core.Name String
"hex2")

_Uchar_Sequence_hex3 :: Name
_Uchar_Sequence_hex3 = (String -> Name
Core.Name String
"hex3")

_Uchar_Sequence_hex4 :: Name
_Uchar_Sequence_hex4 = (String -> Name
Core.Name String
"hex4")

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

_Uchar_Sequence2 :: Name
_Uchar_Sequence2 = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.Uchar.Sequence2")

_Uchar_Sequence2_hex :: Name
_Uchar_Sequence2_hex = (String -> Name
Core.Name String
"hex")

_Uchar_Sequence2_hex2 :: Name
_Uchar_Sequence2_hex2 = (String -> Name
Core.Name String
"hex2")

_Uchar_Sequence2_hex3 :: Name
_Uchar_Sequence2_hex3 = (String -> Name
Core.Name String
"hex3")

_Uchar_Sequence2_hex4 :: Name
_Uchar_Sequence2_hex4 = (String -> Name
Core.Name String
"hex4")

_Uchar_Sequence2_hex5 :: Name
_Uchar_Sequence2_hex5 = (String -> Name
Core.Name String
"hex5")

_Uchar_Sequence2_hex6 :: Name
_Uchar_Sequence2_hex6 = (String -> Name
Core.Name String
"hex6")

_Uchar_Sequence2_hex7 :: Name
_Uchar_Sequence2_hex7 = (String -> Name
Core.Name String
"hex7")

_Uchar_Sequence2_hex8 :: Name
_Uchar_Sequence2_hex8 = (String -> Name
Core.Name String
"hex8")

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

_Echar :: Name
_Echar = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.Echar")

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

_PnCharsBase :: Name
_PnCharsBase = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.PnCharsBase")

_PnCharsBase_regex :: Name
_PnCharsBase_regex = (String -> Name
Core.Name String
"regex")

_PnCharsBase_regex2 :: Name
_PnCharsBase_regex2 = (String -> Name
Core.Name String
"regex2")

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

_PnCharsU :: Name
_PnCharsU = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.PnCharsU")

_PnCharsU_pnCharsBase :: Name
_PnCharsU_pnCharsBase = (String -> Name
Core.Name String
"pnCharsBase")

_PnCharsU_lowbar :: Name
_PnCharsU_lowbar = (String -> Name
Core.Name String
"lowbar")

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

_PnChars :: Name
_PnChars = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.PnChars")

_PnChars_pnCharsU :: Name
_PnChars_pnCharsU = (String -> Name
Core.Name String
"pnCharsU")

_PnChars_minus :: Name
_PnChars_minus = (String -> Name
Core.Name String
"minus")

_PnChars_regex :: Name
_PnChars_regex = (String -> Name
Core.Name String
"regex")

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

_PnPrefix :: Name
_PnPrefix = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.PnPrefix")

_PnPrefix_pnCharsBase :: Name
_PnPrefix_pnCharsBase = (String -> Name
Core.Name String
"pnCharsBase")

_PnPrefix_sequence :: Name
_PnPrefix_sequence = (String -> Name
Core.Name String
"sequence")

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

_PnPrefix_Sequence_Option :: Name
_PnPrefix_Sequence_Option = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.PnPrefix.Sequence.Option")

_PnPrefix_Sequence_Option_alts :: Name
_PnPrefix_Sequence_Option_alts = (String -> Name
Core.Name String
"alts")

_PnPrefix_Sequence_Option_pnChars :: Name
_PnPrefix_Sequence_Option_pnChars = (String -> Name
Core.Name String
"pnChars")

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

_PnPrefix_Sequence_Option_Alts :: Name
_PnPrefix_Sequence_Option_Alts = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.PnPrefix.Sequence.Option.Alts")

_PnPrefix_Sequence_Option_Alts_pnChars :: Name
_PnPrefix_Sequence_Option_Alts_pnChars = (String -> Name
Core.Name String
"pnChars")

_PnPrefix_Sequence_Option_Alts_period :: Name
_PnPrefix_Sequence_Option_Alts_period = (String -> Name
Core.Name String
"period")

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

_PnLocal :: Name
_PnLocal = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.PnLocal")

_PnLocal_alts :: Name
_PnLocal_alts = (String -> Name
Core.Name String
"alts")

_PnLocal_sequence :: Name
_PnLocal_sequence = (String -> Name
Core.Name String
"sequence")

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

_PnLocal_Alts :: Name
_PnLocal_Alts = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.PnLocal.Alts")

_PnLocal_Alts_pnCharsU :: Name
_PnLocal_Alts_pnCharsU = (String -> Name
Core.Name String
"pnCharsU")

_PnLocal_Alts_colon :: Name
_PnLocal_Alts_colon = (String -> Name
Core.Name String
"colon")

_PnLocal_Alts_regex :: Name
_PnLocal_Alts_regex = (String -> Name
Core.Name String
"regex")

_PnLocal_Alts_plx :: Name
_PnLocal_Alts_plx = (String -> Name
Core.Name String
"plx")

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

_PnLocal_Sequence_Option :: Name
_PnLocal_Sequence_Option = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.PnLocal.Sequence.Option")

_PnLocal_Sequence_Option_listOfAlts :: Name
_PnLocal_Sequence_Option_listOfAlts = (String -> Name
Core.Name String
"listOfAlts")

_PnLocal_Sequence_Option_alts :: Name
_PnLocal_Sequence_Option_alts = (String -> Name
Core.Name String
"alts")

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

_PnLocal_Sequence_Option_ListOfAlts_Elmt :: Name
_PnLocal_Sequence_Option_ListOfAlts_Elmt = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.PnLocal.Sequence.Option.ListOfAlts.Elmt")

_PnLocal_Sequence_Option_ListOfAlts_Elmt_pnChars :: Name
_PnLocal_Sequence_Option_ListOfAlts_Elmt_pnChars = (String -> Name
Core.Name String
"pnChars")

_PnLocal_Sequence_Option_ListOfAlts_Elmt_period :: Name
_PnLocal_Sequence_Option_ListOfAlts_Elmt_period = (String -> Name
Core.Name String
"period")

_PnLocal_Sequence_Option_ListOfAlts_Elmt_colon :: Name
_PnLocal_Sequence_Option_ListOfAlts_Elmt_colon = (String -> Name
Core.Name String
"colon")

_PnLocal_Sequence_Option_ListOfAlts_Elmt_plx :: Name
_PnLocal_Sequence_Option_ListOfAlts_Elmt_plx = (String -> Name
Core.Name String
"plx")

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

_PnLocal_Sequence_Option_Alts :: Name
_PnLocal_Sequence_Option_Alts = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.PnLocal.Sequence.Option.Alts")

_PnLocal_Sequence_Option_Alts_pnChars :: Name
_PnLocal_Sequence_Option_Alts_pnChars = (String -> Name
Core.Name String
"pnChars")

_PnLocal_Sequence_Option_Alts_colon :: Name
_PnLocal_Sequence_Option_Alts_colon = (String -> Name
Core.Name String
"colon")

_PnLocal_Sequence_Option_Alts_plx :: Name
_PnLocal_Sequence_Option_Alts_plx = (String -> Name
Core.Name String
"plx")

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

_Plx :: Name
_Plx = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.Plx")

_Plx_percent :: Name
_Plx_percent = (String -> Name
Core.Name String
"percent")

_Plx_pnLocalEsc :: Name
_Plx_pnLocalEsc = (String -> Name
Core.Name String
"pnLocalEsc")

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

_Percent :: Name
_Percent = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.Percent")

_Percent_hex :: Name
_Percent_hex = (String -> Name
Core.Name String
"hex")

_Percent_hex2 :: Name
_Percent_hex2 = (String -> Name
Core.Name String
"hex2")

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

_Hex :: Name
_Hex = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.Hex")

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

_PnLocalEsc :: Name
_PnLocalEsc = (String -> Name
Core.Name String
"hydra/langs/shex/syntax.PnLocalEsc")