{-# LANGUAGE OverloadedStrings #-} module Skylighting.Syntax.Mips (syntax) where import Skylighting.Types import Data.Map import Skylighting.Regex import qualified Data.Set syntax :: Syntax syntax = Syntax { sName = "MIPS Assembler" , sFilename = "mips.xml" , sShortname = "Mips" , sContexts = fromList [ ( "normal" , Context { cName = "normal" , cSyntax = "MIPS Assembler" , cRules = [ Rule { rMatcher = Keyword KeywordAttr { keywordCaseSensitive = False , keywordDelims = Data.Set.fromList "\t\n !%&()*+,-/:;<=>?[\\]^{|}~" } (makeWordSet False [ "abs.d" , "abs.s" , "add" , "add.d" , "add.s" , "addi" , "addiu" , "addu" , "and" , "andi" , "bc0f" , "bc0t" , "bc1f" , "bc1t" , "bc2f" , "bc2t" , "bc3f" , "bc3t" , "beq" , "bgez" , "bgezal" , "bgtz" , "blez" , "bltz" , "bltzal" , "bne" , "break" , "c.eq.d" , "c.eq.s" , "c.le.d" , "c.le.s" , "c.lt.d" , "c.lt.s" , "c.ole.d" , "c.ole.s" , "c.olt.d" , "c.olt.s" , "c.seq.d" , "c.seq.s" , "c.ueq.d" , "c.ueq.s" , "c.ule.d" , "c.ule.s" , "c.ult.d" , "c.ult.s" , "c.un.d" , "c.un.s" , "cvt.d.s" , "cvt.d.w" , "cvt.s.d" , "cvt.s.w" , "cvt.w.d" , "cvt.w.s" , "div.d" , "div.s" , "j" , "jal" , "jalr" , "jr" , "lb" , "lbu" , "lh" , "lhu" , "lui" , "lw" , "lwc0" , "lwc1" , "lwc2" , "lwc3" , "lwl" , "lwr" , "mfc0" , "mfc1" , "mfc2" , "mfc3" , "mfhi" , "mflo" , "mtc0" , "mtc1" , "mtc2" , "mtc3" , "mthi" , "mtlo" , "mul.d" , "mul.s" , "mult" , "multu" , "nor" , "or" , "ori" , "rfe" , "sb" , "sh" , "sll" , "sllv" , "slt" , "slti" , "sltiu" , "sra" , "srav" , "srl" , "srlv" , "sub" , "sub.d" , "sub.s" , "subu" , "sw" , "swc0" , "swc1" , "swc2" , "swc3" , "swcl" , "swl" , "swr" , "syscall" , "xor" , "xori" ]) , 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 [ "abs" , "b" , "beqz" , "bge" , "bgeu" , "bgt" , "bgtu" , "ble" , "bleu" , "blt" , "bltu" , "bnez" , "div" , "divu" , "l.d" , "l.s" , "la" , "ld" , "li" , "li.d" , "li.s" , "mfc0.d" , "mfc1.d" , "mfc2.d" , "mfc3.d" , "mov.d" , "mov.s" , "move" , "mul" , "mulo" , "mulou" , "neg" , "neg.d" , "neg.s" , "negu" , "nop" , "not" , "rem" , "remu" , "rol" , "ror" , "s.d" , "s.s" , "sd" , "seq" , "sge" , "sgeu" , "sgt" , "sgtu" , "sle" , "sleu" , "sne" , "ulh" , "ulhu" , "ulw" , "ush" , "usw" ]) , rAttribute = FunctionTok , 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 [ "$0" , "$1" , "$10" , "$11" , "$12" , "$13" , "$14" , "$15" , "$16" , "$17" , "$18" , "$19" , "$2" , "$20" , "$21" , "$22" , "$23" , "$24" , "$25" , "$26" , "$27" , "$28" , "$29" , "$3" , "$30" , "$31" , "$4" , "$5" , "$6" , "$7" , "$8" , "$9" , "$t0" , "$t1" , "$t2" , "$t3" , "$t4" , "$t5" , "$t6" , "$t7" , "$t8" , "$t9" , "$zero" ]) , rAttribute = DataTypeTok , 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 [ "$a0" , "$a1" , "$a2" , "$a3" , "$at" , "$fp" , "$gp" , "$k0" , "$k1" , "$ra" , "$s0" , "$s1" , "$s2" , "$s3" , "$s4" , "$s5" , "$s6" , "$s7" , "$sp" , "$v0" , "$v1" ]) , rAttribute = DataTypeTok , 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 [ "$f0" , "$f1" , "$f10" , "$f11" , "$f12" , "$f13" , "$f14" , "$f15" , "$f16" , "$f17" , "$f18" , "$f19" , "$f2" , "$f20" , "$f21" , "$f22" , "$f23" , "$f24" , "$f25" , "$f26" , "$f27" , "$f28" , "$f29" , "$f3" , "$f30" , "$f31" , "$f4" , "$f5" , "$f6" , "$f7" , "$f8" , "$f9" ]) , rAttribute = FloatTok , 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 [ ".data" , ".kdata" , ".ktext" , ".text" ]) , 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 [ ".align" , ".ascii" , ".asciiz" , ".byte" , ".double" , ".extern" , ".float" , ".globl" , ".half" , ".sdata" , ".set" , ".space" , ".word" ]) , rAttribute = DataTypeTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "#\\s*BEGIN.*$" , reCompiled = Just (compileRegex True "#\\s*BEGIN.*$") , reCaseSensitive = True } , rAttribute = RegionMarkerTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = True , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "#\\s*END.*$" , reCompiled = Just (compileRegex True "#\\s*END.*$") , reCaseSensitive = True } , rAttribute = RegionMarkerTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = True , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "#.*$" , reCompiled = Just (compileRegex True "#.*$") , reCaseSensitive = True } , rAttribute = CommentTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "[\\w_\\.]+:" , reCompiled = Just (compileRegex True "[\\w_\\.]+:") , reCaseSensitive = True } , rAttribute = OtherTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = True , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = DetectChar '"' , rAttribute = StringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "MIPS Assembler" , "string" ) ] } , Rule { rMatcher = Float , rAttribute = FloatTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = HlCOct , rAttribute = BaseNTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = HlCHex , rAttribute = BaseNTok , 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 = [] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "string" , Context { cName = "string" , cSyntax = "MIPS Assembler" , cRules = [ Rule { rMatcher = RegExpr RE { reString = "\\\\." , reCompiled = Just (compileRegex True "\\\\.") , reCaseSensitive = True } , rAttribute = CharTok , 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 = [ Pop ] } ] , cAttribute = StringTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) ] , sAuthor = "Dominik Haumann (dhdev@gmx.de)" , sVersion = "2" , sLicense = "LGPL" , sExtensions = [ "*.s" ] , sStartingContext = "normal" }