module Text.XML.HXT.DTDValidation.AttributeValueValidation
( checkAttributeValue
, normalizeAttributeValue
)
where
import Text.XML.HXT.Parser.XmlParsec
( parseNMToken
, parseName
)
import Text.XML.HXT.DTDValidation.TypeDefs
checkAttributeValue :: XmlTrees -> XmlTree -> XmlArrow
checkAttributeValue dtdPart attrDecl
| isDTDAttlistNode attrDecl
= choiceA
[ isElem :-> ( checkAttrVal $< getAttrValue attrName )
, isDTDAttlist :-> ( checkAttrVal $< (getDTDAttrl >>^ dtd_default) )
, this :-> none
]
| otherwise
= none
where
al = getDTDAttributes attrDecl
attrName = dtd_value al
attrType = dtd_type al
checkAttrVal attrValue
= checkValue attrType dtdPart normalizedVal attrDecl
where
normalizedVal = normalizeAttributeValue (Just attrDecl) attrValue
checkValue :: String -> XmlTrees -> String -> XmlTree -> XmlArrow
checkValue typ dtdPart attrValue attrDecl
| typ == k_cdata = none
| typ == k_enumeration = checkValueEnumeration attrDecl attrValue
| typ == k_entity = checkValueEntity dtdPart attrDecl attrValue
| typ == k_entities = checkValueEntities dtdPart attrDecl attrValue
| typ == k_id = checkValueId attrDecl attrValue
| typ == k_idref = checkValueIdref attrDecl attrValue
| typ == k_idrefs = checkValueIdrefs attrDecl attrValue
| typ == k_nmtoken = checkValueNmtoken attrDecl attrValue
| typ == k_nmtokens = checkValueNmtokens attrDecl attrValue
| typ == k_notation = checkValueEnumeration attrDecl attrValue
| otherwise = error ("Attribute type " ++ show typ ++ " unknown.")
checkValueEnumeration :: XmlTree -> String -> XmlArrow
checkValueEnumeration attrDecl attrValue
| isDTDAttlistNode attrDecl
&&
attrValue `notElem` enumVals
= err ( "Attribute " ++ show (dtd_value al) ++ " for element " ++ show (dtd_name al) ++
" must have a value from list "++ show enumVals ++ ".")
| otherwise
= none
where
al = getDTDAttributes attrDecl
enumVals :: [String]
enumVals = map (dtd_name . getDTDAttributes) $ (runLA getChildren attrDecl)
checkValueEntity :: XmlTrees -> XmlTree -> String -> XmlArrow
checkValueEntity dtdPart attrDecl attrValue
| isDTDAttlistNode attrDecl
&&
attrValue `notElem` upEntities
= err ( "Entity " ++ show attrValue ++ " of attribute " ++ show (dtd_value al) ++
" for element " ++ show (dtd_name al) ++ " is not unparsed. " ++
"The following unparsed entities exist: " ++ show upEntities ++ ".")
| otherwise
= none
where
al = getDTDAttributes attrDecl
upEntities :: [String]
upEntities = map (dtd_name . getDTDAttributes) (isUnparsedEntity $$ dtdPart)
checkValueEntities ::XmlTrees -> XmlTree -> String -> XmlArrow
checkValueEntities dtdPart attrDecl attrValue
| isDTDAttlistNode attrDecl
= if null valueList
then err ("Attribute " ++ show (dtd_value al) ++ " of element " ++
show (dtd_name al) ++ " must be one or more names.")
else catA . map (checkValueEntity dtdPart attrDecl) $ valueList
| otherwise
= none
where
al = getDTDAttributes attrDecl
valueList = words attrValue
checkValueNmtoken :: XmlTree -> String -> XmlArrow
checkValueNmtoken attrDecl attrValue
| isDTDAttlistNode attrDecl
= constA attrValue >>> checkNmtoken
| otherwise
= none
where
al = getDTDAttributes attrDecl
checkNmtoken
= mkText >>> arrL (parseNMToken "")
>>>
isError
>>>
getErrorMsg
>>>
arr (\ s -> ( "Attribute value " ++ show attrValue ++ " of attribute " ++ show (dtd_value al) ++
" for element " ++ show (dtd_name al) ++ " must be a name token, "++ (lines s) !! 1 ++".") )
>>>
mkError c_err
checkValueNmtokens :: XmlTree -> String -> XmlArrow
checkValueNmtokens attrDecl attrValue
| isDTDAttlistNode attrDecl
= if null valueList
then err ( "Attribute "++ show (dtd_value al) ++" of element " ++
show (dtd_name al) ++ " must be one or more name tokens.")
else catA . map (checkValueNmtoken attrDecl) $ valueList
| otherwise
= none
where
al = getDTDAttributes attrDecl
valueList = words attrValue
checkValueId :: XmlTree -> String -> XmlArrow
checkValueId attrDecl attrValue
= checkForName "Attribute value" attrDecl attrValue
checkValueIdref :: XmlTree -> String -> XmlArrow
checkValueIdref attrDecl attrValue
= checkForName "Attribute value" attrDecl attrValue
checkValueIdrefs :: XmlTree -> String -> XmlArrow
checkValueIdrefs attrDecl attrValue
= catA . map (checkValueIdref attrDecl) . words $ attrValue
checkForName :: String -> XmlTree -> String -> XmlArrow
checkForName msg attrDecl attrValue
| isDTDAttlistNode attrDecl
= constA attrValue >>> checkName
| otherwise
= none
where
al = getDTDAttributes attrDecl
checkName
= mkText >>> arrL (parseName "")
>>>
isError
>>>
getErrorMsg
>>>
arr (\s -> ( msg ++ " " ++ show attrValue ++" of attribute " ++ show (dtd_value al) ++
" for element "++ show (dtd_name al) ++" must be a name, " ++ (lines s) !! 1 ++ ".") )
>>>
mkError c_err
normalizeAttributeValue :: Maybe XmlTree -> String -> String
normalizeAttributeValue (Just attrDecl) value
= normalizeAttribute attrType
where
al = getDTDAttributes attrDecl
attrType = dtd_type al
normalizeAttribute :: String -> String
normalizeAttribute typ
| typ == k_cdata = cdataNormalization value
| otherwise = otherNormalization value
normalizeAttributeValue Nothing value
= cdataNormalization value
cdataNormalization :: String -> String
cdataNormalization = id
otherNormalization :: String -> String
otherNormalization = reduceWSSequences . stringTrim . cdataNormalization
reduceWSSequences :: String -> String
reduceWSSequences str = unwords (words str)