X-Git-Url: http://git.cielonegro.org/gitweb.cgi?a=blobdiff_plain;f=Network%2FHTTP%2FLucu%2FParser.hs;h=c36655b4fc81f65c2fab16da81ecaef21a3c25f6;hb=30fcb38426696db8b80d322196cc594431e30407;hp=7a51ddcab435aa75cfcfc2904370bd104f8caef9;hpb=9961a721f98b101825ef154a2122c1fc2fa6d1ac;p=Lucu.git diff --git a/Network/HTTP/Lucu/Parser.hs b/Network/HTTP/Lucu/Parser.hs index 7a51ddc..c36655b 100644 --- a/Network/HTTP/Lucu/Parser.hs +++ b/Network/HTTP/Lucu/Parser.hs @@ -1,20 +1,51 @@ +-- |Yet another parser combinator. This is mostly a subset of Parsec +-- but there are some differences: +-- +-- * This parser works on ByteString instead of 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 treat reaching EOF (trying to eat one more letter at the +-- end of string) a fatal error or 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(..) - , parse -- Parser a -> ByteString -> Maybe (a, ByteString) - , anyChar -- Parser Char - , satisfy -- (Char -> Bool) -> Parser Char - , char -- Char -> Parser Char - , string -- String -> Parser String - , (<|>) -- Parser a -> Parser a -> Parser a - , oneOf -- [Char] -> Parser Char - , digit -- Parser Char - , notFollowedBy -- Parser a -> Parser () - , many -- Parser a -> Parser [a] - , many1 -- Parser a -> Parser [a] - , manyTill -- Parser a -> Parser end -> Parser [a] - , many1Till -- Parser a -> Parser end -> Parser [a] - , sp -- Parser Char - , crlf -- Parser String + ( Parser + , ParserResult(..) + + , parse + , parseStr + + , anyChar + , eof + , allowEOF + , satisfy + , char + , string + , (<|>) + , oneOf + , digit + , hexDigit + , notFollowedBy + , many + , many1 + , manyTill + , many1Till + , count + , option + , sepBy + , sepBy1 + + , sp + , ht + , crlf ) where @@ -23,37 +54,75 @@ import Control.Monad.State import qualified Data.ByteString.Lazy.Char8 as B import Data.ByteString.Lazy.Char8 (ByteString) +-- |@Parser a@ is obviously a parser which parses and returns @a@. data Parser a = Parser { - runParser :: State ByteString (Maybe a) + runParser :: State ParserState (ParserResult a) } +type ParserState = (ByteString, IsEOFFatal) + +type IsEOFFatal = Bool + +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 -- 失敗した時の爲に状態を保存 + p >>= f = Parser $ do saved@(_, isEOFFatal) <- get -- 失敗した時の爲に状態を保存 result <- runParser p case result of - Just a -> runParser (f a) - Nothing -> do put saved -- 状態を復歸 - return Nothing - return = Parser . return . Just - fail _ = Parser $ return Nothing - - -parse :: Parser a -> ByteString -> Maybe (a, ByteString) -parse p input = case runState (runParser p) input of - (Just a , input') -> Just (a, input') - (Nothing, _ ) -> Nothing + 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') + +-- |@'parseStr' p str@ packs @str@ and parses it. +parseStr :: Parser a -> String -> (ParserResult a, ByteString) +parseStr p input = parse p $ B.pack input anyChar :: Parser Char -anyChar = Parser $ do input <- get +anyChar = Parser $ do (input, isEOFFatal) <- get if B.null input then - return Nothing + return ReachedEOF else do let c = B.head input - put (B.tail input) - return (Just c) + put (B.tail input, isEOFFatal) + return (Success c) + + +eof :: Parser () +eof = Parser $ do (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) + + result <- runParser f + + (input', _) <- get + put (input', isEOFFatal) + + return result satisfy :: (Char -> Bool) -> Parser Char @@ -73,13 +142,20 @@ string str = do mapM_ char str infixr 0 <|> +-- |This is the backtracking alternation. There is no non-backtracking +-- equivalent. (<|>) :: Parser a -> Parser a -> Parser a -f <|> g = Parser $ do saved <- get -- 状態を保存 +f <|> g = Parser $ do saved@(_, isEOFFatal) <- get -- 状態を保存 result <- runParser f case result of - Just a -> return (Just a) - Nothing -> do put saved -- 状態を復歸 - runParser g + Success a -> return $ Success a + IllegalInput -> do put saved -- 状態を復歸 + runParser g + ReachedEOF -> if isEOFFatal then + return ReachedEOF + else + do put saved + runParser g oneOf :: [Char] -> Parser Char @@ -91,7 +167,21 @@ notFollowedBy p = p >>= fail "" <|> return () digit :: Parser Char -digit = oneOf "0123456789" +digit = do c <- anyChar + if c >= '0' && c <= '9' then + return c + else + fail "" + + +hexDigit :: Parser Char +hexDigit = do c <- anyChar + if (c >= '0' && c <= '9') || + (c >= 'a' && c <= 'f') || + (c >= 'A' && c <= 'F') then + return c + else + fail "" many :: Parser a -> Parser [a] @@ -121,9 +211,34 @@ many1Till p end = many1 $ do x <- p return x +count :: Int -> Parser a -> Parser [a] +count 0 _ = return [] +count n p = do x <- p + xs <- count (n-1) p + return (x:xs) + + +option :: a -> Parser a -> Parser a +option def p = p <|> return def + + +sepBy :: Parser a -> Parser sep -> Parser [a] +sepBy p sep = sepBy1 p sep <|> return [] + + +sepBy1 :: Parser a -> Parser sep -> Parser [a] +sepBy1 p sep = 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"