{- This module was generated from data in the Kate syntax highlighting file modula-3.xml, version 1.01,
   by   -}

module Text.Highlighting.Kate.Syntax.Modula3 ( highlight, parseExpression, syntaxName, syntaxExtensions ) where
import Text.Highlighting.Kate.Definitions
import Text.Highlighting.Kate.Common
import Text.ParserCombinators.Parsec
import Control.Monad (when)
import Data.Map (fromList)
import Data.Maybe (fromMaybe, maybeToList)

import qualified Data.Set as Set
-- | Full name of language.
syntaxName :: String
syntaxName = "Modula-3"

-- | Filename extensions for this language.
syntaxExtensions :: String
syntaxExtensions = "*.m3;*.i3;*.ig;*.mg;"

-- | Highlight source code using this syntax definition.
highlight :: String -> Either String [SourceLine]
highlight input =
  case runParser parseSource startingState "source" input of
    Left err     -> Left $ show err
    Right result -> Right result

-- | Parse an expression using appropriate local context.
parseExpression :: GenParser Char SyntaxState LabeledSource
parseExpression = do
  st <- getState
  let oldLang = synStLanguage st
  setState $ st { synStLanguage = "Modula-3" }
  context <- currentContext <|> (pushContext "Normal" >> currentContext)
  result <- parseRules context
  updateState $ \st -> st { synStLanguage = oldLang }
  return result

parseSource = do 
  lineContents <- lookAhead wholeLine
  updateState $ \st -> st { synStCurrentLine = lineContents }
  result <- manyTill parseSourceLine eof
  return $ map normalizeHighlighting result

startingState = SyntaxState {synStContexts = fromList [("Modula-3",["Normal"])], synStLanguage = "Modula-3", synStCurrentLine = "", synStCharsParsedInLine = 0, synStPrevChar = '\n', synStCaseSensitive = True, synStKeywordCaseSensitive = True, synStCaptures = []}

parseSourceLine = manyTill parseExpressionInternal pEndLine

pEndLine = do
  lookAhead $ newline <|> (eof >> return '\n')
  context <- currentContext
  case context of
    "Normal" -> return () >> pHandleEndLine
    "String1" -> (popContext) >> pEndLine
    "Comment2" -> return () >> pHandleEndLine
    "Prep1" -> return () >> pHandleEndLine
    _ -> pHandleEndLine

withAttribute attr txt = do
  when (null txt) $ fail "Parser matched no text"
  let labs = attr : maybeToList (lookup attr styles)
  st <- getState
  let oldCharsParsed = synStCharsParsedInLine st
  let prevchar = if null txt then '\n' else last txt
  updateState $ \st -> st { synStCharsParsedInLine = oldCharsParsed + length txt, synStPrevChar = prevchar } 
  return (labs, txt)

styles = [("Keyword","kw"),("Operator","kw"),("Type","dt"),("Integer","bn"),("Real","fl"),("Constant","dv"),("String","st"),("Char","ch"),("Pervasive","fu"),("StdLib","fu"),("Comment","co"),("Pragma","ot")]

parseExpressionInternal = do
  context <- currentContext
  parseRules context <|> (pDefault >>= withAttribute (fromMaybe "" $ lookup context defaultAttributes))

list_keywords = Set.fromList $ words $ "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"
list_operators = Set.fromList $ words $ "AND DIV IN MOD NOT OR + < # = ; .. : - > { } | := <: * <= ( ) ^ , => / >= [ ] . &"
list_types = Set.fromList $ words $ "ADDRESS BOOLEAN CARDINAL CHAR EXTENDED INTEGER LONGREAL MUTEX NULL REAL REFANY T TEXT"
list_constants = Set.fromList $ words $ "FALSE NIL TRUE"
list_pervasives = Set.fromList $ words $ "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"
list_stdlibs = Set.fromList $ words $ "Text Text.Length Text.Empty Text.Equal Text.Compare Text.Cat Text.Sub Text.Hash Text.HasWideChar Text.GetChar Text.GetWideChar Text.SetChars Text.SetWideChars Text.FromChars Text.FromWideChars Text.FindChar Text.FindWideChar Text.FindCharR Text.FindWideCharR Fmt Fmt.Bool Fmt.Char Fmt.Int Fmt.Unsigned Fmt.Real Fmt.LongReal Fmt.Extended Fmt.Pad Fmt.F Fmt.FN Scan Scan.Bool Scan.Int Scan.Unsigned Scan.Real Scan.LongReal Scan.Extended IO IO.Put IO.PutChar IO.PutWideChar IO.PutInt IO.PutReal IO.EOF IO.GetLine IO.GetChar IO.GetWideChar IO.GetInt IO.GetReal IO.OpenRead IO.OpenWrite Rd Rd.GetChar Rd.GetWideChar Rd.EOF Rd.UnGetChar Rd.CharsReady Rd.GetSub Rd.GetWideSub Rd.GetSubLine Rd.GetWideSubLine Rd.GetText Rd.GetWideText Rd.GetLine Rd.GetWideLine Rd.Seek Rd.Close Rd.Index Rd.Length Rd.Intermittend Rd.Seekable Rd.Closed Wr Wr.PutChar Wr.PutWideChar Wr.PutText Wr.PutWideText Wr.PutString Wr.PutWideString Wr.Seek Wr.Flush Wr.Close Wr.Length Wr.Index Wr.Seekable Wr.Closed Wr.Buffered Lex Lex.Scan Lex.Skip Lex.Match Lex.Bool Lex.Int Lex.Unsigned Lex.Real Lex.LongReal Lex.Extended Params Params.Count Params.Get Env Env.Count Env.Get Env.GetNth"

regex_PROCEDURE'5b'5cs'5d'2e'2a'5c'28 = compileRegex "PROCEDURE[\\s].*\\("
regex_END'5cs'2a'5bA'2dZa'2dz'5d'5bA'2dZa'2dz0'2d9'5f'5d'2a'5c'3b = compileRegex "END\\s*[A-Za-z][A-Za-z0-9_]*\\;"
regex_'5cb'28RECORD'7cOBJECT'7cTRY'7cWHILE'7cFOR'7cREPEAT'7cLOOP'7cIF'7cCASE'7cWITH'29'5cb = compileRegex "\\b(RECORD|OBJECT|TRY|WHILE|FOR|REPEAT|LOOP|IF|CASE|WITH)\\b"
regex_'5cb'28END'3b'7cEND'29'5cb = compileRegex "\\b(END;|END)\\b"
regex_'5cb'5b'5c'2b'7c'5c'2d'5d'7b0'2c1'7d'5b0'2d9'5d'7b1'2c'7d'5c'2e'5b0'2d9'5d'7b1'2c'7d'28'5bE'7ce'7cD'7cd'7cX'7cx'5d'5b'5c'2b'7c'5c'2d'5d'7b0'2c1'7d'5b0'2d9'5d'7b1'2c'7d'29'7b0'2c1'7d'5cb = compileRegex "\\b[\\+|\\-]{0,1}[0-9]{1,}\\.[0-9]{1,}([E|e|D|d|X|x][\\+|\\-]{0,1}[0-9]{1,}){0,1}\\b"
regex_'5cb'28'5b'5c'2b'7c'5c'2d'5d'7b0'2c1'7d'5b0'2d9'5d'7b1'2c'7d'7c'28'5b2'2d9'5d'7c1'5b0'2d6'5d'29'5c'5f'5b0'2d9A'2dFa'2df'5d'7b1'2c'7d'29'5cb = compileRegex "\\b([\\+|\\-]{0,1}[0-9]{1,}|([2-9]|1[0-6])\\_[0-9A-Fa-f]{1,})\\b"
regex_'5c'27'28'2e'7c'5c'5c'5bntrf'5c'5c'27'22'5d'7c'5c'5c'5b0'2d7'5d'7b3'7d'29'5c'27 = compileRegex "\\'(.|\\\\[ntrf\\\\'\"]|\\\\[0-7]{3})\\'"

defaultAttributes = [("Normal","Normal Text"),("String1","String"),("Comment2","Comment"),("Prep1","Pragma")]

parseRules "Normal" = 
  do (attr, result) <- (((pRegExpr regex_PROCEDURE'5b'5cs'5d'2e'2a'5c'28 >>= withAttribute "Keyword"))
                        <|>
                        ((pRegExpr regex_END'5cs'2a'5bA'2dZa'2dz'5d'5bA'2dZa'2dz0'2d9'5f'5d'2a'5c'3b >>= withAttribute "Keyword"))
                        <|>
                        ((pRegExpr regex_'5cb'28RECORD'7cOBJECT'7cTRY'7cWHILE'7cFOR'7cREPEAT'7cLOOP'7cIF'7cCASE'7cWITH'29'5cb >>= withAttribute "Keyword"))
                        <|>
                        ((pRegExpr regex_'5cb'28END'3b'7cEND'29'5cb >>= withAttribute "Keyword"))
                        <|>
                        ((pKeyword " \n\t():!+,-<=>%&*/;?[]^{|}~\\" list_keywords >>= withAttribute "Keyword"))
                        <|>
                        ((pKeyword " \n\t():!+,-<=>%&*/;?[]^{|}~\\" list_operators >>= withAttribute "Operator"))
                        <|>
                        ((pKeyword " \n\t():!+,-<=>%&*/;?[]^{|}~\\" list_types >>= withAttribute "Type"))
                        <|>
                        ((pKeyword " \n\t():!+,-<=>%&*/;?[]^{|}~\\" list_constants >>= withAttribute "Constant"))
                        <|>
                        ((pKeyword " \n\t():!+,-<=>%&*/;?[]^{|}~\\" list_pervasives >>= withAttribute "Pervasive"))
                        <|>
                        ((pKeyword " \n\t():!+,-<=>%&*/;?[]^{|}~\\" list_stdlibs >>= withAttribute "StdLib"))
                        <|>
                        ((pRegExpr regex_'5cb'5b'5c'2b'7c'5c'2d'5d'7b0'2c1'7d'5b0'2d9'5d'7b1'2c'7d'5c'2e'5b0'2d9'5d'7b1'2c'7d'28'5bE'7ce'7cD'7cd'7cX'7cx'5d'5b'5c'2b'7c'5c'2d'5d'7b0'2c1'7d'5b0'2d9'5d'7b1'2c'7d'29'7b0'2c1'7d'5cb >>= withAttribute "Real"))
                        <|>
                        ((pRegExpr regex_'5cb'28'5b'5c'2b'7c'5c'2d'5d'7b0'2c1'7d'5b0'2d9'5d'7b1'2c'7d'7c'28'5b2'2d9'5d'7c1'5b0'2d6'5d'29'5c'5f'5b0'2d9A'2dFa'2df'5d'7b1'2c'7d'29'5cb >>= withAttribute "Integer"))
                        <|>
                        ((pDetectChar False '"' >>= withAttribute "String") >>~ pushContext "String1")
                        <|>
                        ((pRegExpr regex_'5c'27'28'2e'7c'5c'5c'5bntrf'5c'5c'27'22'5d'7c'5c'5c'5b0'2d7'5d'7b3'7d'29'5c'27 >>= withAttribute "Char"))
                        <|>
                        ((pDetect2Chars False '<' '*' >>= withAttribute "Pragma") >>~ pushContext "Prep1")
                        <|>
                        ((pDetect2Chars False '(' '*' >>= withAttribute "Comment") >>~ pushContext "Comment2"))
     return (attr, result)

parseRules "String1" = 
  do (attr, result) <- ((pDetectChar False '"' >>= withAttribute "String") >>~ (popContext))
     return (attr, result)

parseRules "Comment2" = 
  do (attr, result) <- (((pDetect2Chars False '(' '*' >>= withAttribute "Comment") >>~ pushContext "Comment2")
                        <|>
                        ((pDetect2Chars False '*' ')' >>= withAttribute "Comment") >>~ (popContext)))
     return (attr, result)

parseRules "Prep1" = 
  do (attr, result) <- ((pDetect2Chars False '*' '>' >>= withAttribute "Pragma") >>~ (popContext))
     return (attr, result)

parseRules x = fail $ "Unknown context" ++ x