module Text.XML.HXT.DTDValidation.DocValidation
( validateDoc
)
where
import Text.XML.HXT.DTDValidation.TypeDefs
import Text.XML.HXT.DTDValidation.AttributeValueValidation
import Text.XML.HXT.DTDValidation.XmlRE
type ValiEnvTable = [ValiEnv]
type ValiEnv = (ElemName, ValFct)
type ElemName = String
type ValFct = XmlArrow
validateDoc :: XmlTree -> XmlArrow
validateDoc dtdPart
= traverseTree valTable
where
valTable = buildAllValidationFunctions dtdPart
traverseTree :: ValiEnvTable -> XmlArrow
traverseTree valiEnv
= choiceA [ isElem :-> (valFct $< getQName)
, this :-> none
]
<+>
( getChildren >>> traverseTree valiEnv )
where
valFct :: QName -> XmlArrow
valFct name = case (lookup (qualifiedName name) valiEnv) of
Nothing -> err ("Element " ++ show (qualifiedName name) ++ " not declared in DTD.")
Just f -> f
buildAllValidationFunctions :: XmlTree -> ValiEnvTable
buildAllValidationFunctions dtdPart
= concat $
buildValidateRoot dtdPart :
map (buildValidateFunctions dtdNodes) dtdNodes
where
dtdNodes = runLA getChildren dtdPart
buildValidateRoot :: XmlTree -> [ValiEnv]
buildValidateRoot dn
| isDTDDoctypeNode dn = [(t_root, valFct)]
| otherwise = []
where
name = dtd_name . getDTDAttributes $ dn
valFct :: XmlArrow
valFct = isElem
`guards`
( checkRegex (re_sym name)
>>>
msgToErr (("Root Element must be " ++ show name ++ ". ") ++)
)
checkRegex :: RE String -> LA XmlTree String
checkRegex re = listA getChildren
>>> arr (\ cs -> checkRE (matches re cs))
buildValidateFunctions :: XmlTrees -> XmlTree -> [ValiEnv]
buildValidateFunctions dtdPart dn
| isDTDElementNode dn = [(elemName, valFct)]
| otherwise = []
where
elemName = dtd_name . getDTDAttributes $ dn
valFct :: XmlArrow
valFct = buildContentValidation dn
<+>
buildAttributeValidation dtdPart dn
buildContentValidation :: XmlTree -> XmlArrow
buildContentValidation nd
= contentValidation attrType nd
where
attrType = dtd_type . getDTDAttributes $ nd
contentValidation :: String -> XmlTree -> XmlArrow
contentValidation typ dn
| typ == k_pcdata = contentValidationPcdata
| typ == k_empty = contentValidationEmpty
| typ == k_any = contentValidationAny
| typ == v_children = contentValidationChildren cs
| typ == v_mixed = contentValidationMixed cs
| otherwise = none
where
cs = runLA getChildren dn
contentValidationPcdata :: XmlArrow
contentValidationPcdata
= isElem `guards` (contentVal $< getQName)
where
contentVal name
= checkRegex (re_rep (re_sym k_pcdata))
>>>
msgToErr ( ( "The content of element " ++
show (qualifiedName name) ++
" must match (#PCDATA). "
) ++
)
contentValidationEmpty :: XmlArrow
contentValidationEmpty
= isElem `guards` (contentVal $< getQName)
where
contentVal name
= checkRegex re_unit
>>>
msgToErr ( ( "The content of element " ++
show (qualifiedName name) ++
" must match EMPTY. "
) ++
)
contentValidationAny :: XmlArrow
contentValidationAny
= isElem `guards` (contentVal $< getName)
where
contentVal name
= checkRegex (re_rep (re_dot))
>>>
msgToErr ( ( "The content of element " ++
show name ++
" must match ANY. "
) ++
)
contentValidationChildren :: XmlTrees -> XmlArrow
contentValidationChildren cm
= isElem `guards` (contentVal $< getName)
where
contentVal name
= checkRegex re
>>>
msgToErr ( ( "The content of element " ++
show name ++
" must match " ++ printRE re ++ ". "
) ++
)
re = createRE (head cm)
contentValidationMixed :: XmlTrees -> XmlArrow
contentValidationMixed cm
= isElem `guards` (contentVal $< getName)
where
contentVal name
= checkRegex re
>>>
msgToErr ( ( "The content of element " ++
show name ++
" must match " ++ printRE re ++ ". "
) ++
)
re = re_rep (re_alt (re_sym k_pcdata) (createRE (head cm)))
createRE :: XmlTree -> RE String
createRE dn
| isDTDContentNode dn
= processModifier modifier
| isDTDNameNode dn
= re_sym name
| otherwise
= error ("createRE: illegeal parameter:\n" ++ show dn)
where
al = getDTDAttributes dn
name = dtd_name al
modifier = dtd_modifier al
kind = dtd_kind al
cs = runLA getChildren dn
processModifier :: String -> RE String
processModifier m
| m == v_plus = re_plus (processKind kind)
| m == v_star = re_rep (processKind kind)
| m == v_option = re_opt (processKind kind)
| m == v_null = processKind kind
| otherwise = error ("Unknown modifier: " ++ show m)
processKind :: String -> RE String
processKind k
| k == v_seq = makeSequence cs
| k == v_choice = makeChoice cs
| otherwise = error ("Unknown kind: " ++ show k)
makeSequence :: XmlTrees -> RE String
makeSequence [] = re_unit
makeSequence (x:xs) = re_seq (createRE x) (makeSequence xs)
makeChoice :: XmlTrees -> RE String
makeChoice [] = re_zero ""
makeChoice (x:xs) = re_alt (createRE x) (makeChoice xs)
buildAttributeValidation :: XmlTrees -> XmlTree -> XmlArrow
buildAttributeValidation dtdPart nd =
noDoublicateAttributes
<+>
checkNotDeclardAttributes attrDecls nd
<+>
checkRequiredAttributes attrDecls nd
<+>
checkFixedAttributes attrDecls nd
<+>
checkValuesOfAttributes attrDecls dtdPart nd
where
attrDecls = isDTDAttlist $$ dtdPart
noDoublicateAttributes :: XmlArrow
noDoublicateAttributes
= isElem
`guards`
( noDoubles' $< getName )
where
noDoubles' elemName
= listA (getAttrl >>> getName)
>>> applyA (arr (catA . map toErr . doubles . reverse))
where
toErr n1 = err ( "Attribute " ++ show n1 ++
" was already specified for element " ++
show elemName ++ "."
)
checkRequiredAttributes :: XmlTrees -> XmlTree -> XmlArrow
checkRequiredAttributes attrDecls dn
| isDTDElementNode dn
= isElem
`guards`
( checkRequired $< getName )
| otherwise
= none
where
elemName = dtd_name . getDTDAttributes $ dn
requiredAtts = (isAttlistOfElement elemName >>> isRequiredAttrKind) $$ attrDecls
checkRequired :: String -> XmlArrow
checkRequired name
= catA . map checkReq $ requiredAtts
where
checkReq :: XmlTree -> XmlArrow
checkReq attrDecl
= neg (hasAttr attName)
`guards`
err ( "Attribute " ++ show attName ++ " must be declared for element type " ++
show name ++ "." )
where
attName = dtd_value . getDTDAttributes $ attrDecl
checkFixedAttributes :: XmlTrees -> XmlTree -> XmlArrow
checkFixedAttributes attrDecls dn
| isDTDElementNode dn
= isElem
`guards`
( checkFixed $< getName )
| otherwise
= none
where
elemName = dtd_name . getDTDAttributes $ dn
fixedAtts = (isAttlistOfElement elemName >>> isFixedAttrKind) $$ attrDecls
checkFixed :: String -> XmlArrow
checkFixed name
= catA . map checkFix $ fixedAtts
where
checkFix :: XmlTree -> XmlArrow
checkFix an
| isDTDAttlistNode an
= checkFixedVal $< getAttrValue attName
| otherwise
= none
where
al' = getDTDAttributes an
attName = dtd_value al'
defa = dtd_default al'
fixedValue = normalizeAttributeValue (Just an) defa
checkFixedVal :: String -> XmlArrow
checkFixedVal val
= ( ( hasAttr attName
>>>
isA (const (attValue /= fixedValue))
)
`guards`
err ( "Attribute " ++ show attName ++ " of element " ++ show name ++
" with value " ++ show attValue ++ " must have a value of " ++
show fixedValue ++ "." )
)
where
attValue = normalizeAttributeValue (Just an) val
checkNotDeclardAttributes :: XmlTrees -> XmlTree -> XmlArrow
checkNotDeclardAttributes attrDecls elemDescr
= checkNotDeclared
where
elemName = valueOfDTD a_name elemDescr
decls = isAttlistOfElement elemName $$ attrDecls
checkNotDeclared :: XmlArrow
checkNotDeclared
= isElem
`guards`
( getAttrl >>> searchForDeclaredAtt elemName decls )
searchForDeclaredAtt :: String -> XmlTrees -> XmlArrow
searchForDeclaredAtt name (dn : xs)
| isDTDAttlistNode dn
= ( getName >>> isA ( (dtd_value . getDTDAttributes $ dn) /= ) )
`guards`
searchForDeclaredAtt name xs
| otherwise
= searchForDeclaredAtt name xs
searchForDeclaredAtt name []
= mkErr $< getName
where
mkErr n = err ( "Attribute " ++ show n ++ " of element " ++
show name ++ " is not declared in DTD." )
checkValuesOfAttributes :: XmlTrees -> XmlTrees -> XmlTree -> XmlArrow
checkValuesOfAttributes attrDecls dtdPart elemDescr
= checkValues
where
elemName = dtd_name . getDTDAttributes $ elemDescr
decls = isAttlistOfElement elemName $$ attrDecls
checkValues :: XmlArrow
checkValues
= isElem
`guards`
( checkValue $< getAttrl )
checkValue att
= catA . map checkVal $ decls
where
checkVal :: XmlTree -> XmlArrow
checkVal attrDecl
| isDTDAttlistNode attrDecl
&&
nameOfAttr att == dtd_value al'
= checkAttributeValue dtdPart attrDecl
| otherwise
= none
where
al' = getDTDAttributes attrDecl