module Text.Highlighting.Kate.Syntax.LiterateHaskell ( highlight, parseExpression, syntaxName, syntaxExtensions ) where
import Text.Highlighting.Kate.Definitions
import Text.Highlighting.Kate.Common
import qualified Text.Highlighting.Kate.Syntax.Haskell
import Text.ParserCombinators.Parsec
import Control.Monad (when)
import Data.Map (fromList)
import Data.Maybe (fromMaybe, maybeToList)
syntaxName :: String
syntaxName = "Literate Haskell"
syntaxExtensions :: String
syntaxExtensions = "*.lhs"
highlight :: String -> Either String [SourceLine]
highlight input =
  case runParser parseSource startingState "source" input of
    Left err     -> Left $ show err
    Right result -> Right result
parseExpression :: GenParser Char SyntaxState LabeledSource
parseExpression = do
  st <- getState
  let oldLang = synStLanguage st
  setState $ st { synStLanguage = "Literate Haskell" }
  context <- currentContext <|> (pushContext "text" >> 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 [("Literate Haskell",["text"])], synStLanguage = "Literate Haskell", 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
    "text" -> return () >> pHandleEndLine
    "normal" -> (popContext) >> pEndLine
    "normals" -> return () >> pHandleEndLine
    "comments'" -> pushContext "uncomments" >> pHandleEndLine
    "uncomments" -> return () >> pHandleEndLine
    "recomments" -> (popContext) >> pEndLine
    _ -> 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 = [("BirdTrack","ot"),("Comment","co")]
parseExpressionInternal = do
  context <- currentContext
  parseRules context <|> (pDefault >>= withAttribute (fromMaybe "" $ lookup context defaultAttributes))
regex_'5c'7b'2d'5b'5e'23'5d = compileRegex "\\{-[^#]"
defaultAttributes = [("text","Text"),("normal","Normal"),("normals","Normal"),("comments'","Comment"),("uncomments","Text"),("recomments","Comment")]
parseRules "text" = 
  do (attr, result) <- (((pColumn 0 >> pDetectChar False '>' >>= withAttribute "BirdTrack") >>~ pushContext "normal")
                        <|>
                        ((pColumn 0 >> pDetectChar False '<' >>= withAttribute "BirdTrack") >>~ pushContext "normal")
                        <|>
                        ((pString False "\\begin{code}" >>= withAttribute "Text") >>~ pushContext "normals")
                        <|>
                        ((pString False "\\begin{spec}" >>= withAttribute "Text") >>~ pushContext "normals"))
     return (attr, result)
parseRules "normal" = 
  do (attr, result) <- (((pRegExpr regex_'5c'7b'2d'5b'5e'23'5d >>= withAttribute "Comment") >>~ pushContext "comments'")
                        <|>
                        ((Text.Highlighting.Kate.Syntax.Haskell.parseExpression)))
     return (attr, result)
parseRules "normals" = 
  do (attr, result) <- (((pString False "\\end{code}" >>= withAttribute "Normal") >>~ (popContext))
                        <|>
                        ((pString False "\\end{spec}" >>= withAttribute "Normal") >>~ (popContext))
                        <|>
                        ((Text.Highlighting.Kate.Syntax.Haskell.parseExpression)))
     return (attr, result)
parseRules "comments'" = 
  do (attr, result) <- ((pDetect2Chars False '-' '}' >>= withAttribute "Comment") >>~ (popContext))
     return (attr, result)
parseRules "uncomments" = 
  do (attr, result) <- (((pColumn 0 >> pDetectChar False '>' >>= withAttribute "BirdTrack") >>~ pushContext "recomments")
                        <|>
                        ((pColumn 0 >> pDetectChar False '<' >>= withAttribute "BirdTrack") >>~ pushContext "recomments"))
     return (attr, result)
parseRules "recomments" = 
  do (attr, result) <- ((pDetect2Chars False '-' '}' >>= withAttribute "Comment") >>~ (popContext >> popContext >> popContext))
     return (attr, result)
parseRules x = fail $ "Unknown context" ++ x