Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell98 |
Text.XML.HaXml.Schema.XSDTypeModel
Documentation
type FixedValue = String Source #
type DefaultValue = String Source #
type SchemaLocation = String Source #
data ProcessContents Source #
Instances
Eq ProcessContents Source # | |
Defined in Text.XML.HaXml.Schema.XSDTypeModel Methods (==) :: ProcessContents -> ProcessContents -> Bool (/=) :: ProcessContents -> ProcessContents -> Bool | |
Show ProcessContents Source # | |
Defined in Text.XML.HaXml.Schema.XSDTypeModel Methods showsPrec :: Int -> ProcessContents -> ShowS show :: ProcessContents -> String showList :: [ProcessContents] -> ShowS |
Constructors
NoExtension | |
NoRestriction | |
AllFinal |
Instances
type TargetNamespace = URI Source #
Constructors
Qualified | |
Unqualified |
Instances
data Annotation Source #
Constructors
Documentation String | |
AppInfo String | |
NoAnnotation String |
Instances
Eq Annotation Source # | |
Defined in Text.XML.HaXml.Schema.XSDTypeModel | |
Show Annotation Source # | |
Defined in Text.XML.HaXml.Schema.XSDTypeModel Methods showsPrec :: Int -> Annotation -> ShowS show :: Annotation -> String showList :: [Annotation] -> ShowS | |
Semigroup Annotation Source # | |
Defined in Text.XML.HaXml.Schema.XSDTypeModel Methods (<>) :: Annotation -> Annotation -> Annotation sconcat :: NonEmpty Annotation -> Annotation stimes :: Integral b => b -> Annotation -> Annotation | |
Monoid Annotation Source # | |
Defined in Text.XML.HaXml.Schema.XSDTypeModel Methods mempty :: Annotation mappend :: Annotation -> Annotation -> Annotation mconcat :: [Annotation] -> Annotation |
data MyRestriction Source #
Constructors
Range Occurs | |
Pattern Regexp | |
Enumeration [String] |
Instances
Eq MyRestriction Source # | |
Defined in Text.XML.HaXml.Schema.XSDTypeModel | |
Show MyRestriction Source # | |
Defined in Text.XML.HaXml.Schema.XSDTypeModel Methods showsPrec :: Int -> MyRestriction -> ShowS show :: MyRestriction -> String showList :: [MyRestriction] -> ShowS |
data PrimitiveType Source #
Constructors
String | |
Boolean | |
Decimal | |
Float | |
Double | |
Duration | |
DateTime | |
Time | |
Date | |
GYearMonth | |
GYear | |
GMonthDay | |
GDay | |
GMonth | |
Base64Binary | |
HexBinary | |
AnyURI | |
QName | |
Notation |
Instances
Eq PrimitiveType Source # | |
Defined in Text.XML.HaXml.Schema.XSDTypeModel | |
Show PrimitiveType Source # | |
Defined in Text.XML.HaXml.Schema.XSDTypeModel Methods showsPrec :: Int -> PrimitiveType -> ShowS show :: PrimitiveType -> String showList :: [PrimitiveType] -> ShowS |
Constructors
Required | |
Optional | |
Prohibited |
Constructors
Field | |
Fields
|
Instances
Constructors
Selector | |
Fields
|
Constructors
KeyRef | |
Fields
|
Instances
Constructors
Key | |
Fields
|
Constructors
Unique | |
Fields
|
Instances
data UniqueKeyOrKeyRef Source #
Instances
Eq UniqueKeyOrKeyRef Source # | |
Defined in Text.XML.HaXml.Schema.XSDTypeModel Methods (==) :: UniqueKeyOrKeyRef -> UniqueKeyOrKeyRef -> Bool (/=) :: UniqueKeyOrKeyRef -> UniqueKeyOrKeyRef -> Bool | |
Show UniqueKeyOrKeyRef Source # | |
Defined in Text.XML.HaXml.Schema.XSDTypeModel Methods showsPrec :: Int -> UniqueKeyOrKeyRef -> ShowS show :: UniqueKeyOrKeyRef -> String showList :: [UniqueKeyOrKeyRef] -> ShowS |
data AttributeDecl Source #
Constructors
AttributeDecl | |
Fields
|
Instances
Eq AttributeDecl Source # | |
Defined in Text.XML.HaXml.Schema.XSDTypeModel | |
Show AttributeDecl Source # | |
Defined in Text.XML.HaXml.Schema.XSDTypeModel Methods showsPrec :: Int -> AttributeDecl -> ShowS show :: AttributeDecl -> String showList :: [AttributeDecl] -> ShowS |
data NameAndType Source #
Instances
Eq NameAndType Source # | |
Defined in Text.XML.HaXml.Schema.XSDTypeModel | |
Show NameAndType Source # | |
Defined in Text.XML.HaXml.Schema.XSDTypeModel Methods showsPrec :: Int -> NameAndType -> ShowS show :: NameAndType -> String showList :: [NameAndType] -> ShowS |
data ElementDecl Source #
Constructors
ElementDecl | |
Fields
|
Instances
Eq ElementDecl Source # | |
Defined in Text.XML.HaXml.Schema.XSDTypeModel | |
Show ElementDecl Source # | |
Defined in Text.XML.HaXml.Schema.XSDTypeModel Methods showsPrec :: Int -> ElementDecl -> ShowS show :: ElementDecl -> String showList :: [ElementDecl] -> ShowS |
Constructors
AttrGroup | |
Fields
|
Constructors
Any | |
Fields |
data ElementEtc Source #
Constructors
HasElement ElementDecl | |
HasGroup Group | |
HasCS ChoiceOrSeq | |
HasAny Any |
Instances
Eq ElementEtc Source # | |
Defined in Text.XML.HaXml.Schema.XSDTypeModel | |
Show ElementEtc Source # | |
Defined in Text.XML.HaXml.Schema.XSDTypeModel Methods showsPrec :: Int -> ElementEtc -> ShowS show :: ElementEtc -> String showList :: [ElementEtc] -> ShowS |
data ChoiceOrSeq Source #
Constructors
All Annotation [ElementDecl] | |
Choice Annotation Occurs [ElementEtc] | |
Sequence Annotation Occurs [ElementEtc] |
Instances
Eq ChoiceOrSeq Source # | |
Defined in Text.XML.HaXml.Schema.XSDTypeModel | |
Show ChoiceOrSeq Source # | |
Defined in Text.XML.HaXml.Schema.XSDTypeModel Methods showsPrec :: Int -> ChoiceOrSeq -> ShowS show :: ChoiceOrSeq -> String showList :: [ChoiceOrSeq] -> ShowS |
Constructors
Group | |
Fields
|
Instances
data ParticleAttrs Source #
Constructors
PA Particle [Either AttributeDecl AttrGroup] (Maybe AnyAttr) |
Instances
Eq ParticleAttrs Source # | |
Defined in Text.XML.HaXml.Schema.XSDTypeModel | |
Show ParticleAttrs Source # | |
Defined in Text.XML.HaXml.Schema.XSDTypeModel Methods showsPrec :: Int -> ParticleAttrs -> ShowS show :: ParticleAttrs -> String showList :: [ParticleAttrs] -> ShowS |
type Particle = Maybe (Either ChoiceOrSeq Group) Source #
data Restriction1 Source #
Constructors
Restriction1 Particle |
Instances
Eq Restriction1 Source # | |
Defined in Text.XML.HaXml.Schema.XSDTypeModel | |
Show Restriction1 Source # | |
Defined in Text.XML.HaXml.Schema.XSDTypeModel Methods showsPrec :: Int -> Restriction1 -> ShowS show :: Restriction1 -> String showList :: [Restriction1] -> ShowS |
data ComplexItem Source #
Constructors
SimpleContent | |
Fields
| |
ComplexContent | |
Fields
| |
ThisType | |
Fields |
Instances
Eq ComplexItem Source # | |
Defined in Text.XML.HaXml.Schema.XSDTypeModel | |
Show ComplexItem Source # | |
Defined in Text.XML.HaXml.Schema.XSDTypeModel Methods showsPrec :: Int -> ComplexItem -> ShowS show :: ComplexItem -> String showList :: [ComplexItem] -> ShowS |
data ComplexType Source #
Constructors
ComplexType | |
Fields
|
Instances
Eq ComplexType Source # | |
Defined in Text.XML.HaXml.Schema.XSDTypeModel | |
Show ComplexType Source # | |
Defined in Text.XML.HaXml.Schema.XSDTypeModel Methods showsPrec :: Int -> ComplexType -> ShowS show :: ComplexType -> String showList :: [ComplexType] -> ShowS |
Constructors
Constructors
Facet | |
Fields
|
Instances
data Restriction Source #
Constructors
RestrictSim1 | |
Fields
| |
RestrictType | |
Fields
|
Instances
Eq Restriction Source # | |
Defined in Text.XML.HaXml.Schema.XSDTypeModel | |
Show Restriction Source # | |
Defined in Text.XML.HaXml.Schema.XSDTypeModel Methods showsPrec :: Int -> Restriction -> ShowS show :: Restriction -> String showList :: [Restriction] -> ShowS |
data SimpleType Source #
Constructors
Primitive | |
Fields | |
Restricted | |
Fields
| |
ListOf | |
Fields
| |
UnionOf | |
Fields
|
Instances
Eq SimpleType Source # | |
Defined in Text.XML.HaXml.Schema.XSDTypeModel | |
Show SimpleType Source # | |
Defined in Text.XML.HaXml.Schema.XSDTypeModel Methods showsPrec :: Int -> SimpleType -> ShowS show :: SimpleType -> String showList :: [SimpleType] -> ShowS |
data SchemaItem Source #
Constructors
Instances
Eq SchemaItem Source # | |
Defined in Text.XML.HaXml.Schema.XSDTypeModel | |
Show SchemaItem Source # | |
Defined in Text.XML.HaXml.Schema.XSDTypeModel Methods showsPrec :: Int -> SchemaItem -> ShowS show :: SchemaItem -> String showList :: [SchemaItem] -> ShowS |
Constructors
Schema | |
Fields
|