]> gitweb @ CieloNegro.org - Lucu.git/blobdiff - Network/HTTP/Lucu/Parser.hs
Doc fix
[Lucu.git] / Network / HTTP / Lucu / Parser.hs
index cc12cd73733b636ce3270e8518d137ade2eb3266..f2e4be337abdc375503ec4761385a2222a6fbedb 100644 (file)
@@ -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.
@@ -50,11 +51,11 @@ module Network.HTTP.Lucu.Parser
     where
 
 import           Control.Monad.State.Strict
+import           Data.ByteString.Base (LazyByteString)
+import           Data.ByteString.Lazy ()
 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@.
+-- |@'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      :: LazyByteString
       , pstIsEOFFatal :: !Bool
       }
     deriving (Eq, Show)
@@ -87,13 +88,14 @@ 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 :: Parser a -> LazyByteString -> (ParserResult a, LazyByteString)
 parse p input -- input は lazy である必要有り。
     = p `seq`
       let (result, state') = runState (runParser p) (PST input True)
@@ -101,7 +103,7 @@ parse p input -- input は 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, LazyByteString)
 parseStr p input
     = p `seq` -- input は lazy である必要有り。
       parse p $! B.pack input