module Text.XML.HXT.DTDValidation.IdValidation
    ( validateIds
    )
where
import Data.Maybe
import Text.XML.HXT.DTDValidation.TypeDefs
import Text.XML.HXT.DTDValidation.AttributeValueValidation
type IdEnvTable		= [IdEnv]
type IdEnv 		= (ElemName, IdFct)
type ElemName		= String
type IdFct		= XmlArrow
validateIds :: XmlTree -> XmlArrow
validateIds dtdPart
    = validateIds' $< listA (traverseTree idEnv)
      where
      idAttrTypes = runLA (getChildren >>> isIdAttrType) dtdPart
      elements	  = runLA (getChildren >>> isDTDElement) dtdPart
      atts        = runLA (getChildren >>> isDTDAttlist) dtdPart
      idEnv	  = buildIdCollectorFcts idAttrTypes
      validateIds'	:: XmlTrees -> XmlArrow
      validateIds' idNodeList
	  = ( constA idNodeList >>> checkForUniqueIds idAttrTypes )
	    <+>
	    checkIdReferences idRefEnv
	  where
	  idRefEnv   = buildIdrefValidationFcts idAttrTypes elements atts idNodeList
traverseTree :: IdEnvTable -> XmlArrow
traverseTree idEnv
    = multi (isElem `guards` (idFct $< getName))
      where
      idFct 		:: String -> XmlArrow
      idFct name	= fromMaybe none . lookup name $ idEnv
getIdValue	:: XmlTrees -> XmlTree -> String
getIdValue dns
    = concat . runLA (single getIdValue')
    where
    getIdValue'	:: LA XmlTree String
    getIdValue'
	= isElem `guards` catA (map getIdVal dns)
	where
	getIdVal dn
	    | isDTDAttlistNode dn	= hasName elemName
					  `guards`
					  ( getAttrValue0 attrName
					    >>>
					    arr (normalizeAttributeValue (Just dn))
					  )
	    | otherwise			= none
	    where
	    al       = getDTDAttributes dn
	    elemName = dtd_name  al
	    attrName = dtd_value al
buildIdCollectorFcts :: XmlTrees -> IdEnvTable
buildIdCollectorFcts idAttrTypes
    = concatMap buildIdCollectorFct idAttrTypes
      where
      buildIdCollectorFct :: XmlTree -> [IdEnv]
      buildIdCollectorFct dn
	  | isDTDAttlistNode dn	= [(elemName, hasAttr attrName)]
	  | otherwise		= []
	  where
	  al       = getDTDAttributes dn
          elemName = dtd_name  al
	  attrName = dtd_value al
buildIdrefValidationFcts :: XmlTrees -> XmlTrees -> XmlTrees -> XmlTrees -> IdEnvTable
buildIdrefValidationFcts idAttrTypes elements atts idNodeList
    = concatMap buildElemValidationFct elements
      where
      idValueList = map (getIdValue idAttrTypes) idNodeList
      buildElemValidationFct :: XmlTree -> [IdEnv]
      buildElemValidationFct dn
	  | isDTDElementNode dn	= [(elemName, buildIdrefValidationFct idRefAttrTypes)]
	  | otherwise		= []
	  where
	  al             = getDTDAttributes dn
	  elemName       = dtd_name al
	  idRefAttrTypes = (isAttlistOfElement elemName >>> isIdRefAttrType) $$ atts
      buildIdrefValidationFct :: XmlTrees -> XmlArrow
      buildIdrefValidationFct
	  = catA . map buildIdref
      buildIdref	:: XmlTree -> XmlArrow
      buildIdref dn
	  | isDTDAttlistNode dn	= isElem >>> (checkIdref $< getName)
	  | otherwise		= none
	  where
	  al             = getDTDAttributes dn
	  attrName = dtd_value al
	  attrType = dtd_type  al
	  checkIdref :: String -> XmlArrow
	  checkIdref name
	      = hasAttr attrName
		`guards`
		( checkIdVal $< getAttrValue attrName )
	      where
	      checkIdVal	:: String -> XmlArrow
	      checkIdVal av
		  | attrType == k_idref
		      = checkValueDeclared attrValue
		  | null valueList
		      = err ( "Attribute " ++ show attrName ++
			      " of Element " ++ show name ++
			      " must have at least one name."
			    )
		  | otherwise
		      = catA . map checkValueDeclared $ valueList
		  where
		  valueList = words attrValue
		  attrValue = normalizeAttributeValue (Just dn) av
	  checkValueDeclared :: String -> XmlArrow
	  checkValueDeclared  attrValue
	      = if attrValue `elem` idValueList
		then none
		else err ( "An Element with identifier " ++ show attrValue ++
		           " must appear in the document."
			 )
checkForUniqueIds :: XmlTrees -> LA XmlTrees XmlTree
checkForUniqueIds idAttrTypes		 
    = fromSLA [] ( unlistA
		   >>>
		   isElem
		   >>>
		   (checkForUniqueId $<< getName &&& this)
		 )
      where
      checkForUniqueId :: String -> XmlTree -> SLA [String] XmlTree XmlTree
      checkForUniqueId name x
	  = ifA ( getState
		  >>>
		  isA (attrValue `elem`)
		)
	    (err ( "Attribute value " ++ show attrValue ++ " of type ID for element " ++
	           show name ++ " must be unique within the document." ))
            (nextState (attrValue:) >>> none)
	  where
	  attrValue = getIdValue (isAttlistOfElement name $$ idAttrTypes) x
checkIdReferences :: IdEnvTable -> LA XmlTree XmlTree
checkIdReferences idRefEnv
    = traverseTree idRefEnv