module Text.XML.HaXml.Schema.XSDTypeModel
( module Text.XML.HaXml.Schema.XSDTypeModel
) where
import Data.Semigroup (Semigroup (..))
import Data.Monoid (Monoid (..))
import Text.XML.HaXml.Types (Name,Namespace,QName)
data Schema = Schema
{ Schema -> QForm
schema_elementFormDefault :: QForm
, Schema -> QForm
schema_attributeFormDefault :: QForm
, Schema -> Maybe Final
schema_finalDefault :: Maybe Final
, Schema -> Maybe Final
schema_blockDefault :: Maybe Block
, Schema -> Maybe TargetNamespace
schema_targetNamespace :: Maybe TargetNamespace
, Schema -> Maybe TargetNamespace
schema_version :: Maybe String
, Schema -> [Namespace]
schema_namespaces :: [Namespace]
, Schema -> [SchemaItem]
schema_items :: [SchemaItem]
}
deriving (Schema -> Schema -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Schema -> Schema -> Bool
$c/= :: Schema -> Schema -> Bool
== :: Schema -> Schema -> Bool
$c== :: Schema -> Schema -> Bool
Eq,Int -> Schema -> ShowS
[Schema] -> ShowS
Schema -> TargetNamespace
forall a.
(Int -> a -> ShowS)
-> (a -> TargetNamespace) -> ([a] -> ShowS) -> Show a
showList :: [Schema] -> ShowS
$cshowList :: [Schema] -> ShowS
show :: Schema -> TargetNamespace
$cshow :: Schema -> TargetNamespace
showsPrec :: Int -> Schema -> ShowS
$cshowsPrec :: Int -> Schema -> ShowS
Show)
data SchemaItem = Include SchemaLocation Annotation
| Import URI SchemaLocation Annotation
| Redefine SchemaLocation [SchemaItem]
| Annotation Annotation
| Simple SimpleType
| Complex ComplexType
| SchemaElement ElementDecl
| SchemaAttribute AttributeDecl
| AttributeGroup AttrGroup
| SchemaGroup Group
deriving (SchemaItem -> SchemaItem -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SchemaItem -> SchemaItem -> Bool
$c/= :: SchemaItem -> SchemaItem -> Bool
== :: SchemaItem -> SchemaItem -> Bool
$c== :: SchemaItem -> SchemaItem -> Bool
Eq,Int -> SchemaItem -> ShowS
[SchemaItem] -> ShowS
SchemaItem -> TargetNamespace
forall a.
(Int -> a -> ShowS)
-> (a -> TargetNamespace) -> ([a] -> ShowS) -> Show a
showList :: [SchemaItem] -> ShowS
$cshowList :: [SchemaItem] -> ShowS
show :: SchemaItem -> TargetNamespace
$cshow :: SchemaItem -> TargetNamespace
showsPrec :: Int -> SchemaItem -> ShowS
$cshowsPrec :: Int -> SchemaItem -> ShowS
Show)
data SimpleType = Primitive { SimpleType -> PrimitiveType
simple_primitive :: PrimitiveType }
| Restricted { SimpleType -> Annotation
simple_annotation :: Annotation
, SimpleType -> Maybe TargetNamespace
simple_name :: Maybe Name
, SimpleType -> Maybe Final
simple_final :: Maybe Final
, SimpleType -> Restriction
simple_restriction :: Restriction
}
| ListOf { simple_annotation :: Annotation
, simple_name :: Maybe Name
, simple_final :: Maybe Final
, SimpleType -> Either SimpleType QName
simple_type :: Either SimpleType QName
}
| UnionOf { simple_annotation :: Annotation
, simple_name :: Maybe Name
, simple_final :: Maybe Final
, SimpleType -> [SimpleType]
simple_union :: [SimpleType]
, SimpleType -> [QName]
simple_members :: [QName]
}
deriving (SimpleType -> SimpleType -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SimpleType -> SimpleType -> Bool
$c/= :: SimpleType -> SimpleType -> Bool
== :: SimpleType -> SimpleType -> Bool
$c== :: SimpleType -> SimpleType -> Bool
Eq,Int -> SimpleType -> ShowS
[SimpleType] -> ShowS
SimpleType -> TargetNamespace
forall a.
(Int -> a -> ShowS)
-> (a -> TargetNamespace) -> ([a] -> ShowS) -> Show a
showList :: [SimpleType] -> ShowS
$cshowList :: [SimpleType] -> ShowS
show :: SimpleType -> TargetNamespace
$cshow :: SimpleType -> TargetNamespace
showsPrec :: Int -> SimpleType -> ShowS
$cshowsPrec :: Int -> SimpleType -> ShowS
Show)
data Restriction = RestrictSim1 { Restriction -> Annotation
restrict_annotation :: Annotation
, Restriction -> Maybe QName
restrict_base :: Maybe QName
, Restriction -> Restriction1
restrict_r1 :: Restriction1
}
| RestrictType { restrict_annotation :: Annotation
, restrict_base :: Maybe QName
, Restriction -> Maybe SimpleType
restrict_type :: Maybe SimpleType
, Restriction -> [Facet]
restrict_facets :: [Facet]
}
deriving (Restriction -> Restriction -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Restriction -> Restriction -> Bool
$c/= :: Restriction -> Restriction -> Bool
== :: Restriction -> Restriction -> Bool
$c== :: Restriction -> Restriction -> Bool
Eq,Int -> Restriction -> ShowS
[Restriction] -> ShowS
Restriction -> TargetNamespace
forall a.
(Int -> a -> ShowS)
-> (a -> TargetNamespace) -> ([a] -> ShowS) -> Show a
showList :: [Restriction] -> ShowS
$cshowList :: [Restriction] -> ShowS
show :: Restriction -> TargetNamespace
$cshow :: Restriction -> TargetNamespace
showsPrec :: Int -> Restriction -> ShowS
$cshowsPrec :: Int -> Restriction -> ShowS
Show)
data Facet = Facet { Facet -> FacetType
facet_facetType :: FacetType
, Facet -> Annotation
facet_annotation :: Annotation
, Facet -> TargetNamespace
facet_facetValue :: String
, Facet -> Bool
facet_fixed :: Bool
}
deriving (Facet -> Facet -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Facet -> Facet -> Bool
$c/= :: Facet -> Facet -> Bool
== :: Facet -> Facet -> Bool
$c== :: Facet -> Facet -> Bool
Eq,Int -> Facet -> ShowS
[Facet] -> ShowS
Facet -> TargetNamespace
forall a.
(Int -> a -> ShowS)
-> (a -> TargetNamespace) -> ([a] -> ShowS) -> Show a
showList :: [Facet] -> ShowS
$cshowList :: [Facet] -> ShowS
show :: Facet -> TargetNamespace
$cshow :: Facet -> TargetNamespace
showsPrec :: Int -> Facet -> ShowS
$cshowsPrec :: Int -> Facet -> ShowS
Show)
data FacetType = OrderedBoundsMinIncl
| OrderedBoundsMinExcl
| OrderedBoundsMaxIncl
| OrderedBoundsMaxExcl
| OrderedNumericTotalDigits
| OrderedNumericFractionDigits
| UnorderedPattern
| UnorderedEnumeration
| UnorderedWhitespace
| UnorderedLength
| UnorderedMaxLength
| UnorderedMinLength
deriving (FacetType -> FacetType -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FacetType -> FacetType -> Bool
$c/= :: FacetType -> FacetType -> Bool
== :: FacetType -> FacetType -> Bool
$c== :: FacetType -> FacetType -> Bool
Eq,Int -> FacetType -> ShowS
[FacetType] -> ShowS
FacetType -> TargetNamespace
forall a.
(Int -> a -> ShowS)
-> (a -> TargetNamespace) -> ([a] -> ShowS) -> Show a
showList :: [FacetType] -> ShowS
$cshowList :: [FacetType] -> ShowS
show :: FacetType -> TargetNamespace
$cshow :: FacetType -> TargetNamespace
showsPrec :: Int -> FacetType -> ShowS
$cshowsPrec :: Int -> FacetType -> ShowS
Show)
data ComplexType = ComplexType
{ ComplexType -> Annotation
complex_annotation :: Annotation
, ComplexType -> Maybe TargetNamespace
complex_name :: Maybe Name
, ComplexType -> Bool
complex_abstract :: Bool
, ComplexType -> Maybe Final
complex_final :: Maybe Final
, ComplexType -> Maybe Final
complex_block :: Maybe Block
, ComplexType -> Bool
complex_mixed :: Bool
, ComplexType -> ComplexItem
complex_content :: ComplexItem
}
deriving (ComplexType -> ComplexType -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ComplexType -> ComplexType -> Bool
$c/= :: ComplexType -> ComplexType -> Bool
== :: ComplexType -> ComplexType -> Bool
$c== :: ComplexType -> ComplexType -> Bool
Eq,Int -> ComplexType -> ShowS
[ComplexType] -> ShowS
ComplexType -> TargetNamespace
forall a.
(Int -> a -> ShowS)
-> (a -> TargetNamespace) -> ([a] -> ShowS) -> Show a
showList :: [ComplexType] -> ShowS
$cshowList :: [ComplexType] -> ShowS
show :: ComplexType -> TargetNamespace
$cshow :: ComplexType -> TargetNamespace
showsPrec :: Int -> ComplexType -> ShowS
$cshowsPrec :: Int -> ComplexType -> ShowS
Show)
data ComplexItem = SimpleContent
{ ComplexItem -> Annotation
ci_annotation :: Annotation
, ComplexItem -> Either Restriction1 Extension
ci_stuff :: Either Restriction1 Extension
}
| ComplexContent
{ ci_annotation :: Annotation
, ComplexItem -> Bool
ci_mixed :: Bool
, ci_stuff :: Either Restriction1 Extension
}
| ThisType
{ ComplexItem -> ParticleAttrs
ci_thistype :: ParticleAttrs
}
deriving (ComplexItem -> ComplexItem -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ComplexItem -> ComplexItem -> Bool
$c/= :: ComplexItem -> ComplexItem -> Bool
== :: ComplexItem -> ComplexItem -> Bool
$c== :: ComplexItem -> ComplexItem -> Bool
Eq,Int -> ComplexItem -> ShowS
[ComplexItem] -> ShowS
ComplexItem -> TargetNamespace
forall a.
(Int -> a -> ShowS)
-> (a -> TargetNamespace) -> ([a] -> ShowS) -> Show a
showList :: [ComplexItem] -> ShowS
$cshowList :: [ComplexItem] -> ShowS
show :: ComplexItem -> TargetNamespace
$cshow :: ComplexItem -> TargetNamespace
showsPrec :: Int -> ComplexItem -> ShowS
$cshowsPrec :: Int -> ComplexItem -> ShowS
Show)
data Restriction1 = Restriction1 Particle
deriving (Restriction1 -> Restriction1 -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Restriction1 -> Restriction1 -> Bool
$c/= :: Restriction1 -> Restriction1 -> Bool
== :: Restriction1 -> Restriction1 -> Bool
$c== :: Restriction1 -> Restriction1 -> Bool
Eq,Int -> Restriction1 -> ShowS
[Restriction1] -> ShowS
Restriction1 -> TargetNamespace
forall a.
(Int -> a -> ShowS)
-> (a -> TargetNamespace) -> ([a] -> ShowS) -> Show a
showList :: [Restriction1] -> ShowS
$cshowList :: [Restriction1] -> ShowS
show :: Restriction1 -> TargetNamespace
$cshow :: Restriction1 -> TargetNamespace
showsPrec :: Int -> Restriction1 -> ShowS
$cshowsPrec :: Int -> Restriction1 -> ShowS
Show)
data Extension = Extension
{ Extension -> Annotation
extension_annotation :: Annotation
, Extension -> QName
extension_base :: QName
, Extension -> ParticleAttrs
extension_newstuff :: ParticleAttrs
}
deriving (Extension -> Extension -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Extension -> Extension -> Bool
$c/= :: Extension -> Extension -> Bool
== :: Extension -> Extension -> Bool
$c== :: Extension -> Extension -> Bool
Eq,Int -> Extension -> ShowS
[Extension] -> ShowS
Extension -> TargetNamespace
forall a.
(Int -> a -> ShowS)
-> (a -> TargetNamespace) -> ([a] -> ShowS) -> Show a
showList :: [Extension] -> ShowS
$cshowList :: [Extension] -> ShowS
show :: Extension -> TargetNamespace
$cshow :: Extension -> TargetNamespace
showsPrec :: Int -> Extension -> ShowS
$cshowsPrec :: Int -> Extension -> ShowS
Show)
type Particle = Maybe (Either ChoiceOrSeq Group)
data ParticleAttrs = PA Particle [Either AttributeDecl AttrGroup]
(Maybe AnyAttr)
deriving (ParticleAttrs -> ParticleAttrs -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ParticleAttrs -> ParticleAttrs -> Bool
$c/= :: ParticleAttrs -> ParticleAttrs -> Bool
== :: ParticleAttrs -> ParticleAttrs -> Bool
$c== :: ParticleAttrs -> ParticleAttrs -> Bool
Eq,Int -> ParticleAttrs -> ShowS
[ParticleAttrs] -> ShowS
ParticleAttrs -> TargetNamespace
forall a.
(Int -> a -> ShowS)
-> (a -> TargetNamespace) -> ([a] -> ShowS) -> Show a
showList :: [ParticleAttrs] -> ShowS
$cshowList :: [ParticleAttrs] -> ShowS
show :: ParticleAttrs -> TargetNamespace
$cshow :: ParticleAttrs -> TargetNamespace
showsPrec :: Int -> ParticleAttrs -> ShowS
$cshowsPrec :: Int -> ParticleAttrs -> ShowS
Show)
data Group = Group
{ Group -> Annotation
group_annotation :: Annotation
, Group -> Either TargetNamespace QName
group_nameOrRef :: Either Name QName
, Group -> Occurs
group_occurs :: Occurs
, Group -> Maybe ChoiceOrSeq
group_stuff :: Maybe ChoiceOrSeq
}
deriving (Group -> Group -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Group -> Group -> Bool
$c/= :: Group -> Group -> Bool
== :: Group -> Group -> Bool
$c== :: Group -> Group -> Bool
Eq,Int -> Group -> ShowS
[Group] -> ShowS
Group -> TargetNamespace
forall a.
(Int -> a -> ShowS)
-> (a -> TargetNamespace) -> ([a] -> ShowS) -> Show a
showList :: [Group] -> ShowS
$cshowList :: [Group] -> ShowS
show :: Group -> TargetNamespace
$cshow :: Group -> TargetNamespace
showsPrec :: Int -> Group -> ShowS
$cshowsPrec :: Int -> Group -> ShowS
Show)
data ChoiceOrSeq = All Annotation [ElementDecl]
| Choice Annotation Occurs [ElementEtc]
| Sequence Annotation Occurs [ElementEtc]
deriving (ChoiceOrSeq -> ChoiceOrSeq -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ChoiceOrSeq -> ChoiceOrSeq -> Bool
$c/= :: ChoiceOrSeq -> ChoiceOrSeq -> Bool
== :: ChoiceOrSeq -> ChoiceOrSeq -> Bool
$c== :: ChoiceOrSeq -> ChoiceOrSeq -> Bool
Eq,Int -> ChoiceOrSeq -> ShowS
[ChoiceOrSeq] -> ShowS
ChoiceOrSeq -> TargetNamespace
forall a.
(Int -> a -> ShowS)
-> (a -> TargetNamespace) -> ([a] -> ShowS) -> Show a
showList :: [ChoiceOrSeq] -> ShowS
$cshowList :: [ChoiceOrSeq] -> ShowS
show :: ChoiceOrSeq -> TargetNamespace
$cshow :: ChoiceOrSeq -> TargetNamespace
showsPrec :: Int -> ChoiceOrSeq -> ShowS
$cshowsPrec :: Int -> ChoiceOrSeq -> ShowS
Show)
data ElementEtc = HasElement ElementDecl
| HasGroup Group
| HasCS ChoiceOrSeq
| HasAny Any
deriving (ElementEtc -> ElementEtc -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ElementEtc -> ElementEtc -> Bool
$c/= :: ElementEtc -> ElementEtc -> Bool
== :: ElementEtc -> ElementEtc -> Bool
$c== :: ElementEtc -> ElementEtc -> Bool
Eq,Int -> ElementEtc -> ShowS
[ElementEtc] -> ShowS
ElementEtc -> TargetNamespace
forall a.
(Int -> a -> ShowS)
-> (a -> TargetNamespace) -> ([a] -> ShowS) -> Show a
showList :: [ElementEtc] -> ShowS
$cshowList :: [ElementEtc] -> ShowS
show :: ElementEtc -> TargetNamespace
$cshow :: ElementEtc -> TargetNamespace
showsPrec :: Int -> ElementEtc -> ShowS
$cshowsPrec :: Int -> ElementEtc -> ShowS
Show)
data Any = Any
{ Any -> Annotation
any_annotation :: Annotation
, Any -> TargetNamespace
any_namespace :: URI
, Any -> ProcessContents
any_processContents :: ProcessContents
, Any -> Occurs
any_occurs :: Occurs
}
deriving (Any -> Any -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Any -> Any -> Bool
$c/= :: Any -> Any -> Bool
== :: Any -> Any -> Bool
$c== :: Any -> Any -> Bool
Eq,Int -> Any -> ShowS
[Any] -> ShowS
Any -> TargetNamespace
forall a.
(Int -> a -> ShowS)
-> (a -> TargetNamespace) -> ([a] -> ShowS) -> Show a
showList :: [Any] -> ShowS
$cshowList :: [Any] -> ShowS
show :: Any -> TargetNamespace
$cshow :: Any -> TargetNamespace
showsPrec :: Int -> Any -> ShowS
$cshowsPrec :: Int -> Any -> ShowS
Show)
data AnyAttr = AnyAttr
{ AnyAttr -> Annotation
anyattr_annotation :: Annotation
, AnyAttr -> TargetNamespace
anyattr_namespace :: URI
, AnyAttr -> ProcessContents
anyattr_processContents :: ProcessContents
}
deriving (AnyAttr -> AnyAttr -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AnyAttr -> AnyAttr -> Bool
$c/= :: AnyAttr -> AnyAttr -> Bool
== :: AnyAttr -> AnyAttr -> Bool
$c== :: AnyAttr -> AnyAttr -> Bool
Eq,Int -> AnyAttr -> ShowS
[AnyAttr] -> ShowS
AnyAttr -> TargetNamespace
forall a.
(Int -> a -> ShowS)
-> (a -> TargetNamespace) -> ([a] -> ShowS) -> Show a
showList :: [AnyAttr] -> ShowS
$cshowList :: [AnyAttr] -> ShowS
show :: AnyAttr -> TargetNamespace
$cshow :: AnyAttr -> TargetNamespace
showsPrec :: Int -> AnyAttr -> ShowS
$cshowsPrec :: Int -> AnyAttr -> ShowS
Show)
data AttrGroup = AttrGroup
{ AttrGroup -> Annotation
attrgroup_annotation :: Annotation
, AttrGroup -> Either TargetNamespace QName
attrgroup_nameOrRef :: Either Name QName
, AttrGroup -> [Either AttributeDecl AttrGroup]
attrgroup_stuff :: [Either AttributeDecl
AttrGroup]
}
deriving (AttrGroup -> AttrGroup -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AttrGroup -> AttrGroup -> Bool
$c/= :: AttrGroup -> AttrGroup -> Bool
== :: AttrGroup -> AttrGroup -> Bool
$c== :: AttrGroup -> AttrGroup -> Bool
Eq,Int -> AttrGroup -> ShowS
[AttrGroup] -> ShowS
AttrGroup -> TargetNamespace
forall a.
(Int -> a -> ShowS)
-> (a -> TargetNamespace) -> ([a] -> ShowS) -> Show a
showList :: [AttrGroup] -> ShowS
$cshowList :: [AttrGroup] -> ShowS
show :: AttrGroup -> TargetNamespace
$cshow :: AttrGroup -> TargetNamespace
showsPrec :: Int -> AttrGroup -> ShowS
$cshowsPrec :: Int -> AttrGroup -> ShowS
Show)
data ElementDecl = ElementDecl
{ ElementDecl -> Annotation
elem_annotation :: Annotation
, ElementDecl -> Either NameAndType QName
elem_nameOrRef :: Either NameAndType QName
, ElementDecl -> Occurs
elem_occurs :: Occurs
, ElementDecl -> Bool
elem_nillable :: Nillable
, ElementDecl -> Maybe QName
elem_substGroup :: Maybe QName
, ElementDecl -> Bool
elem_abstract :: Bool
, ElementDecl -> Maybe Final
elem_final :: Maybe Final
, ElementDecl -> Maybe Final
elem_block :: Maybe Block
, ElementDecl -> QForm
elem_form :: QForm
, ElementDecl -> Maybe (Either SimpleType ComplexType)
elem_content :: Maybe (Either SimpleType
ComplexType)
, ElementDecl -> [UniqueKeyOrKeyRef]
elem_stuff :: [ UniqueKeyOrKeyRef ]
}
deriving (ElementDecl -> ElementDecl -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ElementDecl -> ElementDecl -> Bool
$c/= :: ElementDecl -> ElementDecl -> Bool
== :: ElementDecl -> ElementDecl -> Bool
$c== :: ElementDecl -> ElementDecl -> Bool
Eq,Int -> ElementDecl -> ShowS
[ElementDecl] -> ShowS
ElementDecl -> TargetNamespace
forall a.
(Int -> a -> ShowS)
-> (a -> TargetNamespace) -> ([a] -> ShowS) -> Show a
showList :: [ElementDecl] -> ShowS
$cshowList :: [ElementDecl] -> ShowS
show :: ElementDecl -> TargetNamespace
$cshow :: ElementDecl -> TargetNamespace
showsPrec :: Int -> ElementDecl -> ShowS
$cshowsPrec :: Int -> ElementDecl -> ShowS
Show)
data NameAndType = NT { NameAndType -> TargetNamespace
theName :: Name, NameAndType -> Maybe QName
theType :: Maybe QName }
deriving (NameAndType -> NameAndType -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NameAndType -> NameAndType -> Bool
$c/= :: NameAndType -> NameAndType -> Bool
== :: NameAndType -> NameAndType -> Bool
$c== :: NameAndType -> NameAndType -> Bool
Eq,Int -> NameAndType -> ShowS
[NameAndType] -> ShowS
NameAndType -> TargetNamespace
forall a.
(Int -> a -> ShowS)
-> (a -> TargetNamespace) -> ([a] -> ShowS) -> Show a
showList :: [NameAndType] -> ShowS
$cshowList :: [NameAndType] -> ShowS
show :: NameAndType -> TargetNamespace
$cshow :: NameAndType -> TargetNamespace
showsPrec :: Int -> NameAndType -> ShowS
$cshowsPrec :: Int -> NameAndType -> ShowS
Show)
data AttributeDecl = AttributeDecl
{ AttributeDecl -> Annotation
attr_annotation :: Annotation
, AttributeDecl -> Either NameAndType QName
attr_nameOrRef :: Either NameAndType QName
, AttributeDecl -> Use
attr_use :: Use
, AttributeDecl -> Maybe (Either TargetNamespace TargetNamespace)
attr_defFixed :: Maybe (Either DefaultValue
FixedValue)
, AttributeDecl -> QForm
attr_form :: QForm
, AttributeDecl -> Maybe SimpleType
attr_simpleType :: Maybe SimpleType
}
deriving (AttributeDecl -> AttributeDecl -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AttributeDecl -> AttributeDecl -> Bool
$c/= :: AttributeDecl -> AttributeDecl -> Bool
== :: AttributeDecl -> AttributeDecl -> Bool
$c== :: AttributeDecl -> AttributeDecl -> Bool
Eq,Int -> AttributeDecl -> ShowS
[AttributeDecl] -> ShowS
AttributeDecl -> TargetNamespace
forall a.
(Int -> a -> ShowS)
-> (a -> TargetNamespace) -> ([a] -> ShowS) -> Show a
showList :: [AttributeDecl] -> ShowS
$cshowList :: [AttributeDecl] -> ShowS
show :: AttributeDecl -> TargetNamespace
$cshow :: AttributeDecl -> TargetNamespace
showsPrec :: Int -> AttributeDecl -> ShowS
$cshowsPrec :: Int -> AttributeDecl -> ShowS
Show)
data UniqueKeyOrKeyRef
= U Unique
| K Key
| KR KeyRef
deriving (UniqueKeyOrKeyRef -> UniqueKeyOrKeyRef -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UniqueKeyOrKeyRef -> UniqueKeyOrKeyRef -> Bool
$c/= :: UniqueKeyOrKeyRef -> UniqueKeyOrKeyRef -> Bool
== :: UniqueKeyOrKeyRef -> UniqueKeyOrKeyRef -> Bool
$c== :: UniqueKeyOrKeyRef -> UniqueKeyOrKeyRef -> Bool
Eq,Int -> UniqueKeyOrKeyRef -> ShowS
[UniqueKeyOrKeyRef] -> ShowS
UniqueKeyOrKeyRef -> TargetNamespace
forall a.
(Int -> a -> ShowS)
-> (a -> TargetNamespace) -> ([a] -> ShowS) -> Show a
showList :: [UniqueKeyOrKeyRef] -> ShowS
$cshowList :: [UniqueKeyOrKeyRef] -> ShowS
show :: UniqueKeyOrKeyRef -> TargetNamespace
$cshow :: UniqueKeyOrKeyRef -> TargetNamespace
showsPrec :: Int -> UniqueKeyOrKeyRef -> ShowS
$cshowsPrec :: Int -> UniqueKeyOrKeyRef -> ShowS
Show)
data Unique = Unique
{ Unique -> Annotation
unique_annotation :: Annotation
, Unique -> TargetNamespace
unique_name :: Name
, Unique -> Selector
unique_selector :: Selector
, Unique -> [Field]
unique_fields :: [Field]
}
deriving (Unique -> Unique -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Unique -> Unique -> Bool
$c/= :: Unique -> Unique -> Bool
== :: Unique -> Unique -> Bool
$c== :: Unique -> Unique -> Bool
Eq,Int -> Unique -> ShowS
[Unique] -> ShowS
Unique -> TargetNamespace
forall a.
(Int -> a -> ShowS)
-> (a -> TargetNamespace) -> ([a] -> ShowS) -> Show a
showList :: [Unique] -> ShowS
$cshowList :: [Unique] -> ShowS
show :: Unique -> TargetNamespace
$cshow :: Unique -> TargetNamespace
showsPrec :: Int -> Unique -> ShowS
$cshowsPrec :: Int -> Unique -> ShowS
Show)
data Key = Key
{ Key -> Annotation
key_annotation :: Annotation
, Key -> TargetNamespace
key_name :: Name
, Key -> Selector
key_selector :: Selector
, Key -> [Field]
key_fields :: [Field]
}
deriving (Key -> Key -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Key -> Key -> Bool
$c/= :: Key -> Key -> Bool
== :: Key -> Key -> Bool
$c== :: Key -> Key -> Bool
Eq,Int -> Key -> ShowS
[Key] -> ShowS
Key -> TargetNamespace
forall a.
(Int -> a -> ShowS)
-> (a -> TargetNamespace) -> ([a] -> ShowS) -> Show a
showList :: [Key] -> ShowS
$cshowList :: [Key] -> ShowS
show :: Key -> TargetNamespace
$cshow :: Key -> TargetNamespace
showsPrec :: Int -> Key -> ShowS
$cshowsPrec :: Int -> Key -> ShowS
Show)
data KeyRef = KeyRef
{ KeyRef -> Annotation
keyref_annotation :: Annotation
, KeyRef -> TargetNamespace
keyref_name :: Name
, KeyRef -> QName
keyref_refer :: QName
, KeyRef -> Selector
keyref_selector :: Selector
, KeyRef -> [Field]
keyref_fields :: [Field]
}
deriving (KeyRef -> KeyRef -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: KeyRef -> KeyRef -> Bool
$c/= :: KeyRef -> KeyRef -> Bool
== :: KeyRef -> KeyRef -> Bool
$c== :: KeyRef -> KeyRef -> Bool
Eq,Int -> KeyRef -> ShowS
[KeyRef] -> ShowS
KeyRef -> TargetNamespace
forall a.
(Int -> a -> ShowS)
-> (a -> TargetNamespace) -> ([a] -> ShowS) -> Show a
showList :: [KeyRef] -> ShowS
$cshowList :: [KeyRef] -> ShowS
show :: KeyRef -> TargetNamespace
$cshow :: KeyRef -> TargetNamespace
showsPrec :: Int -> KeyRef -> ShowS
$cshowsPrec :: Int -> KeyRef -> ShowS
Show)
data Selector = Selector
{ Selector -> Annotation
selector_annotation :: Annotation
, Selector -> TargetNamespace
selector_xpath :: String
}
deriving (Selector -> Selector -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Selector -> Selector -> Bool
$c/= :: Selector -> Selector -> Bool
== :: Selector -> Selector -> Bool
$c== :: Selector -> Selector -> Bool
Eq,Int -> Selector -> ShowS
[Selector] -> ShowS
Selector -> TargetNamespace
forall a.
(Int -> a -> ShowS)
-> (a -> TargetNamespace) -> ([a] -> ShowS) -> Show a
showList :: [Selector] -> ShowS
$cshowList :: [Selector] -> ShowS
show :: Selector -> TargetNamespace
$cshow :: Selector -> TargetNamespace
showsPrec :: Int -> Selector -> ShowS
$cshowsPrec :: Int -> Selector -> ShowS
Show)
data Field = Field
{ Field -> Annotation
field_annotation :: Annotation
, Field -> TargetNamespace
field_xpath :: String
}
deriving (Field -> Field -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Field -> Field -> Bool
$c/= :: Field -> Field -> Bool
== :: Field -> Field -> Bool
$c== :: Field -> Field -> Bool
Eq,Int -> Field -> ShowS
[Field] -> ShowS
Field -> TargetNamespace
forall a.
(Int -> a -> ShowS)
-> (a -> TargetNamespace) -> ([a] -> ShowS) -> Show a
showList :: [Field] -> ShowS
$cshowList :: [Field] -> ShowS
show :: Field -> TargetNamespace
$cshow :: Field -> TargetNamespace
showsPrec :: Int -> Field -> ShowS
$cshowsPrec :: Int -> Field -> ShowS
Show)
data Occurs = Occurs (Maybe Int) (Maybe Int)
deriving (Occurs -> Occurs -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Occurs -> Occurs -> Bool
$c/= :: Occurs -> Occurs -> Bool
== :: Occurs -> Occurs -> Bool
$c== :: Occurs -> Occurs -> Bool
Eq,Int -> Occurs -> ShowS
[Occurs] -> ShowS
Occurs -> TargetNamespace
forall a.
(Int -> a -> ShowS)
-> (a -> TargetNamespace) -> ([a] -> ShowS) -> Show a
showList :: [Occurs] -> ShowS
$cshowList :: [Occurs] -> ShowS
show :: Occurs -> TargetNamespace
$cshow :: Occurs -> TargetNamespace
showsPrec :: Int -> Occurs -> ShowS
$cshowsPrec :: Int -> Occurs -> ShowS
Show)
data Use = Required | Optional | Prohibited
deriving (Use -> Use -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Use -> Use -> Bool
$c/= :: Use -> Use -> Bool
== :: Use -> Use -> Bool
$c== :: Use -> Use -> Bool
Eq,Int -> Use -> ShowS
[Use] -> ShowS
Use -> TargetNamespace
forall a.
(Int -> a -> ShowS)
-> (a -> TargetNamespace) -> ([a] -> ShowS) -> Show a
showList :: [Use] -> ShowS
$cshowList :: [Use] -> ShowS
show :: Use -> TargetNamespace
$cshow :: Use -> TargetNamespace
showsPrec :: Int -> Use -> ShowS
$cshowsPrec :: Int -> Use -> ShowS
Show)
data PrimitiveType = String | Boolean | Decimal | Float | Double
| Duration | DateTime | Time | Date
| GYearMonth | GYear | GMonthDay | GDay | GMonth
| Base64Binary | HexBinary
| AnyURI | QName | Notation
deriving (PrimitiveType -> PrimitiveType -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PrimitiveType -> PrimitiveType -> Bool
$c/= :: PrimitiveType -> PrimitiveType -> Bool
== :: PrimitiveType -> PrimitiveType -> Bool
$c== :: PrimitiveType -> PrimitiveType -> Bool
Eq,Int -> PrimitiveType -> ShowS
[PrimitiveType] -> ShowS
PrimitiveType -> TargetNamespace
forall a.
(Int -> a -> ShowS)
-> (a -> TargetNamespace) -> ([a] -> ShowS) -> Show a
showList :: [PrimitiveType] -> ShowS
$cshowList :: [PrimitiveType] -> ShowS
show :: PrimitiveType -> TargetNamespace
$cshow :: PrimitiveType -> TargetNamespace
showsPrec :: Int -> PrimitiveType -> ShowS
$cshowsPrec :: Int -> PrimitiveType -> ShowS
Show)
data MyRestriction = Range Occurs
| Pattern Regexp
| Enumeration [String]
deriving (MyRestriction -> MyRestriction -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MyRestriction -> MyRestriction -> Bool
$c/= :: MyRestriction -> MyRestriction -> Bool
== :: MyRestriction -> MyRestriction -> Bool
$c== :: MyRestriction -> MyRestriction -> Bool
Eq,Int -> MyRestriction -> ShowS
[MyRestriction] -> ShowS
MyRestriction -> TargetNamespace
forall a.
(Int -> a -> ShowS)
-> (a -> TargetNamespace) -> ([a] -> ShowS) -> Show a
showList :: [MyRestriction] -> ShowS
$cshowList :: [MyRestriction] -> ShowS
show :: MyRestriction -> TargetNamespace
$cshow :: MyRestriction -> TargetNamespace
showsPrec :: Int -> MyRestriction -> ShowS
$cshowsPrec :: Int -> MyRestriction -> ShowS
Show)
type Mixed = Bool
type Nillable = Bool
type Fixed = Bool
data Annotation = Documentation String
| AppInfo String
| NoAnnotation String
deriving (Annotation -> Annotation -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Annotation -> Annotation -> Bool
$c/= :: Annotation -> Annotation -> Bool
== :: Annotation -> Annotation -> Bool
$c== :: Annotation -> Annotation -> Bool
Eq,Int -> Annotation -> ShowS
[Annotation] -> ShowS
Annotation -> TargetNamespace
forall a.
(Int -> a -> ShowS)
-> (a -> TargetNamespace) -> ([a] -> ShowS) -> Show a
showList :: [Annotation] -> ShowS
$cshowList :: [Annotation] -> ShowS
show :: Annotation -> TargetNamespace
$cshow :: Annotation -> TargetNamespace
showsPrec :: Int -> Annotation -> ShowS
$cshowsPrec :: Int -> Annotation -> ShowS
Show)
data QForm = Qualified | Unqualified
deriving (QForm -> QForm -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: QForm -> QForm -> Bool
$c/= :: QForm -> QForm -> Bool
== :: QForm -> QForm -> Bool
$c== :: QForm -> QForm -> Bool
Eq,Int -> QForm -> ShowS
[QForm] -> ShowS
QForm -> TargetNamespace
forall a.
(Int -> a -> ShowS)
-> (a -> TargetNamespace) -> ([a] -> ShowS) -> Show a
showList :: [QForm] -> ShowS
$cshowList :: [QForm] -> ShowS
show :: QForm -> TargetNamespace
$cshow :: QForm -> TargetNamespace
showsPrec :: Int -> QForm -> ShowS
$cshowsPrec :: Int -> QForm -> ShowS
Show)
type TargetNamespace
= URI
data Final = NoExtension | NoRestriction | AllFinal
deriving (Final -> Final -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Final -> Final -> Bool
$c/= :: Final -> Final -> Bool
== :: Final -> Final -> Bool
$c== :: Final -> Final -> Bool
Eq,Int -> Final -> ShowS
[Final] -> ShowS
Final -> TargetNamespace
forall a.
(Int -> a -> ShowS)
-> (a -> TargetNamespace) -> ([a] -> ShowS) -> Show a
showList :: [Final] -> ShowS
$cshowList :: [Final] -> ShowS
show :: Final -> TargetNamespace
$cshow :: Final -> TargetNamespace
showsPrec :: Int -> Final -> ShowS
$cshowsPrec :: Int -> Final -> ShowS
Show)
type Block = Final
data ProcessContents
= Skip | Lax | Strict
deriving (ProcessContents -> ProcessContents -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ProcessContents -> ProcessContents -> Bool
$c/= :: ProcessContents -> ProcessContents -> Bool
== :: ProcessContents -> ProcessContents -> Bool
$c== :: ProcessContents -> ProcessContents -> Bool
Eq,Int -> ProcessContents -> ShowS
[ProcessContents] -> ShowS
ProcessContents -> TargetNamespace
forall a.
(Int -> a -> ShowS)
-> (a -> TargetNamespace) -> ([a] -> ShowS) -> Show a
showList :: [ProcessContents] -> ShowS
$cshowList :: [ProcessContents] -> ShowS
show :: ProcessContents -> TargetNamespace
$cshow :: ProcessContents -> TargetNamespace
showsPrec :: Int -> ProcessContents -> ShowS
$cshowsPrec :: Int -> ProcessContents -> ShowS
Show)
type SchemaLocation= String
type DefaultValue = String
type FixedValue = String
type Regexp = String
type URI = String
type TypeName = String
instance Monoid Annotation where
mempty :: Annotation
mempty = TargetNamespace -> Annotation
NoAnnotation TargetNamespace
"Monoid.mempty <Annotation>"
mappend :: Annotation -> Annotation -> Annotation
mappend = forall a. Semigroup a => a -> a -> a
(<>)
instance Semigroup Annotation where
(Documentation TargetNamespace
d) <> :: Annotation -> Annotation -> Annotation
<> (Documentation TargetNamespace
e) = TargetNamespace -> Annotation
Documentation (TargetNamespace
dforall a. [a] -> [a] -> [a]
++TargetNamespace
"\n"forall a. [a] -> [a] -> [a]
++TargetNamespace
e)
Annotation
_ <> (Documentation TargetNamespace
e) = TargetNamespace -> Annotation
Documentation TargetNamespace
e
Annotation
ann <> Annotation
_ = Annotation
ann
instance Monoid Schema where
mempty :: Schema
mempty = Schema{ schema_items :: [SchemaItem]
schema_items=[] }
mappend :: Schema -> Schema -> Schema
mappend = forall a. Semigroup a => a -> a -> a
(<>)
instance Semigroup Schema where
Schema
s <> :: Schema -> Schema -> Schema
<> Schema
t = Schema
s{ schema_items :: [SchemaItem]
schema_items = Schema -> [SchemaItem]
schema_items Schema
s forall a. [a] -> [a] -> [a]
++ Schema -> [SchemaItem]
schema_items Schema
t }