{- This module was generated from data in the Kate syntax highlighting file xslt.xml, version 1.03,
   by  Peter Lammich (views@gmx.de) -}

module Text.Highlighting.Kate.Syntax.Xslt ( highlight, parseExpression, syntaxName, syntaxExtensions ) where
import Text.Highlighting.Kate.Definitions
import Text.Highlighting.Kate.Common
import Text.ParserCombinators.Parsec
import Control.Monad (when)
import Data.Map (fromList)
import Data.Maybe (fromMaybe, maybeToList)

import qualified Data.Set as Set
-- | Full name of language.
syntaxName :: String
syntaxName = "xslt"

-- | Filename extensions for this language.
syntaxExtensions :: String
syntaxExtensions = "*.xsl;*.xslt"

-- | Highlight source code using this syntax definition.
highlight :: String -> Either String [SourceLine]
highlight input =
  case runParser parseSource startingState "source" input of
    Left err     -> Left $ show err
    Right result -> Right result

-- | Parse an expression using appropriate local context.
parseExpression :: GenParser Char SyntaxState LabeledSource
parseExpression = do
  st <- getState
  let oldLang = synStLanguage st
  setState $ st { synStLanguage = "xslt" }
  context <- currentContext <|> (pushContext "normalText" >> currentContext)
  result <- parseRules context
  updateState $ \st -> st { synStLanguage = oldLang }
  return result

parseSource = do 
  lineContents <- lookAhead wholeLine
  updateState $ \st -> st { synStCurrentLine = lineContents }
  result <- manyTill parseSourceLine eof
  return $ map normalizeHighlighting result

startingState = SyntaxState {synStContexts = fromList [("xslt",["normalText"])], synStLanguage = "xslt", synStCurrentLine = "", synStCharsParsedInLine = 0, synStPrevChar = '\n', synStCaseSensitive = True, synStKeywordCaseSensitive = False, synStCaptures = []}

parseSourceLine = manyTill parseExpressionInternal pEndLine

pEndLine = do
  lookAhead $ newline <|> (eof >> return '\n')
  context <- currentContext
  case context of
    "normalText" -> return () >> pHandleEndLine
    "CDATA" -> return () >> pHandleEndLine
    "PI" -> return () >> pHandleEndLine
    "Doctype" -> return () >> pHandleEndLine
    "Doctype Internal Subset" -> return () >> pHandleEndLine
    "Doctype Markupdecl" -> return () >> pHandleEndLine
    "Doctype Markupdecl DQ" -> return () >> pHandleEndLine
    "Doctype Markupdecl SQ" -> return () >> pHandleEndLine
    "detectEntRef" -> return () >> pHandleEndLine
    "FindPEntityRefs" -> return () >> pHandleEndLine
    "tagname" -> return () >> pHandleEndLine
    "attributes" -> return () >> pHandleEndLine
    "attrValue" -> return () >> pHandleEndLine
    "xattributes" -> return () >> pHandleEndLine
    "xattrValue" -> return () >> pHandleEndLine
    "string" -> return () >> pHandleEndLine
    "sqstring" -> return () >> pHandleEndLine
    "comment" -> return () >> pHandleEndLine
    "xpath" -> return () >> pHandleEndLine
    "sqxpath" -> return () >> pHandleEndLine
    "sqxpathstring" -> return () >> pHandleEndLine
    "xpathstring" -> return () >> pHandleEndLine
    _ -> pHandleEndLine

withAttribute attr txt = do
  when (null txt) $ fail "Parser matched no text"
  let labs = attr : maybeToList (lookup attr styles)
  st <- getState
  let oldCharsParsed = synStCharsParsedInLine st
  let prevchar = if null txt then '\n' else last txt
  updateState $ \st -> st { synStCharsParsedInLine = oldCharsParsed + length txt, synStPrevChar = prevchar } 
  return (labs, txt)

styles = [("Tag","kw"),("Attribute","ot"),("Invalid","er"),("Alert","al"),("Attribute Value","st"),("XPath","ot"),("XPath String","st"),("XPath Axis","kw"),("XPath/ XSLT Function","kw"),("XPath 2.0/ XSLT 2.0 Function","kw"),("Comment","co"),("XSLT Tag","kw"),("XSLT 2.0 Tag","kw"),("Entity Reference","dv"),("CDATA","bn"),("Processing Instruction","kw"),("Doctype","dt"),("PEntity Reference","dv")]

parseExpressionInternal = do
  context <- currentContext
  parseRules context <|> (pDefault >>= withAttribute (fromMaybe "" $ lookup context defaultAttributes))

list_keytags = Set.fromList $ words $ "xsl:value-of xsl:output xsl:decimal-format xsl:apply-templates xsl:param xsl:transform xsl:namespace-alias xsl:comment xsl:element xsl:attribute xsl:apply-imports xsl:text xsl:when xsl:template xsl:processing-instruction xsl:include xsl:copy-of xsl:copy xsl:with-param xsl:stylesheet xsl:for-each xsl:choose xsl:sort xsl:otherwise xsl:key xsl:variable xsl:number xsl:message xsl:fallback xsl:strip-space xsl:import xsl:preserve-space xsl:if xsl:call-template xsl:attribute-set"
list_keytags'5f2'2e0 = Set.fromList $ words $ "xsl:perform-sort xsl:import-schema xsl:for-each-group xsl:sequence xsl:non-matching-substring xsl:namespace xsl:next-match xsl:function xsl:analyze-string xsl:output-character xsl:matching-substring xsl:result-document xsl:character-map xsl:document"
list_functions = Set.fromList $ words $ "format-number position lang substring-before substring normalize-space round translate starts-with concat local-name key count document system-property current boolean number contains name last unparsed-entity-uri sum generate-id function-available element-available false substring-after not string-length id floor ceiling namespace-uri true string text"
list_functions'5f2'2e0 = Set.fromList $ words $ "zero-or-one replace namespace-uri-for-prefix current-grouping-key seconds-from-duration resolve-uri node-kind minutes-from-datetime implicit-timezone exactly-one current-time current-datetime unordered subtract-dates-yielding-daytimeduration string-join static-base-uri months-from-duration input exists default-collation datetime current-group current-date collection timezone-from-time matches local-name-from-qname day-from-date timezone-from-date round-half-to-even month-from-datetime month-from-date hours-from-duration escape-uri distinct-values avg years-from-duration unparsed-text unparsed-entity-public-id subtract-datetimes-yielding-daytimeduration subtract-dates-yielding-yearmonthduration string-to-codepoints sequence-node-identical hours-from-time hours-from-datetime format-time codepoints-to-string trace tokenize subtract-datetimes-yielding-yearmonthduration subsequence seconds-from-datetime regex-group one-or-more node-name namespace-uri-from-qname min idref format-datetime format-date days-from-duration compare base-uri seconds-from-time in-scope-prefixes expanded-qname adjust-date-to-timezone year-from-date resolve-qname remove qname minutes-from-time max lower-case index-of doc deep-equal data minutes-from-duration adjust-datetime-to-timezone abs timezone-from-datetime reverse error ends-with day-from-datetime year-from-datetime upper-case root normalize-unicode empty insert-before document-uri adjust-time-to-timezone"

regex_'3c'21DOCTYPE'5cs'2b = compileRegex "<!DOCTYPE\\s+"
regex_'3c'5c'3f'5b'5cw'3a'5f'2d'5d'2a = compileRegex "<\\?[\\w:_-]*"
regex_'26'28'23'5b0'2d9'5d'2b'7c'23'5bxX'5d'5b0'2d9A'2dFa'2df'5d'2b'7c'5bA'2dZa'2dz'5f'3a'5d'5b'5cw'2e'3a'5f'2d'5d'2a'29'3b = compileRegex "&(#[0-9]+|#[xX][0-9A-Fa-f]+|[A-Za-z_:][\\w.:_-]*);"
regex_'3c'21'28ELEMENT'7cENTITY'7cATTLIST'7cNOTATION'29'5cb = compileRegex "<!(ELEMENT|ENTITY|ATTLIST|NOTATION)\\b"
regex_'25'5bA'2dZa'2dz'5f'3a'5d'5b'5cw'2e'3a'5f'2d'5d'2a'3b = compileRegex "%[A-Za-z_:][\\w.:_-]*;"
regex_'5cs'2a = compileRegex "\\s*"
regex_'5cs'2a'3d'5cs'2a = compileRegex "\\s*=\\s*"
regex_select'5cs'2a'3d'5cs'2a = compileRegex "select\\s*=\\s*"
regex_test'5cs'2a'3d'5cs'2a = compileRegex "test\\s*=\\s*"
regex_match'5cs'2a'3d'5cs'2a = compileRegex "match\\s*=\\s*"
regex_'2d'28'2d'28'3f'21'2d'3e'29'29'2b = compileRegex "-(-(?!->))+"
regex_'28FIXME'7cTODO'7cHACK'29 = compileRegex "(FIXME|TODO|HACK)"
regex_'28ancestor'7cancestor'2dor'2dself'7cattribute'7cchild'7cdescendant'7cdescendant'2dor'2dself'7cfollowing'7cfollowing'2dsibling'7cnamespace'7cparent'7cpreceding'7cpreceding'2dsibling'7cself'29'3a'3a = compileRegex "(ancestor|ancestor-or-self|attribute|child|descendant|descendant-or-self|following|following-sibling|namespace|parent|preceding|preceding-sibling|self)::"
regex_'40'5bA'2dZa'2dz'5f'3a'5d'5b'5cw'2e'3a'5f'2d'5d'2a = compileRegex "@[A-Za-z_:][\\w.:_-]*"
regex_'5c'24'5bA'2dZa'2dz'5f'3a'5d'5b'5cw'2e'3a'5f'2d'5d'2a = compileRegex "\\$[A-Za-z_:][\\w.:_-]*"
regex_'5bA'2dZa'2dz'5f'3a'5d'5b'5cw'2e'3a'5f'2d'5d'2a = compileRegex "[A-Za-z_:][\\w.:_-]*"

defaultAttributes = [("normalText","Normal Text"),("CDATA","Normal Text"),("PI","Normal Text"),("Doctype","Normal Text"),("Doctype Internal Subset","Normal Text"),("Doctype Markupdecl","Normal Text"),("Doctype Markupdecl DQ","Value"),("Doctype Markupdecl SQ","Value"),("detectEntRef","Normal Text"),("FindPEntityRefs","Normal Text"),("tagname","Tag"),("attributes","Attribute"),("attrValue","Invalid"),("xattributes","Attribute"),("xattrValue","Invalid"),("string","Attribute Value"),("sqstring","Attribute Value"),("comment","Comment"),("xpath","XPath"),("sqxpath","XPath"),("sqxpathstring","XPath String"),("xpathstring","XPath String")]

parseRules "normalText" = 
  do (attr, result) <- (((pString False "<!--" >>= withAttribute "Comment") >>~ pushContext "comment")
                        <|>
                        ((pString False "<![CDATA[" >>= withAttribute "CDATA") >>~ pushContext "CDATA")
                        <|>
                        ((pRegExpr regex_'3c'21DOCTYPE'5cs'2b >>= withAttribute "Doctype") >>~ pushContext "Doctype")
                        <|>
                        ((pRegExpr regex_'3c'5c'3f'5b'5cw'3a'5f'2d'5d'2a >>= withAttribute "Processing Instruction") >>~ pushContext "PI")
                        <|>
                        ((pDetectChar False '<' >>= withAttribute "Tag") >>~ pushContext "tagname")
                        <|>
                        ((pRegExpr regex_'26'28'23'5b0'2d9'5d'2b'7c'23'5bxX'5d'5b0'2d9A'2dFa'2df'5d'2b'7c'5bA'2dZa'2dz'5f'3a'5d'5b'5cw'2e'3a'5f'2d'5d'2a'29'3b >>= withAttribute "Entity Reference")))
     return (attr, result)

parseRules "CDATA" = 
  do (attr, result) <- (((pDetectSpaces >>= withAttribute "Normal Text"))
                        <|>
                        ((pDetectIdentifier >>= withAttribute "Normal Text"))
                        <|>
                        ((pString False "]]>" >>= withAttribute "CDATA") >>~ (popContext))
                        <|>
                        ((pString False "]]&gt;" >>= withAttribute "Entity Reference")))
     return (attr, result)

parseRules "PI" = 
  do (attr, result) <- ((pDetect2Chars False '?' '>' >>= withAttribute "Processing Instruction") >>~ (popContext))
     return (attr, result)

parseRules "Doctype" = 
  do (attr, result) <- (((pDetectChar False '>' >>= withAttribute "Doctype") >>~ (popContext))
                        <|>
                        ((pDetectChar False '[' >>= withAttribute "Doctype") >>~ pushContext "Doctype Internal Subset"))
     return (attr, result)

parseRules "Doctype Internal Subset" = 
  do (attr, result) <- (((pDetectChar False ']' >>= withAttribute "Doctype") >>~ (popContext))
                        <|>
                        ((pRegExpr regex_'3c'21'28ELEMENT'7cENTITY'7cATTLIST'7cNOTATION'29'5cb >>= withAttribute "Doctype") >>~ pushContext "Doctype Markupdecl")
                        <|>
                        ((pString False "<!--" >>= withAttribute "Comment") >>~ pushContext "comment")
                        <|>
                        ((pRegExpr regex_'3c'5c'3f'5b'5cw'3a'5f'2d'5d'2a >>= withAttribute "Processing Instruction") >>~ pushContext "PI")
                        <|>
                        ((parseRules "FindPEntityRefs")))
     return (attr, result)

parseRules "Doctype Markupdecl" = 
  do (attr, result) <- (((pDetectChar False '>' >>= withAttribute "Doctype") >>~ (popContext))
                        <|>
                        ((pDetectChar False '"' >>= withAttribute "Value") >>~ pushContext "Doctype Markupdecl DQ")
                        <|>
                        ((pDetectChar False '\'' >>= withAttribute "Value") >>~ pushContext "Doctype Markupdecl SQ"))
     return (attr, result)

parseRules "Doctype Markupdecl DQ" = 
  do (attr, result) <- (((pDetectChar False '"' >>= withAttribute "Value") >>~ (popContext))
                        <|>
                        ((parseRules "FindPEntityRefs")))
     return (attr, result)

parseRules "Doctype Markupdecl SQ" = 
  do (attr, result) <- (((pDetectChar False '\'' >>= withAttribute "Value") >>~ (popContext))
                        <|>
                        ((parseRules "FindPEntityRefs")))
     return (attr, result)

parseRules "detectEntRef" = 
  do (attr, result) <- ((pRegExpr regex_'26'28'23'5b0'2d9'5d'2b'7c'23'5bxX'5d'5b0'2d9A'2dFa'2df'5d'2b'7c'5bA'2dZa'2dz'5f'3a'5d'5b'5cw'2e'3a'5f'2d'5d'2a'29'3b >>= withAttribute "Entity Reference"))
     return (attr, result)

parseRules "FindPEntityRefs" = 
  do (attr, result) <- (((pRegExpr regex_'26'28'23'5b0'2d9'5d'2b'7c'23'5bxX'5d'5b0'2d9A'2dFa'2df'5d'2b'7c'5bA'2dZa'2dz'5f'3a'5d'5b'5cw'2e'3a'5f'2d'5d'2a'29'3b >>= withAttribute "Entity Reference"))
                        <|>
                        ((pRegExpr regex_'25'5bA'2dZa'2dz'5f'3a'5d'5b'5cw'2e'3a'5f'2d'5d'2a'3b >>= withAttribute "PEntity Reference"))
                        <|>
                        ((pAnyChar "&%" >>= withAttribute "Error")))
     return (attr, result)

parseRules "tagname" = 
  do (attr, result) <- (((pKeyword " \n\t.()!+,<=>%&*/;?[]^{|}~\\\"{}" list_keytags >>= withAttribute "XSLT Tag") >>~ pushContext "xattributes")
                        <|>
                        ((pKeyword " \n\t.()!+,<=>%&*/;?[]^{|}~\\\"{}" list_keytags'5f2'2e0 >>= withAttribute "XSLT 2.0 Tag") >>~ pushContext "xattributes")
                        <|>
                        ((pRegExpr regex_'5cs'2a >>= withAttribute "Attribute") >>~ pushContext "attributes")
                        <|>
                        ((pDetectChar False '>' >>= withAttribute "Tag") >>~ (popContext)))
     return (attr, result)

parseRules "attributes" = 
  do (attr, result) <- (((pDetect2Chars False '/' '>' >>= withAttribute "Tag") >>~ (popContext >> popContext))
                        <|>
                        ((pDetectChar False '>' >>= withAttribute "Tag") >>~ (popContext >> popContext))
                        <|>
                        ((pRegExpr regex_'5cs'2a'3d'5cs'2a >>= withAttribute "Normal Text") >>~ pushContext "attrValue"))
     return (attr, result)

parseRules "attrValue" = 
  do (attr, result) <- (((pDetect2Chars False '/' '>' >>= withAttribute "Invalid") >>~ (popContext >> popContext >> popContext))
                        <|>
                        ((pDetectChar False '>' >>= withAttribute "Invalid") >>~ (popContext >> popContext >> popContext))
                        <|>
                        ((pDetectChar False '"' >>= withAttribute "Attribute Value") >>~ pushContext "string")
                        <|>
                        ((pDetectChar False '\'' >>= withAttribute "Attribute Value") >>~ pushContext "sqstring"))
     return (attr, result)

parseRules "xattributes" = 
  do (attr, result) <- (((pDetect2Chars False '/' '>' >>= withAttribute "Tag") >>~ (popContext >> popContext))
                        <|>
                        ((pDetectChar False '>' >>= withAttribute "Tag") >>~ (popContext >> popContext))
                        <|>
                        ((pRegExpr regex_select'5cs'2a'3d'5cs'2a >>= withAttribute "Attribute") >>~ pushContext "xattrValue")
                        <|>
                        ((pRegExpr regex_test'5cs'2a'3d'5cs'2a >>= withAttribute "Attribute") >>~ pushContext "xattrValue")
                        <|>
                        ((pRegExpr regex_match'5cs'2a'3d'5cs'2a >>= withAttribute "Attribute") >>~ pushContext "xattrValue")
                        <|>
                        ((pRegExpr regex_'5cs'2a'3d'5cs'2a >>= withAttribute "Attribute") >>~ pushContext "attrValue"))
     return (attr, result)

parseRules "xattrValue" = 
  do (attr, result) <- (((pDetect2Chars False '/' '>' >>= withAttribute "Invalid") >>~ (popContext >> popContext >> popContext))
                        <|>
                        ((pDetectChar False '>' >>= withAttribute "Invalid") >>~ (popContext >> popContext >> popContext))
                        <|>
                        ((pDetectChar False '"' >>= withAttribute "XPath") >>~ pushContext "xpath")
                        <|>
                        ((pDetectChar False '\'' >>= withAttribute "XPath") >>~ pushContext "sqxpath"))
     return (attr, result)

parseRules "string" = 
  do (attr, result) <- (((pDetectChar False '{' >>= withAttribute "XPath") >>~ pushContext "xpath")
                        <|>
                        ((pDetectChar False '"' >>= withAttribute "Attribute Value") >>~ (popContext >> popContext))
                        <|>
                        ((parseRules "detectEntRef")))
     return (attr, result)

parseRules "sqstring" = 
  do (attr, result) <- (((pDetectChar False '{' >>= withAttribute "XPath") >>~ pushContext "sqxpath")
                        <|>
                        ((pDetectChar False '\'' >>= withAttribute "Attribute Value") >>~ (popContext >> popContext))
                        <|>
                        ((parseRules "detectEntRef")))
     return (attr, result)

parseRules "comment" = 
  do (attr, result) <- (((pString False "-->" >>= withAttribute "Comment") >>~ (popContext))
                        <|>
                        ((pRegExpr regex_'2d'28'2d'28'3f'21'2d'3e'29'29'2b >>= withAttribute "Invalid"))
                        <|>
                        ((pRegExpr regex_'28FIXME'7cTODO'7cHACK'29 >>= withAttribute "Alert")))
     return (attr, result)

parseRules "xpath" = 
  do (attr, result) <- (((pKeyword " \n\t.()!+,<=>%&*/;?[]^{|}~\\\"{}" list_functions >>= withAttribute "XPath/ XSLT Function"))
                        <|>
                        ((pKeyword " \n\t.()!+,<=>%&*/;?[]^{|}~\\\"{}" list_functions'5f2'2e0 >>= withAttribute "XPath 2.0/ XSLT 2.0 Function"))
                        <|>
                        ((pRegExpr regex_'28ancestor'7cancestor'2dor'2dself'7cattribute'7cchild'7cdescendant'7cdescendant'2dor'2dself'7cfollowing'7cfollowing'2dsibling'7cnamespace'7cparent'7cpreceding'7cpreceding'2dsibling'7cself'29'3a'3a >>= withAttribute "XPath Axis"))
                        <|>
                        ((pDetectChar False '}' >>= withAttribute "XPath") >>~ (popContext))
                        <|>
                        ((pDetectChar False '\'' >>= withAttribute "XPath String") >>~ pushContext "sqxpathstring")
                        <|>
                        ((pDetectChar False '"' >>= withAttribute "XPath") >>~ (popContext >> popContext))
                        <|>
                        ((pRegExpr regex_'40'5bA'2dZa'2dz'5f'3a'5d'5b'5cw'2e'3a'5f'2d'5d'2a >>= withAttribute "XPath Attribute"))
                        <|>
                        ((pRegExpr regex_'5c'24'5bA'2dZa'2dz'5f'3a'5d'5b'5cw'2e'3a'5f'2d'5d'2a >>= withAttribute "Variable"))
                        <|>
                        ((pRegExpr regex_'5bA'2dZa'2dz'5f'3a'5d'5b'5cw'2e'3a'5f'2d'5d'2a >>= withAttribute "XPath"))
                        <|>
                        ((pDetectChar False '$' >>= withAttribute "Invalid"))
                        <|>
                        ((parseRules "detectEntRef")))
     return (attr, result)

parseRules "sqxpath" = 
  do (attr, result) <- (((pKeyword " \n\t.()!+,<=>%&*/;?[]^{|}~\\\"{}" list_functions >>= withAttribute "XPath/ XSLT Function"))
                        <|>
                        ((pKeyword " \n\t.()!+,<=>%&*/;?[]^{|}~\\\"{}" list_functions'5f2'2e0 >>= withAttribute "XPath 2.0/ XSLT 2.0 Function"))
                        <|>
                        ((pRegExpr regex_'28ancestor'7cancestor'2dor'2dself'7cattribute'7cchild'7cdescendant'7cdescendant'2dor'2dself'7cfollowing'7cfollowing'2dsibling'7cnamespace'7cparent'7cpreceding'7cpreceding'2dsibling'7cself'29'3a'3a >>= withAttribute "XPath Axis"))
                        <|>
                        ((pDetectChar False '}' >>= withAttribute "XPath") >>~ (popContext))
                        <|>
                        ((pDetectChar False '"' >>= withAttribute "XPath String") >>~ pushContext "xpathstring")
                        <|>
                        ((pDetectChar False '\'' >>= withAttribute "XPath") >>~ (popContext >> popContext))
                        <|>
                        ((pRegExpr regex_'40'5bA'2dZa'2dz'5f'3a'5d'5b'5cw'2e'3a'5f'2d'5d'2a >>= withAttribute "XPath Attribute"))
                        <|>
                        ((pRegExpr regex_'5c'24'5bA'2dZa'2dz'5f'3a'5d'5b'5cw'2e'3a'5f'2d'5d'2a >>= withAttribute "Variable"))
                        <|>
                        ((pRegExpr regex_'5bA'2dZa'2dz'5f'3a'5d'5b'5cw'2e'3a'5f'2d'5d'2a >>= withAttribute "XPath"))
                        <|>
                        ((pDetectChar False '$' >>= withAttribute "Invalid"))
                        <|>
                        ((parseRules "detectEntRef")))
     return (attr, result)

parseRules "sqxpathstring" = 
  do (attr, result) <- (((pDetectChar False '\'' >>= withAttribute "XPath String") >>~ (popContext))
                        <|>
                        ((parseRules "detectEntRef")))
     return (attr, result)

parseRules "xpathstring" = 
  do (attr, result) <- (((pDetectChar False '"' >>= withAttribute "XPath String") >>~ (popContext))
                        <|>
                        ((parseRules "detectEntRef")))
     return (attr, result)

parseRules x = fail $ "Unknown context" ++ x