{- This module was generated from data in the Kate syntax highlighting file julia.xml, version 0.2, by -} module Text.Highlighting.Kate.Syntax.Julia (highlight, parseExpression, syntaxName, syntaxExtensions) where import Text.Highlighting.Kate.Types import Text.Highlighting.Kate.Common 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 = "Julia" -- | Filename extensions for this language. syntaxExtensions :: String syntaxExtensions = "*.jl" -- | 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 = [("Julia","_normal")], synStLineNumber = 0, synStPrevChar = '\n', synStPrevNonspace = False, synStCaseSensitive = True, synStKeywordCaseSensitive = True, synStCaptures = []} pEndLine = do updateState $ \st -> st{ synStPrevNonspace = False } context <- currentContext contexts <- synStContexts `fmap` getState if length contexts >= 2 then case context of ("Julia","_normal") -> return () ("Julia","region_marker") -> (popContext) >> pEndLine ("Julia","nested") -> return () ("Julia","squared") -> return () ("Julia","curly") -> return () ("Julia","_adjoint") -> (popContext) >> pEndLine ("Julia","String") -> (popContext) >> pEndLine ("Julia","1-comment") -> (popContext) >> pEndLine _ -> 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_block'5fbegin = Set.fromList $ words $ "begin do for function if let quote try type while" list_block'5feb = Set.fromList $ words $ "catch else elseif" list_block'5fend = Set.fromList $ words $ "end" list_keywords = Set.fromList $ words $ "abstract bitstype break ccall const continue export global import in local macro module return typealias" list_types = Set.fromList $ words $ "AbstractArray AbstractMatrix AbstractVector Any Array ASCIIString Associative Bool ByteString Char Complex Complex64 Complex128 ComplexPair DArray Dict Exception Expr Float Float32 Float64 Function ObjectIdDict Int Int8 Int16 Int32 Int64 Integer IntSet IO IOStream Matrix Nothing None NTuple Number Ptr Range Range1 Ranges Rational Real Regex RegexMatch Set Signed StridedArray StridedMatrix StridedVecOrMat StridedVector String SubArray SubString Symbol Task Tuple Type Uint Uint8 Uint16 Uint32 Uint64 Union Unsigned UTF8String VecOrMat Vector Void WeakRef" regex_'5ba'2dzA'2dZ'5d'5cw'2a'28'3f'3d'27'29 = compileRegex "[a-zA-Z]\\w*(?=')" regex_'28'5cd'2b'28'5c'2e'5cd'2b'29'3f'7c'5c'2e'5cd'2b'29'28'5beE'5d'5b'2b'2d'5d'3f'5cd'2b'29'3f'28im'29'3f'28'3f'3d'27'29 = compileRegex "(\\d+(\\.\\d+)?|\\.\\d+)([eE][+-]?\\d+)?(im)?(?=')" regex_'5b'5c'29'5c'5d'7d'5d'28'3f'3d'27'29 = compileRegex "[\\)\\]}](?=')" regex_'5c'2e'27'28'3f'3d'27'29 = compileRegex "\\.'(?=')" regex_'27'5b'5e'27'5d'2a'28'27'27'5b'5e'27'5d'2a'29'2a'27'28'3f'3d'5b'5e'27'5d'7c'24'29 = compileRegex "'[^']*(''[^']*)*'(?=[^']|$)" regex_'27'5b'5e'27'5d'2a'28'27'27'5b'5e'27'5d'2a'29'2a = compileRegex "'[^']*(''[^']*)*" regex_0x'5b0'2d9a'2dfA'2dF'5d'2b'28im'29'3f = compileRegex "0x[0-9a-fA-F]+(im)?" regex_'28'5cd'2b'28'5c'2e'5cd'2b'29'3f'7c'5c'2e'5cd'2b'29'28'5beE'5d'5b'2b'2d'5d'3f'5cd'2b'29'3f'28im'29'3f = compileRegex "(\\d+(\\.\\d+)?|\\.\\d+)([eE][+-]?\\d+)?(im)?" regex_'27'2b = compileRegex "'+" parseRules ("Julia","_normal") = (((pDetectSpaces >>= withAttribute NormalTok)) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_block'5fbegin >>= withAttribute KeywordTok)) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_block'5feb >>= withAttribute KeywordTok)) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_block'5fend >>= withAttribute KeywordTok)) <|> ((pString False "#BEGIN" >>= withAttribute CommentTok) >>~ pushContext ("Julia","region_marker")) <|> ((pString False "#END" >>= withAttribute CommentTok) >>~ pushContext ("Julia","region_marker")) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_keywords >>= withAttribute KeywordTok)) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_types >>= withAttribute DataTypeTok)) <|> ((pDetectChar False '#' >>= withAttribute CommentTok) >>~ pushContext ("Julia","1-comment")) <|> ((pDetectChar False '"' >>= withAttribute StringTok) >>~ pushContext ("Julia","String")) <|> ((pString False "..." >>= withAttribute NormalTok)) <|> ((pString False "::" >>= withAttribute NormalTok)) <|> ((pString False ">>>" >>= withAttribute NormalTok)) <|> ((pString False ">>" >>= withAttribute NormalTok)) <|> ((pString False "<<" >>= withAttribute NormalTok)) <|> ((pString False "==" >>= withAttribute NormalTok)) <|> ((pString False "!=" >>= withAttribute NormalTok)) <|> ((pString False "<=" >>= withAttribute NormalTok)) <|> ((pString False ">=" >>= withAttribute NormalTok)) <|> ((pString False "&&" >>= withAttribute NormalTok)) <|> ((pString False "||" >>= withAttribute NormalTok)) <|> ((pString False ".*" >>= withAttribute NormalTok)) <|> ((pString False ".^" >>= withAttribute NormalTok)) <|> ((pString False "./" >>= withAttribute NormalTok)) <|> ((pString False ".'" >>= withAttribute NormalTok)) <|> ((pString False "+=" >>= withAttribute NormalTok)) <|> ((pString False "-=" >>= withAttribute NormalTok)) <|> ((pString False "*=" >>= withAttribute NormalTok)) <|> ((pString False "/=" >>= withAttribute NormalTok)) <|> ((pString False "&=" >>= withAttribute NormalTok)) <|> ((pString False "|=" >>= withAttribute NormalTok)) <|> ((pString False "$=" >>= withAttribute NormalTok)) <|> ((pString False ">>>=" >>= withAttribute NormalTok)) <|> ((pString False ">>=" >>= withAttribute NormalTok)) <|> ((pString False "<<=" >>= withAttribute NormalTok)) <|> ((pRegExpr regex_'5ba'2dzA'2dZ'5d'5cw'2a'28'3f'3d'27'29 >>= withAttribute NormalTok) >>~ pushContext ("Julia","_adjoint")) <|> ((pRegExpr regex_'28'5cd'2b'28'5c'2e'5cd'2b'29'3f'7c'5c'2e'5cd'2b'29'28'5beE'5d'5b'2b'2d'5d'3f'5cd'2b'29'3f'28im'29'3f'28'3f'3d'27'29 >>= withAttribute FloatTok) >>~ pushContext ("Julia","_adjoint")) <|> ((pRegExpr regex_'5b'5c'29'5c'5d'7d'5d'28'3f'3d'27'29 >>= withAttribute NormalTok) >>~ pushContext ("Julia","_adjoint")) <|> ((pRegExpr regex_'5c'2e'27'28'3f'3d'27'29 >>= withAttribute NormalTok) >>~ pushContext ("Julia","_adjoint")) <|> ((pRegExpr regex_'27'5b'5e'27'5d'2a'28'27'27'5b'5e'27'5d'2a'29'2a'27'28'3f'3d'5b'5e'27'5d'7c'24'29 >>= withAttribute CharTok)) <|> ((pRegExpr regex_'27'5b'5e'27'5d'2a'28'27'27'5b'5e'27'5d'2a'29'2a >>= withAttribute CharTok)) <|> ((pDetectIdentifier >>= withAttribute NormalTok)) <|> ((pRegExpr regex_0x'5b0'2d9a'2dfA'2dF'5d'2b'28im'29'3f >>= withAttribute BaseNTok)) <|> ((pRegExpr regex_'28'5cd'2b'28'5c'2e'5cd'2b'29'3f'7c'5c'2e'5cd'2b'29'28'5beE'5d'5b'2b'2d'5d'3f'5cd'2b'29'3f'28im'29'3f >>= withAttribute FloatTok)) <|> ((pAnyChar "()[]{}" >>= withAttribute NormalTok)) <|> ((pAnyChar "*+-/\\&|<>~$!^=,;:@" >>= withAttribute NormalTok)) <|> (currentContext >>= \x -> guard (x == ("Julia","_normal")) >> pDefault >>= withAttribute NormalTok)) parseRules ("Julia","region_marker") = (((parseRules ("Julia","1-comment"))) <|> (currentContext >>= \x -> guard (x == ("Julia","region_marker")) >> pDefault >>= withAttribute CommentTok)) parseRules ("Julia","nested") = (((pDetectChar False ')' >>= withAttribute NormalTok) >>~ (popContext)) <|> (currentContext >>= \x -> guard (x == ("Julia","nested")) >> pDefault >>= withAttribute NormalTok)) parseRules ("Julia","squared") = (((pDetectChar False ']' >>= withAttribute NormalTok) >>~ (popContext)) <|> (currentContext >>= \x -> guard (x == ("Julia","squared")) >> pDefault >>= withAttribute NormalTok)) parseRules ("Julia","curly") = (((pDetectChar False '}' >>= withAttribute NormalTok) >>~ (popContext)) <|> (currentContext >>= \x -> guard (x == ("Julia","curly")) >> pDefault >>= withAttribute NormalTok)) parseRules ("Julia","_adjoint") = (((pRegExpr regex_'27'2b >>= withAttribute NormalTok) >>~ (popContext)) <|> (currentContext >>= \x -> guard (x == ("Julia","_adjoint")) >> pDefault >>= withAttribute NormalTok)) parseRules ("Julia","String") = (((pDetectSpaces >>= withAttribute StringTok)) <|> ((pDetectIdentifier >>= withAttribute StringTok)) <|> ((pLineContinue >>= withAttribute StringTok)) <|> ((pHlCStringChar >>= withAttribute NormalTok)) <|> ((pDetectChar False '"' >>= withAttribute StringTok) >>~ (popContext)) <|> (currentContext >>= \x -> guard (x == ("Julia","String")) >> pDefault >>= withAttribute StringTok)) parseRules ("Julia","1-comment") = (((pDetectSpaces >>= withAttribute CommentTok)) <|> ((pDetectIdentifier >>= withAttribute CommentTok)) <|> (currentContext >>= \x -> guard (x == ("Julia","1-comment")) >> pDefault >>= withAttribute CommentTok)) parseRules x = parseRules ("Julia","_normal") <|> fail ("Unknown context" ++ show x)