module Data.Attoparsec.ByteString.Internal
    (
    
      Parser
    , Result
    
    , parse
    , parseOnly
    
    , module Data.Attoparsec.Combinator
    
    , satisfy
    , satisfyWith
    , anyWord8
    , skip
    , word8
    , notWord8
    
    , peekWord8
    , peekWord8'
    
    , inClass
    , notInClass
    
    , storable
    
    , skipWhile
    , string
    , stringTransform
    , take
    , scan
    , runScanner
    , takeWhile
    , takeWhile1
    , takeTill
    
    , takeByteString
    , takeLazyByteString
    
    , endOfLine
    , endOfInput
    , match
    , atEnd
    ) where
import Control.Applicative ((<|>), (<$>))
import Control.Monad (when)
import Data.Attoparsec.ByteString.Buffer (Buffer, buffer)
import Data.Attoparsec.ByteString.FastSet (charClass, memberWord8)
import Data.Attoparsec.Combinator ((<?>))
import Data.Attoparsec.Internal
import Data.Attoparsec.Internal.Fhthagn (inlinePerformIO)
import Data.Attoparsec.Internal.Types hiding (Parser, Failure, Success)
import Data.ByteString (ByteString)
import Data.Word (Word8)
import Foreign.ForeignPtr (withForeignPtr)
import Foreign.Ptr (castPtr, minusPtr, plusPtr)
import Foreign.Storable (Storable(peek, sizeOf))
import Prelude hiding (getChar, succ, take, takeWhile)
import qualified Data.Attoparsec.ByteString.Buffer as Buf
import qualified Data.Attoparsec.Internal.Types as T
import qualified Data.ByteString as B8
import qualified Data.ByteString.Char8 as B
import qualified Data.ByteString.Internal as B
import qualified Data.ByteString.Lazy as L
import qualified Data.ByteString.Unsafe as B
type Parser = T.Parser ByteString
type Result = IResult ByteString
type Failure r = T.Failure ByteString Buffer r
type Success a r = T.Success ByteString Buffer a r
satisfy :: (Word8 -> Bool) -> Parser Word8
satisfy p = do
  h <- peekWord8'
  if p h
    then advance 1 >> return h
    else fail "satisfy"
skip :: (Word8 -> Bool) -> Parser ()
skip p = do
  h <- peekWord8'
  if p h
    then advance 1
    else fail "skip"
satisfyWith :: (Word8 -> a) -> (a -> Bool) -> Parser a
satisfyWith f p = do
  h <- peekWord8'
  let c = f h
  if p c
    then advance 1 >> return c
    else fail "satisfyWith"
storable :: Storable a => Parser a
storable = hack undefined
 where
  hack :: Storable b => b -> Parser b
  hack dummy = do
    (fp,o,_) <- B.toForeignPtr `fmap` take (sizeOf dummy)
    return . B.inlinePerformIO . withForeignPtr fp $ \p ->
        peek (castPtr $ p `plusPtr` o)
takeWith :: Int -> (ByteString -> Bool) -> Parser ByteString
takeWith n0 p = do
  let n = max n0 0
  s <- ensure n
  if p s
    then advance n >> return s
    else fail "takeWith"
take :: Int -> Parser ByteString
take n = takeWith n (const True)
string :: ByteString -> Parser ByteString
string s = takeWith (B.length s) (==s)
stringTransform :: (ByteString -> ByteString) -> ByteString
                -> Parser ByteString
stringTransform f s = takeWith (B.length s) ((==f s) . f)
skipWhile :: (Word8 -> Bool) -> Parser ()
skipWhile p = go
 where
  go = do
    t <- B8.takeWhile p <$> get
    continue <- inputSpansChunks (B.length t)
    when continue go
takeTill :: (Word8 -> Bool) -> Parser ByteString
takeTill p = takeWhile (not . p)
takeWhile :: (Word8 -> Bool) -> Parser ByteString
takeWhile p = (B.concat . reverse) `fmap` go []
 where
  go acc = do
    s <- B8.takeWhile p <$> get
    continue <- inputSpansChunks (B.length s)
    if continue
      then go (s:acc)
      else return (s:acc)
takeRest :: Parser [ByteString]
takeRest = go []
 where
  go acc = do
    input <- wantInput
    if input
      then do
        s <- get
        advance (B.length s)
        go (s:acc)
      else return (reverse acc)
takeByteString :: Parser ByteString
takeByteString = B.concat `fmap` takeRest
takeLazyByteString :: Parser L.ByteString
takeLazyByteString = L.fromChunks `fmap` takeRest
data T s = T  !Int s
scan_ :: (s -> [ByteString] -> Parser r) -> s -> (s -> Word8 -> Maybe s)
         -> Parser r
scan_ f s0 p = go [] s0
 where
  go acc s1 = do
    let scanner (B.PS fp off len) =
          withForeignPtr fp $ \ptr0 -> do
            let start = ptr0 `plusPtr` off
                end   = start `plusPtr` len
                inner ptr !s
                  | ptr < end = do
                    w <- peek ptr
                    case p s w of
                      Just s' -> inner (ptr `plusPtr` 1) s'
                      _       -> done (ptr `minusPtr` start) s
                  | otherwise = done (ptr `minusPtr` start) s
                done !i !s = return (T i s)
            inner start s1
    bs <- get
    let T i s' = inlinePerformIO $ scanner bs
        !h = B.unsafeTake i bs
    continue <- inputSpansChunks i
    if continue
      then go (h:acc) s'
      else f s' (h:acc)
scan :: s -> (s -> Word8 -> Maybe s) -> Parser ByteString
scan = scan_ $ \_ chunks ->
  case chunks of
    [x] -> return x
    xs  -> return $! B.concat $ reverse xs
runScanner :: s -> (s -> Word8 -> Maybe s) -> Parser (ByteString, s)
runScanner = scan_ $ \s xs -> return (B.concat (reverse xs), s)
takeWhile1 :: (Word8 -> Bool) -> Parser ByteString
takeWhile1 p = do
  (`when` demandInput) =<< endOfChunk
  s <- B8.takeWhile p <$> get
  let len = B.length s
  if len == 0
    then fail "takeWhile1"
    else do
      advance len
      eoc <- endOfChunk
      if eoc
        then (s<>) `fmap` takeWhile p
        else return s
inClass :: String -> Word8 -> Bool
inClass s = (`memberWord8` mySet)
    where mySet = charClass s
          
notInClass :: String -> Word8 -> Bool
notInClass s = not . inClass s
anyWord8 :: Parser Word8
anyWord8 = satisfy $ const True
word8 :: Word8 -> Parser Word8
word8 c = satisfy (== c) <?> show c
notWord8 :: Word8 -> Parser Word8
notWord8 c = satisfy (/= c) <?> "not " ++ show c
peekWord8 :: Parser (Maybe Word8)
peekWord8 = T.Parser $ \t pos@(Pos pos_) more _lose succ ->
  case () of
    _| pos_ < Buf.length t ->
       let !w = Buf.unsafeIndex t pos_
       in succ t pos more (Just w)
     | more == Complete ->
       succ t pos more Nothing
     | otherwise ->
       let succ' t' pos' more' = let !w = Buf.unsafeIndex t' pos_
                                 in succ t' pos' more' (Just w)
           lose' t' pos' more' = succ t' pos' more' Nothing
       in prompt t pos more lose' succ'
peekWord8' :: Parser Word8
peekWord8' = T.Parser $ \t pos more lose succ ->
    if lengthAtLeast pos 1 t
    then succ t pos more (Buf.unsafeIndex t (fromPos pos))
    else let succ' t' pos' more' bs' = succ t' pos' more' $! B.unsafeHead bs'
         in ensureSuspended 1 t pos more lose succ'
endOfLine :: Parser ()
endOfLine = (word8 10 >> return ()) <|> (string "\r\n" >> return ())
failK :: Failure a
failK t (Pos pos) _more stack msg = Fail (Buf.unsafeDrop pos t) stack msg
successK :: Success a a
successK t (Pos pos) _more a = Done (Buf.unsafeDrop pos t) a
parse :: Parser a -> ByteString -> Result a
parse m s = T.runParser m (buffer s) (Pos 0) Incomplete failK successK
parseOnly :: Parser a -> ByteString -> Either String a
parseOnly m s = case T.runParser m (buffer s) (Pos 0) Complete failK successK of
                  Fail _ _ err -> Left err
                  Done _ a     -> Right a
                  _            -> error "parseOnly: impossible error!"
get :: Parser ByteString
get = T.Parser $ \t pos more _lose succ ->
  succ t pos more (Buf.unsafeDrop (fromPos pos) t)
endOfChunk :: Parser Bool
endOfChunk = T.Parser $ \t pos more _lose succ ->
  succ t pos more (fromPos pos == Buf.length t)
inputSpansChunks :: Int -> Parser Bool
inputSpansChunks i = T.Parser $ \t pos_ more _lose succ ->
  let pos = pos_ + Pos i
  in if fromPos pos < Buf.length t || more == Complete
     then succ t pos more False
     else let lose' t' pos' more' = succ t' pos' more' False
              succ' t' pos' more' = succ t' pos' more' True
          in prompt t pos more lose' succ'
advance :: Int -> Parser ()
advance n = T.Parser $ \t pos more _lose succ ->
  succ t (pos + Pos n) more ()
ensureSuspended :: Int -> Buffer -> Pos -> More
                -> Failure r
                -> Success ByteString r
                -> Result r
ensureSuspended n t pos more lose succ =
    runParser (demandInput >> go) t pos more lose succ
  where go = T.Parser $ \t' pos' more' lose' succ' ->
          if lengthAtLeast pos' n t'
          then succ' t' pos' more' (substring pos (Pos n) t')
          else runParser (demandInput >> go) t' pos' more' lose' succ'
ensure :: Int -> Parser ByteString
ensure n = T.Parser $ \t pos more lose succ ->
    if lengthAtLeast pos n t
    then succ t pos more (substring pos (Pos n) t)
    
    else ensureSuspended n t pos more lose succ
match :: Parser a -> Parser (ByteString, a)
match p = T.Parser $ \t pos more lose succ ->
  let succ' t' pos' more' a =
        succ t' pos' more' (substring pos (pos'pos) t', a)
  in runParser p t pos more lose succ'
lengthAtLeast :: Pos -> Int -> Buffer -> Bool
lengthAtLeast (Pos pos) n bs = Buf.length bs >= pos + n
substring :: Pos -> Pos -> Buffer -> ByteString
substring (Pos pos) (Pos n) = Buf.substring pos n