module Darcs.Patch.TokenReplace
    ( tryTokReplace
    , forceTokReplace
    , annotateReplace
    , breakToTokens
    , defaultToks
    ) where
import Prelude ()
import Darcs.Prelude
import qualified Data.ByteString as B
import qualified Data.ByteString.Char8 as BC
import Darcs.Patch.RegChars ( regChars )
breakOutToken :: String -> BC.ByteString
              -> Maybe (BC.ByteString, BC.ByteString, BC.ByteString)
breakOutToken tokChars input
  | not (B.null tok) = Just (before, tok, remaining)
  | otherwise = Nothing
  where
    isTokChar = regChars tokChars
    (before, tokAndRest) = BC.break isTokChar input
    (tok, remaining) = BC.break (not . isTokChar) tokAndRest
tryTokReplace :: String -> B.ByteString -> B.ByteString
              -> B.ByteString -> Maybe B.ByteString
tryTokReplace tokChars old new
  | B.null old = bug "tryTokInternal called with empty old token"
  | BC.any (not . isTokChar) old = bug "tryTokInternal called with old non-token"
  | BC.any (not . isTokChar) new = bug "tryTokInternal called with new non-token"
  | otherwise = fmap B.concat . loop 0
    where
      isTokChar = regChars tokChars
      loop !from input =
        case BC.findIndex isTokChar (B.drop from input) of
          Nothing -> Just [input]
          Just start ->
            case BC.span isTokChar (B.drop (from + start) input) of
              (tok, rest)
                | tok == old ->
                    (B.take (from + start) input :).(new :) <$> loop 0 rest
                | tok == new -> Nothing
                | otherwise ->
                    loop (from + start + B.length tok) input
forceTokReplace :: String -> B.ByteString -> B.ByteString
                -> B.ByteString -> B.ByteString
forceTokReplace tokChars old new
  | B.null old = bug "tryTokInternal called with empty old token"
  | BC.any (not . isTokChar) old = bug "tryTokInternal called with old non-token"
  | BC.any (not . isTokChar) new = bug "tryTokInternal called with new non-token"
  | otherwise = B.concat . loop 0
    where
      isTokChar = regChars tokChars
      len = B.length old
      loop !from input =
        case B.breakSubstring old (B.drop from input) of
          (before, match)
            | B.null match -> [input] 
            | B.null before || not (isTokChar (BC.last before))
            , B.length match == len || not (isTokChar (BC.index match len)) ->
                
                B.take (from + B.length before) input : new :
                  loop 0 (B.drop len match)
            | otherwise ->
                
                loop (from + B.length before + len) input
annotateReplace :: String -> B.ByteString -> B.ByteString -> B.ByteString -> Bool
annotateReplace tokChars old new input =
  case breakOutToken tokChars input of
    Just (_, tok, remaining) ->
      (tok == old || annotateReplace tokChars old new remaining)
    Nothing -> False
breakToTokens :: BC.ByteString -> [BC.ByteString]
breakToTokens input =
  case breakOutToken defaultToks input of
    Nothing -> []
    Just (_, tok, remaining) -> tok : breakToTokens remaining
defaultToks :: String
defaultToks = "A-Za-z_0-9"