{- This module was generated from data in the Kate syntax highlighting file literate-haskell.xml, version 2.0.2, by Nicolas Wu (zenzike@gmail.com) -} module Text.Highlighting.Kate.Syntax.LiterateHaskell (highlight, parseExpression, syntaxName, syntaxExtensions) where import Text.Highlighting.Kate.Types import Text.Highlighting.Kate.Common import qualified Text.Highlighting.Kate.Syntax.Haskell import Text.ParserCombinators.Parsec hiding (State) import Data.Map (fromList) import Control.Monad.State import Data.Char (isSpace) import Data.Maybe (fromMaybe) -- | Full name of language. syntaxName :: String syntaxName = "Literate Haskell" -- | Filename extensions for this language. syntaxExtensions :: String syntaxExtensions = "*.lhs" -- | 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 parseExpressionInternal pEndLine -- | Parse an expression using appropriate local context. parseExpression :: KateParser Token parseExpression = do st <- getState let oldLang = synStLanguage st setState $ st { synStLanguage = "Literate Haskell" } context <- currentContext <|> (pushContext "text" >> currentContext) result <- parseRules context optional $ eof >> pEndLine updateState $ \st -> st { synStLanguage = oldLang } return result startingState = SyntaxState {synStContexts = fromList [("Literate Haskell",["text"])], synStLanguage = "Literate Haskell", synStLineNumber = 0, synStPrevChar = '\n', synStPrevNonspace = False, synStCaseSensitive = True, synStKeywordCaseSensitive = True, synStCaptures = []} pEndLine = do updateState $ \st -> st{ synStPrevNonspace = False } context <- currentContext case context of "text" -> return () "normal" -> (popContext) >> pEndLine "normals" -> return () "comments'" -> pushContext "uncomments" >> return () "uncomments" -> return () "recomments" -> (popContext) >> pEndLine _ -> 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) parseExpressionInternal = do context <- currentContext parseRules context <|> (pDefault >>= withAttribute (fromMaybe NormalTok $ lookup context defaultAttributes)) regex_'5c'7b'2d'5b'5e'23'5d = compileRegex "\\{-[^#]" defaultAttributes = [("text",NormalTok),("normal",NormalTok),("normals",NormalTok),("comments'",CommentTok),("uncomments",NormalTok),("recomments",CommentTok)] parseRules "text" = (((pColumn 0 >> pDetectChar False '>' >>= withAttribute OtherTok) >>~ pushContext "normal") <|> ((pColumn 0 >> pDetectChar False '<' >>= withAttribute OtherTok) >>~ pushContext "normal") <|> ((pString False "\\begin{code}" >>= withAttribute NormalTok) >>~ pushContext "normals") <|> ((pString False "\\begin{spec}" >>= withAttribute NormalTok) >>~ pushContext "normals")) parseRules "normal" = (((pRegExpr regex_'5c'7b'2d'5b'5e'23'5d >>= withAttribute CommentTok) >>~ pushContext "comments'") <|> ((Text.Highlighting.Kate.Syntax.Haskell.parseExpression))) parseRules "normals" = (((pString False "\\end{code}" >>= withAttribute NormalTok) >>~ (popContext)) <|> ((pString False "\\end{spec}" >>= withAttribute NormalTok) >>~ (popContext)) <|> ((Text.Highlighting.Kate.Syntax.Haskell.parseExpression))) parseRules "comments'" = ((pDetect2Chars False '-' '}' >>= withAttribute CommentTok) >>~ (popContext)) parseRules "uncomments" = (((pColumn 0 >> pDetectChar False '>' >>= withAttribute OtherTok) >>~ pushContext "recomments") <|> ((pColumn 0 >> pDetectChar False '<' >>= withAttribute OtherTok) >>~ pushContext "recomments")) parseRules "recomments" = ((pDetect2Chars False '-' '}' >>= withAttribute CommentTok) >>~ (popContext >> popContext >> popContext)) parseRules "" = parseRules "text" parseRules x = fail $ "Unknown context" ++ x