{-# LANGUAGE OverloadedStrings #-} module Skylighting.Syntax.Modula3 (syntax) where import Skylighting.Types syntax :: Syntax syntax = read $! "Syntax {sName = \"Modula-3\", sFilename = \"modula-3.xml\", sShortname = \"Modula3\", sContexts = fromList [(\"Comment2\",Context {cName = \"Comment2\", cSyntax = \"Modula-3\", cRules = [Rule {rMatcher = Detect2Chars '(' '*', rAttribute = CommentTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Modula-3\",\"Comment2\")]},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}),(\"Normal\",Context {cName = \"Normal\", cSyntax = \"Modula-3\", cRules = [Rule {rMatcher = RegExpr (RE {reString = \"PROCEDURE[\\\\s].*\\\\(\", reCaseSensitive = True}), rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"END\\\\s*[A-Za-z][A-Za-z0-9_]*\\\\;\", reCaseSensitive = True}), rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"\\\\b(RECORD|OBJECT|TRY|WHILE|FOR|REPEAT|LOOP|IF|CASE|WITH)\\\\b\", reCaseSensitive = True}), rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"\\\\b(END;|END)\\\\b\", reCaseSensitive = True}), rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = Keyword (KeywordAttr {keywordCaseSensitive = True, keywordDelims = fromList \"\\t\\n !%&()*+,-/:;<=>?[\\\\]^{|}~\"}) (CaseSensitiveWords (fromList [\"ANY\",\"ARRAY\",\"AS\",\"BEGIN\",\"BITS\",\"BRANDED\",\"BY\",\"CASE\",\"CONST\",\"DO\",\"ELSE\",\"ELSIF\",\"END\",\"EVAL\",\"EXCEPT\",\"EXCEPTION\",\"EXIT\",\"EXPORTS\",\"FINALLY\",\"FOR\",\"FROM\",\"GENERIC\",\"IF\",\"IMPORT\",\"INTERFACE\",\"LOCK\",\"LOOP\",\"METHODS\",\"MODULE\",\"OBJECT\",\"OF\",\"OVERRIDES\",\"PROCEDURE\",\"RAISE\",\"RAISES\",\"READONLY\",\"RECORD\",\"REF\",\"REPEAT\",\"RETURN\",\"REVEAL\",\"ROOT\",\"SET\",\"THEN\",\"TO\",\"TRY\",\"TYPE\",\"TYPECASE\",\"UNSAFE\",\"UNTIL\",\"UNTRACED\",\"VALUE\",\"VAR\",\"WHILE\",\"WITH\"])), rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = Keyword (KeywordAttr {keywordCaseSensitive = True, keywordDelims = fromList \"\\t\\n !%&()*+,-/:;<=>?[\\\\]^{|}~\"}) (CaseSensitiveWords (fromList [\"#\",\"&\",\"(\",\")\",\"*\",\"+\",\",\",\"-\",\".\",\"..\",\"/\",\":\",\":=\",\";\",\"<\",\"<:\",\"<=\",\"=\",\"=>\",\">\",\">=\",\"AND\",\"DIV\",\"IN\",\"MOD\",\"NOT\",\"OR\",\"[\",\"]\",\"^\",\"{\",\"|\",\"}\"])), rAttribute = KeywordTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = Keyword (KeywordAttr {keywordCaseSensitive = True, keywordDelims = fromList \"\\t\\n !%&()*+,-/:;<=>?[\\\\]^{|}~\"}) (CaseSensitiveWords (fromList [\"ADDRESS\",\"BOOLEAN\",\"CARDINAL\",\"CHAR\",\"EXTENDED\",\"INTEGER\",\"LONGREAL\",\"MUTEX\",\"NULL\",\"REAL\",\"REFANY\",\"T\",\"TEXT\"])), rAttribute = DataTypeTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = Keyword (KeywordAttr {keywordCaseSensitive = True, keywordDelims = fromList \"\\t\\n !%&()*+,-/:;<=>?[\\\\]^{|}~\"}) (CaseSensitiveWords (fromList [\"FALSE\",\"NIL\",\"TRUE\"])), rAttribute = DecValTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = Keyword (KeywordAttr {keywordCaseSensitive = True, keywordDelims = fromList \"\\t\\n !%&()*+,-/:;<=>?[\\\\]^{|}~\"}) (CaseSensitiveWords (fromList [\"ABS\",\"ADR\",\"ADRSIZE\",\"BITSIZE\",\"BYTESIZE\",\"CEILING\",\"DEC\",\"DISPOSE\",\"FIRST\",\"FLOAT\",\"FLOOR\",\"INC\",\"ISTYPE\",\"LAST\",\"LOOPHOLE\",\"MAX\",\"MIN\",\"NARROW\",\"NEW\",\"NUMBER\",\"ORD\",\"ROUND\",\"SUBARRAY\",\"TRUNC\",\"TYPECODE\",\"VAL\"])), rAttribute = FunctionTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = Keyword (KeywordAttr {keywordCaseSensitive = True, keywordDelims = fromList \"\\t\\n !%&()*+,-/:;<=>?[\\\\]^{|}~\"}) (CaseSensitiveWords (fromList [\"Env\",\"Env.Count\",\"Env.Get\",\"Env.GetNth\",\"Fmt\",\"Fmt.Bool\",\"Fmt.Char\",\"Fmt.Extended\",\"Fmt.F\",\"Fmt.FN\",\"Fmt.Int\",\"Fmt.LongReal\",\"Fmt.Pad\",\"Fmt.Real\",\"Fmt.Unsigned\",\"IO\",\"IO.EOF\",\"IO.GetChar\",\"IO.GetInt\",\"IO.GetLine\",\"IO.GetReal\",\"IO.GetWideChar\",\"IO.OpenRead\",\"IO.OpenWrite\",\"IO.Put\",\"IO.PutChar\",\"IO.PutInt\",\"IO.PutReal\",\"IO.PutWideChar\",\"Lex\",\"Lex.Bool\",\"Lex.Extended\",\"Lex.Int\",\"Lex.LongReal\",\"Lex.Match\",\"Lex.Real\",\"Lex.Scan\",\"Lex.Skip\",\"Lex.Unsigned\",\"Params\",\"Params.Count\",\"Params.Get\",\"Rd\",\"Rd.CharsReady\",\"Rd.Close\",\"Rd.Closed\",\"Rd.EOF\",\"Rd.GetChar\",\"Rd.GetLine\",\"Rd.GetSub\",\"Rd.GetSubLine\",\"Rd.GetText\",\"Rd.GetWideChar\",\"Rd.GetWideLine\",\"Rd.GetWideSub\",\"Rd.GetWideSubLine\",\"Rd.GetWideText\",\"Rd.Index\",\"Rd.Intermittend\",\"Rd.Length\",\"Rd.Seek\",\"Rd.Seekable\",\"Rd.UnGetChar\",\"Scan\",\"Scan.Bool\",\"Scan.Extended\",\"Scan.Int\",\"Scan.LongReal\",\"Scan.Real\",\"Scan.Unsigned\",\"Text\",\"Text.Cat\",\"Text.Compare\",\"Text.Empty\",\"Text.Equal\",\"Text.FindChar\",\"Text.FindCharR\",\"Text.FindWideChar\",\"Text.FindWideCharR\",\"Text.FromChars\",\"Text.FromWideChars\",\"Text.GetChar\",\"Text.GetWideChar\",\"Text.HasWideChar\",\"Text.Hash\",\"Text.Length\",\"Text.SetChars\",\"Text.SetWideChars\",\"Text.Sub\",\"Wr\",\"Wr.Buffered\",\"Wr.Close\",\"Wr.Closed\",\"Wr.Flush\",\"Wr.Index\",\"Wr.Length\",\"Wr.PutChar\",\"Wr.PutString\",\"Wr.PutText\",\"Wr.PutWideChar\",\"Wr.PutWideString\",\"Wr.PutWideText\",\"Wr.Seek\",\"Wr.Seekable\"])), rAttribute = FunctionTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"\\\\b[\\\\+|\\\\-]{0,1}[0-9]{1,}\\\\.[0-9]{1,}([E|e|D|d|X|x][\\\\+|\\\\-]{0,1}[0-9]{1,}){0,1}\\\\b\", reCaseSensitive = True}), rAttribute = FloatTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = []},Rule {rMatcher = RegExpr (RE {reString = \"\\\\b([\\\\+|\\\\-]{0,1}[0-9]{1,}|([2-9]|1[0-6])\\\\_[0-9A-Fa-f]{1,})\\\\b\", reCaseSensitive = True}), rAttribute = BaseNTok, 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 (\"Modula-3\",\"String1\")]},Rule {rMatcher = RegExpr (RE {reString = \"\\\\'(.|\\\\\\\\[ntrf\\\\\\\\'\\\"]|\\\\\\\\[0-7]{3})\\\\'\", reCaseSensitive = True}), rAttribute = CharTok, 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 (\"Modula-3\",\"Prep1\")]},Rule {rMatcher = Detect2Chars '(' '*', rAttribute = CommentTok, rIncludeAttribute = False, rDynamic = False, rCaseSensitive = True, rChildren = [], rLookahead = False, rFirstNonspace = False, rColumn = Nothing, rContextSwitch = [Push (\"Modula-3\",\"Comment2\")]}], cAttribute = NormalTok, cLineEmptyContext = [], cLineEndContext = [], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False}),(\"Prep1\",Context {cName = \"Prep1\", cSyntax = \"Modula-3\", 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 = [], cLineBeginContext = [], cFallthrough = False, cFallthroughContext = [], cDynamic = False}),(\"String1\",Context {cName = \"String1\", cSyntax = \"Modula-3\", 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 = \"\", sVersion = \"1.01\", sLicense = \"LGPL\", sExtensions = [\"*.m3\",\"*.i3\",\"*.ig\",\"*.mg\"], sStartingContext = \"Normal\"}"