{-# LANGUAGE OverloadedStrings #-} module Skylighting.Syntax.Postscript (syntax) where import Skylighting.Types import Data.Map import Skylighting.Regex import qualified Data.Set syntax :: Syntax syntax = Syntax { sName = "PostScript" , sFilename = "postscript.xml" , sShortname = "Postscript" , sContexts = fromList [ ( "Comment" , Context { cName = "Comment" , cSyntax = "PostScript" , cRules = [] , cAttribute = CommentTok , cLineEmptyContext = [] , cLineEndContext = [ Pop ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "Header" , Context { cName = "Header" , cSyntax = "PostScript" , cRules = [] , cAttribute = OtherTok , cLineEmptyContext = [] , cLineEndContext = [ Pop ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "Normal" , Context { cName = "Normal" , cSyntax = "PostScript" , cRules = [ Rule { rMatcher = Keyword KeywordAttr { keywordCaseSensitive = False , keywordDelims = Data.Set.fromList "\t\n !%&()*+,-./:;<=>?[\\]^{|}~" } (makeWordSet False [ "abs" , "add" , "aload" , "anchorsearch" , "and" , "arc" , "arcn" , "arct" , "arcto" , "array" , "ASCII85Decode" , "ASCII85Encode" , "ASCIIHexDecode" , "ASCIIHexEncode" , "ashow" , "astore" , "atan" , "awidthshow" , "banddevice" , "begin" , "bind" , "bitshift" , "bytesavailable" , "cachestatus" , "CCITTFaxDecode" , "CCITTFaxEncode" , "ceiling" , "charpath" , "CIEBasedA" , "CIEBasedABC" , "CIEBasedDEF" , "CIEBasedDEFG" , "clear" , "cleardictstack" , "cleartomark" , "clip" , "clippath" , "closefile" , "closepath" , "colorimage" , "concat" , "concatmatrix" , "condition" , "copy" , "copypage" , "cos" , "count" , "countdictstack" , "countexecstack" , "counttomark" , "Courier" , "Courier-Bold" , "Courier-BoldOblique" , "Courier-Oblique" , "cshow" , "currentblackgeneration" , "currentcacheparams" , "currentcmykcolor" , "currentcolor" , "currentcolorrendering" , "currentcolorscreen" , "currentcolorspace" , "currentcolortransfer" , "currentcontext" , "currentdash" , "currentdevparams" , "currentdict" , "currentfile" , "currentflat" , "currentfont" , "currentglobal" , "currentgray" , "currentgstate" , "currenthalftone" , "currenthalftonephase" , "currenthsbcolor" , "currentlinecap" , "currentlinejoin" , "currentlinewidth" , "currentmatrix" , "currentmiterlimit" , "currentobjectformat" , "currentoverprint" , "currentpacking" , "currentpagedevice" , "currentpoint" , "currentrgbcolor" , "currentscreen" , "currentshared" , "currentstrokeadjust" , "currentsystemparams" , "currenttransfer" , "currentundercolorremoval" , "currentuserparams" , "curveto" , "cvi" , "cvlit" , "cvn" , "cvr" , "cvrs" , "cvs" , "cvx" , "DCTDecode" , "DCTEncode" , "def" , "defaultmatrix" , "definefont" , "defineresource" , "defineusername" , "defineuserobject" , "deletefile" , "detach" , "DeviceCMYK" , "DeviceGray" , "deviceinfo" , "DeviceN" , "DeviceRGB" , "dict" , "dictstack" , "div" , "dtransform" , "dup" , "echo" , "end" , "eoclip" , "eofill" , "eoviewclip" , "eq" , "erasepage" , "errordict" , "exch" , "exec" , "execform" , "execstack" , "execuserobject" , "executeonly" , "exit" , "exp" , "false" , "file" , "filenameforall" , "fileposition" , "fill" , "filter" , "findencoding" , "findfont" , "findresource" , "flattenpath" , "floor" , "flush" , "flushfile" , "FontDirectory" , "for" , "forall" , "fork" , "framedevice" , "gcheck" , "ge" , "get" , "getinterval" , "globaldict" , "GlobalFontDirectory" , "glyphshow" , "grestore" , "grestoreall" , "gsave" , "gstate" , "gt" , "handleerror" , "Helvetica" , "Helvetica-Bold" , "Helvetica-BoldOblique" , "Helvetica-Oblique" , "identmatrix" , "idiv" , "idtransform" , "if" , "ifelse" , "image" , "imagemask" , "index" , "Indexed" , "ineofill" , "infill" , "initclip" , "initgraphics" , "initmatrix" , "initviewclip" , "instroke" , "inueofill" , "inufill" , "inustroke" , "invertmatrix" , "ISOLatin1Encoding" , "itransform" , "join" , "known" , "kshow" , "languagelevel" , "le" , "length" , "lineto" , "ln" , "load" , "lock" , "log" , "loop" , "lt" , "LZWDecode" , "LZWEncode" , "makefont" , "makepattern" , "mark" , "matrix" , "maxlength" , "mod" , "monitor" , "moveto" , "mul" , "ne" , "neg" , "newpath" , "noaccess" , "not" , "notify" , "null" , "nulldevice" , "NullEncode" , "or" , "packedarray" , "pathbbox" , "pathforall" , "Pattern" , "pop" , "print" , "printobject" , "product" , "pstack" , "put" , "putinterval" , "quit" , "rand" , "rcheck" , "rcurveto" , "read" , "readhexstring" , "readline" , "readonly" , "readstring" , "realtime" , "rectclip" , "rectfill" , "rectstroke" , "rectviewclip" , "renamefile" , "renderbands" , "repeat" , "resetfile" , "resourceforall" , "resourcestatus" , "restore" , "reversepath" , "revision" , "rlineto" , "rmoveto" , "roll" , "rootfont" , "rotate" , "round" , "rrand" , "run" , "RunLengthDecode" , "RunLengthEncode" , "save" , "scale" , "scalefont" , "scheck" , "search" , "selectfont" , "Separation" , "serialnumber" , "setbbox" , "setblackgeneration" , "setcachedevice" , "setcachedevice2" , "setcachelimit" , "setcacheparams" , "setcharwidth" , "setcmykcolor" , "setcolor" , "setcolorrendering" , "setcolorscreen" , "setcolorspace" , "setcolortransfer" , "setdash" , "setdevparams" , "setfileposition" , "setflat" , "setfont" , "setglobal" , "setgray" , "setgstate" , "sethalftone" , "sethalftonephase" , "sethsbcolor" , "setlinecap" , "setlinejoin" , "setlinewidth" , "setmatrix" , "setmiterlimit" , "setobjectformat" , "setoverprint" , "setpacking" , "setpagedevice" , "setpattern" , "setrgbcolor" , "setscreen" , "setshared" , "setstrokeadjust" , "setsystemparams" , "settransfer" , "setucacheparams" , "setundercolorremoval" , "setuserparams" , "setvmthreshold" , "shareddict" , "SharedFontDirectory" , "show" , "showpage" , "sin" , "sqrt" , "srand" , "stack" , "StandardEncoding" , "startjob" , "status" , "statusdict" , "stop" , "stopped" , "store" , "string" , "stringwidth" , "stroke" , "strokepath" , "sub" , "SubFileDecode" , "Symbol" , "systemdict" , "Times-Bold" , "Times-BoldItalic" , "Times-Italic" , "Times-Roman" , "token" , "transform" , "translate" , "true" , "truncate" , "type" , "uappend" , "ucache" , "ucachestatus" , "ueofill" , "ufill" , "undef" , "undefinefont" , "undefineresource" , "undefineuserobject" , "upath" , "userdict" , "UserObjects" , "usertime" , "ustroke" , "ustrokepath" , "version" , "viewclip" , "viewclippath" , "vmreclaim" , "vmstatus" , "wait" , "wcheck" , "where" , "widthshow" , "write" , "writehexstring" , "writeobject" , "writestring" , "wtranslation" , "xcheck" , "xor" , "xshow" , "xyshow" , "yield" , "yshow" ]) , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Detect2Chars '%' '!' , rAttribute = OtherTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "PostScript" , "Header" ) ] } , Rule { rMatcher = DetectChar '%' , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "PostScript" , "Comment" ) ] } , Rule { rMatcher = Float , rAttribute = FloatTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Int , rAttribute = DecValTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = DetectChar '(' , rAttribute = StringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "PostScript" , "String" ) ] } , Rule { rMatcher = RegExpr RE { reString = "\\/{1,2}[^\\s\\(\\)\\{\\}\\[\\]%/]*" , reCompiled = Just (compileRegex True "\\/{1,2}[^\\s\\(\\)\\{\\}\\[\\]%/]*") , reCaseSensitive = True } , rAttribute = DataTypeTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "String" , Context { cName = "String" , cSyntax = "PostScript" , cRules = [ Rule { rMatcher = DetectChar ')' , rAttribute = StringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } ] , cAttribute = StringTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) ] , sAuthor = "" , sVersion = "2" , sLicense = "" , sExtensions = [ "*.ps" , "*.ai" , "*.eps" ] , sStartingContext = "Normal" }