module Text.XML.HaXml.Schema.HaskellTypeModel
( module Text.XML.HaXml.Schema.HaskellTypeModel
) where
import Text.XML.HaXml.Schema.NameConversion
import Text.XML.HaXml.Schema.XSDTypeModel (Schema(..),Occurs)
import Text.XML.HaXml.Schema.Parse (lookupBy)
import Text.XML.HaXml.Types (QName(..),Namespace(..))
import Data.List (partition)
type = Maybe String
data Module = Module
{ Module -> XName
module_name :: XName
, Module -> Maybe XName
module_xsd_ns :: Maybe XName
, Module -> [Decl]
module_re_exports :: [Decl]
, Module -> [Decl]
module_import_only :: [Decl]
, Module -> [Decl]
module_decls :: [Decl]
}
data Decl
= NamedSimpleType XName XName Comment
| RestrictSimpleType XName XName [Restrict] Comment
| ExtendSimpleType XName XName [Attribute] Comment
| UnionSimpleTypes XName [XName] Comment
| EnumSimpleType XName [(XName,Comment)] Comment
| ElementsAttrs XName [Element] [Attribute] Comment
| ElementsAttrsAbstract XName
[(XName,Maybe XName)]
Comment
| ElementOfType Element
| ElementAbstractOfType XName
XName
[(XName,Maybe XName)]
Comment
| Choice XName [Element] Comment
| Group XName [Element] Comment
| RestrictComplexType XName XName Comment
| ExtendComplexType XName XName [Element] [Attribute]
[Element] [Attribute]
(Maybe XName)
Bool
[XName]
Comment
| ExtendComplexTypeAbstract XName XName
[(XName,Maybe XName)]
(Maybe XName)
[XName]
Comment
| XSDInclude XName Comment
| XSDImport XName (Maybe XName) Comment
| Comment
deriving (Decl -> Decl -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Decl -> Decl -> Bool
$c/= :: Decl -> Decl -> Bool
== :: Decl -> Decl -> Bool
$c== :: Decl -> Decl -> Bool
Eq,Int -> Decl -> ShowS
[Decl] -> ShowS
Decl -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [Decl] -> ShowS
$cshowList :: [Decl] -> ShowS
show :: Decl -> [Char]
$cshow :: Decl -> [Char]
showsPrec :: Int -> Decl -> ShowS
$cshowsPrec :: Int -> Decl -> ShowS
Show)
data Element = Element { Element -> XName
elem_name :: XName
, Element -> XName
elem_type :: XName
, Element -> Modifier
elem_modifier :: Modifier
, Element -> Bool
elem_byRef :: Bool
, Element -> [Decl]
elem_locals :: [Decl]
, Element -> Maybe [XName]
elem_substs :: Maybe [XName]
, :: Comment
}
| OneOf { Element -> [[Element]]
elem_oneOf :: [[Element]]
, elem_modifier :: Modifier
, :: Comment
}
| AnyElem { elem_modifier :: Modifier
, :: Comment
}
| Text
deriving (Element -> Element -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Element -> Element -> Bool
$c/= :: Element -> Element -> Bool
== :: Element -> Element -> Bool
$c== :: Element -> Element -> Bool
Eq,Int -> Element -> ShowS
[Element] -> ShowS
Element -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [Element] -> ShowS
$cshowList :: [Element] -> ShowS
show :: Element -> [Char]
$cshow :: Element -> [Char]
showsPrec :: Int -> Element -> ShowS
$cshowsPrec :: Int -> Element -> ShowS
Show)
data Attribute = Attribute { Attribute -> XName
attr_name :: XName
, Attribute -> XName
attr_type :: XName
, Attribute -> Bool
attr_required:: Bool
, :: Comment
}
deriving (Attribute -> Attribute -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Attribute -> Attribute -> Bool
$c/= :: Attribute -> Attribute -> Bool
== :: Attribute -> Attribute -> Bool
$c== :: Attribute -> Attribute -> Bool
Eq,Int -> Attribute -> ShowS
[Attribute] -> ShowS
Attribute -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [Attribute] -> ShowS
$cshowList :: [Attribute] -> ShowS
show :: Attribute -> [Char]
$cshow :: Attribute -> [Char]
showsPrec :: Int -> Attribute -> ShowS
$cshowsPrec :: Int -> Attribute -> ShowS
Show)
data Modifier = Single
| Optional
| Range Occurs
deriving (Modifier -> Modifier -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Modifier -> Modifier -> Bool
$c/= :: Modifier -> Modifier -> Bool
== :: Modifier -> Modifier -> Bool
$c== :: Modifier -> Modifier -> Bool
Eq,Int -> Modifier -> ShowS
[Modifier] -> ShowS
Modifier -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [Modifier] -> ShowS
$cshowList :: [Modifier] -> ShowS
show :: Modifier -> [Char]
$cshow :: Modifier -> [Char]
showsPrec :: Int -> Modifier -> ShowS
$cshowsPrec :: Int -> Modifier -> ShowS
Show)
data Restrict = RangeR Occurs Comment
| Pattern String Comment
| Enumeration [(String,Comment)]
| StrLength Occurs Comment
deriving (Restrict -> Restrict -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Restrict -> Restrict -> Bool
$c/= :: Restrict -> Restrict -> Bool
== :: Restrict -> Restrict -> Bool
$c== :: Restrict -> Restrict -> Bool
Eq,Int -> Restrict -> ShowS
[Restrict] -> ShowS
Restrict -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [Restrict] -> ShowS
$cshowList :: [Restrict] -> ShowS
show :: Restrict -> [Char]
$cshow :: Restrict -> [Char]
showsPrec :: Int -> Restrict -> ShowS
$cshowsPrec :: Int -> Restrict -> ShowS
Show)
mkModule :: String -> Schema -> [Decl] -> Module
mkModule :: [Char] -> Schema -> [Decl] -> Module
mkModule [Char]
name Schema
schema [Decl]
decls =
Module { module_name :: XName
module_name = QName -> XName
XName forall a b. (a -> b) -> a -> b
$ [Char] -> QName
N [Char]
name
, module_xsd_ns :: Maybe XName
module_xsd_ns = [Namespace] -> Maybe XName
xsdQualification
(Schema -> [Namespace]
schema_namespaces Schema
schema)
, module_re_exports :: [Decl]
module_re_exports = [Decl]
reexports
, module_import_only :: [Decl]
module_import_only = [Decl]
imports
, module_decls :: [Decl]
module_decls = [Decl]
theRest
}
where ([Decl]
reexports,[Decl]
other) = forall a. (a -> Bool) -> [a] -> ([a], [a])
partition Decl -> Bool
xsdinclude [Decl]
decls
([Decl]
imports, [Decl]
theRest) = forall a. (a -> Bool) -> [a] -> ([a], [a])
partition Decl -> Bool
xsdimport [Decl]
other
xsdinclude :: Decl -> Bool
xsdinclude (XSDInclude XName
_ Comment
_) = Bool
True
xsdinclude Decl
_ = Bool
False
xsdimport :: Decl -> Bool
xsdimport (XSDImport XName
_ Maybe XName
_ Comment
_) = Bool
True
xsdimport Decl
_ = Bool
False
xsdQualification :: [Namespace] -> Maybe XName
xsdQualification [Namespace]
nss = QName -> XName
XName forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> QName
N forall b c a. (b -> c) -> (a -> b) -> a -> c
. Namespace -> [Char]
nsPrefix forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
forall a. (a -> Bool) -> [a] -> Maybe a
lookupBy ((forall a. Eq a => a -> a -> Bool
==[Char]
xsd)forall b c a. (b -> c) -> (a -> b) -> a -> c
.Namespace -> [Char]
nsURI) [Namespace]
nss
where xsd :: [Char]
xsd = [Char]
"http://www.w3.org/2001/XMLSchema"