module Text.XML.HXT.DTDValidation.DTDValidation
    ( removeDoublicateDefs
    , validateDTD
    )
where
import Text.XML.HXT.DTDValidation.TypeDefs
import Text.XML.HXT.DTDValidation.AttributeValueValidation
validateDTD :: XmlArrow
validateDTD 
    = isDTDDoctype
      `guards`
      ( listA getChildren
        >>>
        ( validateParts $<< (getNotationNames &&& getElemNames) )
      )
    where
    validateParts notationNames elemNames
        = validateNotations
          <+>
          validateEntities notationNames
          <+>
          validateElements elemNames
          <+>
          validateAttributes elemNames notationNames
    getNotationNames    :: LA [XmlTree] [String]
    getNotationNames    = listA $ unlistA >>> isDTDNotation >>> getDTDAttrValue a_name
    getElemNames        :: LA [XmlTree] [String]
    getElemNames        = listA $ unlistA >>> isDTDElement  >>> getDTDAttrValue a_name
checkName       :: String -> SLA [String] XmlTree XmlTree -> SLA [String] XmlTree XmlTree
checkName name msg
    = ifA ( getState
            >>>
            isA (name `elem`)
          )
      msg
      (nextState (name:) >>> none)
validateNotations :: LA XmlTrees XmlTree
validateNotations
    = fromSLA [] ( unlistA
                   >>>
                   isDTDNotation
                   >>>
                   (checkForUniqueNotation $< getDTDAttrl)
                 )
      where
      checkForUniqueNotation :: Attributes -> SLA [String] XmlTree XmlTree
      checkForUniqueNotation al
          = checkName name $
            err ( "Notation "++ show name ++ " was already specified." )
          where
          name = dtd_name al
validateEntities        :: [String] -> LA XmlTrees XmlTree
validateEntities notationNames
    = ( fromSLA [] ( unlistA
                     >>>
                     isDTDEntity
                     >>>
                     (checkForUniqueEntity $< getDTDAttrl)
                   )
      )
      <+>
      ( unlistA
        >>>
        isUnparsedEntity
        >>>
        (checkNotationDecl $< getDTDAttrl)
      )
      where
      
      checkForUniqueEntity      :: Attributes -> SLA [String] XmlTree XmlTree
      checkForUniqueEntity al
          = checkName name $
            warn ( "Entity "++ show name ++ " was already specified. " ++
                    "First declaration will be used." )
          where
          name = dtd_name al
      
      checkNotationDecl         :: Attributes -> XmlArrow
      checkNotationDecl al
          | notationName `elem` notationNames
              = none
          | otherwise
              = err ( "The notation " ++ show notationName ++ " must be declared " ++
                      "when referenced in the unparsed entity declaration for " ++
                      show upEntityName ++ "."
                    )
          where
          notationName = lookup1 k_ndata al
          upEntityName = dtd_name  al
validateElements        :: [String] -> LA XmlTrees XmlTree
validateElements elemNames 
    = ( fromSLA [] ( unlistA
                     >>>
                     isDTDElement
                     >>>
                     (checkForUniqueElement $< getDTDAttrl)
                   )
      )
      <+>
      ( unlistA
        >>>
        isMixedContentElement
        >>>
        (checkMixedContent $< getDTDAttrl)
      )
      <+>
      ( unlistA
        >>>
        isDTDElement
        >>>
        (checkContentModel elemNames $< getDTDAttrl)
      )
      where
      
      checkForUniqueElement :: Attributes -> SLA [String] XmlTree XmlTree
      checkForUniqueElement al
          = checkName name $
            err ( "Element type " ++ show name ++
                  " must not be declared more than once." )
          where
          name = dtd_name al
      
      checkMixedContent :: Attributes -> XmlArrow
      checkMixedContent al
          = fromSLA [] ( getChildren
                         >>>
                         getChildren
                         >>>
                         isDTDName
                         >>>
                         (check $< getDTDAttrl)
                       )
            where
            elemName = dtd_name al
            check al'
                = checkName name $
                  err ( "The element type " ++ show name ++
                         " was already specified in the mixed-content model of the element declaration " ++
                         show elemName ++ "." )
                where
                name = dtd_name al'
      
      
      checkContentModel :: [String] -> Attributes -> XmlArrow
      checkContentModel names al
          | cm `elem` [v_children, v_mixed]
              = getChildren >>> checkContent
          | otherwise
              = none
          where
          elemName = dtd_name al
          cm       = dtd_type al
          checkContent :: XmlArrow
          checkContent
              = choiceA
                [ isDTDName    :-> ( checkName' $< getDTDAttrl )
                , isDTDContent :-> ( getChildren >>> checkContent )
                , this         :-> none
                ]
              where
              checkName' al'
                  | childElemName `elem` names
                      = none
                  | otherwise
                      = warn ( "The element type "++ show childElemName ++
                               ", used in content model of element "++ show elemName ++
                               ", is not declared."
                             )
                  where
                  childElemName = dtd_name al'
validateAttributes :: [String] -> [String] -> LA XmlTrees XmlTree
validateAttributes elemNames notationNames
    = 
      ( runCheck this (checkDeclaredElements elemNames) )
      <+>
      
      ( runNameCheck this checkForUniqueAttributeDeclaration )
      <+>
      
      ( runCheck (isEnumAttrType `orElse` isNotationAttrType) checkEnumeratedTypes )
      <+>
      
      ( runNameCheck isIdAttrType checkForUniqueId )
      <+>
      
      ( runNameCheck isNotationAttrType checkForUniqueNotation )
      <+>
      
      ( runCheck isIdAttrType checkIdKindConstraint )
      <+>
      
      ( runCheck isNotationAttrType (checkNotationDeclaration notationNames) )
      <+>
      
      ( checkNoNotationForEmptyElements $< listA ( unlistA
                                                   >>>
                                                   isEmptyElement
                                                   >>>
                                                   getDTDAttrValue a_name
                                                 )
      )
      <+>
      
      ( checkDefaultValueTypes $< this )
      where
      
      
      runCheck select check
          = unlistA >>> isDTDAttlist
            >>>
            select
            >>>
            (check $< getDTDAttrl)
      runNameCheck select check
          = fromSLA [] $ runCheck select check
      
      
      checkDeclaredElements :: [String] -> Attributes -> XmlArrow
      checkDeclaredElements elemNames' al
          | en `elem` elemNames'
              = none
          | otherwise
              = warn ( "The element type \""++ en ++ "\" used in dclaration "++
                       "of attribute \""++ an ++"\" is not declared."
                     )
          where
          en = dtd_name al
          an = dtd_value al
      
      
      checkForUniqueAttributeDeclaration ::  Attributes -> SLA [String] XmlTree XmlTree
      checkForUniqueAttributeDeclaration al
          = checkName name $
            warn ( "Attribute \""++ aname ++"\" for element type \""++
                   ename ++"\" is already declared. First "++
                   "declaration will be used." )
          where
          ename = dtd_name al
          aname = dtd_value al
          name  = ename ++ "|" ++ aname
      
      
      checkEnumeratedTypes :: Attributes -> XmlArrow
      checkEnumeratedTypes al
          = fromSLA [] ( getChildren
                         >>>
                         isDTDName
                         >>>
                         (checkForUniqueType $< getDTDAttrl)
                       )
          where
          checkForUniqueType :: Attributes -> SLA [String] XmlTree XmlTree
          checkForUniqueType al'
              = checkName nmtoken $
                warn ( "Nmtoken \""++ nmtoken ++"\" should not "++
                       "occur more than once in attribute \""++ dtd_value al ++
                       "\" for element \""++ dtd_name al ++ "\"." )
              where
              nmtoken = dtd_name al'
      
      
      checkForUniqueId :: Attributes -> SLA [String] XmlTree XmlTree
      checkForUniqueId al
          = checkName ename $
            err ( "Element \""++ ename ++ "\" already has attribute of type "++
                  "ID, another attribute \""++ dtd_value al ++ "\" of type ID is "++
                  "not permitted." )
          where
          ename = dtd_name al
      
      
      checkForUniqueNotation :: Attributes -> SLA [String] XmlTree XmlTree
      checkForUniqueNotation al
          = checkName ename $
            err ( "Element \""++ ename ++ "\" already has attribute of type "++
                  "NOTATION, another attribute \""++ dtd_value al ++ "\" of type NOTATION "++
                  "is not permitted." )
          where
          ename = dtd_name al
      
      
      checkIdKindConstraint :: Attributes -> XmlArrow
      checkIdKindConstraint al
          | attKind `elem` [k_implied, k_required]
              = none
          | otherwise
              = err ( "ID attribute \""++ dtd_value al ++"\" must have a declared default "++
                      "of \"#IMPLIED\" or \"REQUIRED\"")
          where
          attKind = dtd_kind al
      
      
      checkNotationDeclaration :: [String] -> Attributes -> XmlArrow
      checkNotationDeclaration notations al
          = getChildren
            >>>
            isDTDName
            >>>
            (checkNotations $< getDTDAttrl)
          where
          checkNotations :: Attributes -> XmlArrow
          checkNotations al'
              | notation `elem` notations
                  = none
              | otherwise
                  = err ( "The notation \""++ notation ++"\" must be declared when "++
                          "referenced in the notation type list for attribute \""++ dtd_value al ++
                          "\" of element \""++ dtd_name al ++"\"."
                        )
              where
              notation = dtd_name al'
      
      
      checkNoNotationForEmptyElements :: [String] -> LA XmlTrees XmlTree
      checkNoNotationForEmptyElements emptyElems
          = unlistA
            >>>
            isDTDAttlist
            >>>
            isNotationAttrType
            >>>
            (checkNoNotationForEmptyElement $< getDTDAttrl)
          where
          checkNoNotationForEmptyElement :: Attributes -> XmlArrow
          checkNoNotationForEmptyElement al
              | ename `elem` emptyElems
                  = err ( "Attribute \""++ dtd_value al ++"\" of type NOTATION must not be "++
                          "declared on the element \""++ ename ++"\" declared EMPTY."
                        )
              | otherwise
                  = none
              where
              ename = dtd_name al
      
      
      checkDefaultValueTypes :: XmlTrees -> LA XmlTrees XmlTree
      checkDefaultValueTypes dtdPart'
          = unlistA >>> isDTDAttlist
            >>>
            isDefaultAttrKind
            >>>
            (checkAttributeValue dtdPart' $< this)
removeDoublicateDefs :: XmlArrow
removeDoublicateDefs
    = replaceChildren
      ( fromSLA [] ( getChildren
                     >>>
                     choiceA [ isDTDAttlist :-> (removeDoubleAttlist $< getDTDAttrl)
                             , isDTDEntity  :-> (removeDoubleEntity  $< getDTDAttrl)
                             , this         :-> this
                             ]
                   )
      )
      `when`
      isDTDDoctype
    where
    checkName' n'
        = ifA ( getState
                >>>
                isA (n' `elem`)
              )
          none
          (this >>> perform (nextState (n':)))
    removeDoubleAttlist :: Attributes -> SLA [String] XmlTree XmlTree
    removeDoubleAttlist al
        = checkName' elemAttr
        where
        elemAttr = elemName ++ "|" ++ attrName
        attrName = dtd_value al
        elemName = dtd_name al
    removeDoubleEntity  :: Attributes -> SLA [String] XmlTree XmlTree
    removeDoubleEntity al
        = checkName' (dtd_name al)