module Text.XML.HaXml.Schema.Schema
( SchemaType(..)
, SimpleType(..)
, Extension(..)
, Restricts(..)
, FwdDecl(..)
, getAttribute
, between
, Occurs(..)
, parseSimpleType
, parseText
, AnyElement(..)
, parseAnyElement
, Content(..)
, XMLParser(..)
, posnElement
, posnElementWith
, element
, interior
, text
, module Text.ParserCombinators.Poly
, module Text.Parse
, module Text.XML.HaXml.OneOfN
, toXMLElement
, toXMLText
, toXMLAnyElement
, toXMLAttribute
, addXMLAttributes
) where
import Text.ParserCombinators.Poly
import Text.Parse
import Text.XML.HaXml.Types
import Text.XML.HaXml.Posn
import Text.XML.HaXml.Namespaces (printableName)
import Text.XML.HaXml.XmlContent.Parser hiding (Document,Reference)
import Text.XML.HaXml.Schema.XSDTypeModel (Occurs(..))
import Text.XML.HaXml.Schema.PrimitiveTypes
import Text.XML.HaXml.Schema.PrimitiveTypes as Prim
import Text.XML.HaXml.OneOfN
import Text.XML.HaXml.Verbatim
class SchemaType a where
parseSchemaType :: String -> XMLParser a
schemaTypeToXML :: String -> a -> [Content ()]
class Extension t s where
supertype :: t -> s
class Restricts t s | t -> s where
restricts :: t -> s
class FwdDecl fd a | fd -> a
parseSimpleType :: SimpleType t => XMLParser t
parseSimpleType = do s <- text
case runParser acceptingParser s of
(Left err, _) -> fail err
(Right v, "") -> return v
(Right v, _) -> return v
between :: PolyParse p => Occurs -> p a -> p [a]
between (Occurs Nothing Nothing) p = fmap (:[]) p
between (Occurs (Just i) Nothing) p = return (++) `apply` exactly i p
`apply` many p
between (Occurs Nothing (Just j)) p = upto j p
between (Occurs (Just i) (Just j)) p = return (++) `apply` exactly i p
`apply` upto (ji) p
getAttribute :: (SimpleType a, Show a) =>
String -> Element Posn -> Posn -> XMLParser a
getAttribute aname (Elem t as _) pos =
case qnLookup aname as of
Nothing -> fail $ "attribute missing: " ++ aname
++ " in element <" ++ printableName t
++ "> at " ++ show pos
Just atv -> case runParser acceptingParser (attr2str atv) of
(Right val, "") -> return val
(Right val, rest) -> failBad $
"Bad attribute value for "
++ aname ++ " in element <"
++ printableName t
++ ">: got "++show val
++ "\n but trailing text: "
++ rest ++ "\n at " ++ show pos
(Left err, rest) -> failBad $ err ++ " in attribute "
++ aname ++ " of element <"
++ printableName t
++ "> at " ++ show pos
where
qnLookup :: String -> [(QName,a)] -> Maybe a
qnLookup s = Prelude.lookup s . map (\(qn,v)-> (printableName qn, v))
data AnyElement = forall a . (SchemaType a, Show a) => ANYSchemaType a
| UnconvertedANY (Content Posn)
instance Show AnyElement where
show (UnconvertedANY c) = "Unconverted "++ show (verbatim c)
show (ANYSchemaType a) = "ANYSchemaType "++show a
instance Eq AnyElement where
a == b = show a == show b
instance SchemaType AnyElement where
parseSchemaType _ = parseAnyElement
schemaTypeToXML _ = toXMLAnyElement
parseAnyElement :: XMLParser AnyElement
parseAnyElement = fmap UnconvertedANY next
parseText :: XMLParser String
parseText = text
`onFail` return ""
toXMLElement :: String -> [[Attribute]] -> [[Content ()]] -> [Content ()]
toXMLElement name attrs content =
[CElem (Elem (N name) (concat attrs) (concat content)) ()]
toXMLText :: String -> [Content ()]
toXMLText text =
[CString False text ()]
toXMLAnyElement :: AnyElement -> [Content ()]
toXMLAnyElement (UnconvertedANY c) = [fmap (const ()) c]
toXMLAttribute :: (SimpleType a) => String -> a -> [Attribute]
toXMLAttribute name val = [ (N name, AttValue [Left (simpleTypeText val)]) ]
addXMLAttributes :: [[Attribute]] -> [Content ()] -> [Content ()]
addXMLAttributes extra [CElem (Elem n attrs content) ()] =
[CElem (Elem n (attrs++concat extra) content) ()]
addXMLAttributes _ x = x
#define SchemaInstance(TYPE) instance SchemaType TYPE where { parseSchemaType s = do { e <- element [s]; interior e $ parseSimpleType; }; schemaTypeToXML s x = toXMLElement s [] [toXMLText (simpleTypeText x)] }
SchemaInstance(XsdString)
SchemaInstance(Prim.Boolean)
SchemaInstance(Prim.Base64Binary)
SchemaInstance(Prim.HexBinary)
SchemaInstance(Float)
SchemaInstance(Decimal)
SchemaInstance(Double)
SchemaInstance(Prim.AnyURI)
SchemaInstance(Prim.NOTATION)
SchemaInstance(Prim.Duration)
SchemaInstance(Prim.DateTime)
SchemaInstance(Prim.Time)
SchemaInstance(Prim.Date)
SchemaInstance(Prim.GYearMonth)
SchemaInstance(Prim.GYear)
SchemaInstance(Prim.GMonthDay)
SchemaInstance(Prim.GDay)
SchemaInstance(Prim.GMonth)
SchemaInstance(Prim.NormalizedString)
SchemaInstance(Prim.Token)
SchemaInstance(Prim.Language)
SchemaInstance(Prim.Name)
SchemaInstance(Prim.NCName)
SchemaInstance(Prim.ID)
SchemaInstance(Prim.IDREF)
SchemaInstance(Prim.IDREFS)
SchemaInstance(Prim.ENTITY)
SchemaInstance(Prim.ENTITIES)
SchemaInstance(Prim.NMTOKEN)
SchemaInstance(Prim.NMTOKENS)
SchemaInstance(Integer)
SchemaInstance(Prim.NonPositiveInteger)
SchemaInstance(Prim.NegativeInteger)
SchemaInstance(Prim.Long)
SchemaInstance(Int)
SchemaInstance(Prim.Short)
SchemaInstance(Prim.Byte)
SchemaInstance(Prim.NonNegativeInteger)
SchemaInstance(Prim.UnsignedLong)
SchemaInstance(Prim.UnsignedInt)
SchemaInstance(Prim.UnsignedShort)
SchemaInstance(Prim.UnsignedByte)
SchemaInstance(Prim.PositiveInteger)