{- This module was generated from data in the Kate syntax highlighting file elixir.xml, version 1, by Rubén Caro (ruben.caro.estevez@gmail.com), Boris Egorov (egorov@linux.com) -} module Text.Highlighting.Kate.Syntax.Elixir (highlight, parseExpression, syntaxName, syntaxExtensions) where import Text.Highlighting.Kate.Types import Text.Highlighting.Kate.Common import qualified Text.Highlighting.Kate.Syntax.Markdown import Text.ParserCombinators.Parsec hiding (State) import Control.Monad.State import Data.Char (isSpace) import qualified Data.Set as Set -- | Full name of language. syntaxName :: String syntaxName = "Elixir" -- | Filename extensions for this language. syntaxExtensions :: String syntaxExtensions = "*.ex;*.exs;*.eex;*.xml.eex;*.js.eex" -- | Highlight source code using this syntax definition. highlight :: String -> [SourceLine] highlight input = evalState (mapM parseSourceLine $ lines input) startingState parseSourceLine :: String -> State SyntaxState SourceLine parseSourceLine = mkParseSourceLine (parseExpression Nothing) -- | Parse an expression using appropriate local context. parseExpression :: Maybe (String,String) -> KateParser Token parseExpression mbcontext = do (lang,cont) <- maybe currentContext return mbcontext result <- parseRules (lang,cont) optional $ do eof updateState $ \st -> st{ synStPrevChar = '\n' } pEndLine return result startingState = SyntaxState {synStContexts = [("Elixir","Normal")], synStLineNumber = 0, synStPrevChar = '\n', synStPrevNonspace = False, synStContinuation = False, synStCaseSensitive = True, synStKeywordCaseSensitive = True, synStCaptures = []} pEndLine = do updateState $ \st -> st{ synStPrevNonspace = False } context <- currentContext contexts <- synStContexts `fmap` getState st <- getState if length contexts >= 2 then case context of _ | synStContinuation st -> updateState $ \st -> st{ synStContinuation = False } ("Elixir","Normal") -> return () ("Elixir","Find closing block brace") -> return () ("Elixir","Documentation") -> return () ("Elixir","Triple Quoted String") -> return () ("Elixir","Quoted String") -> return () ("Elixir","Apostrophed String") -> return () ("Elixir","Subst") -> return () ("Elixir","Short Subst") -> (popContext) >> pEndLine ("Elixir","Comment Line") -> (popContext) >> pEndLine ("Elixir","General Comment") -> (popContext) >> pEndLine ("Elixir","regexpr_rules") -> return () ("Elixir","Markdown Code") -> return () _ -> return () else return () withAttribute attr txt = do when (null txt) $ fail "Parser matched no text" updateState $ \st -> st { synStPrevChar = last txt , synStPrevNonspace = synStPrevNonspace st || not (all isSpace txt) } return (attr, txt) list_control'2dflow = Set.fromList $ words $ "catch cond else if raise rescue throw try unless" list_keywords = Set.fromList $ words $ "do end case bc lc for receive exit after quote unquote super and not or when xor in inlist inbits" list_pseudo'2dvariables = Set.fromList $ words $ "nil true false" list_definitions = Set.fromList $ words $ "fn defmodule def defp defprotocol defimpl defrecord defstruct defmacro defmacrop defdelegate defcallback defmacrocallback defexception defoverridable" list_mixin'2dmacros = Set.fromList $ words $ "import require alias use" regex_'23'21'5c'2f'2e'2a = compileRegex True "#!\\/.*" regex_'5cb'5b'5fA'2dZ'5d'2b'5bA'2dZ'5f0'2d9'5d'2b'5cb = compileRegex True "\\b[_A-Z]+[A-Z_0-9]+\\b" regex_'5cb'5bA'2dZ'5d'2b'5f'2a'28'5b0'2d9'5d'7c'5ba'2dz'5d'29'5b'5fa'2dzA'2dZ0'2d9'5d'2a'5cb = compileRegex True "\\b[A-Z]+_*([0-9]|[a-z])[_a-zA-Z0-9]*\\b" regex_'5cb'5c'2d'3f0'5bxX'5d'28'5b0'2d9a'2dfA'2dF'5d'7c'5f'5b0'2d9a'2dfA'2dF'5d'29'2b = compileRegex True "\\b\\-?0[xX]([0-9a-fA-F]|_[0-9a-fA-F])+" regex_'5cb'5c'2d'3f0'5bbB'5d'28'5b01'5d'7c'5f'5b01'5d'29'2b = compileRegex True "\\b\\-?0[bB]([01]|_[01])+" regex_'5cb'5c'2d'3f0'5b1'2d7'5d'28'5b0'2d7'5d'7c'5f'5b0'2d7'5d'29'2a = compileRegex True "\\b\\-?0[1-7]([0-7]|_[0-7])*" regex_'5cb'5c'2d'3f'5b0'2d9'5d'28'5b0'2d9'5d'7c'5f'5b0'2d9'5d'29'2a'5c'2e'5b0'2d9'5d'28'5b0'2d9'5d'7c'5f'5b0'2d9'5d'29'2a'28'5beE'5d'5c'2d'3f'5b1'2d9'5d'28'5b0'2d9'5d'7c'5f'5b0'2d9'5d'29'2a'28'5c'2e'5b0'2d9'5d'2a'29'3f'29'3f = compileRegex True "\\b\\-?[0-9]([0-9]|_[0-9])*\\.[0-9]([0-9]|_[0-9])*([eE]\\-?[1-9]([0-9]|_[0-9])*(\\.[0-9]*)?)?" regex_'5cb'5c'2d'3f'5b1'2d9'5d'28'5b0'2d9'5d'7c'5f'5b0'2d9'5d'29'2a'5cb = compileRegex True "\\b\\-?[1-9]([0-9]|_[0-9])*\\b" regex_'5cs'5b'5c'3f'5c'3a'5c'25'5d'5cs = compileRegex True "\\s[\\?\\:\\%]\\s" regex_'5b'7c'26'3c'3e'5c'5e'5c'2b'2a'7e'5c'2d'3d'2f'5d'2b = compileRegex True "[|&<>\\^\\+*~\\-=/]+" regex_'5cs'21 = compileRegex True "\\s!" regex_'2f'3d'5cs = compileRegex True "/=\\s" regex_'3a'28'40'7b1'2c2'7d'7c'5c'24'29'3f'5ba'2dzA'2dZ'5f'5d'5ba'2dzA'2dZ0'2d9'5f'5d'2a'5b'3d'3f'21'5d'3f = compileRegex True ":(@{1,2}|\\$)?[a-zA-Z_][a-zA-Z0-9_]*[=?!]?" regex_'5cb'28'40'7b1'2c2'7d'7c'5c'24'29'3f'5ba'2dzA'2dZ'5f'5d'5ba'2dzA'2dZ0'2d9'5f'5d'2a'5b'3d'3f'21'5d'3f'3a = compileRegex True "\\b(@{1,2}|\\$)?[a-zA-Z_][a-zA-Z0-9_]*[=?!]?:" regex_'3a'5c'5b'5c'5d'3d'3f = compileRegex True ":\\[\\]=?" regex_'40'28module'29'3fdoc'5cs'2b'22'22'22 = compileRegex True "@(module)?doc\\s+\"\"\"" regex_'40'5ba'2dzA'2dZ'5f0'2d9'5d'2b = compileRegex True "@[a-zA-Z_0-9]+" regex_'5cs'2a'23'2b'5cs'2e'2a'5b'23'5d'3f'24 = compileRegex True "\\s*#+\\s.*[#]?$" regex_'5cs'2a'5b'5c'2a'5c'2b'5c'2d'5d'5cs = compileRegex True "\\s*[\\*\\+\\-]\\s" regex_'5cs'2a'5b'5cd'5d'2b'5c'2e'5cs = compileRegex True "\\s*[\\d]+\\.\\s" regex_'5cs'2a'5c'60'5c'60'5c'60'5cs'2a'24 = compileRegex True "\\s*\\`\\`\\`\\s*$" regex_'5c'5c'5c'22 = compileRegex True "\\\\\\\"" regex_'23'40'7b1'2c2'7d = compileRegex True "#@{1,2}" regex_'5c'5c'5c'27 = compileRegex True "\\\\\\'" regex_'5cw'28'3f'21'5cw'29 = compileRegex True "\\w(?!\\w)" parseRules ("Elixir","Normal") = (((pColumn 0 >> pRegExpr regex_'23'21'5c'2f'2e'2a >>= withAttribute KeywordTok)) <|> ((pKeyword " \n\t.():+,-<=>%&*/;[]^{|}~\\" list_keywords >>= withAttribute KeywordTok)) <|> ((pKeyword " \n\t.():+,-<=>%&*/;[]^{|}~\\" list_control'2dflow >>= withAttribute ControlFlowTok)) <|> ((pKeyword " \n\t.():+,-<=>%&*/;[]^{|}~\\" list_definitions >>= withAttribute KeywordTok)) <|> ((pKeyword " \n\t.():+,-<=>%&*/;[]^{|}~\\" list_pseudo'2dvariables >>= withAttribute ConstantTok)) <|> ((pKeyword " \n\t.():+,-<=>%&*/;[]^{|}~\\" list_mixin'2dmacros >>= withAttribute ImportTok)) <|> ((pRegExpr regex_'5cb'5b'5fA'2dZ'5d'2b'5bA'2dZ'5f0'2d9'5d'2b'5cb >>= withAttribute ConstantTok)) <|> ((pRegExpr regex_'5cb'5bA'2dZ'5d'2b'5f'2a'28'5b0'2d9'5d'7c'5ba'2dz'5d'29'5b'5fa'2dzA'2dZ0'2d9'5d'2a'5cb >>= withAttribute ConstantTok)) <|> ((pRegExpr regex_'5cb'5c'2d'3f0'5bxX'5d'28'5b0'2d9a'2dfA'2dF'5d'7c'5f'5b0'2d9a'2dfA'2dF'5d'29'2b >>= withAttribute BaseNTok)) <|> ((pRegExpr regex_'5cb'5c'2d'3f0'5bbB'5d'28'5b01'5d'7c'5f'5b01'5d'29'2b >>= withAttribute BaseNTok)) <|> ((pRegExpr regex_'5cb'5c'2d'3f0'5b1'2d7'5d'28'5b0'2d7'5d'7c'5f'5b0'2d7'5d'29'2a >>= withAttribute BaseNTok)) <|> ((pRegExpr regex_'5cb'5c'2d'3f'5b0'2d9'5d'28'5b0'2d9'5d'7c'5f'5b0'2d9'5d'29'2a'5c'2e'5b0'2d9'5d'28'5b0'2d9'5d'7c'5f'5b0'2d9'5d'29'2a'28'5beE'5d'5c'2d'3f'5b1'2d9'5d'28'5b0'2d9'5d'7c'5f'5b0'2d9'5d'29'2a'28'5c'2e'5b0'2d9'5d'2a'29'3f'29'3f >>= withAttribute FloatTok)) <|> ((pRegExpr regex_'5cb'5c'2d'3f'5b1'2d9'5d'28'5b0'2d9'5d'7c'5f'5b0'2d9'5d'29'2a'5cb >>= withAttribute DecValTok)) <|> ((pInt >>= withAttribute DecValTok)) <|> ((pHlCChar >>= withAttribute CharTok)) <|> ((pDetectChar False '.' >>= withAttribute OperatorTok)) <|> ((pDetect2Chars False '&' '&' >>= withAttribute OperatorTok)) <|> ((pDetect2Chars False '|' '|' >>= withAttribute OperatorTok)) <|> ((pRegExpr regex_'5cs'5b'5c'3f'5c'3a'5c'25'5d'5cs >>= withAttribute OperatorTok)) <|> ((pRegExpr regex_'5b'7c'26'3c'3e'5c'5e'5c'2b'2a'7e'5c'2d'3d'2f'5d'2b >>= withAttribute OperatorTok)) <|> ((pRegExpr regex_'5cs'21 >>= withAttribute OperatorTok)) <|> ((pRegExpr regex_'2f'3d'5cs >>= withAttribute OperatorTok)) <|> ((pString False "%=" >>= withAttribute OperatorTok)) <|> ((pRegExpr regex_'3a'28'40'7b1'2c2'7d'7c'5c'24'29'3f'5ba'2dzA'2dZ'5f'5d'5ba'2dzA'2dZ0'2d9'5f'5d'2a'5b'3d'3f'21'5d'3f >>= withAttribute VariableTok)) <|> ((pRegExpr regex_'5cb'28'40'7b1'2c2'7d'7c'5c'24'29'3f'5ba'2dzA'2dZ'5f'5d'5ba'2dzA'2dZ0'2d9'5f'5d'2a'5b'3d'3f'21'5d'3f'3a >>= withAttribute VariableTok)) <|> ((pRegExpr regex_'3a'5c'5b'5c'5d'3d'3f >>= withAttribute VariableTok)) <|> ((pRegExpr regex_'40'28module'29'3fdoc'5cs'2b'22'22'22 >>= withAttribute OtherTok) >>~ pushContext ("Elixir","Documentation")) <|> ((pString False "\"\"\"" >>= withAttribute StringTok) >>~ pushContext ("Elixir","Triple Quoted String")) <|> ((pDetectChar False '"' >>= withAttribute StringTok) >>~ pushContext ("Elixir","Quoted String")) <|> ((pDetectChar False '\'' >>= withAttribute VerbatimStringTok) >>~ pushContext ("Elixir","Apostrophed String")) <|> ((pString False "?#" >>= withAttribute NormalTok)) <|> ((pDetectChar False '#' >>= withAttribute CommentTok) >>~ pushContext ("Elixir","General Comment")) <|> ((pDetectChar False '[' >>= withAttribute NormalTok)) <|> ((pDetectChar False ']' >>= withAttribute NormalTok)) <|> ((pRegExpr regex_'40'5ba'2dzA'2dZ'5f0'2d9'5d'2b >>= withAttribute OtherTok)) <|> ((pDetectChar False ')' >>= withAttribute NormalTok)) <|> ((pDetectIdentifier >>= withAttribute NormalTok)) <|> (currentContext >>= \x -> guard (x == ("Elixir","Normal")) >> pDefault >>= withAttribute NormalTok)) parseRules ("Elixir","Find closing block brace") = (((pDetectChar False '}' >>= withAttribute OperatorTok) >>~ (popContext)) <|> ((parseRules ("Elixir","Normal"))) <|> (currentContext >>= \x -> guard (x == ("Elixir","Find closing block brace")) >> pDefault >>= withAttribute NormalTok)) parseRules ("Elixir","Documentation") = (((pString False "\"\"\"" >>= withAttribute OtherTok) >>~ (popContext)) <|> ((pColumn 0 >> pRegExpr regex_'5cs'2a'23'2b'5cs'2e'2a'5b'23'5d'3f'24 >>= withAttribute FunctionTok)) <|> ((pColumn 0 >> pRegExpr regex_'5cs'2a'5b'5c'2a'5c'2b'5c'2d'5d'5cs >>= withAttribute FunctionTok)) <|> ((pColumn 0 >> pRegExpr regex_'5cs'2a'5b'5cd'5d'2b'5c'2e'5cs >>= withAttribute FunctionTok)) <|> ((pColumn 0 >> pRegExpr regex_'5cs'2a'5c'60'5c'60'5c'60'5cs'2a'24 >>= withAttribute FunctionTok) >>~ pushContext ("Elixir","Markdown Code")) <|> ((pDetectSpaces >>= withAttribute CommentTok)) <|> ((Text.Highlighting.Kate.Syntax.Markdown.parseExpression (Just ("Markdown","Normal Text")) >>= ((withAttribute CommentTok) . snd))) <|> (currentContext >>= \x -> guard (x == ("Elixir","Documentation")) >> pDefault >>= withAttribute CommentTok)) parseRules ("Elixir","Triple Quoted String") = (((pString False "\"\"\"" >>= withAttribute StringTok) >>~ (popContext)) <|> (currentContext >>= \x -> guard (x == ("Elixir","Triple Quoted String")) >> pDefault >>= withAttribute StringTok)) parseRules ("Elixir","Quoted String") = (((pString False "\\\\" >>= withAttribute StringTok)) <|> ((pRegExpr regex_'5c'5c'5c'22 >>= withAttribute StringTok)) <|> ((pRegExpr regex_'23'40'7b1'2c2'7d >>= withAttribute OtherTok) >>~ pushContext ("Elixir","Short Subst")) <|> ((pDetect2Chars False '#' '{' >>= withAttribute OtherTok) >>~ pushContext ("Elixir","Subst")) <|> ((pDetectChar False '"' >>= withAttribute StringTok) >>~ (popContext)) <|> (currentContext >>= \x -> guard (x == ("Elixir","Quoted String")) >> pDefault >>= withAttribute StringTok)) parseRules ("Elixir","Apostrophed String") = (((pString False "\\\\" >>= withAttribute StringTok)) <|> ((pRegExpr regex_'5c'5c'5c'27 >>= withAttribute StringTok)) <|> ((pDetectChar False '\'' >>= withAttribute VerbatimStringTok) >>~ (popContext)) <|> (currentContext >>= \x -> guard (x == ("Elixir","Apostrophed String")) >> pDefault >>= withAttribute VerbatimStringTok)) parseRules ("Elixir","Subst") = (((pDetectChar False '}' >>= withAttribute OtherTok) >>~ (popContext)) <|> ((parseRules ("Elixir","Normal"))) <|> (currentContext >>= \x -> guard (x == ("Elixir","Subst")) >> pDefault >>= withAttribute NormalTok)) parseRules ("Elixir","Short Subst") = (((pRegExpr regex_'23'40'7b1'2c2'7d >>= withAttribute OtherTok)) <|> ((pRegExpr regex_'5cw'28'3f'21'5cw'29 >>= withAttribute OtherTok) >>~ (popContext)) <|> (currentContext >>= \x -> guard (x == ("Elixir","Short Subst")) >> pDefault >>= withAttribute OtherTok)) parseRules ("Elixir","Comment Line") = (currentContext >>= \x -> guard (x == ("Elixir","Comment Line")) >> pDefault >>= withAttribute CommentTok) parseRules ("Elixir","General Comment") = (currentContext >>= \x -> guard (x == ("Elixir","General Comment")) >> pDefault >>= withAttribute CommentTok) parseRules ("Elixir","regexpr_rules") = (((pDetect2Chars False '\\' '\\' >>= withAttribute SpecialStringTok)) <|> ((pRegExpr regex_'23'40'7b1'2c2'7d >>= withAttribute OtherTok) >>~ pushContext ("Elixir","Short Subst")) <|> ((pDetect2Chars False '#' '{' >>= withAttribute OtherTok) >>~ pushContext ("Elixir","Subst")) <|> (currentContext >>= \x -> guard (x == ("Elixir","regexpr_rules")) >> pDefault >>= withAttribute SpecialStringTok)) parseRules ("Elixir","Markdown Code") = (((pColumn 0 >> pRegExpr regex_'5cs'2a'5c'60'5c'60'5c'60'5cs'2a'24 >>= withAttribute FunctionTok) >>~ (popContext)) <|> (currentContext >>= \x -> guard (x == ("Elixir","Markdown Code")) >> pDefault >>= withAttribute FunctionTok)) parseRules ("Markdown", _) = Text.Highlighting.Kate.Syntax.Markdown.parseExpression Nothing parseRules x = parseRules ("Elixir","Normal") <|> fail ("Unknown context" ++ show x)