{- This module was generated from data in the Kate syntax highlighting file asp.xml, version 1.04, by Antonio Salazar (savedfastcool@gmail.com) -} module Text.Highlighting.Kate.Syntax.Asp (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 Data.Maybe (fromMaybe) import qualified Data.Set as Set -- | Full name of language. syntaxName :: String syntaxName = "ASP" -- | Filename extensions for this language. syntaxExtensions :: String syntaxExtensions = "*.asp;" -- | 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 -- | Parse an expression using appropriate local context. parseExpression :: KateParser Token parseExpression = do (lang,cont) <- currentContext result <- parseRules (lang,cont) optional $ do eof updateState $ \st -> st{ synStPrevChar = '\n' } pEndLine return result startingState = SyntaxState {synStContexts = [("ASP","nosource")], synStLineNumber = 0, synStPrevChar = '\n', synStPrevNonspace = False, synStCaseSensitive = True, synStKeywordCaseSensitive = False, synStCaptures = []} pEndLine = do updateState $ \st -> st{ synStPrevNonspace = False } context <- currentContext case context of ("ASP","nosource") -> return () ("ASP","aspsource") -> return () ("ASP","asp_onelinecomment") -> (popContext) >> pEndLine ("ASP","doublequotestring") -> return () ("ASP","singlequotestring") -> return () ("ASP","htmltag") -> return () ("ASP","htmlcomment") -> return () ("ASP","identifiers") -> return () ("ASP","types1") -> return () ("ASP","types2") -> return () ("ASP","scripts") -> return () ("ASP","scripts_onelinecomment") -> (popContext) >> pEndLine ("ASP","twolinecomment") -> return () _ -> 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_structures = Set.fromList $ words $ "select case end select if then else elseif end if while do until loop wend for each to in next exit continue" list_keywords = Set.fromList $ words $ "dim redim preserve const erase nothing set new me function sub call class private public with randomize open close movenext execute eof not true false or and xor" list_functions = Set.fromList $ words $ "response write redirect end request form querystring servervariables cookies session server createobject abs array asc atn cbool cbyte ccur cdate cdbl chr cint clng cos csng cstr date dateadd datediff datepart dateserial datevalue date day exp filter fix formatcurrency formatdatetime formatnumber formatpercent getobject hex hour inputbox instr instrrev int isarray isdate isempty isnull isnumeric isobject join lbound lcase left len loadpicture log ltrim mid minute month monthname msgbox now oct replace rgb right rnd round rtrim scriptengine scriptenginebuildversion scriptenginemajorversion scriptengineminorversion second sgn sin space split sqr strcomp strreverse string tan time timer timeserial timevalue trim typename ubound ucase vartype weekday weekdayname year add addfolders buildpath clear close copy copyfile copyfolder createfolder createtextfile delete deletefile deletefolder driveexists exists fileexists folderexists getabsolutepathname getbasename getdrive getdrivename getextensionname getfile getfilename getfolder getparentfoldername getspecialfolder gettempname items item keys move movefile movefolder openastextstream opentextfile raise read readall readline remove removeall skip skipline write writeblanklines writeline" regex_'3c'5cs'2ascript'5cs'2alanguage'3d'22VBScript'22'5b'5e'3e'5d'2a'3e = compileRegex "<\\s*script\\s*language=\"VBScript\"[^>]*>" regex_'3c'5cs'2ascript'28'5cs'7c'3e'29 = compileRegex "<\\s*script(\\s|>)" regex_'3c'5cs'2a'5c'2f'3f'5cs'2a'5ba'2dzA'2dZ'5f'3a'5d'5ba'2dzA'2dZ0'2d9'2e'5f'3a'2d'5d'2a = compileRegex "<\\s*\\/?\\s*[a-zA-Z_:][a-zA-Z0-9._:-]*" regex_'3c'5cs'2a'5c'2f'5cs'2ascript'5cs'2a'3e = compileRegex "<\\s*\\/\\s*script\\s*>" regex_ = compileRegex "" regex_'5b0123456789'5d'2a'5c'2e'5c'2e'5c'2e'5b0123456789'5d'2a = compileRegex "[0123456789]*\\.\\.\\.[0123456789]*" regex_'5cbelseif'5cb = compileRegex "\\belseif\\b" regex_'5cbelse'5cb = compileRegex "\\belse\\b" regex_'5cbif'5cb = compileRegex "\\bif\\b" regex_'5cbend_if'5cb = compileRegex "\\bend if\\b" regex_'5cbexit_function'5cb = compileRegex "\\bexit function\\b" regex_'5cbfunction'5cb = compileRegex "\\bfunction\\b" regex_'5cbend_function'5cb = compileRegex "\\bend function\\b" regex_'5cbexit_sub'5cb = compileRegex "\\bexit sub\\b" regex_'5cbsub'5cb = compileRegex "\\bsub\\b" regex_'5cbend_sub'5cb = compileRegex "\\bend sub\\b" regex_'5cbclass'5cb = compileRegex "\\bclass\\b" regex_'5cbend_class'5cb = compileRegex "\\bend class\\b" regex_'5cbexit_do'5cb = compileRegex "\\bexit do\\b" regex_'5cbdo'28'5cs'2b'28while'29'29'3f'5cb = compileRegex "\\bdo(\\s+(while))?\\b" regex_'5cbloop'5cb = compileRegex "\\bloop\\b" regex_'5cbexit_while'5cb = compileRegex "\\bexit while\\b" regex_'5cbwhile'5cb = compileRegex "\\bwhile\\b" regex_'5cbwend'5cb = compileRegex "\\bwend\\b" regex_'5cbexit_for'5cb = compileRegex "\\bexit for\\b" regex_'5cbfor'5cb = compileRegex "\\bfor\\b" regex_'5cbnext'5cb = compileRegex "\\bnext\\b" regex_'5cbselect_case'5cb = compileRegex "\\bselect case\\b" regex_'5cbend_select'5cb = compileRegex "\\bend select\\b" regex_'5c'5c'5b0'2d7'5d'7b1'2c3'7d = compileRegex "\\\\[0-7]{1,3}" regex_'5c'5cx'5b0'2d9A'2dFa'2df'5d'7b1'2c2'7d = compileRegex "\\\\x[0-9A-Fa-f]{1,2}" regex_'5cs'2a'3d'5cs'2a = compileRegex "\\s*=\\s*" regex_'5cs'2a'23'3f'5ba'2dzA'2dZ0'2d9'5d'2a = compileRegex "\\s*#?[a-zA-Z0-9]*" defaultAttributes = [(("ASP","nosource"),NormalTok),(("ASP","aspsource"),NormalTok),(("ASP","asp_onelinecomment"),CommentTok),(("ASP","doublequotestring"),StringTok),(("ASP","singlequotestring"),StringTok),(("ASP","htmltag"),OtherTok),(("ASP","htmlcomment"),CommentTok),(("ASP","identifiers"),OtherTok),(("ASP","types1"),DataTypeTok),(("ASP","types2"),DataTypeTok),(("ASP","scripts"),NormalTok),(("ASP","scripts_onelinecomment"),CommentTok),(("ASP","twolinecomment"),CommentTok)] parseRules ("ASP","nosource") = (((pString False "<%" >>= withAttribute KeywordTok) >>~ pushContext ("ASP","aspsource")) <|> ((pRegExpr regex_'3c'5cs'2ascript'5cs'2alanguage'3d'22VBScript'22'5b'5e'3e'5d'2a'3e >>= withAttribute KeywordTok) >>~ pushContext ("ASP","aspsource")) <|> ((pRegExpr regex_'3c'5cs'2ascript'28'5cs'7c'3e'29 >>= withAttribute KeywordTok) >>~ pushContext ("ASP","scripts")) <|> ((pRegExpr regex_'3c'5cs'2a'5c'2f'3f'5cs'2a'5ba'2dzA'2dZ'5f'3a'5d'5ba'2dzA'2dZ0'2d9'2e'5f'3a'2d'5d'2a >>= withAttribute KeywordTok) >>~ pushContext ("ASP","htmltag")) <|> ((pString False "" >>= withAttribute CommentTok) >>~ (popContext)) <|> ((pRegExpr regex_'5cs'2a'3d'5cs'2a >>= withAttribute NormalTok) >>~ pushContext ("ASP","identifiers")) <|> (currentContext >>= \x -> guard (x == ("ASP","htmlcomment")) >> pDefault >>= withAttribute (fromMaybe NormalTok $ lookup ("ASP","htmlcomment") defaultAttributes))) parseRules ("ASP","identifiers") = (((pRegExpr regex_'5cs'2a'23'3f'5ba'2dzA'2dZ0'2d9'5d'2a >>= withAttribute StringTok) >>~ (popContext)) <|> ((pDetectChar False '\'' >>= withAttribute DataTypeTok) >>~ pushContext ("ASP","types1")) <|> ((pDetectChar False '"' >>= withAttribute DataTypeTok) >>~ pushContext ("ASP","types2")) <|> (currentContext >>= \x -> guard (x == ("ASP","identifiers")) >> pDefault >>= withAttribute (fromMaybe NormalTok $ lookup ("ASP","identifiers") defaultAttributes))) parseRules ("ASP","types1") = (((pString False "<%" >>= withAttribute KeywordTok) >>~ pushContext ("ASP","aspsource")) <|> ((pString False "<%" >>= withAttribute KeywordTok) >>~ pushContext ("ASP","aspsource")) <|> ((pDetectChar False '\'' >>= withAttribute DataTypeTok) >>~ (popContext >> popContext)) <|> (currentContext >>= \x -> guard (x == ("ASP","types1")) >> pDefault >>= withAttribute (fromMaybe NormalTok $ lookup ("ASP","types1") defaultAttributes))) parseRules ("ASP","types2") = (((pString False "<%" >>= withAttribute KeywordTok) >>~ pushContext ("ASP","aspsource")) <|> ((pString False "<%" >>= withAttribute KeywordTok) >>~ pushContext ("ASP","aspsource")) <|> ((pDetectChar False '"' >>= withAttribute DataTypeTok) >>~ (popContext >> popContext)) <|> (currentContext >>= \x -> guard (x == ("ASP","types2")) >> pDefault >>= withAttribute (fromMaybe NormalTok $ lookup ("ASP","types2") defaultAttributes))) parseRules ("ASP","scripts") = (((pDetect2Chars False '/' '/' >>= withAttribute CommentTok) >>~ pushContext ("ASP","scripts_onelinecomment")) <|> ((pDetect2Chars False '/' '*' >>= withAttribute CommentTok) >>~ pushContext ("ASP","twolinecomment")) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_control_structures >>= withAttribute KeywordTok)) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_keywords >>= withAttribute KeywordTok)) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_functions >>= withAttribute KeywordTok)) <|> ((pString False "<%" >>= withAttribute KeywordTok) >>~ pushContext ("ASP","aspsource")) <|> ((pRegExpr regex_'3c'5cs'2a'5c'2f'5cs'2ascript'5cs'2a'3e >>= withAttribute KeywordTok) >>~ (popContext)) <|> ((pDetectChar False '"' >>= withAttribute StringTok) >>~ pushContext ("ASP","doublequotestring")) <|> ((pDetectChar False '\'' >>= withAttribute StringTok) >>~ pushContext ("ASP","singlequotestring")) <|> ((pHlCOct >>= withAttribute BaseNTok)) <|> ((pHlCHex >>= withAttribute BaseNTok)) <|> ((pFloat >>= withAttribute FloatTok)) <|> ((pInt >>= withAttribute DecValTok)) <|> ((pDetectChar False '{' >>= withAttribute NormalTok)) <|> ((pDetectChar False '}' >>= withAttribute NormalTok)) <|> ((pAnyChar ";()}{:,[]" >>= withAttribute OtherTok)) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" Set.empty >>= withAttribute OtherTok)) <|> (currentContext >>= \x -> guard (x == ("ASP","scripts")) >> pDefault >>= withAttribute (fromMaybe NormalTok $ lookup ("ASP","scripts") defaultAttributes))) parseRules ("ASP","scripts_onelinecomment") = (((pRegExpr regex_'3c'5cs'2a'5c'2f'5cs'2ascript'5cs'2a'3e >>= withAttribute KeywordTok) >>~ (popContext >> popContext)) <|> (currentContext >>= \x -> guard (x == ("ASP","scripts_onelinecomment")) >> pDefault >>= withAttribute (fromMaybe NormalTok $ lookup ("ASP","scripts_onelinecomment") defaultAttributes))) parseRules ("ASP","twolinecomment") = (((pDetect2Chars False '*' '/' >>= withAttribute CommentTok) >>~ (popContext)) <|> (currentContext >>= \x -> guard (x == ("ASP","twolinecomment")) >> pDefault >>= withAttribute (fromMaybe NormalTok $ lookup ("ASP","twolinecomment") defaultAttributes))) parseRules x = parseRules ("ASP","nosource") <|> fail ("Unknown context" ++ show x)