{- This module was generated from data in the Kate syntax highlighting file noweb.xml, version 1.0, by Scott Collins (scc@scottcollins.net) -} module Text.Highlighting.Kate.Syntax.Noweb ( highlight, parseExpression, syntaxName, syntaxExtensions ) where import Text.Highlighting.Kate.Definitions import Text.Highlighting.Kate.Common import qualified Text.Highlighting.Kate.Syntax.Html import qualified Text.Highlighting.Kate.Syntax.Cpp import Text.ParserCombinators.Parsec import Control.Monad (when) import Data.Map (fromList) import Data.Maybe (fromMaybe, maybeToList) -- | Full name of language. syntaxName :: String syntaxName = "noweb" -- | Filename extensions for this language. syntaxExtensions :: String syntaxExtensions = "*.w;*.nw" -- | 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 = "noweb" } context <- currentContext <|> (pushContext "RawDocumentation" >> 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 [("noweb",["RawDocumentation"])], synStLanguage = "noweb", synStCurrentLine = "", synStCharsParsedInLine = 0, synStPrevChar = '\n', synStCaseSensitive = True, synStKeywordCaseSensitive = True, synStCaptures = []} parseSourceLine = manyTill parseExpressionInternal pEndLine pEndLine = do lookAhead $ newline <|> (eof >> return '\n') context <- currentContext case context of "RawDocumentation" -> return () >> pHandleEndLine "CodeQuote" -> return () >> pHandleEndLine "CodeSection" -> return () >> pHandleEndLine "SectionNames" -> return () >> pHandleEndLine _ -> pHandleEndLine withAttribute attr txt = do when (null txt) $ fail "Parser matched no text" let labs = attr : maybeToList (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 (labs, txt) styles = [("Punctuation","re"),("SectionName","re")] parseExpressionInternal = do context <- currentContext parseRules context <|> (pDefault >>= withAttribute (fromMaybe "" $ lookup context defaultAttributes)) regex_'3c'3c'2e'2a'3e'3e'3d'24 = compileRegex "<<.*>>=$" regex_'5c'5d'5c'5d'28'3f'21'5c'5d'29 = compileRegex "\\]\\](?!\\])" regex_'40'24 = compileRegex "@$" regex_'40'28'3f'3d'5b'5cs'25'5d'29 = compileRegex "@(?=[\\s%])" regex_'40'3c'3c = compileRegex "@<<" regex_'3c'3c'2e'2a'5b'5e'40'5d'3e'3e'28'3f'21'3d'29 = compileRegex "<<.*[^@]>>(?!=)" defaultAttributes = [("RawDocumentation","Prose"),("CodeQuote","Code"),("CodeSection","Code"),("SectionNames","Prose")] parseRules "RawDocumentation" = do (attr, result) <- (((pColumn 0 >> pRegExpr regex_'3c'3c'2e'2a'3e'3e'3d'24 >>= withAttribute "SectionName") >>~ pushContext "CodeSection") <|> ((pDetect2Chars False '@' '[' >>= withAttribute "Prose")) <|> ((pDetect2Chars False '[' '[' >>= withAttribute "Punctuation") >>~ pushContext "CodeQuote") <|> ((Text.Highlighting.Kate.Syntax.Html.parseExpression))) return (attr, result) parseRules "CodeQuote" = do (attr, result) <- (((pDetect2Chars False '@' ']' >>= withAttribute "Code")) <|> ((pRegExpr regex_'5c'5d'5c'5d'28'3f'21'5c'5d'29 >>= withAttribute "Punctuation") >>~ (popContext)) <|> ((parseRules "SectionNames")) <|> ((Text.Highlighting.Kate.Syntax.Cpp.parseExpression))) return (attr, result) parseRules "CodeSection" = do (attr, result) <- (((pColumn 0 >> pRegExpr regex_'40'24 >>= withAttribute "Punctuation") >>~ pushContext "RawDocumentation") <|> ((pColumn 0 >> pRegExpr regex_'40'28'3f'3d'5b'5cs'25'5d'29 >>= withAttribute "Punctuation") >>~ pushContext "RawDocumentation") <|> ((pColumn 0 >> lookAhead (pRegExpr regex_'3c'3c'2e'2a'3e'3e'3d'24) >> return ([],"") ) >>~ pushContext "RawDocumentation") <|> ((parseRules "SectionNames")) <|> ((Text.Highlighting.Kate.Syntax.Cpp.parseExpression))) return (attr, result) parseRules "SectionNames" = do (attr, result) <- (((pRegExpr regex_'40'3c'3c >>= withAttribute "Prose")) <|> ((pRegExpr regex_'3c'3c'2e'2a'5b'5e'40'5d'3e'3e'28'3f'21'3d'29 >>= withAttribute "SectionName"))) return (attr, result) parseRules x = fail $ "Unknown context" ++ x