{- This module was generated from data in the Kate syntax highlighting file asp.xml, version 1.03, by Antonio Salazar (savedfastcool@gmail.com) -} module Text.Highlighting.Kate.Syntax.Asp ( 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) -- | 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 -> 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 = "ASP" } context <- currentContext <|> (pushContext "nosource" >> 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 [("ASP",["nosource"])], synStLanguage = "ASP", 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 "nosource" -> return () "aspsource" -> return () "asp_onelinecomment" -> (popContext >> return ()) "doublequotestring" -> return () "singlequotestring" -> return () "htmltag" -> return () "htmlcomment" -> return () "identifiers" -> return () "types1" -> return () "types2" -> return () "scripts" -> return () "scripts_onelinecomment" -> (popContext >> return ()) "twolinecomment" -> 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"),("ASP Text","Normal"),("Keyword","Keyword"),("Function","Keyword"),("Decimal","DecVal"),("Octal","BaseN"),("Hex","BaseN"),("Float","Float"),("String","String"),("Comment","Comment"),("Variable","Keyword"),("Control Structures","Keyword"),("Escape Code","Keyword"),("Other","Others"),("HTML Tag","Keyword"),("HTML Comment","Comment"),("Identifier","Others"),("Types","DataType")] parseExpressionInternal = do context <- currentContext parseRules context <|> (pDefault >>= withAttribute (fromMaybe "" $ lookup context defaultAttributes)) list7e571cf5b90c4461e9e29c05d83b378d7e20b6e8 = 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" list417287ae6697bddbefccd4578fa0e44bbbe53dbb = 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" list404afa5c70ae5bb86b5d535d31057f8fbbe1ae45 = 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" defaultAttributes = [("nosource","Normal Text"),("aspsource","ASP Text"),("asp_onelinecomment","Comment"),("doublequotestring","String"),("singlequotestring","String"),("htmltag","Identifier"),("htmlcomment","HTML Comment"),("identifiers","Identifier"),("types1","Types"),("types2","Types"),("scripts","Normal Text"),("scripts_onelinecomment","Comment"),("twolinecomment","Comment")] parseRules "nosource" = do (attr, result) <- (((pString False "<%" >>= withAttribute "Keyword") >>~ pushContext "aspsource") <|> ((pRegExpr (compileRegex "<\\s*script\\s*language=\"VBScript\"[^>]*>") >>= withAttribute "HTML Tag") >>~ pushContext "aspsource") <|> ((pRegExpr (compileRegex "<\\s*script(\\s|>)") >>= withAttribute "HTML Tag") >>~ pushContext "scripts") <|> ((pRegExpr (compileRegex "<\\s*\\/?\\s*[a-zA-Z_:][a-zA-Z0-9._:-]*") >>= withAttribute "HTML Tag") >>~ pushContext "htmltag") <|> ((pString False "" >>= withAttribute "HTML Comment") >>~ (popContext >> return ())) <|> ((pRegExpr (compileRegex "\\s*=\\s*") >>= withAttribute "Normal Text") >>~ pushContext "identifiers")) return (attr, result) parseRules "identifiers" = do (attr, result) <- (((pRegExpr (compileRegex "\\s*#?[a-zA-Z0-9]*") >>= withAttribute "String") >>~ (popContext >> return ())) <|> ((pDetectChar False '\'' >>= withAttribute "Types") >>~ pushContext "types1") <|> ((pDetectChar False '"' >>= withAttribute "Types") >>~ pushContext "types2")) return (attr, result) parseRules "types1" = do (attr, result) <- (((pString False "<%" >>= withAttribute "Keyword") >>~ pushContext "aspsource") <|> ((pString False "<%" >>= withAttribute "Keyword") >>~ pushContext "aspsource") <|> ((pDetectChar False '\'' >>= withAttribute "Types") >>~ (popContext >> popContext >> return ()))) return (attr, result) parseRules "types2" = do (attr, result) <- (((pString False "<%" >>= withAttribute "Keyword") >>~ pushContext "aspsource") <|> ((pString False "<%" >>= withAttribute "Keyword") >>~ pushContext "aspsource") <|> ((pDetectChar False '"' >>= withAttribute "Types") >>~ (popContext >> popContext >> return ()))) return (attr, result) parseRules "scripts" = do (attr, result) <- (((pDetect2Chars False '/' '/' >>= withAttribute "Comment") >>~ pushContext "scripts_onelinecomment") <|> ((pDetect2Chars False '/' '*' >>= withAttribute "Comment") >>~ pushContext "twolinecomment") <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list7e571cf5b90c4461e9e29c05d83b378d7e20b6e8 >>= withAttribute "Control Structures")) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list417287ae6697bddbefccd4578fa0e44bbbe53dbb >>= withAttribute "Keyword")) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list404afa5c70ae5bb86b5d535d31057f8fbbe1ae45 >>= withAttribute "Function")) <|> ((pString False "<%" >>= withAttribute "Keyword") >>~ pushContext "aspsource") <|> ((pRegExpr (compileRegex "<\\s*\\/\\s*script\\s*>") >>= withAttribute "HTML Tag") >>~ (popContext >> return ())) <|> ((pDetectChar False '"' >>= withAttribute "String") >>~ pushContext "doublequotestring") <|> ((pDetectChar False '\'' >>= withAttribute "String") >>~ pushContext "singlequotestring") <|> ((pHlCOct >>= withAttribute "Octal")) <|> ((pHlCHex >>= withAttribute "Hex")) <|> ((pFloat >>= withAttribute "Float")) <|> ((pInt >>= withAttribute "Decimal")) <|> ((pDetectChar False '{' >>= withAttribute "Normal Text")) <|> ((pDetectChar False '}' >>= withAttribute "Normal Text")) <|> ((pAnyChar ";()}{:,[]" >>= withAttribute "Other")) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" Set.empty >>= withAttribute "Other"))) return (attr, result) parseRules "scripts_onelinecomment" = do (attr, result) <- ((pRegExpr (compileRegex "<\\s*\\/\\s*script\\s*>") >>= withAttribute "HTML Tag") >>~ (popContext >> popContext >> return ())) return (attr, result) parseRules "twolinecomment" = do (attr, result) <- ((pDetect2Chars False '*' '/' >>= withAttribute "Comment") >>~ (popContext >> return ())) return (attr, result) parseRules x = fail $ "Unknown context" ++ x