fadno-xml-1.0.3: XML/XSD combinators/schemas/codegen

Safe HaskellNone
LanguageHaskell2010

Fadno.Xml.ParseXsd

Contents

Description

Parse an XSD into types with the ability to resolve references.

Synopsis

Parsers and utilities

parseFile :: FilePath -> IO Schema Source #

Parse an XSD file.

loadXsdSchema :: FilePath -> IO Schema Source #

Load XSD itself as a Schema.

schemaParser :: XParser m => m Schema Source #

Main parser.

namespaceSchema :: String -> Schema -> Schema Source #

Adjust top-level names to have supplied prefix.

qnParser :: Parsec String m QN Source #

QName parser.

attrParser :: Parsec String m String Source #

Attribute text parser, without whitespace.

parsec :: Stream s Identity t => Parsec s () a -> s -> a Source #

Run parsec.

qn :: String -> QN Source #

Parse a QName.

anySimpleTypeName :: QN Source #

XML Schema "anySimpleType" (ie, built-ins like string, double etc).

Type References

class Typeable a => Resolvable a where Source #

Resolvable indicates a type has a Ref member that it can resolve from a top-level Schema production.

Minimal complete definition

resolve

Methods

resolve :: Schema -> a -> a Source #

Instances

Resolvable Group Source # 

Methods

resolve :: Schema -> Group -> Group Source #

Resolvable ComplexContent Source # 
Resolvable SimpleContent Source # 
Resolvable ComplexType Source # 
Resolvable Element Source # 
Resolvable AttributeGroup Source # 
Resolvable Attribute Source # 
Resolvable Union Source # 

Methods

resolve :: Schema -> Union -> Union Source #

Resolvable SimpleRestriction Source # 
Resolvable SimpleType Source # 
Resolvable (Ref (Either ComplexType SimpleType)) Source # 
Resolvable (Ref Group) Source # 
Resolvable (Ref ComplexType) Source # 
Resolvable (Ref Element) Source # 
Resolvable (Ref AttributeGroup) Source # 
Resolvable (Ref Attribute) Source # 
Resolvable (Ref SimpleType) Source # 

refResolve :: Resolvable r => String -> Getting (Map QN r) Schema (Map QN r) -> Schema -> Ref r -> Ref r Source #

Resolve a Ref against a Schema.

Schema, QNs, Refs

data Ref a Source #

Model an outward XSD reference.

Constructors

Unresolved

Just type name.

Fields

Resolved

Type name and resolved value.

Fields

Final

Reserved for built-in types (string, etc)

Instances

Eq a => Eq (Ref a) Source # 

Methods

(==) :: Ref a -> Ref a -> Bool #

(/=) :: Ref a -> Ref a -> Bool #

Data a => Data (Ref a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Ref a -> c (Ref a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Ref a) #

toConstr :: Ref a -> Constr #

dataTypeOf :: Ref a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Ref a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Ref a)) #

gmapT :: (forall b. Data b => b -> b) -> Ref a -> Ref a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Ref a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Ref a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Ref a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Ref a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Ref a -> m (Ref a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Ref a -> m (Ref a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Ref a -> m (Ref a) #

Show (Ref a) Source # 

Methods

showsPrec :: Int -> Ref a -> ShowS #

show :: Ref a -> String #

showList :: [Ref a] -> ShowS #

Resolvable (Ref (Either ComplexType SimpleType)) Source # 
Resolvable (Ref Group) Source # 
Resolvable (Ref ComplexType) Source # 
Resolvable (Ref Element) Source # 
Resolvable (Ref AttributeGroup) Source # 
Resolvable (Ref Attribute) Source # 
Resolvable (Ref SimpleType) Source # 

unresolved :: forall a. Traversal' (Ref a) QN Source #

resolved :: forall a. Traversal' (Ref a) QN Source #

refvalue :: forall a a. Traversal (Ref a) (Ref a) a a Source #

data Schema Source #

Schema type, mapping top-level productions to qnames.

Instances

Eq Schema Source # 

Methods

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

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

Data Schema Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Schema -> c Schema #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Schema #

toConstr :: Schema -> Constr #

dataTypeOf :: Schema -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Schema) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Schema) #

gmapT :: (forall b. Data b => b -> b) -> Schema -> Schema #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Schema -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Schema -> r #

gmapQ :: (forall d. Data d => d -> u) -> Schema -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Schema -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Schema -> m Schema #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Schema -> m Schema #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Schema -> m Schema #

Show Schema Source # 
Monoid Schema Source # 

data QN Source #

QName type.

Constructors

QN 

Instances

Eq QN Source # 

Methods

(==) :: QN -> QN -> Bool #

(/=) :: QN -> QN -> Bool #

Data QN Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> QN -> c QN #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c QN #

toConstr :: QN -> Constr #

dataTypeOf :: QN -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c QN) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c QN) #

gmapT :: (forall b. Data b => b -> b) -> QN -> QN #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> QN -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> QN -> r #

gmapQ :: (forall d. Data d => d -> u) -> QN -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> QN -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> QN -> m QN #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> QN -> m QN #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> QN -> m QN #

Ord QN Source # 

Methods

compare :: QN -> QN -> Ordering #

(<) :: QN -> QN -> Bool #

(<=) :: QN -> QN -> Bool #

(>) :: QN -> QN -> Bool #

(>=) :: QN -> QN -> Bool #

max :: QN -> QN -> QN #

min :: QN -> QN -> QN #

Show QN Source # 

Methods

showsPrec :: Int -> QN -> ShowS #

show :: QN -> String #

showList :: [QN] -> ShowS #

Productions

data SimpleType Source #

XSD simpleType production.

Instances

Eq SimpleType Source # 
Data SimpleType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SimpleType -> c SimpleType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SimpleType #

toConstr :: SimpleType -> Constr #

dataTypeOf :: SimpleType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c SimpleType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SimpleType) #

gmapT :: (forall b. Data b => b -> b) -> SimpleType -> SimpleType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SimpleType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SimpleType -> r #

gmapQ :: (forall d. Data d => d -> u) -> SimpleType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SimpleType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SimpleType -> m SimpleType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SimpleType -> m SimpleType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SimpleType -> m SimpleType #

Show SimpleType Source # 
Resolvable SimpleType Source # 
Resolvable (Ref (Either ComplexType SimpleType)) Source # 
Resolvable (Ref SimpleType) Source # 

data Bound a Source #

Model min/max restrictions.

Constructors

Inclusive a 
Exclusive a 

Instances

Functor Bound Source # 

Methods

fmap :: (a -> b) -> Bound a -> Bound b #

(<$) :: a -> Bound b -> Bound a #

Eq a => Eq (Bound a) Source # 

Methods

(==) :: Bound a -> Bound a -> Bool #

(/=) :: Bound a -> Bound a -> Bool #

Data a => Data (Bound a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Bound a -> c (Bound a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Bound a) #

toConstr :: Bound a -> Constr #

dataTypeOf :: Bound a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Bound a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Bound a)) #

gmapT :: (forall b. Data b => b -> b) -> Bound a -> Bound a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Bound a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Bound a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Bound a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Bound a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Bound a -> m (Bound a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Bound a -> m (Bound a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Bound a -> m (Bound a) #

Ord a => Ord (Bound a) Source # 

Methods

compare :: Bound a -> Bound a -> Ordering #

(<) :: Bound a -> Bound a -> Bool #

(<=) :: Bound a -> Bound a -> Bool #

(>) :: Bound a -> Bound a -> Bool #

(>=) :: Bound a -> Bound a -> Bool #

max :: Bound a -> Bound a -> Bound a #

min :: Bound a -> Bound a -> Bound a #

Show a => Show (Bound a) Source # 

Methods

showsPrec :: Int -> Bound a -> ShowS #

show :: Bound a -> String #

showList :: [Bound a] -> ShowS #

data SimpleRestriction Source #

simple type restriction production.

Instances

Eq SimpleRestriction Source # 
Data SimpleRestriction Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SimpleRestriction -> c SimpleRestriction #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SimpleRestriction #

toConstr :: SimpleRestriction -> Constr #

dataTypeOf :: SimpleRestriction -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c SimpleRestriction) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SimpleRestriction) #

gmapT :: (forall b. Data b => b -> b) -> SimpleRestriction -> SimpleRestriction #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SimpleRestriction -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SimpleRestriction -> r #

gmapQ :: (forall d. Data d => d -> u) -> SimpleRestriction -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SimpleRestriction -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SimpleRestriction -> m SimpleRestriction #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SimpleRestriction -> m SimpleRestriction #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SimpleRestriction -> m SimpleRestriction #

Show SimpleRestriction Source # 
Resolvable SimpleRestriction Source # 

data Union Source #

Simple type union production.

Instances

Eq Union Source # 

Methods

(==) :: Union -> Union -> Bool #

(/=) :: Union -> Union -> Bool #

Data Union Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Union -> c Union #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Union #

toConstr :: Union -> Constr #

dataTypeOf :: Union -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Union) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Union) #

gmapT :: (forall b. Data b => b -> b) -> Union -> Union #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Union -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Union -> r #

gmapQ :: (forall d. Data d => d -> u) -> Union -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Union -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Union -> m Union #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Union -> m Union #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Union -> m Union #

Show Union Source # 

Methods

showsPrec :: Int -> Union -> ShowS #

show :: Union -> String #

showList :: [Union] -> ShowS #

Resolvable Union Source # 

Methods

resolve :: Schema -> Union -> Union Source #

data Attribute Source #

XSD attribute production.

Instances

Eq Attribute Source # 
Data Attribute Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Attribute -> c Attribute #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Attribute #

toConstr :: Attribute -> Constr #

dataTypeOf :: Attribute -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Attribute) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Attribute) #

gmapT :: (forall b. Data b => b -> b) -> Attribute -> Attribute #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Attribute -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Attribute -> r #

gmapQ :: (forall d. Data d => d -> u) -> Attribute -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Attribute -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Attribute -> m Attribute #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Attribute -> m Attribute #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Attribute -> m Attribute #

Show Attribute Source # 
Resolvable Attribute Source # 
Resolvable (Ref Attribute) Source # 

data Use Source #

XSD "use" values.

Constructors

Required 
Optional 
Prohibited 

Instances

Eq Use Source # 

Methods

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

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

Data Use Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Use -> c Use #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Use #

toConstr :: Use -> Constr #

dataTypeOf :: Use -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Use) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Use) #

gmapT :: (forall b. Data b => b -> b) -> Use -> Use #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Use -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Use -> r #

gmapQ :: (forall d. Data d => d -> u) -> Use -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Use -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Use -> m Use #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Use -> m Use #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Use -> m Use #

Show Use Source # 

Methods

showsPrec :: Int -> Use -> ShowS #

show :: Use -> String #

showList :: [Use] -> ShowS #

data AttributeGroup Source #

XSD attribute-group production.

Instances

Eq AttributeGroup Source # 
Data AttributeGroup Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AttributeGroup -> c AttributeGroup #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AttributeGroup #

toConstr :: AttributeGroup -> Constr #

dataTypeOf :: AttributeGroup -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c AttributeGroup) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AttributeGroup) #

gmapT :: (forall b. Data b => b -> b) -> AttributeGroup -> AttributeGroup #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AttributeGroup -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AttributeGroup -> r #

gmapQ :: (forall d. Data d => d -> u) -> AttributeGroup -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AttributeGroup -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AttributeGroup -> m AttributeGroup #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AttributeGroup -> m AttributeGroup #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AttributeGroup -> m AttributeGroup #

Show AttributeGroup Source # 
Resolvable AttributeGroup Source # 
Resolvable (Ref AttributeGroup) Source # 

data Attributes Source #

Convenience grouping of attributes and attribute groups, which are always showing up together in xsd.

Instances

Eq Attributes Source # 
Data Attributes Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Attributes -> c Attributes #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Attributes #

toConstr :: Attributes -> Constr #

dataTypeOf :: Attributes -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Attributes) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Attributes) #

gmapT :: (forall b. Data b => b -> b) -> Attributes -> Attributes #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Attributes -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Attributes -> r #

gmapQ :: (forall d. Data d => d -> u) -> Attributes -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Attributes -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Attributes -> m Attributes #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Attributes -> m Attributes #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Attributes -> m Attributes #

Show Attributes Source # 

data Occurs Source #

"occurs-min" and "occurs-max"

Constructors

Occurs 

Instances

Eq Occurs Source # 

Methods

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

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

Data Occurs Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Occurs -> c Occurs #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Occurs #

toConstr :: Occurs -> Constr #

dataTypeOf :: Occurs -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Occurs) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Occurs) #

gmapT :: (forall b. Data b => b -> b) -> Occurs -> Occurs #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Occurs -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Occurs -> r #

gmapQ :: (forall d. Data d => d -> u) -> Occurs -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Occurs -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Occurs -> m Occurs #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Occurs -> m Occurs #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Occurs -> m Occurs #

Show Occurs Source # 

data Element Source #

XSD element production.

Instances

Eq Element Source # 

Methods

(==) :: Element -> Element -> Bool #

(/=) :: Element -> Element -> Bool #

Data Element Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Element -> c Element #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Element #

toConstr :: Element -> Constr #

dataTypeOf :: Element -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Element) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Element) #

gmapT :: (forall b. Data b => b -> b) -> Element -> Element #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Element -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Element -> r #

gmapQ :: (forall d. Data d => d -> u) -> Element -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Element -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Element -> m Element #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Element -> m Element #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Element -> m Element #

Show Element Source # 
Resolvable Element Source # 
Resolvable (Ref Element) Source # 

data ComplexType Source #

XSD complexType production.

Instances

Eq ComplexType Source # 
Data ComplexType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ComplexType -> c ComplexType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ComplexType #

toConstr :: ComplexType -> Constr #

dataTypeOf :: ComplexType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ComplexType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ComplexType) #

gmapT :: (forall b. Data b => b -> b) -> ComplexType -> ComplexType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ComplexType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ComplexType -> r #

gmapQ :: (forall d. Data d => d -> u) -> ComplexType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ComplexType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ComplexType -> m ComplexType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ComplexType -> m ComplexType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ComplexType -> m ComplexType #

Show ComplexType Source # 
Resolvable ComplexType Source # 
Resolvable (Ref (Either ComplexType SimpleType)) Source # 
Resolvable (Ref ComplexType) Source # 

data SimpleContent Source #

simpleContent under a complex type.

Instances

Eq SimpleContent Source # 
Data SimpleContent Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SimpleContent -> c SimpleContent #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SimpleContent #

toConstr :: SimpleContent -> Constr #

dataTypeOf :: SimpleContent -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c SimpleContent) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SimpleContent) #

gmapT :: (forall b. Data b => b -> b) -> SimpleContent -> SimpleContent #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SimpleContent -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SimpleContent -> r #

gmapQ :: (forall d. Data d => d -> u) -> SimpleContent -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SimpleContent -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SimpleContent -> m SimpleContent #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SimpleContent -> m SimpleContent #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SimpleContent -> m SimpleContent #

Show SimpleContent Source # 
Resolvable SimpleContent Source # 

data ComplexContent Source #

complexContent under a complex type. TODO: restrictions

Instances

Eq ComplexContent Source # 
Data ComplexContent Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ComplexContent -> c ComplexContent #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ComplexContent #

toConstr :: ComplexContent -> Constr #

dataTypeOf :: ComplexContent -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ComplexContent) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ComplexContent) #

gmapT :: (forall b. Data b => b -> b) -> ComplexContent -> ComplexContent #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ComplexContent -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ComplexContent -> r #

gmapQ :: (forall d. Data d => d -> u) -> ComplexContent -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ComplexContent -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ComplexContent -> m ComplexContent #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ComplexContent -> m ComplexContent #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ComplexContent -> m ComplexContent #

Show ComplexContent Source # 
Resolvable ComplexContent Source # 

data Compositor Source #

Compositors.

Instances

Eq Compositor Source # 
Data Compositor Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Compositor -> c Compositor #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Compositor #

toConstr :: Compositor -> Constr #

dataTypeOf :: Compositor -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Compositor) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Compositor) #

gmapT :: (forall b. Data b => b -> b) -> Compositor -> Compositor #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Compositor -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Compositor -> r #

gmapQ :: (forall d. Data d => d -> u) -> Compositor -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Compositor -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Compositor -> m Compositor #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Compositor -> m Compositor #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Compositor -> m Compositor #

Show Compositor Source # 

data Group Source #

XSD "group" production.

Instances

Eq Group Source # 

Methods

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

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

Data Group Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Group -> c Group #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Group #

toConstr :: Group -> Constr #

dataTypeOf :: Group -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Group) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Group) #

gmapT :: (forall b. Data b => b -> b) -> Group -> Group #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Group -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Group -> r #

gmapQ :: (forall d. Data d => d -> u) -> Group -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Group -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Group -> m Group #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Group -> m Group #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Group -> m Group #

Show Group Source # 

Methods

showsPrec :: Int -> Group -> ShowS #

show :: Group -> String #

showList :: [Group] -> ShowS #

Resolvable Group Source # 

Methods

resolve :: Schema -> Group -> Group Source #

Resolvable (Ref Group) Source # 

data Particle Source #

Particles.

Instances

Eq Particle Source # 
Data Particle Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Particle -> c Particle #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Particle #

toConstr :: Particle -> Constr #

dataTypeOf :: Particle -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Particle) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Particle) #

gmapT :: (forall b. Data b => b -> b) -> Particle -> Particle #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Particle -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Particle -> r #

gmapQ :: (forall d. Data d => d -> u) -> Particle -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Particle -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Particle -> m Particle #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Particle -> m Particle #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Particle -> m Particle #

Show Particle Source # 

data Choice Source #

XSD choice

Constructors

Choice 

Instances

Eq Choice Source # 

Methods

(==) :: Choice -> Choice -> Bool #

(/=) :: Choice -> Choice -> Bool #

Data Choice Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Choice -> c Choice #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Choice #

toConstr :: Choice -> Constr #

dataTypeOf :: Choice -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Choice) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Choice) #

gmapT :: (forall b. Data b => b -> b) -> Choice -> Choice #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Choice -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Choice -> r #

gmapQ :: (forall d. Data d => d -> u) -> Choice -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Choice -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Choice -> m Choice #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Choice -> m Choice #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Choice -> m Choice #

Show Choice Source # 

data Sequence Source #

XSD sequence.

Instances

Eq Sequence Source # 
Data Sequence Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Sequence -> c Sequence #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Sequence #

toConstr :: Sequence -> Constr #

dataTypeOf :: Sequence -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Sequence) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Sequence) #

gmapT :: (forall b. Data b => b -> b) -> Sequence -> Sequence #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Sequence -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Sequence -> r #

gmapQ :: (forall d. Data d => d -> u) -> Sequence -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Sequence -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Sequence -> m Sequence #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Sequence -> m Sequence #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Sequence -> m Sequence #

Show Sequence Source # 

newtype Documentation Source #

Constructors

Documentation String 

Instances

Eq Documentation Source # 
Data Documentation Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Documentation -> c Documentation #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Documentation #

toConstr :: Documentation -> Constr #

dataTypeOf :: Documentation -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Documentation) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Documentation) #

gmapT :: (forall b. Data b => b -> b) -> Documentation -> Documentation #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Documentation -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Documentation -> r #

gmapQ :: (forall d. Data d => d -> u) -> Documentation -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Documentation -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Documentation -> m Documentation #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Documentation -> m Documentation #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Documentation -> m Documentation #

Ord Documentation Source # 
Show Documentation Source #