X-Git-Url: http://git.cielonegro.org/gitweb.cgi?a=blobdiff_plain;f=Network%2FHTTP%2FLucu%2FParser.hs;h=90c52696fbb4293e95849e5335758d7a255913bd;hb=1196f43ecedbb123515065f0440844864af906fb;hp=cc12cd73733b636ce3270e8518d137ade2eb3266;hpb=7b3c7c2c5be4fc05ee03008aa0af56fab798e1bb;p=Lucu.git diff --git a/Network/HTTP/Lucu/Parser.hs b/Network/HTTP/Lucu/Parser.hs index cc12cd7..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. @@ -32,6 +33,7 @@ module Network.HTTP.Lucu.Parser , char , string , (<|>) + , choice , oneOf , digit , hexDigit @@ -50,11 +52,10 @@ module Network.HTTP.Lucu.Parser where import Control.Monad.State.Strict -import qualified Data.ByteString.Lazy.Char8 as B -import Data.ByteString.Lazy.Char8 (ByteString) +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@. +-- |@'Parser' a@ is obviously a parser which parses and returns @a@. newtype Parser a = Parser { runParser :: State ParserState (ParserResult a) } @@ -62,7 +63,7 @@ newtype Parser a = Parser { data ParserState = PST { - pstInput :: ByteString + pstInput :: Lazy.ByteString , pstIsEOFFatal :: !Bool } deriving (Eq, Show) @@ -87,24 +88,25 @@ instance Monad Parser where return x = x `seq` Parser $! return $! Success x fail _ = Parser $! return $! IllegalInput --- |@'failP'@ is just a synonym for @'Prelude.fail Prelude.undefined'@. +-- |@'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 -> ByteString -> (ParserResult a, ByteString) +-- |@'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 である必要有り。 + result `seq` (# result, pstInput state' #) -- pstInput state' も lazy である必要有り。 -- |@'parseStr' p str@ packs @str@ and parses it. -parseStr :: Parser a -> String -> (ParserResult a, ByteString) +parseStr :: Parser a -> String -> (# ParserResult a, Lazy.ByteString #) parseStr p input = p `seq` -- input は lazy である必要有り。 - parse p $! B.pack input + parse p (B.pack input) anyChar :: Parser Char @@ -142,7 +144,7 @@ allowEOF f = f `seq` satisfy :: (Char -> Bool) -> Parser Char satisfy f = f `seq` do c <- anyChar - if f c then + if f $! c then return c else failP @@ -165,7 +167,7 @@ infixr 0 <|> (<|>) :: Parser a -> Parser a -> Parser a f <|> g = f `seq` g `seq` - Parser $! do saved <- get -- 状態を保存 + Parser $! do saved <- get -- 状態を保存 result <- runParser f case result of Success a -> return $! Success a @@ -178,13 +180,26 @@ f <|> g 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` - (p >> failP) <|> 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