HaXml-1.25.6: Utilities for manipulating XML documents
Safe HaskellSafe-Inferred
LanguageHaskell98

Text.XML.HaXml.Schema.XSDTypeModel

Documentation

type TypeName = String Source #

type URI = String Source #

type Regexp = String Source #

type FixedValue = String Source #

type DefaultValue = String Source #

type SchemaLocation = String Source #

data ProcessContents Source #

Constructors

Skip 
Lax 
Strict 

Instances

Instances details
Eq ProcessContents Source # 
Instance details

Defined in Text.XML.HaXml.Schema.XSDTypeModel

Show ProcessContents Source # 
Instance details

Defined in Text.XML.HaXml.Schema.XSDTypeModel

Methods

showsPrec :: Int -> ProcessContents -> ShowS

show :: ProcessContents -> String

showList :: [ProcessContents] -> ShowS

data Final Source #

Instances

Instances details
Eq Final Source # 
Instance details

Defined in Text.XML.HaXml.Schema.XSDTypeModel

Methods

(==) :: Final -> Final -> Bool

(/=) :: Final -> Final -> Bool

Show Final Source # 
Instance details

Defined in Text.XML.HaXml.Schema.XSDTypeModel

Methods

showsPrec :: Int -> Final -> ShowS

show :: Final -> String

showList :: [Final] -> ShowS

data QForm Source #

Constructors

Qualified 
Unqualified 

Instances

Instances details
Eq QForm Source # 
Instance details

Defined in Text.XML.HaXml.Schema.XSDTypeModel

Methods

(==) :: QForm -> QForm -> Bool

(/=) :: QForm -> QForm -> Bool

Show QForm Source # 
Instance details

Defined in Text.XML.HaXml.Schema.XSDTypeModel

Methods

showsPrec :: Int -> QForm -> ShowS

show :: QForm -> String

showList :: [QForm] -> ShowS

data Annotation Source #

Constructors

Documentation String 
AppInfo String 
NoAnnotation String 

Instances

Instances details
Eq Annotation Source # 
Instance details

Defined in Text.XML.HaXml.Schema.XSDTypeModel

Methods

(==) :: Annotation -> Annotation -> Bool

(/=) :: Annotation -> Annotation -> Bool

Show Annotation Source # 
Instance details

Defined in Text.XML.HaXml.Schema.XSDTypeModel

Methods

showsPrec :: Int -> Annotation -> ShowS

show :: Annotation -> String

showList :: [Annotation] -> ShowS

Semigroup Annotation Source # 
Instance details

Defined in Text.XML.HaXml.Schema.XSDTypeModel

Methods

(<>) :: Annotation -> Annotation -> Annotation

sconcat :: NonEmpty Annotation -> Annotation

stimes :: Integral b => b -> Annotation -> Annotation

Monoid Annotation Source # 
Instance details

Defined in Text.XML.HaXml.Schema.XSDTypeModel

type Fixed = Bool Source #

type Nillable = Bool Source #

type Mixed = Bool Source #

data MyRestriction Source #

Constructors

Range Occurs 
Pattern Regexp 
Enumeration [String] 

Instances

Instances details
Eq MyRestriction Source # 
Instance details

Defined in Text.XML.HaXml.Schema.XSDTypeModel

Show MyRestriction Source # 
Instance details

Defined in Text.XML.HaXml.Schema.XSDTypeModel

Methods

showsPrec :: Int -> MyRestriction -> ShowS

show :: MyRestriction -> String

showList :: [MyRestriction] -> ShowS

data Use Source #

Constructors

Required 
Optional 
Prohibited 

Instances

Instances details
Eq Use Source # 
Instance details

Defined in Text.XML.HaXml.Schema.XSDTypeModel

Methods

(==) :: Use -> Use -> Bool

(/=) :: Use -> Use -> Bool

Show Use Source # 
Instance details

Defined in Text.XML.HaXml.Schema.XSDTypeModel

Methods

showsPrec :: Int -> Use -> ShowS

show :: Use -> String

showList :: [Use] -> ShowS

data Occurs Source #

Constructors

Occurs (Maybe Int) (Maybe Int) 

Instances

Instances details
Eq Occurs Source # 
Instance details

Defined in Text.XML.HaXml.Schema.XSDTypeModel

Methods

(==) :: Occurs -> Occurs -> Bool

(/=) :: Occurs -> Occurs -> Bool

Show Occurs Source # 
Instance details

Defined in Text.XML.HaXml.Schema.XSDTypeModel

Methods

showsPrec :: Int -> Occurs -> ShowS

show :: Occurs -> String

showList :: [Occurs] -> ShowS

Semigroup Occurs 
Instance details

Defined in Text.XML.HaXml.Schema.TypeConversion

Methods

(<>) :: Occurs -> Occurs -> Occurs

sconcat :: NonEmpty Occurs -> Occurs

stimes :: Integral b => b -> Occurs -> Occurs

Monoid Occurs 
Instance details

Defined in Text.XML.HaXml.Schema.TypeConversion

data Field Source #

Constructors

Field 

Instances

Instances details
Eq Field Source # 
Instance details

Defined in Text.XML.HaXml.Schema.XSDTypeModel

Methods

(==) :: Field -> Field -> Bool

(/=) :: Field -> Field -> Bool

Show Field Source # 
Instance details

Defined in Text.XML.HaXml.Schema.XSDTypeModel

Methods

showsPrec :: Int -> Field -> ShowS

show :: Field -> String

showList :: [Field] -> ShowS

data Selector Source #

Constructors

Selector 

Instances

Instances details
Eq Selector Source # 
Instance details

Defined in Text.XML.HaXml.Schema.XSDTypeModel

Methods

(==) :: Selector -> Selector -> Bool

(/=) :: Selector -> Selector -> Bool

Show Selector Source # 
Instance details

Defined in Text.XML.HaXml.Schema.XSDTypeModel

Methods

showsPrec :: Int -> Selector -> ShowS

show :: Selector -> String

showList :: [Selector] -> ShowS

data KeyRef Source #

Instances

Instances details
Eq KeyRef Source # 
Instance details

Defined in Text.XML.HaXml.Schema.XSDTypeModel

Methods

(==) :: KeyRef -> KeyRef -> Bool

(/=) :: KeyRef -> KeyRef -> Bool

Show KeyRef Source # 
Instance details

Defined in Text.XML.HaXml.Schema.XSDTypeModel

Methods

showsPrec :: Int -> KeyRef -> ShowS

show :: KeyRef -> String

showList :: [KeyRef] -> ShowS

data Key Source #

Instances

Instances details
Eq Key Source # 
Instance details

Defined in Text.XML.HaXml.Schema.XSDTypeModel

Methods

(==) :: Key -> Key -> Bool

(/=) :: Key -> Key -> Bool

Show Key Source # 
Instance details

Defined in Text.XML.HaXml.Schema.XSDTypeModel

Methods

showsPrec :: Int -> Key -> ShowS

show :: Key -> String

showList :: [Key] -> ShowS

data Unique Source #

Instances

Instances details
Eq Unique Source # 
Instance details

Defined in Text.XML.HaXml.Schema.XSDTypeModel

Methods

(==) :: Unique -> Unique -> Bool

(/=) :: Unique -> Unique -> Bool

Show Unique Source # 
Instance details

Defined in Text.XML.HaXml.Schema.XSDTypeModel

Methods

showsPrec :: Int -> Unique -> ShowS

show :: Unique -> String

showList :: [Unique] -> ShowS

data UniqueKeyOrKeyRef Source #

Constructors

U Unique 
K Key 
KR KeyRef 

Instances

Instances details
Eq UniqueKeyOrKeyRef Source # 
Instance details

Defined in Text.XML.HaXml.Schema.XSDTypeModel

Show UniqueKeyOrKeyRef Source # 
Instance details

Defined in Text.XML.HaXml.Schema.XSDTypeModel

Methods

showsPrec :: Int -> UniqueKeyOrKeyRef -> ShowS

show :: UniqueKeyOrKeyRef -> String

showList :: [UniqueKeyOrKeyRef] -> ShowS

data AttributeDecl Source #

Instances

Instances details
Eq AttributeDecl Source # 
Instance details

Defined in Text.XML.HaXml.Schema.XSDTypeModel

Show AttributeDecl Source # 
Instance details

Defined in Text.XML.HaXml.Schema.XSDTypeModel

Methods

showsPrec :: Int -> AttributeDecl -> ShowS

show :: AttributeDecl -> String

showList :: [AttributeDecl] -> ShowS

data NameAndType Source #

Constructors

NT 

Fields

Instances

Instances details
Eq NameAndType Source # 
Instance details

Defined in Text.XML.HaXml.Schema.XSDTypeModel

Methods

(==) :: NameAndType -> NameAndType -> Bool

(/=) :: NameAndType -> NameAndType -> Bool

Show NameAndType Source # 
Instance details

Defined in Text.XML.HaXml.Schema.XSDTypeModel

Methods

showsPrec :: Int -> NameAndType -> ShowS

show :: NameAndType -> String

showList :: [NameAndType] -> ShowS

data ElementDecl Source #

Instances

Instances details
Eq ElementDecl Source # 
Instance details

Defined in Text.XML.HaXml.Schema.XSDTypeModel

Methods

(==) :: ElementDecl -> ElementDecl -> Bool

(/=) :: ElementDecl -> ElementDecl -> Bool

Show ElementDecl Source # 
Instance details

Defined in Text.XML.HaXml.Schema.XSDTypeModel

Methods

showsPrec :: Int -> ElementDecl -> ShowS

show :: ElementDecl -> String

showList :: [ElementDecl] -> ShowS

data AttrGroup Source #

Instances

Instances details
Eq AttrGroup Source # 
Instance details

Defined in Text.XML.HaXml.Schema.XSDTypeModel

Methods

(==) :: AttrGroup -> AttrGroup -> Bool

(/=) :: AttrGroup -> AttrGroup -> Bool

Show AttrGroup Source # 
Instance details

Defined in Text.XML.HaXml.Schema.XSDTypeModel

Methods

showsPrec :: Int -> AttrGroup -> ShowS

show :: AttrGroup -> String

showList :: [AttrGroup] -> ShowS

data AnyAttr Source #

Instances

Instances details
Eq AnyAttr Source # 
Instance details

Defined in Text.XML.HaXml.Schema.XSDTypeModel

Methods

(==) :: AnyAttr -> AnyAttr -> Bool

(/=) :: AnyAttr -> AnyAttr -> Bool

Show AnyAttr Source # 
Instance details

Defined in Text.XML.HaXml.Schema.XSDTypeModel

Methods

showsPrec :: Int -> AnyAttr -> ShowS

show :: AnyAttr -> String

showList :: [AnyAttr] -> ShowS

data Any Source #

Instances

Instances details
Eq Any Source # 
Instance details

Defined in Text.XML.HaXml.Schema.XSDTypeModel

Methods

(==) :: Any -> Any -> Bool

(/=) :: Any -> Any -> Bool

Show Any Source # 
Instance details

Defined in Text.XML.HaXml.Schema.XSDTypeModel

Methods

showsPrec :: Int -> Any -> ShowS

show :: Any -> String

showList :: [Any] -> ShowS

data ElementEtc Source #

Instances

Instances details
Eq ElementEtc Source # 
Instance details

Defined in Text.XML.HaXml.Schema.XSDTypeModel

Methods

(==) :: ElementEtc -> ElementEtc -> Bool

(/=) :: ElementEtc -> ElementEtc -> Bool

Show ElementEtc Source # 
Instance details

Defined in Text.XML.HaXml.Schema.XSDTypeModel

Methods

showsPrec :: Int -> ElementEtc -> ShowS

show :: ElementEtc -> String

showList :: [ElementEtc] -> ShowS

data ChoiceOrSeq Source #

Instances

Instances details
Eq ChoiceOrSeq Source # 
Instance details

Defined in Text.XML.HaXml.Schema.XSDTypeModel

Methods

(==) :: ChoiceOrSeq -> ChoiceOrSeq -> Bool

(/=) :: ChoiceOrSeq -> ChoiceOrSeq -> Bool

Show ChoiceOrSeq Source # 
Instance details

Defined in Text.XML.HaXml.Schema.XSDTypeModel

Methods

showsPrec :: Int -> ChoiceOrSeq -> ShowS

show :: ChoiceOrSeq -> String

showList :: [ChoiceOrSeq] -> ShowS

data Group Source #

Instances

Instances details
Eq Group Source # 
Instance details

Defined in Text.XML.HaXml.Schema.XSDTypeModel

Methods

(==) :: Group -> Group -> Bool

(/=) :: Group -> Group -> Bool

Show Group Source # 
Instance details

Defined in Text.XML.HaXml.Schema.XSDTypeModel

Methods

showsPrec :: Int -> Group -> ShowS

show :: Group -> String

showList :: [Group] -> ShowS

data ParticleAttrs Source #

Constructors

PA Particle [Either AttributeDecl AttrGroup] (Maybe AnyAttr) 

Instances

Instances details
Eq ParticleAttrs Source # 
Instance details

Defined in Text.XML.HaXml.Schema.XSDTypeModel

Show ParticleAttrs Source # 
Instance details

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 Extension Source #

Instances

Instances details
Eq Extension Source # 
Instance details

Defined in Text.XML.HaXml.Schema.XSDTypeModel

Methods

(==) :: Extension -> Extension -> Bool

(/=) :: Extension -> Extension -> Bool

Show Extension Source # 
Instance details

Defined in Text.XML.HaXml.Schema.XSDTypeModel

Methods

showsPrec :: Int -> Extension -> ShowS

show :: Extension -> String

showList :: [Extension] -> ShowS

data Restriction1 Source #

Constructors

Restriction1 Particle 

Instances

Instances details
Eq Restriction1 Source # 
Instance details

Defined in Text.XML.HaXml.Schema.XSDTypeModel

Methods

(==) :: Restriction1 -> Restriction1 -> Bool

(/=) :: Restriction1 -> Restriction1 -> Bool

Show Restriction1 Source # 
Instance details

Defined in Text.XML.HaXml.Schema.XSDTypeModel

Methods

showsPrec :: Int -> Restriction1 -> ShowS

show :: Restriction1 -> String

showList :: [Restriction1] -> ShowS

data ComplexItem Source #

Instances

Instances details
Eq ComplexItem Source # 
Instance details

Defined in Text.XML.HaXml.Schema.XSDTypeModel

Methods

(==) :: ComplexItem -> ComplexItem -> Bool

(/=) :: ComplexItem -> ComplexItem -> Bool

Show ComplexItem Source # 
Instance details

Defined in Text.XML.HaXml.Schema.XSDTypeModel

Methods

showsPrec :: Int -> ComplexItem -> ShowS

show :: ComplexItem -> String

showList :: [ComplexItem] -> ShowS

data ComplexType Source #

Instances

Instances details
Eq ComplexType Source # 
Instance details

Defined in Text.XML.HaXml.Schema.XSDTypeModel

Methods

(==) :: ComplexType -> ComplexType -> Bool

(/=) :: ComplexType -> ComplexType -> Bool

Show ComplexType Source # 
Instance details

Defined in Text.XML.HaXml.Schema.XSDTypeModel

Methods

showsPrec :: Int -> ComplexType -> ShowS

show :: ComplexType -> String

showList :: [ComplexType] -> ShowS

data Facet Source #

Instances

Instances details
Eq Facet Source # 
Instance details

Defined in Text.XML.HaXml.Schema.XSDTypeModel

Methods

(==) :: Facet -> Facet -> Bool

(/=) :: Facet -> Facet -> Bool

Show Facet Source # 
Instance details

Defined in Text.XML.HaXml.Schema.XSDTypeModel

Methods

showsPrec :: Int -> Facet -> ShowS

show :: Facet -> String

showList :: [Facet] -> ShowS

data Restriction Source #

Instances

Instances details
Eq Restriction Source # 
Instance details

Defined in Text.XML.HaXml.Schema.XSDTypeModel

Methods

(==) :: Restriction -> Restriction -> Bool

(/=) :: Restriction -> Restriction -> Bool

Show Restriction Source # 
Instance details

Defined in Text.XML.HaXml.Schema.XSDTypeModel

Methods

showsPrec :: Int -> Restriction -> ShowS

show :: Restriction -> String

showList :: [Restriction] -> ShowS

data SimpleType Source #

Instances

Instances details
Eq SimpleType Source # 
Instance details

Defined in Text.XML.HaXml.Schema.XSDTypeModel

Methods

(==) :: SimpleType -> SimpleType -> Bool

(/=) :: SimpleType -> SimpleType -> Bool

Show SimpleType Source # 
Instance details

Defined in Text.XML.HaXml.Schema.XSDTypeModel

Methods

showsPrec :: Int -> SimpleType -> ShowS

show :: SimpleType -> String

showList :: [SimpleType] -> ShowS

data Schema Source #

Instances

Instances details
Eq Schema Source # 
Instance details

Defined in Text.XML.HaXml.Schema.XSDTypeModel

Methods

(==) :: Schema -> Schema -> Bool

(/=) :: Schema -> Schema -> Bool

Show Schema Source # 
Instance details

Defined in Text.XML.HaXml.Schema.XSDTypeModel

Methods

showsPrec :: Int -> Schema -> ShowS

show :: Schema -> String

showList :: [Schema] -> ShowS

Semigroup Schema Source # 
Instance details

Defined in Text.XML.HaXml.Schema.XSDTypeModel

Methods

(<>) :: Schema -> Schema -> Schema

sconcat :: NonEmpty Schema -> Schema

stimes :: Integral b => b -> Schema -> Schema

Monoid Schema Source #

This instance is pretty unsatisfactory, and is useful only for building environments involving recursive modules. The mappend method is left-biased, and the mempty value contains lots of undefined values.

Instance details

Defined in Text.XML.HaXml.Schema.XSDTypeModel