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 Data.List (nub)
import qualified Data.Set as Set
import Data.Map (fromList)
import Data.Maybe (fromMaybe)
syntaxName :: String
syntaxName = "xslt"
syntaxExtensions :: String
syntaxExtensions = "*.xsl;*.xslt"
highlight :: String -> Either String [SourceLine]
highlight input =
case runParser parseSource startingState "source" input of
Left err -> Left $ show err
Right result -> Right result
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
newline <|> (eof >> return '\n')
context <- currentContext
case context of
"normalText" -> return ()
"detectEntRef" -> return ()
"tagname" -> return ()
"attributes" -> return ()
"attrValue" -> return ()
"xattributes" -> return ()
"xattrValue" -> return ()
"string" -> return ()
"sqstring" -> return ()
"comment" -> return ()
"xpath" -> return ()
"sqxpath" -> return ()
"sqxpathstring" -> return ()
"xpathstring" -> return ()
_ -> return ()
lineContents <- lookAhead wholeLine
updateState $ \st -> st { synStCurrentLine = lineContents, synStCharsParsedInLine = 0, synStPrevChar = '\n' }
withAttribute attr txt = do
if null txt
then fail "Parser matched no text"
else return ()
let style = fromMaybe "" $ 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 (nub [style, attr], txt)
styles = [("Normal Text","Normal"),("Tag","Keyword"),("Attribute","Others"),("Invalid","Error"),("Alert","Alert"),("Attribute Value","String"),("XPath","Others"),("XPath String","String"),("XPath Axis","Keyword"),("XPath/ XSLT Function","Keyword"),("XPath 2.0/ XSLT 2.0 Function","Keyword"),("XPath Attribute","Normal"),("Variable","Normal"),("Comment","Comment"),("XSLT Tag","Keyword"),("XSLT 2.0 Tag","Keyword"),("Entity Reference","DecVal")]
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_'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_'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"),("detectEntRef","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")
<|>
((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 "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 "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 ())))
return (attr, result)
parseRules "attributes" =
do (attr, result) <- (((pDetect2Chars False '/' '>' >>= withAttribute "Tag") >>~ (popContext >> popContext >> return ()))
<|>
((pDetectChar False '>' >>= withAttribute "Tag") >>~ (popContext >> popContext >> return ()))
<|>
((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 >> return ()))
<|>
((pDetectChar False '>' >>= withAttribute "Invalid") >>~ (popContext >> popContext >> popContext >> return ()))
<|>
((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 >> return ()))
<|>
((pDetectChar False '>' >>= withAttribute "Tag") >>~ (popContext >> popContext >> return ()))
<|>
((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 >> return ()))
<|>
((pDetectChar False '>' >>= withAttribute "Invalid") >>~ (popContext >> popContext >> popContext >> return ()))
<|>
((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 >> return ()))
<|>
((parseRules "detectEntRef")))
return (attr, result)
parseRules "sqstring" =
do (attr, result) <- (((pDetectChar False '{' >>= withAttribute "XPath") >>~ pushContext "sqxpath")
<|>
((pDetectChar False '\'' >>= withAttribute "Attribute Value") >>~ (popContext >> popContext >> return ()))
<|>
((parseRules "detectEntRef")))
return (attr, result)
parseRules "comment" =
do (attr, result) <- (((pString False "-->" >>= withAttribute "Comment") >>~ (popContext >> return ()))
<|>
((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 >> return ()))
<|>
((pDetectChar False '\'' >>= withAttribute "XPath String") >>~ pushContext "sqxpathstring")
<|>
((pDetectChar False '"' >>= withAttribute "XPath") >>~ (popContext >> popContext >> return ()))
<|>
((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 >> return ()))
<|>
((pDetectChar False '"' >>= withAttribute "XPath String") >>~ pushContext "xpathstring")
<|>
((pDetectChar False '\'' >>= withAttribute "XPath") >>~ (popContext >> popContext >> return ()))
<|>
((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 >> return ()))
<|>
((parseRules "detectEntRef")))
return (attr, result)
parseRules "xpathstring" =
do (attr, result) <- (((pDetectChar False '"' >>= withAttribute "XPath String") >>~ (popContext >> return ()))
<|>
((parseRules "detectEntRef")))
return (attr, result)
parseRules x = fail $ "Unknown context" ++ x