{-# LANGUAGE OverloadedStrings #-} module Skylighting.Syntax.Pascal (syntax) where import Skylighting.Types import Data.Map import Skylighting.Regex import qualified Data.Set syntax :: Syntax syntax = Syntax { sName = "Pascal" , sFilename = "pascal.xml" , sShortname = "Pascal" , sContexts = fromList [ ( "CharNum" , Context { cName = "CharNum" , cSyntax = "Pascal" , cRules = [ Rule { rMatcher = DetectChar '$' , rAttribute = BaseNTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Pascal" , "HexCharNum" ) ] } , Rule { rMatcher = RegExpr RE { reString = "[^0-9]" , reCompiled = Just (compileRegex True "[^0-9]") , reCaseSensitive = True } , rAttribute = StringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } ] , cAttribute = StringTok , cLineEmptyContext = [] , cLineEndContext = [ Pop ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "Comment1" , Context { cName = "Comment1" , cSyntax = "Pascal" , cRules = [ Rule { rMatcher = Keyword KeywordAttr { keywordCaseSensitive = False , keywordDelims = Data.Set.fromList "\t\n !%&()*+,-./:;<=>?[\\]^{|}~" } (makeWordSet False [ "###" , "FIXME" , "NOTE" , "TODO" ]) , rAttribute = AlertTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = DetectChar '}' , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } ] , cAttribute = CommentTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "Comment2" , Context { cName = "Comment2" , cSyntax = "Pascal" , cRules = [ Rule { rMatcher = Keyword KeywordAttr { keywordCaseSensitive = False , keywordDelims = Data.Set.fromList "\t\n !%&()*+,-./:;<=>?[\\]^{|}~" } (makeWordSet False [ "###" , "FIXME" , "NOTE" , "TODO" ]) , rAttribute = AlertTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Detect2Chars '*' ')' , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } ] , cAttribute = CommentTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "Comment3" , Context { cName = "Comment3" , cSyntax = "Pascal" , cRules = [ Rule { rMatcher = Keyword KeywordAttr { keywordCaseSensitive = False , keywordDelims = Data.Set.fromList "\t\n !%&()*+,-./:;<=>?[\\]^{|}~" } (makeWordSet False [ "###" , "FIXME" , "NOTE" , "TODO" ]) , rAttribute = AlertTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = CommentTok , cLineEmptyContext = [] , cLineEndContext = [ Pop ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "Hex" , Context { cName = "Hex" , cSyntax = "Pascal" , cRules = [ Rule { rMatcher = RegExpr RE { reString = "[^a-fA-F0-9]" , reCompiled = Just (compileRegex True "[^a-fA-F0-9]") , reCaseSensitive = True } , rAttribute = BaseNTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } ] , cAttribute = BaseNTok , cLineEmptyContext = [] , cLineEndContext = [ Pop ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "HexCharNum" , Context { cName = "HexCharNum" , cSyntax = "Pascal" , cRules = [ Rule { rMatcher = RegExpr RE { reString = "[^a-fA-F0-9]" , reCompiled = Just (compileRegex True "[^a-fA-F0-9]") , reCaseSensitive = True } , rAttribute = BaseNTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop , Pop ] } ] , cAttribute = BaseNTok , cLineEmptyContext = [] , cLineEndContext = [ Pop ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "Normal" , Context { cName = "Normal" , cSyntax = "Pascal" , cRules = [ Rule { rMatcher = RegExpr RE { reString = "\\b(begin|case|record)(?=(\\{[^}]*(\\}|$)|\\(\\*.*(\\*\\)|$))*([\\s]|$|//))" , reCompiled = Just (compileRegex False "\\b(begin|case|record)(?=(\\{[^}]*(\\}|$)|\\(\\*.*(\\*\\)|$))*([\\s]|$|//))") , reCaseSensitive = False } , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\\b((object|class)(?=(\\(.*\\))?(\\{[^}]*(\\}|$)|\\(\\*.*(\\*\\)|$))*;?([\\s]|$|//))|try(?=(\\{[^}]*(\\}|$)|\\(\\*.*(\\*\\)|$))*([\\s]|$|//)))" , reCompiled = Just (compileRegex False "\\b((object|class)(?=(\\(.*\\))?(\\{[^}]*(\\}|$)|\\(\\*.*(\\*\\)|$))*;?([\\s]|$|//))|try(?=(\\{[^}]*(\\}|$)|\\(\\*.*(\\*\\)|$))*([\\s]|$|//)))") , reCaseSensitive = False } , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "\\bend(?=((\\{[^}]*(\\}|$)|\\(\\*.*(\\*\\)|$))*)([.;\\s]|$)|//|$)" , reCompiled = Just (compileRegex False "\\bend(?=((\\{[^}]*(\\}|$)|\\(\\*.*(\\*\\)|$))*)([.;\\s]|$)|//|$)") , reCaseSensitive = False } , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = False , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Keyword KeywordAttr { keywordCaseSensitive = False , keywordDelims = Data.Set.fromList "\t\n !%&()*+,-./:;<=>?[\\]^{|}~" } (makeWordSet False [ "and" , "array" , "asm" , "at" , "automated" , "break" , "case" , "const" , "continue" , "dispinterface" , "dispose" , "div" , "do" , "downto" , "else" , "exit" , "false" , "file" , "finalization" , "for" , "function" , "goto" , "if" , "in" , "initialization" , "label" , "library" , "mod" , "new" , "nil" , "not" , "of" , "operator" , "or" , "packed" , "procedure" , "program" , "published" , "record" , "repeat" , "resourcestring" , "self" , "set" , "then" , "to" , "true" , "type" , "unit" , "until" , "uses" , "var" , "while" , "with" , "xor" ]) , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Keyword KeywordAttr { keywordCaseSensitive = False , keywordDelims = Data.Set.fromList "\t\n !%&()*+,-./:;<=>?[\\]^{|}~" } (makeWordSet False [ "abstract" , "as" , "bindable" , "constructor" , "destructor" , "except" , "export" , "finally" , "implementation" , "import" , "inherited" , "inline" , "interface" , "is" , "module" , "on" , "only" , "otherwise" , "override" , "private" , "property" , "protected" , "public" , "qualified" , "raise" , "read" , "restricted" , "shl" , "shr" , "threadvar" , "try" , "virtual" , "write" ]) , rAttribute = KeywordTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Keyword KeywordAttr { keywordCaseSensitive = False , keywordDelims = Data.Set.fromList "\t\n !%&()*+,-./:;<=>?[\\]^{|}~" } (makeWordSet False [ "AnsiChar" , "AnsiString" , "Boolean" , "Byte" , "ByteBool" , "Cardinal" , "Char" , "Comp" , "Currency" , "Double" , "DWord" , "Extended" , "File" , "Int64" , "Integer" , "LongBool" , "LongInt" , "LongWord" , "Pointer" , "QWord" , "Real" , "Real48" , "ShortInt" , "ShortString" , "Single" , "SmallInt" , "String" , "Text" , "Variant" , "WideChar" , "WideString" , "Word" , "WordBool" ]) , rAttribute = DataTypeTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Float , rAttribute = DecValTok , 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 = BaseNTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Pascal" , "Hex" ) ] } , Rule { rMatcher = DetectChar '#' , rAttribute = StringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Pascal" , "CharNum" ) ] } , Rule { rMatcher = DetectChar '\'' , rAttribute = StringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Pascal" , "String" ) ] } , Rule { rMatcher = StringDetect "(*$" , rAttribute = OtherTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Pascal" , "Prep1" ) ] } , Rule { rMatcher = Detect2Chars '{' '$' , rAttribute = OtherTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Pascal" , "Prep2" ) ] } , Rule { rMatcher = DetectChar '{' , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Pascal" , "Comment1" ) ] } , Rule { rMatcher = Detect2Chars '(' '*' , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Pascal" , "Comment2" ) ] } , Rule { rMatcher = Detect2Chars '/' '/' , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "Pascal" , "Comment3" ) ] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "Prep1" , Context { cName = "Prep1" , cSyntax = "Pascal" , cRules = [ Rule { rMatcher = Detect2Chars '*' ')' , rAttribute = OtherTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } ] , cAttribute = OtherTok , cLineEmptyContext = [] , cLineEndContext = [ Pop ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "Prep2" , Context { cName = "Prep2" , cSyntax = "Pascal" , cRules = [ Rule { rMatcher = DetectChar '}' , rAttribute = OtherTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } ] , cAttribute = OtherTok , cLineEmptyContext = [] , cLineEndContext = [ Pop ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "String" , Context { cName = "String" , cSyntax = "Pascal" , 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 = [ Pop ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) ] , sAuthor = "Unnamed people and Liu Sizhuang(oldherl@gmail.com)" , sVersion = "2" , sLicense = "" , sExtensions = [ "*.p" , "*.pas" , "*.pp" ] , sStartingContext = "Normal" }