-- |Yet another parser combinator. This is mostly a subset of
-- "Text.ParserCombinators.Parsec" but there are some differences:
--
-- * This parser works on 'Data.ByteString.Base.LazyByteString'
--   instead of 'Prelude.String'.
--
-- * Backtracking is the only possible behavior so there is no \"try\"
--   action.
--
-- * On success, the remaining string is returned as well as the
--   parser result.
--
-- * You can choose whether to treat reaching EOF (trying to eat one
--   more letter at the end of string) a fatal error or to treat it a
--   normal failure. If a fatal error occurs, the entire parsing
--   process immediately fails without trying any backtracks. The
--   default behavior is to treat EOF fatal.
--
-- In general, you don't have to use this module directly.
module Network.HTTP.Lucu.Parser
    ( Parser
    , ParserResult(..)

    , failP

    , parse
    , parseStr

    , anyChar
    , eof
    , allowEOF
    , satisfy
    , char
    , string
    , (<|>)
    , choice
    , oneOf
    , digit
    , hexDigit
    , notFollowedBy
    , many
    , many1
    , count
    , option
    , sepBy
    , sepBy1

    , sp
    , ht
    , crlf
    )
    where

import           Control.Monad.State.Strict
import qualified Data.ByteString.Lazy as Lazy (ByteString)
import qualified Data.ByteString.Lazy.Char8 as B hiding (ByteString)

-- |@'Parser' a@ is obviously a parser which parses and returns @a@.
newtype Parser a = Parser {
      runParser :: State ParserState (ParserResult a)
    }


data ParserState
    = PST {
        pstInput      :: Lazy.ByteString
      , pstIsEOFFatal :: !Bool
      }
    deriving (Eq, Show)


data ParserResult a = Success !a
                    | IllegalInput -- 受理出來ない入力があった
                    | ReachedEOF   -- 限界を越えて讀まうとした
                      deriving (Eq, Show)


--  (>>=) :: Parser a -> (a -> Parser b) -> Parser b
instance Monad Parser where
    p >>= f = Parser $! do saved <- get -- 失敗した時の爲に状態を保存
                           result <- runParser p
                           case result of
                             Success a    -> runParser (f a)
                             IllegalInput -> do put saved -- 状態を復歸
                                                return IllegalInput
                             ReachedEOF   -> do put saved -- 状態を復歸
                                                return ReachedEOF
    return x = x `seq` Parser $! return $! Success x
    fail _   = Parser $! return $! IllegalInput

-- |@'failP'@ is just a synonym for @'Prelude.fail'
-- 'Prelude.undefined'@.
failP :: Parser a
failP = fail undefined

-- |@'parse' p bstr@ parses @bstr@ with @p@ and returns @(# result,
-- remaining #)@.
parse :: Parser a -> Lazy.ByteString -> (# ParserResult a, Lazy.ByteString #)
parse p input -- input は lazy である必要有り。
    = p `seq`
      let (result, state') = runState (runParser p) (PST input True)
      in
        result `seq` (# result, pstInput state' #) -- pstInput state' も lazy である必要有り。

-- |@'parseStr' p str@ packs @str@ and parses it.
parseStr :: Parser a -> String -> (# ParserResult a, Lazy.ByteString #)
parseStr p input
    = p `seq` -- input は lazy である必要有り。
      parse p (B.pack input)


anyChar :: Parser Char
anyChar = Parser $!
          do state@(PST input _) <- get
             if B.null input then
                 return ReachedEOF
               else
                 do put $! state { pstInput = B.tail input }
                    return (Success $! B.head input)


eof :: Parser ()
eof = Parser $!
      do PST input _ <- get
         if B.null input then
             return $! Success ()
           else
             return IllegalInput

-- |@'allowEOF' p@ makes @p@ treat reaching EOF a normal failure.
allowEOF :: Parser a -> Parser a
allowEOF f = f `seq`
             Parser $! do saved@(PST _ isEOFFatal) <- get
                          put $! saved { pstIsEOFFatal = False }

                          result <- runParser f
                         
                          state <- get
                          put $! state { pstIsEOFFatal = isEOFFatal }

                          return result


satisfy :: (Char -> Bool) -> Parser Char
satisfy f = f `seq`
            do c <- anyChar
               if f $! c then
                   return c
                 else
                   failP


char :: Char -> Parser Char
char c = c `seq` satisfy (== c)


string :: String -> Parser String
string str = str `seq`
             do mapM_ char str
                return str


infixr 0 <|>

-- |This is the backtracking alternation. There is no non-backtracking
-- equivalent.
(<|>) :: Parser a -> Parser a -> Parser a
f <|> g
    = f `seq` g `seq`
      Parser $! do saved  <- get -- 状態を保存
                   result <- runParser f
                   case result of
                     Success a    -> return $! Success a
                     IllegalInput -> do put saved -- 状態を復歸
                                        runParser g
                     ReachedEOF   -> if pstIsEOFFatal saved then
                                         return ReachedEOF
                                     else
                                         do put saved
                                            runParser g


choice :: [Parser a] -> Parser a
choice = foldl (<|>) failP


oneOf :: [Char] -> Parser Char
oneOf = foldl (<|>) failP . map char


notFollowedBy :: Parser a -> Parser ()
notFollowedBy p
    = p `seq`
      Parser $! do saved  <- get -- 状態を保存
                   result <- runParser p
                   case result of
                     Success _    -> do put saved -- 状態を復歸
                                        return IllegalInput
                     IllegalInput -> do put saved -- 状態を復歸
                                        return $! Success ()
                     ReachedEOF   -> do put saved -- 状態を復歸
                                        return $! Success ()


digit :: Parser Char
digit = do c <- anyChar
           if c >= '0' && c <= '9' then
               return c
             else
               failP


hexDigit :: Parser Char
hexDigit = do c <- anyChar
              if (c >= '0' && c <= '9') ||
                 (c >= 'a' && c <= 'f') ||
                 (c >= 'A' && c <= 'F') then
                  return c
                else
                  failP


many :: Parser a -> Parser [a]
many p = p `seq`
         do x  <- p
            xs <- many p
            return (x:xs)
         <|>
         return []


many1 :: Parser a -> Parser [a]
many1 p = p `seq`
          do x  <- p
             xs <- many p
             return (x:xs)


count :: Int -> Parser a -> Parser [a]
count 0 _ = return []
count n p = n `seq` p `seq`
            do x  <- p
               xs <- count (n-1) p
               return (x:xs)

-- def may be a _|_
option :: a -> Parser a -> Parser a
option def p = p `seq`
               p <|> return def


sepBy :: Parser a -> Parser sep -> Parser [a]
sepBy p sep = p `seq` sep `seq`
              sepBy1 p sep <|> return []


sepBy1 :: Parser a -> Parser sep -> Parser [a]
sepBy1 p sep = p `seq` sep `seq`
               do x  <- p
                  xs <- many $! sep >> p
                  return (x:xs)


sp :: Parser Char
sp = char ' '


ht :: Parser Char
ht = char '\t'


crlf :: Parser String
crlf = string "\x0d\x0a"