{- This module was generated from data in the Kate syntax highlighting file roff.xml, version 0.11, by Matthew Woehlke (mw_triad@users.sourceforge.net) -} module Text.Highlighting.Kate.Syntax.Roff (highlight, parseExpression, syntaxName, syntaxExtensions) where import Text.Highlighting.Kate.Types import Text.Highlighting.Kate.Common import qualified Text.Highlighting.Kate.Syntax.Alert 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 = "Roff" -- | Filename extensions for this language. syntaxExtensions :: String syntaxExtensions = "" -- | 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 = [("Roff","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 ("Roff","Normal") -> return () ("Roff","DetectComments") -> return () ("Roff","DetectOthers") -> return () ("Roff","DetectEscape") -> (popContext) >> pEndLine ("Roff","DetectDirective") -> (popContext) >> pEndLine ("Roff","Comment") -> (popContext) >> pEndLine ("Roff","Error") -> return () ("Roff","Directive") -> (popContext) >> pEndLine ("Roff","String") -> (popContext) >> pEndLine ("Roff","LiteralSL") -> (popContext) >> pEndLine ("Roff","LiteralIL") -> pushContext ("Roff","Error") >> return () ("Roff","Argument") -> pushContext ("Roff","Error") >> return () ("Roff","GlyphArgument") -> pushContext ("Roff","Error") >> return () ("Roff","Measurement") -> pushContext ("Roff","Error") >> return () ("Roff","deDirective") -> pushContext ("Roff","deBody") >> return () ("Roff","deBody") -> return () ("Roff","diDirective") -> pushContext ("Roff","diBody") >> return () ("Roff","diBody") -> return () ("Roff","daDirective") -> pushContext ("Roff","daBody") >> return () ("Roff","daBody") -> return () ("Roff","dsDirective") -> (popContext) >> pEndLine ("Roff","dsString") -> (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_layout = Set.fromList $ words $ "br sp" list_formatting = Set.fromList $ words $ "" list_gnuext = Set.fromList $ words $ "" regex_'5c'2e'5cs'2a'5c'5c'22 = compileRegex "\\.\\s*\\\\\"" regex_'5c'5c'28'5c'2a'7cn'5b'2b'2d'5d'3f'29'28'5b'5e'5d'5cs'5d'7c'5c'28'5b'5e'5d'5cs'5d'7b2'7d'7c'5c'5b'5b'5e'5d'5cs'5d'2b'5c'5d'29 = compileRegex "\\\\(\\*|n[+-]?)([^]\\s]|\\([^]\\s]{2}|\\[[^]\\s]+\\])" regex_'5c'5c'5bfF'5d'28'5b'5e'5d'5cs'5d'7c'5c'28'5b'5e'5d'5cs'5d'7b2'7d'7c'5c'5b'5b'5e'5d'5cs'5d'2b'5c'5d'29 = compileRegex "\\\\[fF]([^]\\s]|\\([^]\\s]{2}|\\[[^]\\s]+\\])" regex_'5c'5cf'28'5b0'2d9'5d'7c'5c'28'5b0'2d9'5d'5b0'2d9'5d'7c'5c'5b'5b0'2d9'5d'2b'5c'5d'29 = compileRegex "\\\\f([0-9]|\\([0-9][0-9]|\\[[0-9]+\\])" regex_'5c'5cs'28'5c'5b'28'5b1'2d3'5d'5b0'2d9'5d'7c'5b04'2d9'5d'29'5c'5d'7c'5b04'2d9'5d'7c'5b'2b'2d'5d'5b0'2d9'5d'7c'28'5b'2b'2d'5d'3f'5c'28'7c'5c'28'5b'2b'2d'5d'29'5b0'2d9'5d'5b0'2d9'5d'29 = compileRegex "\\\\s(\\[([1-3][0-9]|[04-9])\\]|[04-9]|[+-][0-9]|([+-]?\\(|\\([+-])[0-9][0-9])" regex_'5c'5c'28'5c'24'5b0'2d9'2a'40'5d'7c'5b'2e'3a'25_'7c'5e'7b'7d'5f'21'3f'40'29'2f'2c'26'3a'7e0acdeEprtu'5d'29 = compileRegex "\\\\(\\$[0-9*@]|[.:% |^{}_!?@)/,&:~0acdeEprtu])" regex_'5c'5c'5bAbBDowXZ'5d'28'5b'5e'5c'5c'5d'7c'5c'5c'5b'25_'7c'5e'7b'7d'27'60'2d'5f'21'3f'40'29'2f'2c'26'3a'7e0acdeEprtu'5d'29 = compileRegex "\\\\[AbBDowXZ]([^\\\\]|\\\\[% |^{}'`-_!?@)/,&:~0acdeEprtu])" regex_'5c'5c'5bgkmMVYz'5d'28'5b'5e'5d'5cs'5d'7c'5c'28'5b'5e'5d'5cs'5d'7b2'7d'7c'5c'5b'5b'5e'5d'5cs'5d'2b'5c'5d'29 = compileRegex "\\\\[gkmMVYz]([^]\\s]|\\([^]\\s]{2}|\\[[^]\\s]+\\])" regex_'5c'5cO'28'5b0'2d4'5d'7c'5c'5b5'5blrci'5d'5b'5e'5d'5d'5c'5d'29 = compileRegex "\\\\O([0-4]|\\[5[lrci][^]]\\])" regex_'5c'5c'5bhHSvx'5d'28'5b'5e'5c'5c'5d'7c'5c'5c'5b'25_'7c'5e'7b'7d'27'60'2d'5f'21'3f'40'29'2f'2c'26'3a'7e0acdeEprtu'5d'29 = compileRegex "\\\\[hHSvx]([^\\\\]|\\\\[% |^{}'`-_!?@)/,&:~0acdeEprtu])" regex_'5c'5c'5blL'5d'28'5b'5e'5c'5c'5d'7c'5c'5c'5b'25_'7c'5e'7b'7d'27'60'2d'5f'21'3f'40'29'2f'2c'26'3a'7e0acdeEprtu'5d'29'7c'3f = compileRegex "\\\\[lL]([^\\\\]|\\\\[% |^{}'`-_!?@)/,&:~0acdeEprtu])|?" regex_'5c'5cR'28'5b'5e'5c'5c'5d'7c'5c'5c'5b'25_'7c'5e'7b'7d'27'60'2d'5f'21'3f'40'29'2f'2c'26'3a'7e0acdeEprtu'5d'29 = compileRegex "\\\\R([^\\\\]|\\\\[% |^{}'`-_!?@)/,&:~0acdeEprtu])" regex_'5c'5cC'28'5b'5e'5c'5c'5d'7c'5c'5c'5b'25_'7c'5e'7b'7d'27'60'2d'5f'21'3f'40'29'2f'2c'26'3a'7e0acdeEprtu'5d'29 = compileRegex "\\\\C([^\\\\]|\\\\[% |^{}'`-_!?@)/,&:~0acdeEprtu])" regex_'5c'5cN'28'5b'5e'5c'5c0'2d9'5d'7c'5c'5c'5b'25'3a'7b'7d'27'60'2d'5f'21'40'2fcep'5d'29'5b0'2d9'5d'2b'5c1 = compileRegex "\\\\N([^\\\\0-9]|\\\\[%:{}'`-_!@/cep])[0-9]+\\1" regex_'5c'5c'28'5b'5e'5d'5cs'5d'7c'5c'28'5b'5e'5d'5cs'5d'7b2'7d'7c'5c'5b'5b'5e'5d'5cs'5d'2b'5c'5d'29 = compileRegex "\\\\([^]\\s]|\\([^]\\s]{2}|\\[[^]\\s]+\\])" regex_'5c'5c'24 = compileRegex "\\\\$" regex_'5cs'2ads'5cb = compileRegex "\\s*ds\\b" regex_'5cs'2ade'5cb = compileRegex "\\s*de\\b" regex_'5cs'2ada'28'3f'3d'5cs'2b'5bA'2dZa'2dz'5d'2b'29 = compileRegex "\\s*da(?=\\s+[A-Za-z]+)" regex_'5cs'2adi'28'3f'3d'5cs'2b'5bA'2dZa'2dz'5d'2b'29 = compileRegex "\\s*di(?=\\s+[A-Za-z]+)" regex_'5cs'2a'5bA'2dZa'2dz'5d'2b'5cb = compileRegex "\\s*[A-Za-z]+\\b" regex_'5c'2e'5cs'2adi'5cb = compileRegex "\\.\\s*di\\b" regex_'5c'2e'5cs'2ada'5cb = compileRegex "\\.\\s*da\\b" parseRules ("Roff","Normal") = (((parseRules ("Roff","DetectComments"))) <|> ((pColumn 0 >> pDetectChar False '.' >>= withAttribute FunctionTok) >>~ pushContext ("Roff","DetectDirective")) <|> ((parseRules ("Roff","DetectOthers"))) <|> (currentContext >>= \x -> guard (x == ("Roff","Normal")) >> pDefault >>= withAttribute NormalTok)) parseRules ("Roff","DetectComments") = (((pColumn 0 >> pRegExpr regex_'5c'2e'5cs'2a'5c'5c'22 >>= withAttribute CommentTok) >>~ pushContext ("Roff","Comment")) <|> ((pDetect2Chars False '\\' '"' >>= withAttribute CommentTok) >>~ pushContext ("Roff","Comment")) <|> ((pDetect2Chars False '\\' '#' >>= withAttribute CommentTok) >>~ pushContext ("Roff","Comment")) <|> (currentContext >>= \x -> guard (x == ("Roff","DetectComments")) >> pDefault >>= withAttribute NormalTok)) parseRules ("Roff","DetectOthers") = (((parseRules ("Roff","DetectComments"))) <|> ((lookAhead (pDetectChar False '\\') >> pushContext ("Roff","DetectEscape") >> currentContext >>= parseRules)) <|> ((pDetectChar False '"' >>= withAttribute StringTok) >>~ pushContext ("Roff","String")) <|> (currentContext >>= \x -> guard (x == ("Roff","DetectOthers")) >> pDefault >>= withAttribute NormalTok)) parseRules ("Roff","DetectEscape") = (((pRegExpr regex_'5c'5c'28'5c'2a'7cn'5b'2b'2d'5d'3f'29'28'5b'5e'5d'5cs'5d'7c'5c'28'5b'5e'5d'5cs'5d'7b2'7d'7c'5c'5b'5b'5e'5d'5cs'5d'2b'5c'5d'29 >>= withAttribute OtherTok) >>~ (popContext)) <|> ((pRegExpr regex_'5c'5c'5bfF'5d'28'5b'5e'5d'5cs'5d'7c'5c'28'5b'5e'5d'5cs'5d'7b2'7d'7c'5c'5b'5b'5e'5d'5cs'5d'2b'5c'5d'29 >>= withAttribute OtherTok) >>~ (popContext)) <|> ((pRegExpr regex_'5c'5cf'28'5b0'2d9'5d'7c'5c'28'5b0'2d9'5d'5b0'2d9'5d'7c'5c'5b'5b0'2d9'5d'2b'5c'5d'29 >>= withAttribute OtherTok) >>~ (popContext)) <|> ((pRegExpr regex_'5c'5cs'28'5c'5b'28'5b1'2d3'5d'5b0'2d9'5d'7c'5b04'2d9'5d'29'5c'5d'7c'5b04'2d9'5d'7c'5b'2b'2d'5d'5b0'2d9'5d'7c'28'5b'2b'2d'5d'3f'5c'28'7c'5c'28'5b'2b'2d'5d'29'5b0'2d9'5d'5b0'2d9'5d'29 >>= withAttribute OtherTok) >>~ (popContext)) <|> ((pDetect2Chars False '\\' '\\' >>= withAttribute CharTok) >>~ (popContext)) <|> ((pRegExpr regex_'5c'5c'28'5c'24'5b0'2d9'2a'40'5d'7c'5b'2e'3a'25_'7c'5e'7b'7d'5f'21'3f'40'29'2f'2c'26'3a'7e0acdeEprtu'5d'29 >>= withAttribute CharTok) >>~ (popContext)) <|> ((pRegExpr regex_'5c'5c'5bAbBDowXZ'5d'28'5b'5e'5c'5c'5d'7c'5c'5c'5b'25_'7c'5e'7b'7d'27'60'2d'5f'21'3f'40'29'2f'2c'26'3a'7e0acdeEprtu'5d'29 >>= withAttribute CharTok) >>~ pushContext ("Roff","Argument")) <|> ((pRegExpr regex_'5c'5c'5bgkmMVYz'5d'28'5b'5e'5d'5cs'5d'7c'5c'28'5b'5e'5d'5cs'5d'7b2'7d'7c'5c'5b'5b'5e'5d'5cs'5d'2b'5c'5d'29 >>= withAttribute CharTok) >>~ (popContext)) <|> ((pRegExpr regex_'5c'5cO'28'5b0'2d4'5d'7c'5c'5b5'5blrci'5d'5b'5e'5d'5d'5c'5d'29 >>= withAttribute CharTok) >>~ (popContext)) <|> ((pRegExpr regex_'5c'5c'5bhHSvx'5d'28'5b'5e'5c'5c'5d'7c'5c'5c'5b'25_'7c'5e'7b'7d'27'60'2d'5f'21'3f'40'29'2f'2c'26'3a'7e0acdeEprtu'5d'29 >>= withAttribute CharTok) >>~ pushContext ("Roff","Measurement")) <|> ((pRegExpr regex_'5c'5c'5blL'5d'28'5b'5e'5c'5c'5d'7c'5c'5c'5b'25_'7c'5e'7b'7d'27'60'2d'5f'21'3f'40'29'2f'2c'26'3a'7e0acdeEprtu'5d'29'7c'3f >>= withAttribute CharTok) >>~ pushContext ("Roff","Measurement")) <|> ((pRegExpr regex_'5c'5cR'28'5b'5e'5c'5c'5d'7c'5c'5c'5b'25_'7c'5e'7b'7d'27'60'2d'5f'21'3f'40'29'2f'2c'26'3a'7e0acdeEprtu'5d'29 >>= withAttribute CharTok) >>~ pushContext ("Roff","Argument")) <|> ((pRegExpr regex_'5c'5cC'28'5b'5e'5c'5c'5d'7c'5c'5c'5b'25_'7c'5e'7b'7d'27'60'2d'5f'21'3f'40'29'2f'2c'26'3a'7e0acdeEprtu'5d'29 >>= withAttribute OtherTok) >>~ pushContext ("Roff","GlyphArgument")) <|> ((pRegExpr regex_'5c'5cN'28'5b'5e'5c'5c0'2d9'5d'7c'5c'5c'5b'25'3a'7b'7d'27'60'2d'5f'21'40'2fcep'5d'29'5b0'2d9'5d'2b'5c1 >>= withAttribute OtherTok) >>~ (popContext)) <|> ((pRegExpr regex_'5c'5c'28'5b'5e'5d'5cs'5d'7c'5c'28'5b'5e'5d'5cs'5d'7b2'7d'7c'5c'5b'5b'5e'5d'5cs'5d'2b'5c'5d'29 >>= withAttribute OtherTok) >>~ (popContext)) <|> ((pRegExpr regex_'5c'5c'24 >>= withAttribute CharTok) >>~ (popContext)) <|> ((pDetectChar False '\\' >>= withAttribute ErrorTok) >>~ (popContext)) <|> (currentContext >>= \x -> guard (x == ("Roff","DetectEscape")) >> pDefault >>= withAttribute ErrorTok)) parseRules ("Roff","DetectDirective") = (((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_layout >>= withAttribute KeywordTok) >>~ pushContext ("Roff","Directive")) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_formatting >>= withAttribute KeywordTok) >>~ pushContext ("Roff","Directive")) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_gnuext >>= withAttribute DataTypeTok) >>~ pushContext ("Roff","Directive")) <|> ((pColumn 1 >> pRegExpr regex_'5cs'2ads'5cb >>= withAttribute FunctionTok) >>~ pushContext ("Roff","dsDirective")) <|> ((pColumn 1 >> pRegExpr regex_'5cs'2ade'5cb >>= withAttribute FunctionTok) >>~ pushContext ("Roff","deDirective")) <|> ((pColumn 1 >> pRegExpr regex_'5cs'2ada'28'3f'3d'5cs'2b'5bA'2dZa'2dz'5d'2b'29 >>= withAttribute FunctionTok) >>~ pushContext ("Roff","daDirective")) <|> ((pColumn 1 >> pRegExpr regex_'5cs'2adi'28'3f'3d'5cs'2b'5bA'2dZa'2dz'5d'2b'29 >>= withAttribute FunctionTok) >>~ pushContext ("Roff","diDirective")) <|> ((pColumn 1 >> pRegExpr regex_'5cs'2a'5bA'2dZa'2dz'5d'2b'5cb >>= withAttribute FunctionTok) >>~ pushContext ("Roff","Directive")) <|> (currentContext >>= \x -> guard (x == ("Roff","DetectDirective")) >> pDefault >>= withAttribute FunctionTok)) parseRules ("Roff","Comment") = (((Text.Highlighting.Kate.Syntax.Alert.parseExpression (Just ("Alerts","")) >>= ((withAttribute CommentTok) . snd))) <|> (currentContext >>= \x -> guard (x == ("Roff","Comment")) >> pDefault >>= withAttribute CommentTok)) parseRules ("Roff","Error") = (currentContext >>= \x -> guard (x == ("Roff","Error")) >> pDefault >>= withAttribute ErrorTok) parseRules ("Roff","Directive") = (((pFloat >>= withAttribute DecValTok)) <|> ((pInt >>= withAttribute DecValTok)) <|> ((pDetect2Chars False '\\' '"' >>= withAttribute CommentTok) >>~ pushContext ("Roff","Comment")) <|> ((parseRules ("Roff","DetectOthers"))) <|> (currentContext >>= \x -> guard (x == ("Roff","Directive")) >> pDefault >>= withAttribute StringTok)) parseRules ("Roff","String") = (((pDetect2Chars False '\\' '"' >>= withAttribute CharTok)) <|> ((pDetectChar False '"' >>= withAttribute StringTok) >>~ (popContext)) <|> ((parseRules ("Roff","DetectOthers"))) <|> (currentContext >>= \x -> guard (x == ("Roff","String")) >> pDefault >>= withAttribute StringTok)) parseRules ("Roff","LiteralSL") = (currentContext >>= \x -> guard (x == ("Roff","LiteralSL")) >> pDefault >>= withAttribute NormalTok) parseRules ("Roff","LiteralIL") = (((pDetect2Chars False '\\' '\\' >>= withAttribute CharTok)) <|> ((pDetect2Chars False '\\' '?' >>= withAttribute CharTok) >>~ (popContext)) <|> (currentContext >>= \x -> guard (x == ("Roff","LiteralIL")) >> pDefault >>= withAttribute NormalTok)) parseRules ("Roff","Argument") = (((pRegExprDynamic "%1" >>= withAttribute CharTok) >>~ (popContext >> popContext)) <|> ((parseRules ("Roff","DetectOthers"))) <|> (currentContext >>= \x -> guard (x == ("Roff","Argument")) >> pDefault >>= withAttribute StringTok)) parseRules ("Roff","GlyphArgument") = (((pRegExprDynamic "%1" >>= withAttribute OtherTok) >>~ (popContext >> popContext)) <|> (currentContext >>= \x -> guard (x == ("Roff","GlyphArgument")) >> pDefault >>= withAttribute OtherTok)) parseRules ("Roff","Measurement") = (((pRegExprDynamic "%1" >>= withAttribute CharTok) >>~ (popContext >> popContext)) <|> (currentContext >>= \x -> guard (x == ("Roff","Measurement")) >> pDefault >>= withAttribute ErrorTok)) parseRules ("Roff","deDirective") = (currentContext >>= \x -> guard (x == ("Roff","deDirective")) >> pDefault >>= withAttribute StringTok) parseRules ("Roff","deBody") = (((pColumn 0 >> pDetect2Chars False '.' '.' >>= withAttribute FunctionTok) >>~ (popContext >> popContext)) <|> ((parseRules ("Roff","Normal"))) <|> (currentContext >>= \x -> guard (x == ("Roff","deBody")) >> pDefault >>= withAttribute NormalTok)) parseRules ("Roff","diDirective") = (currentContext >>= \x -> guard (x == ("Roff","diDirective")) >> pDefault >>= withAttribute StringTok) parseRules ("Roff","diBody") = (((pColumn 0 >> pRegExpr regex_'5c'2e'5cs'2adi'5cb >>= withAttribute FunctionTok) >>~ (popContext >> popContext)) <|> ((pDetect2Chars False '\\' '!' >>= withAttribute CharTok) >>~ pushContext ("Roff","LiteralSL")) <|> ((pDetect2Chars False '\\' '?' >>= withAttribute CharTok) >>~ pushContext ("Roff","LiteralIL")) <|> ((parseRules ("Roff","Normal"))) <|> (currentContext >>= \x -> guard (x == ("Roff","diBody")) >> pDefault >>= withAttribute NormalTok)) parseRules ("Roff","daDirective") = (currentContext >>= \x -> guard (x == ("Roff","daDirective")) >> pDefault >>= withAttribute StringTok) parseRules ("Roff","daBody") = (((pColumn 0 >> pRegExpr regex_'5c'2e'5cs'2ada'5cb >>= withAttribute FunctionTok) >>~ (popContext >> popContext)) <|> ((pDetect2Chars False '\\' '!' >>= withAttribute CharTok) >>~ pushContext ("Roff","LiteralSL")) <|> ((pDetect2Chars False '\\' '?' >>= withAttribute CharTok) >>~ pushContext ("Roff","LiteralIL")) <|> ((parseRules ("Roff","Normal"))) <|> (currentContext >>= \x -> guard (x == ("Roff","daBody")) >> pDefault >>= withAttribute NormalTok)) parseRules ("Roff","dsDirective") = (((pInt >>= withAttribute DecValTok)) <|> ((pFloat >>= withAttribute DecValTok)) <|> ((pDetect2Chars False '\\' '"' >>= withAttribute CommentTok) >>~ pushContext ("Roff","Comment")) <|> ((pDetectChar False '"' >>= withAttribute StringTok) >>~ pushContext ("Roff","dsString")) <|> ((parseRules ("Roff","DetectOthers"))) <|> (currentContext >>= \x -> guard (x == ("Roff","dsDirective")) >> pDefault >>= withAttribute StringTok)) parseRules ("Roff","dsString") = (((parseRules ("Roff","DetectOthers"))) <|> (currentContext >>= \x -> guard (x == ("Roff","dsString")) >> pDefault >>= withAttribute StringTok)) parseRules ("Alerts", _) = Text.Highlighting.Kate.Syntax.Alert.parseExpression Nothing parseRules x = parseRules ("Roff","Normal") <|> fail ("Unknown context" ++ show x)