{- This module was generated from data in the Kate syntax highlighting file metafont.xml, version 0.9, by Yedvilun (yedvilun@gmail.com) -} module Text.Highlighting.Kate.Syntax.Metafont (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 = "Metapost/Metafont" -- | Filename extensions for this language. syntaxExtensions :: String syntaxExtensions = "*.mp;*.mps;*.mpost;*.mf" -- | 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 -- | Parse an expression using appropriate local context. parseExpression :: KateParser Token parseExpression = do (lang,cont) <- currentContext result <- parseRules (lang,cont) optional $ do eof updateState $ \st -> st{ synStPrevChar = '\n' } pEndLine return result startingState = SyntaxState {synStContexts = [("Metapost/Metafont","Normal Text")], synStLineNumber = 0, synStPrevChar = '\n', synStPrevNonspace = False, synStCaseSensitive = True, synStKeywordCaseSensitive = False, synStCaptures = []} pEndLine = do updateState $ \st -> st{ synStPrevNonspace = False } context <- currentContext contexts <- synStContexts `fmap` getState if length contexts >= 2 then case context of ("Metapost/Metafont","Normal Text") -> return () ("Metapost/Metafont","string") -> return () ("Metapost/Metafont","TeXMode") -> return () ("Metapost/Metafont","ContrSeq") -> (popContext) >> pEndLine ("Metapost/Metafont","ToEndOfLine") -> (popContext) >> pEndLine ("Metapost/Metafont","Verb") -> (popContext >> popContext) >> pEndLine ("Metapost/Metafont","VerbEnd") -> (popContext >> popContext >> popContext) >> pEndLine ("Metapost/Metafont","MathMode") -> return () ("Metapost/Metafont","MathContrSeq") -> (popContext) >> pEndLine ("Metapost/Metafont","Comment") -> (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_mfBoolExp = Set.fromList $ words $ "true false known unknown odd charexists not and or" list_mfNumExp = Set.fromList $ words $ "normaldeviate length ascii oct hex angle turningnumber totalweight directiontime xpart ypart xxpart xypart yxpart yypart sqrt sind cosd mlog mexp floor uniformdeviate abs div dotprod max min mod ceiling" list_mfInternal = Set.fromList $ words $ "tracingtitles tracingequations tracingcapsules tracingchoices tracingspecs tracingpens tracingcommands tracingrestores tracingmacros tracingedges tracingoutput tracingonline tracingstats pausing showstopping fontmaking proofing turningcheck warningcheck smoothing autorounding granularity fillin year month day time charcode charext charwd charht chardp charic chardx chardy designsize hppp vppp xoffset yoffset boundarychar" list_mfPairExp = Set.fromList $ words $ "point of precontrol postcontrol penoffset rotated scaled shifted slanted transformed xscaled yscaled zscaled" list_mfPathExp = Set.fromList $ words $ "makepath reverse subpath curl tension atleast controls cycle" list_mfPenExp = Set.fromList $ words $ "nullpen pencircle makepen" list_mfPicExp = Set.fromList $ words $ "nullpicture" list_mfStringExp = Set.fromList $ words $ "jobname readstring str char decimal substring" list_mfCommand = Set.fromList $ words $ "end dump save interim newinternal randomseed let delimiters outer everyjob show showvariable showtoken showdependencies showstats message errmessage errhelp batchmode nonstopmode scrollmode errorstopmode addto also contour doublepath withpen withweight cull keeping dropping display inwindow openwindow at from to shipout special numspecial" list_mfType = Set.fromList $ words $ "boolean numeric pair path pen picture string transform" list_mfDefinition = Set.fromList $ words $ "expr suffix text primary secondary tertiary primarydef secondarydef tertiarydef" list_mfCondition = Set.fromList $ words $ "else elseif step until upto exitif" list_mfPrimitive = Set.fromList $ words $ "charlist endinput expandafter extensible fontdimen headerbyte inner input intersectiontimes kern ligtable quote scantokens skipto" list_mfMacro = Set.fromList $ words $ "addto_currentpicture aspect_ratio base_name base_version blacker blankpicture bot bye byte capsule_def change_width clear_pen_memory clearit clearpen clearxy counterclockwise culldraw cullit currentpen currentpen_path currentpicture currenttransform currentwindow cutdraw cutoff d decr define_blacker_pixels define_corrected_pixels define_good_x_pixels define_good_y_pixels define_horizontal_corrected_pixels define_pixels define_whole_blacker_pixels define_whole_pixels define_whole_vertical_blacker_pixels define_whole_vertical_pixels dir direction directionpoint displaying ditto down downto draw drawdot eps epsilon extra_setup erase exitunless fill filldraw fix_units flex font_coding_scheme font_extra_space font_identifier font_normal_shrink font_normal_space font_normal_stretch font_quad font_setup font_size font_slant font_x_height fullcircle generate gfcorners gobble gobbled grayfont h halfcircle hide hround identity image_rules incr infinity interact interpath intersectionpoint inverse italcorr join_radius killtext labelfont labels left lft localfont loggingall lowres lowres_fix mag magstep makebox makegrid makelabel maketicks mode mode_def mode_name mode_setup nodisplays notransforms number_of_modes numtok o_correction openit origin pen_bot pen_lft pen_rt pen_top penlabels penpos penrazor penspeck pensquare penstroke pickup pixels_per_inch proof proofoffset proofrule proofrulethickness quartercircle range reflectedabout relax right rotatedabout rotatedaround round rt rulepen savepen screenchars screen_rows screen_cols screenrule screenstrokes shipit showit slantfont smode smoke softjoin solve stop superellipse takepower tensepath titlefont tolerance top tracingall tracingnone undraw undrawdot unfill unfilldraw unitpixel unitsquare unitvector up upto vround w whatever" list_mpInternal = Set.fromList $ words $ "bluepart clip color dashed fontsize greenpart infont linecap linejoin llcorner lrcorner miterlimit mpxbreak prologues redpart setbounds tracinglostchars truecorners ulcorner urcorner withcolor" list_notDefined = Set.fromList $ words $ "autorounding chardx chardy fillin granularity hppp proofing smoothing tracingedges tracingpens turningcheck vppp xoffset yoffset" list_mpMacro = Set.fromList $ words $ "ahangle ahlength background bbox bboxmargin beveled black blue buildcycle butt center cutafter cutbefore cuttings dashpattern defaultfont defaultpen defaultscale dotlabel dotlabels drawarrow drawdblarrow drawoptions evenly green label labeloffset mitered red rounded squared thelabel white base_name base_version upto downto exitunless relax gobble gobbled interact loggingall tracingall tracingnone eps epsilon infinity right left up down origin quartercircle halfcircle fullcircle unitsquare identity blankpicture withdots ditto eof pensquare penrazor penspeck whatever round byte dir unitvector inverse counterclockwise tensepath takepower direction directionpoint intersectionpoint softjoin incr decr reflectedabout rotatedaround rotatedabout flex superellipse interpath magstep currentpen currentpen_path currentpicture fill draw filldraw drawdot unfill undraw unfilldraw undrawdot erase cutdraw image pickup numeric_pickup pen_lft pen_rt pen_top pen_bot savepen clearpen clear_pen_memory lft rt top bot ulft urt llft lrt penpos penstroke arrowhead makelabel labels penlabel range numtok thru clearxy clearit clearpen pickup shipit bye hide stop solve blacker capsule_def change_width define_blacker_pixels define_corrected_pixels define_good_x_pixels define_good_y_pixels define_horizontal_corrected_pixels define_pixels define_whole_blacker_pixels define_whole_vertical_blacker_pixels define_whole_vertical_pixels extra_setup font_coding_scheme font_extra_space font_identifier font_normal_shrink font_normal_space font_normal_stretch font_quad font_size font_slant font_x_height italcorr labelfont makebox makegrid maketicks mode_def mode_setup o_correction proofrule proofrulethickness rulepen smode cullit currenttransform gfcorners grayfont hround imagerules lowres_fix nodisplays notransforms openit proofoffset screenchars screenrule screenstrokes showit slantfont titlefont unitpixel vround circmargin defaultdx defaultdy boxit boxjoin bpath circleit drawboxed drawboxes drawunboxed fixpos fixsize pic" list_EnvDelimiters = Set.fromList $ words $ "beginchar endchar extra_beginchar extra_endchar beginlogochar beginfig endfig extra_beginfig extra_endfig" regex_'28'5c'2b'7c'5c'2d'7c'5c'2a'7c'5c'2f'7c'5c'3d'7c'5c'3a'5c'3d'29 = compileRegex "(\\+|\\-|\\*|\\/|\\=|\\:\\=)" regex_'5cb'28bp'7ccc'7ccm'7cdd'7cin'7cmm'7cpc'7cpt'29'5cb = compileRegex "\\b(bp|cc|cm|dd|in|mm|pc|pt)\\b" regex_'5cb'2d'3f'5cd'2b'28bp'7ccc'7ccm'7cdd'7cin'7cmm'7cpc'7cpt'29'23'3f'5cb = compileRegex "\\b-?\\d+(bp|cc|cm|dd|in|mm|pc|pt)#?\\b" regex_'5cb'2d'3f'5c'2e'5cd'2b'28bp'7ccc'7ccm'7cdd'7cin'7cmm'7cpc'7cpt'29'23'3f'5cb = compileRegex "\\b-?\\.\\d+(bp|cc|cm|dd|in|mm|pc|pt)#?\\b" regex_'5cb'2d'3f'5cd'2b'5c'2e'5cd'2b'28bp'7ccc'7ccm'7cdd'7cin'7cmm'7cpc'7cpt'29'23'3f'5cb = compileRegex "\\b-?\\d+\\.\\d+(bp|cc|cm|dd|in|mm|pc|pt)#?\\b" regex_'5cb'5bxy'5d'5cd'28'5cw'7c'5c'27'29'2a = compileRegex "\\b[xy]\\d(\\w|\\')*" regex_'5cbz'5cd'28'5cw'7c'5c'27'29'2a = compileRegex "\\bz\\d(\\w|\\')*" regex_'5cbp'5cd'28'5cw'7c'5c'27'29'2a = compileRegex "\\bp\\d(\\w|\\')*" regex_'5cb'28verbatimtex'7cbtex'29'5cb = compileRegex "\\b(verbatimtex|btex)\\b" regex_'5cbbegin'28group'7cfig'7cchar'29'5cb = compileRegex "\\bbegin(group|fig|char)\\b" regex_'5cbend'28group'7cfig'7cchar'29'5cb = compileRegex "\\bend(group|fig|char)\\b" regex_'5cbextra'5fbegin'28group'7cfig'7cchar'29'5cb = compileRegex "\\bextra_begin(group|fig|char)\\b" regex_'5cbextra'5fend'28group'7cfig'7cchar'29'5cb = compileRegex "\\bextra_end(group|fig|char)\\b" regex_'5cb'28def'7cvardef'29'5cb = compileRegex "\\b(def|vardef)\\b" regex_'5cbenddef'5cb = compileRegex "\\benddef\\b" regex_'5cbif'5cb = compileRegex "\\bif\\b" regex_'5cbfi'5cb = compileRegex "\\bfi\\b" regex_'5cb'28for'7cforsuffixes'7cforever'29'5cb = compileRegex "\\b(for|forsuffixes|forever)\\b" regex_'5cbendfor'5cb = compileRegex "\\bendfor\\b" regex_'5cbetex'5cb = compileRegex "\\betex\\b" regex_verb'28'3f'3d'5b'5ea'2dzA'2dZ'5d'29 = compileRegex "verb(?=[^a-zA-Z])" regex_'5ba'2dzA'2dZ'5d'2b'28'5c'2b'3f'7c'5c'2a'7b0'2c3'7d'29 = compileRegex "[a-zA-Z]+(\\+?|\\*{0,3})" regex_'5b'5ea'2dzA'2dZ'5d = compileRegex "[^a-zA-Z]" regex_'5ba'2dzA'2dZ'5d'2b'5c'2a'3f = compileRegex "[a-zA-Z]+\\*?" regex_'28FIXME'7cTODO'29'3a'3f = compileRegex "(FIXME|TODO):?" parseRules ("Metapost/Metafont","Normal Text") = (((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_mfBoolExp >>= withAttribute KeywordTok)) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_mfNumExp >>= withAttribute FunctionTok)) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_mfInternal >>= withAttribute NormalTok)) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_mfPairExp >>= withAttribute NormalTok)) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_mfPathExp >>= withAttribute NormalTok)) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_mfPenExp >>= withAttribute NormalTok)) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_mfPicExp >>= withAttribute NormalTok)) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_mfStringExp >>= withAttribute NormalTok)) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_mfCommand >>= withAttribute NormalTok)) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_mfType >>= withAttribute DataTypeTok)) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" Set.empty >>= withAttribute NormalTok)) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_mfDefinition >>= withAttribute NormalTok)) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_mfCondition >>= withAttribute KeywordTok)) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_mfPrimitive >>= withAttribute NormalTok)) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_mfMacro >>= withAttribute KeywordTok)) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_mpInternal >>= withAttribute NormalTok)) <|> ((pKeyword " \n\t.():!+,-<=>%&*/;?[]^{|}~\\" list_mpMacro >>= withAttribute KeywordTok)) <|> ((pDetectChar False '%' >>= withAttribute CommentTok) >>~ pushContext ("Metapost/Metafont","Comment")) <|> ((pDetectChar False '"' >>= withAttribute StringTok) >>~ pushContext ("Metapost/Metafont","string")) <|> ((pRegExpr regex_'28'5c'2b'7c'5c'2d'7c'5c'2a'7c'5c'2f'7c'5c'3d'7c'5c'3a'5c'3d'29 >>= withAttribute KeywordTok)) <|> ((pDetect2Chars False '.' '.' >>= withAttribute KeywordTok)) <|> ((pHlCOct >>= withAttribute BaseNTok)) <|> ((pHlCHex >>= withAttribute BaseNTok)) <|> ((pFloat >>= withAttribute FloatTok)) <|> ((pInt >>= withAttribute DecValTok)) <|> ((pRegExpr regex_'5cb'28bp'7ccc'7ccm'7cdd'7cin'7cmm'7cpc'7cpt'29'5cb >>= withAttribute FloatTok)) <|> ((pRegExpr regex_'5cb'2d'3f'5cd'2b'28bp'7ccc'7ccm'7cdd'7cin'7cmm'7cpc'7cpt'29'23'3f'5cb >>= withAttribute FloatTok)) <|> ((pRegExpr regex_'5cb'2d'3f'5c'2e'5cd'2b'28bp'7ccc'7ccm'7cdd'7cin'7cmm'7cpc'7cpt'29'23'3f'5cb >>= withAttribute FloatTok)) <|> ((pRegExpr regex_'5cb'2d'3f'5cd'2b'5c'2e'5cd'2b'28bp'7ccc'7ccm'7cdd'7cin'7cmm'7cpc'7cpt'29'23'3f'5cb >>= withAttribute FloatTok)) <|> ((pRegExpr regex_'5cb'5bxy'5d'5cd'28'5cw'7c'5c'27'29'2a >>= withAttribute KeywordTok)) <|> ((pRegExpr regex_'5cbz'5cd'28'5cw'7c'5c'27'29'2a >>= withAttribute KeywordTok)) <|> ((pRegExpr regex_'5cbp'5cd'28'5cw'7c'5c'27'29'2a >>= withAttribute KeywordTok)) <|> ((pDetectChar False '$' >>= withAttribute KeywordTok)) <|> ((pRegExpr regex_'5cb'28verbatimtex'7cbtex'29'5cb >>= withAttribute KeywordTok) >>~ pushContext ("Metapost/Metafont","TeXMode")) <|> ((pRegExpr regex_'5cbbegin'28group'7cfig'7cchar'29'5cb >>= withAttribute KeywordTok)) <|> ((pRegExpr regex_'5cbend'28group'7cfig'7cchar'29'5cb >>= withAttribute KeywordTok)) <|> ((pRegExpr regex_'5cbextra'5fbegin'28group'7cfig'7cchar'29'5cb >>= withAttribute KeywordTok)) <|> ((pRegExpr regex_'5cbextra'5fend'28group'7cfig'7cchar'29'5cb >>= withAttribute KeywordTok)) <|> ((pRegExpr regex_'5cb'28def'7cvardef'29'5cb >>= withAttribute KeywordTok)) <|> ((pRegExpr regex_'5cbenddef'5cb >>= withAttribute KeywordTok)) <|> ((pRegExpr regex_'5cbif'5cb >>= withAttribute KeywordTok)) <|> ((pRegExpr regex_'5cbfi'5cb >>= withAttribute KeywordTok)) <|> ((pRegExpr regex_'5cb'28for'7cforsuffixes'7cforever'29'5cb >>= withAttribute KeywordTok)) <|> ((pRegExpr regex_'5cbendfor'5cb >>= withAttribute KeywordTok)) <|> (currentContext >>= \x -> guard (x == ("Metapost/Metafont","Normal Text")) >> pDefault >>= withAttribute NormalTok)) parseRules ("Metapost/Metafont","string") = (((pDetectIdentifier >>= withAttribute StringTok)) <|> ((pDetect2Chars False '\\' '"' >>= withAttribute StringTok)) <|> ((pDetect2Chars False '\\' '\\' >>= withAttribute StringTok)) <|> ((pDetectChar False '"' >>= withAttribute StringTok) >>~ (popContext)) <|> (currentContext >>= \x -> guard (x == ("Metapost/Metafont","string")) >> pDefault >>= withAttribute StringTok)) parseRules ("Metapost/Metafont","TeXMode") = (((pDetectChar False '\\' >>= withAttribute NormalTok) >>~ pushContext ("Metapost/Metafont","ContrSeq")) <|> ((pDetectChar False '$' >>= withAttribute NormalTok) >>~ pushContext ("Metapost/Metafont","MathMode")) <|> ((pString False "\\(" >>= withAttribute NormalTok) >>~ pushContext ("Metapost/Metafont","MathMode")) <|> ((pRegExpr regex_'5cbetex'5cb >>= withAttribute KeywordTok) >>~ (popContext)) <|> (currentContext >>= \x -> guard (x == ("Metapost/Metafont","TeXMode")) >> pDefault >>= withAttribute NormalTok)) parseRules ("Metapost/Metafont","ContrSeq") = (((pString False "verb*" >>= withAttribute NormalTok) >>~ pushContext ("Metapost/Metafont","Verb")) <|> ((pRegExpr regex_verb'28'3f'3d'5b'5ea'2dzA'2dZ'5d'29 >>= withAttribute NormalTok) >>~ pushContext ("Metapost/Metafont","Verb")) <|> ((pDetectChar False '\215' >>= withAttribute NormalTok)) <|> ((pRegExpr regex_'5ba'2dzA'2dZ'5d'2b'28'5c'2b'3f'7c'5c'2a'7b0'2c3'7d'29 >>= withAttribute NormalTok) >>~ (popContext)) <|> ((pRegExpr regex_'5b'5ea'2dzA'2dZ'5d >>= withAttribute NormalTok) >>~ (popContext)) <|> (currentContext >>= \x -> guard (x == ("Metapost/Metafont","ContrSeq")) >> pDefault >>= withAttribute NormalTok)) parseRules ("Metapost/Metafont","ToEndOfLine") = (currentContext >>= \x -> guard (x == ("Metapost/Metafont","ToEndOfLine")) >> pDefault >>= withAttribute NormalTok) parseRules ("Metapost/Metafont","Verb") = (((pRegExprDynamic "(.)" >>= withAttribute NormalTok) >>~ pushContext ("Metapost/Metafont","VerbEnd")) <|> (currentContext >>= \x -> guard (x == ("Metapost/Metafont","Verb")) >> pDefault >>= withAttribute NormalTok)) parseRules ("Metapost/Metafont","VerbEnd") = (((pString True "%1" >>= withAttribute NormalTok) >>~ (popContext >> popContext >> popContext)) <|> ((pDetectChar False '\215' >>= withAttribute NormalTok)) <|> ((pRegExprDynamic "[^%1\\xd7]*" >>= withAttribute NormalTok)) <|> (currentContext >>= \x -> guard (x == ("Metapost/Metafont","VerbEnd")) >> pDefault >>= withAttribute NormalTok)) parseRules ("Metapost/Metafont","MathMode") = (((pString False "$$" >>= withAttribute AlertTok)) <|> ((pDetectChar False '\\' >>= withAttribute NormalTok) >>~ pushContext ("Metapost/Metafont","MathContrSeq")) <|> ((pDetectChar False '$' >>= withAttribute NormalTok) >>~ (popContext)) <|> ((pDetect2Chars False '\\' ')' >>= withAttribute NormalTok) >>~ (popContext)) <|> ((pDetect2Chars False '\\' ']' >>= withAttribute AlertTok)) <|> (currentContext >>= \x -> guard (x == ("Metapost/Metafont","MathMode")) >> pDefault >>= withAttribute NormalTok)) parseRules ("Metapost/Metafont","MathContrSeq") = (((pDetectChar False '\215' >>= withAttribute NormalTok)) <|> ((pRegExpr regex_'5ba'2dzA'2dZ'5d'2b'5c'2a'3f >>= withAttribute NormalTok) >>~ (popContext)) <|> ((pRegExpr regex_'5b'5ea'2dzA'2dZ'5d >>= withAttribute NormalTok) >>~ (popContext)) <|> (currentContext >>= \x -> guard (x == ("Metapost/Metafont","MathContrSeq")) >> pDefault >>= withAttribute NormalTok)) parseRules ("Metapost/Metafont","Comment") = (((pRegExpr regex_'28FIXME'7cTODO'29'3a'3f >>= withAttribute AlertTok)) <|> ((pDetectChar False '\215' >>= withAttribute NormalTok)) <|> (currentContext >>= \x -> guard (x == ("Metapost/Metafont","Comment")) >> pDefault >>= withAttribute CommentTok)) parseRules x = parseRules ("Metapost/Metafont","Normal Text") <|> fail ("Unknown context" ++ show x)