{- This module was generated from data in the Kate syntax highlighting file haskell.xml, version 2.2, by Nicolas Wu (zenzike@gmail.com) -} module Text.Highlighting.Kate.Syntax.Haskell (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 qualified Data.Set as Set -- | Full name of language. syntaxName :: String syntaxName = "Haskell" -- | Filename extensions for this language. syntaxExtensions :: String syntaxExtensions = "*.hs;*.chs" -- | 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 = [("Haskell","code")], 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 ("Haskell","code") -> return () ("Haskell","comment") -> (popContext) >> pEndLine ("Haskell","comments") -> return () ("Haskell","char") -> (popContext) >> pEndLine ("Haskell","string") -> return () ("Haskell","infix") -> return () ("Haskell","import") -> (popContext) >> pEndLine ("Haskell","c2hs directive") -> return () ("Haskell","c2hs import") -> return () ("Haskell","c2hs include") -> (popContext) >> pEndLine ("Haskell","c2hs pointer") -> return () ("Haskell","c2hs fun") -> return () ("Haskell","c2hs enum") -> return () _ -> 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_keywords = Set.fromList $ words $ "case class data deriving do else if in infixl infixr instance let module newtype of primitive then type where" list_prelude_function = Set.fromList $ words $ "abs acos acosh all and any appendFile approxRational asTypeOf asin asinh atan atan2 atanh basicIORun break catch ceiling chr compare concat concatMap const cos cosh curry cycle decodeFloat denominator digitToInt div divMod drop dropWhile either elem encodeFloat enumFrom enumFromThen enumFromThenTo enumFromTo error even exp exponent fail filter flip floatDigits floatRadix floatRange floor fmap foldl foldl1 foldr foldr1 fromDouble fromEnum fromInt fromInteger fromIntegral fromRational fst gcd getChar getContents getLine group head id inRange index init intToDigit interact ioError isAlpha isAlphaNum isAscii isControl isDenormalized isDigit isHexDigit isIEEE isInfinite isLower isNaN isNegativeZero isOctDigit isPrint isSpace isUpper iterate last lcm length lex lexDigits lexLitChar lines log logBase lookup map mapM mapM_ max maxBound maximum maybe min minBound minimum mod negate not notElem null numerator odd or ord otherwise pack pi pred primExitWith print product properFraction putChar putStr putStrLn quot quotRem range rangeSize read readDec readFile readFloat readHex readIO readInt readList readLitChar readLn readOct readParen readSigned reads readsPrec realToFrac recip rem repeat replicate return reverse round scaleFloat scanl scanl1 scanr scanr1 seq sequence sequence_ show showChar showInt showList showLitChar showParen showSigned showString shows showsPrec significand signum sin sinh snd sort span splitAt sqrt subtract succ sum tail take takeWhile tan tanh threadToIOResult toEnum toInt toInteger toLower toRational toUpper truncate uncurry undefined unlines until unwords unzip unzip3 userError words writeFile zip zip3 zipWith zipWith3" list_prelude_class = Set.fromList $ words $ "Bounded Enum Eq Floating Fractional Functor Integral Ix Monad Num Ord Read Real RealFloat RealFrac Show" list_prelude_type = Set.fromList $ words $ "Bool Char Double Either FilePath Float Int Integer IO IOError Maybe Ordering Ratio Rational ReadS ShowS String ByteString" list_prelude_data = Set.fromList $ words $ "False True Left Right Just Nothing EQ LT GT" list_class = Set.fromList $ words $ "Applicative Foldable Traversable" list_c2hs'5fkeywords = Set.fromList $ words $ "qualified lib prefix as with call pure unsafe get set foreign stable nocode" list_import'5fkeywords = Set.fromList $ words $ "as qualified hiding" regex_'5c'7b'2d'23'2e'2a'23'2d'5c'7d = compileRegex "\\{-#.*#-\\}" regex_'5c'7b'2d'5b'5e'23'5d'3f = compileRegex "\\{-[^#]?" regex_'2d'2d'5b'5e'5c'2d'21'23'5c'24'25'26'5c'2a'5c'2b'2f'3c'3d'3e'5c'3f'5c'40'5c'5e'5c'7c'7e'5c'2e'3a'5d'2e'2a'24 = compileRegex "--[^\\-!#\\$%&\\*\\+/<=>\\?\\@\\^\\|~\\.:].*$" regex_import'5cs'2b = compileRegex "import\\s+" regex_'5c'7b'23 = compileRegex "\\{#" regex_'23 = compileRegex "#" regex_'28'3a'3a'7c'3d'3e'7c'5c'2d'3e'7c'3c'5c'2d'29 = compileRegex "(::|=>|\\->|<\\-)" regex_'5cs'2a'5ba'2dz'5d'5ba'2dzA'2dZ0'2d9'5f'27'5d'2a'5cs'2a'28'3f'3d'3a'3a'5b'5e'5c'2d'21'23'5c'24'25'26'5c'2a'5c'2b'2f'3c'3d'3e'5c'3f'5c'40'5c'5e'5c'7c'7e'5c'2e'3a'5d'29 = compileRegex "\\s*[a-z][a-zA-Z0-9_']*\\s*(?=::[^\\-!#\\$%&\\*\\+/<=>\\?\\@\\^\\|~\\.:])" regex_'5cs'2a'28'5c'28'5b'5c'2d'21'23'5c'24'25'26'5c'2a'5c'2b'2f'3c'3d'3e'5c'3f'5c'40'5c'5e'5c'7c'7e'5c'2e'3a'5d'2a'5c'29'29'2a'5cs'2a'28'3f'3d'3a'3a'5b'5e'5c'2d'21'23'5c'24'25'26'5c'2a'5c'2b'2f'3c'3d'3e'5c'3f'5c'40'5c'5e'5c'7c'7e'5c'2e'3a'5d'29 = compileRegex "\\s*(\\([\\-!#\\$%&\\*\\+/<=>\\?\\@\\^\\|~\\.:]*\\))*\\s*(?=::[^\\-!#\\$%&\\*\\+/<=>\\?\\@\\^\\|~\\.:])" regex_'28'5bA'2dZ'5d'5ba'2dzA'2dZ0'2d9'5f'27'5d'2a'5c'2e'29'2a'5ba'2dz'5d'5ba'2dzA'2dZ0'2d9'5f'27'5d'2a = compileRegex "([A-Z][a-zA-Z0-9_']*\\.)*[a-z][a-zA-Z0-9_']*" regex_'28'5bA'2dZ'5d'5ba'2dzA'2dZ0'2d0'5f'27'5d'2a'5c'2e'29'2a'5b'5c'2d'21'23'5c'24'25'26'5c'2a'5c'2b'2f'3c'3d'3e'5c'3f'5c'40'5c'5e'5c'7c'7e'5c'2e'3a'5d'2b = compileRegex "([A-Z][a-zA-Z0-0_']*\\.)*[\\-!#\\$%&\\*\\+/<=>\\?\\@\\^\\|~\\.:]+" regex_'28'5bA'2dZ'5d'5ba'2dzA'2dZ0'2d9'5f'27'5d'2a'5c'2e'29'2a'5bA'2dZ'5d'5ba'2dzA'2dZ0'2d9'5f'27'5d'2a = compileRegex "([A-Z][a-zA-Z0-9_']*\\.)*[A-Z][a-zA-Z0-9_']*" regex_'5cd'2b'5c'2e'5cd'2b = compileRegex "\\d+\\.\\d+" regex_'5c'5c'2e = compileRegex "\\\\." regex_context = compileRegex "context" regex_call = compileRegex "call" regex_sizeof = compileRegex "sizeof" regex_alignof = compileRegex "alignof" regex_fun = compileRegex "fun" regex_pointer = compileRegex "pointer" regex_enum = compileRegex "enum" regex_import = compileRegex "import" regex_include = compileRegex "include" regex_'2a'2e'3e'24 = compileRegex "*.>$" regex_newtype = compileRegex "newtype" regex_'60'5b'5e'27'5d'2a'27 = compileRegex "`[^']*'" parseRules ("Haskell","code") = (((pRegExpr regex_'5c'7b'2d'23'2e'2a'23'2d'5c'7d >>= withAttribute OtherTok)) <|> ((pRegExpr regex_'5c'7b'2d'5b'5e'23'5d'3f >>= withAttribute CommentTok) >>~ pushContext ("Haskell","comments")) <|> ((pRegExpr regex_'2d'2d'5b'5e'5c'2d'21'23'5c'24'25'26'5c'2a'5c'2b'2f'3c'3d'3e'5c'3f'5c'40'5c'5e'5c'7c'7e'5c'2e'3a'5d'2e'2a'24 >>= withAttribute CommentTok) >>~ pushContext ("Haskell","comment")) <|> ((pRegExpr regex_import'5cs'2b >>= withAttribute KeywordTok) >>~ pushContext ("Haskell","import")) <|> ((pRegExpr regex_'5c'7b'23 >>= withAttribute StringTok) >>~ pushContext ("Haskell","c2hs directive")) <|> ((pRegExpr regex_'23 >>= withAttribute StringTok) >>~ pushContext ("Haskell","c2hs include")) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_keywords >>= withAttribute KeywordTok)) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_prelude_function >>= withAttribute NormalTok)) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_prelude_type >>= withAttribute DataTypeTok)) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_prelude_data >>= withAttribute DataTypeTok)) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_prelude_class >>= withAttribute DataTypeTok)) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_class >>= withAttribute DataTypeTok)) <|> ((pRegExpr regex_'28'3a'3a'7c'3d'3e'7c'5c'2d'3e'7c'3c'5c'2d'29 >>= withAttribute OtherTok)) <|> ((pAnyChar "\8759\8658\8594\8592\8704\8707" >>= withAttribute OtherTok)) <|> ((pRegExpr regex_'5cs'2a'5ba'2dz'5d'5ba'2dzA'2dZ0'2d9'5f'27'5d'2a'5cs'2a'28'3f'3d'3a'3a'5b'5e'5c'2d'21'23'5c'24'25'26'5c'2a'5c'2b'2f'3c'3d'3e'5c'3f'5c'40'5c'5e'5c'7c'7e'5c'2e'3a'5d'29 >>= withAttribute OtherTok)) <|> ((pRegExpr regex_'5cs'2a'28'5c'28'5b'5c'2d'21'23'5c'24'25'26'5c'2a'5c'2b'2f'3c'3d'3e'5c'3f'5c'40'5c'5e'5c'7c'7e'5c'2e'3a'5d'2a'5c'29'29'2a'5cs'2a'28'3f'3d'3a'3a'5b'5e'5c'2d'21'23'5c'24'25'26'5c'2a'5c'2b'2f'3c'3d'3e'5c'3f'5c'40'5c'5e'5c'7c'7e'5c'2e'3a'5d'29 >>= withAttribute OtherTok)) <|> ((pRegExpr regex_'28'5bA'2dZ'5d'5ba'2dzA'2dZ0'2d9'5f'27'5d'2a'5c'2e'29'2a'5ba'2dz'5d'5ba'2dzA'2dZ0'2d9'5f'27'5d'2a >>= withAttribute NormalTok)) <|> ((pRegExpr regex_'28'5bA'2dZ'5d'5ba'2dzA'2dZ0'2d0'5f'27'5d'2a'5c'2e'29'2a'5b'5c'2d'21'23'5c'24'25'26'5c'2a'5c'2b'2f'3c'3d'3e'5c'3f'5c'40'5c'5e'5c'7c'7e'5c'2e'3a'5d'2b >>= withAttribute FunctionTok)) <|> ((pRegExpr regex_'28'5bA'2dZ'5d'5ba'2dzA'2dZ0'2d9'5f'27'5d'2a'5c'2e'29'2a'5bA'2dZ'5d'5ba'2dzA'2dZ0'2d9'5f'27'5d'2a >>= withAttribute DataTypeTok)) <|> ((pInt >>= withAttribute DecValTok)) <|> ((pRegExpr regex_'5cd'2b'5c'2e'5cd'2b >>= withAttribute FloatTok)) <|> ((pDetectChar False '\'' >>= withAttribute CharTok) >>~ pushContext ("Haskell","char")) <|> ((pDetectChar False '"' >>= withAttribute StringTok) >>~ pushContext ("Haskell","string")) <|> ((pDetectChar False '`' >>= withAttribute OtherTok) >>~ pushContext ("Haskell","infix")) <|> ((pDetect2Chars False '.' '.' >>= withAttribute OtherTok)) <|> ((pAnyChar "\8229" >>= withAttribute OtherTok)) <|> (currentContext >>= \x -> guard (x == ("Haskell","code")) >> pDefault >>= withAttribute NormalTok)) parseRules ("Haskell","comment") = (currentContext >>= \x -> guard (x == ("Haskell","comment")) >> pDefault >>= withAttribute CommentTok) parseRules ("Haskell","comments") = (((pDetect2Chars False '-' '}' >>= withAttribute CommentTok) >>~ (popContext)) <|> (currentContext >>= \x -> guard (x == ("Haskell","comments")) >> pDefault >>= withAttribute CommentTok)) parseRules ("Haskell","char") = (((pRegExpr regex_'5c'5c'2e >>= withAttribute CharTok)) <|> ((pDetectChar False '\'' >>= withAttribute CharTok) >>~ (popContext)) <|> (currentContext >>= \x -> guard (x == ("Haskell","char")) >> pDefault >>= withAttribute CharTok)) parseRules ("Haskell","string") = (((pRegExpr regex_'5c'5c'2e >>= withAttribute StringTok)) <|> ((pDetectChar False '"' >>= withAttribute StringTok) >>~ (popContext)) <|> (currentContext >>= \x -> guard (x == ("Haskell","string")) >> pDefault >>= withAttribute StringTok)) parseRules ("Haskell","infix") = (((pDetectChar False '`' >>= withAttribute OtherTok) >>~ (popContext)) <|> (currentContext >>= \x -> guard (x == ("Haskell","infix")) >> pDefault >>= withAttribute OtherTok)) parseRules ("Haskell","import") = (((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_import'5fkeywords >>= withAttribute KeywordTok)) <|> ((pRegExpr regex_'28'5bA'2dZ'5d'5ba'2dzA'2dZ0'2d9'5f'27'5d'2a'5c'2e'29'2a'5ba'2dz'5d'5ba'2dzA'2dZ0'2d9'5f'27'5d'2a >>= withAttribute NormalTok)) <|> ((pRegExpr regex_'28'5bA'2dZ'5d'5ba'2dzA'2dZ0'2d9'5f'27'5d'2a'5c'2e'29'2a'5bA'2dZ'5d'5ba'2dzA'2dZ0'2d9'5f'27'5d'2a >>= withAttribute DataTypeTok)) <|> ((pRegExpr regex_'5c'7b'2d'23'2e'2a'23'2d'5c'7d >>= withAttribute OtherTok)) <|> ((pRegExpr regex_'5c'7b'2d'5b'5e'23'5d'3f >>= withAttribute CommentTok) >>~ pushContext ("Haskell","comments")) <|> ((pRegExpr regex_'2d'2d'5b'5e'5c'2d'21'23'5c'24'25'26'5c'2a'5c'2b'2f'3c'3d'3e'5c'3f'5c'40'5c'5e'5c'7c'7e'5c'2e'3a'5d'2e'2a'24 >>= withAttribute CommentTok) >>~ pushContext ("Haskell","comment")) <|> (currentContext >>= \x -> guard (x == ("Haskell","import")) >> pDefault >>= withAttribute NormalTok)) parseRules ("Haskell","c2hs directive") = (((pDetect2Chars False '#' '}' >>= withAttribute StringTok) >>~ (popContext)) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_c2hs'5fkeywords >>= withAttribute KeywordTok)) <|> ((pRegExpr regex_context >>= withAttribute KeywordTok)) <|> ((pRegExpr regex_call >>= withAttribute KeywordTok)) <|> ((pRegExpr regex_sizeof >>= withAttribute KeywordTok)) <|> ((pRegExpr regex_alignof >>= withAttribute KeywordTok)) <|> ((pRegExpr regex_fun >>= withAttribute KeywordTok) >>~ pushContext ("Haskell","c2hs fun")) <|> ((pRegExpr regex_pointer >>= withAttribute KeywordTok) >>~ pushContext ("Haskell","c2hs pointer")) <|> ((pRegExpr regex_enum >>= withAttribute KeywordTok) >>~ pushContext ("Haskell","c2hs enum")) <|> ((pRegExpr regex_import >>= withAttribute KeywordTok) >>~ pushContext ("Haskell","c2hs import")) <|> (currentContext >>= \x -> guard (x == ("Haskell","c2hs directive")) >> pDefault >>= withAttribute StringTok)) parseRules ("Haskell","c2hs import") = (((pRegExpr regex_'28'5bA'2dZ'5d'5ba'2dzA'2dZ0'2d9'5f'27'5d'2a'5c'2e'29'2a'5bA'2dZ'5d'5ba'2dzA'2dZ0'2d9'5f'27'5d'2a >>= withAttribute DataTypeTok)) <|> ((pDetect2Chars False '#' '}' >>= withAttribute StringTok) >>~ (popContext >> popContext)) <|> (currentContext >>= \x -> guard (x == ("Haskell","c2hs import")) >> pDefault >>= withAttribute StringTok)) parseRules ("Haskell","c2hs include") = (((pRegExpr regex_include >>= withAttribute KeywordTok)) <|> ((pRegExpr regex_'2a'2e'3e'24 >>= withAttribute StringTok)) <|> (currentContext >>= \x -> guard (x == ("Haskell","c2hs include")) >> pDefault >>= withAttribute StringTok)) parseRules ("Haskell","c2hs pointer") = (((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_c2hs'5fkeywords >>= withAttribute KeywordTok)) <|> ((pRegExpr regex_newtype >>= withAttribute KeywordTok)) <|> ((pRegExpr regex_'28'5bA'2dZ'5d'5ba'2dzA'2dZ0'2d9'5f'27'5d'2a'5c'2e'29'2a'5bA'2dZ'5d'5ba'2dzA'2dZ0'2d9'5f'27'5d'2a >>= withAttribute DataTypeTok)) <|> ((pDetect2Chars False '#' '}' >>= withAttribute StringTok) >>~ (popContext >> popContext)) <|> (currentContext >>= \x -> guard (x == ("Haskell","c2hs pointer")) >> pDefault >>= withAttribute StringTok)) parseRules ("Haskell","c2hs fun") = (((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_c2hs'5fkeywords >>= withAttribute KeywordTok)) <|> ((pRegExpr regex_'60'5b'5e'27'5d'2a'27 >>= withAttribute DataTypeTok)) <|> ((pDetect2Chars False '#' '}' >>= withAttribute StringTok) >>~ (popContext >> popContext)) <|> (currentContext >>= \x -> guard (x == ("Haskell","c2hs fun")) >> pDefault >>= withAttribute StringTok)) parseRules ("Haskell","c2hs enum") = (((pRegExpr regex_'28'5bA'2dZ'5d'5ba'2dzA'2dZ0'2d9'5f'27'5d'2a'5c'2e'29'2a'5bA'2dZ'5d'5ba'2dzA'2dZ0'2d9'5f'27'5d'2a >>= withAttribute DataTypeTok)) <|> ((pDetect2Chars False '#' '}' >>= withAttribute StringTok) >>~ (popContext >> popContext)) <|> (currentContext >>= \x -> guard (x == ("Haskell","c2hs enum")) >> pDefault >>= withAttribute StringTok)) parseRules x = parseRules ("Haskell","code") <|> fail ("Unknown context" ++ show x)