X-Git-Url: http://git.cielonegro.org/gitweb.cgi?a=blobdiff_plain;f=Network%2FHTTP%2FLucu%2FParser.hs;h=90c52696fbb4293e95849e5335758d7a255913bd;hb=1196f43ecedbb123515065f0440844864af906fb;hp=4c44f0be3e7dfa75d74b0af3bd05260d3f5b47e9;hpb=0b4db5681e3b0b27357a87316822ea3671f8c174;p=Lucu.git diff --git a/Network/HTTP/Lucu/Parser.hs b/Network/HTTP/Lucu/Parser.hs index 4c44f0b..90c5269 100644 --- a/Network/HTTP/Lucu/Parser.hs +++ b/Network/HTTP/Lucu/Parser.hs @@ -1,7 +1,8 @@ --- |Yet another parser combinator. This is mostly a subset of Parsec --- but there are some differences: +-- |Yet another parser combinator. This is mostly a subset of +-- "Text.ParserCombinators.Parsec" but there are some differences: -- --- * This parser works on ByteString instead of String. +-- * This parser works on 'Data.ByteString.Base.LazyByteString' +-- instead of 'Prelude.String'. -- -- * Backtracking is the only possible behavior so there is no \"try\" -- action. @@ -20,6 +21,8 @@ module Network.HTTP.Lucu.Parser ( Parser , ParserResult(..) + , failP + , parse , parseStr @@ -30,14 +33,13 @@ module Network.HTTP.Lucu.Parser , char , string , (<|>) + , choice , oneOf , digit , hexDigit , notFollowedBy , many , many1 - , manyTill - , many1Till , count , option , sepBy @@ -49,21 +51,25 @@ module Network.HTTP.Lucu.Parser ) where -import Control.Monad -import Control.Monad.State -import qualified Data.ByteString.Lazy.Char8 as B -import Data.ByteString.Lazy.Char8 (ByteString) +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@. -data Parser a = Parser { +-- |@'Parser' a@ is obviously a parser which parses and returns @a@. +newtype Parser a = Parser { runParser :: State ParserState (ParserResult a) } -type ParserState = (ByteString, IsEOFFatal) -type IsEOFFatal = Bool +data ParserState + = PST { + pstInput :: Lazy.ByteString + , pstIsEOFFatal :: !Bool + } + deriving (Eq, Show) + -data ParserResult a = Success a +data ParserResult a = Success !a | IllegalInput -- 受理出來ない入力があった | ReachedEOF -- 限界を越えて讀まうとした deriving (Eq, Show) @@ -71,72 +77,86 @@ data ParserResult a = Success a -- (>>=) :: Parser a -> (a -> Parser b) -> Parser b instance Monad Parser where - p >>= f = Parser $ do saved@(_, isEOFFatal) <- get -- 失敗した時の爲に状態を保存 - result <- runParser p - case result of - Success a -> runParser (f a) - IllegalInput -> do put saved -- 状態を復歸 - return IllegalInput - ReachedEOF -> do unless isEOFFatal - $ put saved -- 状態を復歸 - return ReachedEOF - return = Parser . return . Success - fail _ = Parser $ return IllegalInput - --- |@'parse' p bstr@ parses @bstr@ with @p@ and returns @(result, --- remaining)@. -parse :: Parser a -> ByteString -> (ParserResult a, ByteString) -parse p input = let (result, (input', _)) = runState (runParser p) (input, True) - in - (result, input') + 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, ByteString) -parseStr p input = parse p $ B.pack input +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 (input, isEOFFatal) <- get - if B.null input then - return ReachedEOF - else - do let c = B.head input - put (B.tail input, isEOFFatal) - return (Success c) +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 (input, _) <- get - if B.null input then - return $ Success () - else - return IllegalInput +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 = Parser $ do (input, isEOFFatal) <- get - put (input, False) +allowEOF f = f `seq` + Parser $! do saved@(PST _ isEOFFatal) <- get + put $! saved { pstIsEOFFatal = False } - result <- runParser f + result <- runParser f - (input', _) <- get - put (input', isEOFFatal) + state <- get + put $! state { pstIsEOFFatal = isEOFFatal } - return result + return result satisfy :: (Char -> Bool) -> Parser Char -satisfy f = do c <- anyChar - unless (f c) (fail "") - return c +satisfy f = f `seq` + do c <- anyChar + if f $! c then + return c + else + failP char :: Char -> Parser Char -char c = satisfy (== c) +char c = c `seq` satisfy (== c) string :: String -> Parser String -string str = do mapM_ char str +string str = str `seq` + do mapM_ char str return str @@ -145,25 +165,41 @@ infixr 0 <|> -- |This is the backtracking alternation. There is no non-backtracking -- equivalent. (<|>) :: Parser a -> Parser a -> Parser a -f <|> g = Parser $ do saved@(_, isEOFFatal) <- get -- 状態を保存 - result <- runParser f - case result of - Success a -> return $ Success a - IllegalInput -> do put saved -- 状態を復歸 - runParser g - ReachedEOF -> if isEOFFatal then - return ReachedEOF - else - do put saved - runParser g +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 (<|>) (fail "") . map char +oneOf = foldl (<|>) failP . map char notFollowedBy :: Parser a -> Parser () -notFollowedBy p = p >>= fail "" <|> return () +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 @@ -171,7 +207,7 @@ digit = do c <- anyChar if c >= '0' && c <= '9' then return c else - fail "" + failP hexDigit :: Parser Char @@ -181,11 +217,12 @@ hexDigit = do c <- anyChar (c >= 'A' && c <= 'F') then return c else - fail "" + failP many :: Parser a -> Parser [a] -many p = do x <- p +many p = p `seq` + do x <- p xs <- many p return (x:xs) <|> @@ -193,42 +230,34 @@ many p = do x <- p many1 :: Parser a -> Parser [a] -many1 p = do ret <- many p - case ret of - [] -> fail "" - xs -> return xs - - -manyTill :: Parser a -> Parser end -> Parser [a] -manyTill p end = many $ do x <- p - end - return x - - -many1Till :: Parser a -> Parser end -> Parser [a] -many1Till p end = many1 $ do x <- p - end - return x +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 = do x <- p +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 <|> return def +option def p = p `seq` + p <|> return def sepBy :: Parser a -> Parser sep -> Parser [a] -sepBy p sep = sepBy1 p sep <|> return [] +sepBy p sep = p `seq` sep `seq` + sepBy1 p sep <|> return [] sepBy1 :: Parser a -> Parser sep -> Parser [a] -sepBy1 p sep = do x <- p - xs <- many $ sep >> p +sepBy1 p sep = p `seq` sep `seq` + do x <- p + xs <- many $! sep >> p return (x:xs)