{- This module was generated from data in the Kate syntax highlighting file mips.xml, version 1.03, by Dominik Haumann (dhdev@gmx.de) -} module Text.Highlighting.Kate.Syntax.Mips (highlight, parseExpression, syntaxName, syntaxExtensions) where import Text.Highlighting.Kate.Types import Text.Highlighting.Kate.Common import Text.ParserCombinators.Parsec hiding (State) import Data.Map (fromList) import Control.Monad.State import Data.Char (isSpace) import Data.Maybe (fromMaybe) import qualified Data.Set as Set -- | Full name of language. syntaxName :: String syntaxName = "MIPS Assembler" -- | Filename extensions for this language. syntaxExtensions :: String syntaxExtensions = "*.s;" -- | 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 parseExpressionInternal pEndLine -- | Parse an expression using appropriate local context. parseExpression :: KateParser Token parseExpression = do st <- getState let oldLang = synStLanguage st setState $ st { synStLanguage = "MIPS Assembler" } context <- currentContext <|> (pushContext "normal" >> currentContext) result <- parseRules context optional $ eof >> pEndLine updateState $ \st -> st { synStLanguage = oldLang } return result startingState = SyntaxState {synStContexts = fromList [("MIPS Assembler",["normal"])], synStLanguage = "MIPS Assembler", synStLineNumber = 0, synStPrevChar = '\n', synStPrevNonspace = False, synStCaseSensitive = True, synStKeywordCaseSensitive = False, synStCaptures = []} pEndLine = do updateState $ \st -> st{ synStPrevNonspace = False } context <- currentContext case context of "normal" -> return () "string" -> return () _ -> 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) parseExpressionInternal = do context <- currentContext parseRules context <|> (pDefault >>= withAttribute (fromMaybe NormalTok $ lookup context defaultAttributes)) list_type = Set.fromList $ words $ ".align .ascii .asciiz .byte .double .extern .float .globl .half .sdata .set .space .word" list_section = Set.fromList $ words $ ".data .kdata .ktext .text" list_hardware = Set.fromList $ words $ "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.seq.s c.seq.d c.ueq.s c.ueq.d c.olt.d c.olt.s c.ole.d c.ole.s c.ult.d c.ult.s c.ule.d c.ule.s c.le.d c.le.s c.lt.d c.lt.s c.un.s c.un.d 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 sw swcl swl swr sll sllv slt slti sltiu sra srav srl srlv sub sub.d sub.s subu sw swc0 swc1 swc2 swc3 swl swr syscall xor xori" list_pseudo = Set.fromList $ words $ "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" list_register1 = Set.fromList $ words $ "$0 $1 $2 $3 $4 $5 $6 $7 $8 $9 $10 $11 $12 $13 $14 $15 $16 $17 $18 $19 $20 $21 $22 $23 $24 $25 $26 $27 $28 $29 $30 $31 $zero $t0 $t1 $t2 $t3 $t4 $t5 $t6 $t7 $t8 $t9" list_register2 = Set.fromList $ words $ "$v0 $v1 $a0 $a1 $a2 $a3 $k0 $k1 $at $gp $sp $fp $s0 $s1 $s2 $s3 $s4 $s5 $s6 $s7 $ra" list_fp = Set.fromList $ words $ "$f0 $f1 $f2 $f3 $f4 $f5 $f6 $f7 $f8 $f9 $f10 $f11 $f12 $f13 $f14 $f15 $f16 $f17 $f18 $f19 $f20 $f21 $f22 $f23 $f24 $f25 $f26 $f27 $f28 $f29 $f30 $f31" regex_'23'5cs'2aBEGIN'2e'2a'24 = compileRegex "#\\s*BEGIN.*$" regex_'23'5cs'2aEND'2e'2a'24 = compileRegex "#\\s*END.*$" regex_'23'2e'2a'24 = compileRegex "#.*$" regex_'5b'5cw'5f'5c'2e'5d'2b'3a = compileRegex "[\\w_\\.]+:" regex_'5c'5c'2e = compileRegex "\\\\." defaultAttributes = [("normal",NormalTok),("string",StringTok)] parseRules "normal" = (((pKeyword " \n\t():!+,-<=>%&*/;?[]^{|}~\\" list_hardware >>= withAttribute KeywordTok)) <|> ((pKeyword " \n\t():!+,-<=>%&*/;?[]^{|}~\\" list_pseudo >>= withAttribute FunctionTok)) <|> ((pKeyword " \n\t():!+,-<=>%&*/;?[]^{|}~\\" list_register1 >>= withAttribute DataTypeTok)) <|> ((pKeyword " \n\t():!+,-<=>%&*/;?[]^{|}~\\" list_register2 >>= withAttribute DataTypeTok)) <|> ((pKeyword " \n\t():!+,-<=>%&*/;?[]^{|}~\\" list_fp >>= withAttribute FloatTok)) <|> ((pKeyword " \n\t():!+,-<=>%&*/;?[]^{|}~\\" list_section >>= withAttribute KeywordTok)) <|> ((pKeyword " \n\t():!+,-<=>%&*/;?[]^{|}~\\" list_type >>= withAttribute DataTypeTok)) <|> ((pFirstNonSpace >> pRegExpr regex_'23'5cs'2aBEGIN'2e'2a'24 >>= withAttribute RegionMarkerTok)) <|> ((pFirstNonSpace >> pRegExpr regex_'23'5cs'2aEND'2e'2a'24 >>= withAttribute RegionMarkerTok)) <|> ((pRegExpr regex_'23'2e'2a'24 >>= withAttribute CommentTok)) <|> ((pFirstNonSpace >> pRegExpr regex_'5b'5cw'5f'5c'2e'5d'2b'3a >>= withAttribute OtherTok)) <|> ((pDetectChar False '"' >>= withAttribute StringTok) >>~ pushContext "string") <|> ((pFloat >>= withAttribute FloatTok)) <|> ((pHlCOct >>= withAttribute BaseNTok)) <|> ((pHlCHex >>= withAttribute BaseNTok)) <|> ((pInt >>= withAttribute DecValTok))) parseRules "string" = (((pRegExpr regex_'5c'5c'2e >>= withAttribute CharTok)) <|> ((pDetectChar False '"' >>= withAttribute StringTok) >>~ (popContext))) parseRules "" = parseRules "normal" parseRules x = fail $ "Unknown context" ++ x