]> gitweb @ CieloNegro.org - Lucu.git/blob - Network/HTTP/Lucu/Parser.hs
Doc fix, optimization, and more.
[Lucu.git] / Network / HTTP / Lucu / Parser.hs
1 -- |Yet another parser combinator. This is mostly a subset of
2 -- "Text.ParserCombinators.Parsec" but there are some differences:
3 --
4 -- * This parser works on 'Data.ByteString.Base.LazyByteString'
5 --   instead of 'Prelude.String'.
6 --
7 -- * Backtracking is the only possible behavior so there is no \"try\"
8 --   action.
9 --
10 -- * On success, the remaining string is returned as well as the
11 --   parser result.
12 --
13 -- * You can choose whether to treat reaching EOF (trying to eat one
14 --   more letter at the end of string) a fatal error or to treat it a
15 --   normal failure. If a fatal error occurs, the entire parsing
16 --   process immediately fails without trying any backtracks. The
17 --   default behavior is to treat EOF fatal.
18 --
19 -- In general, you don't have to use this module directly.
20 module Network.HTTP.Lucu.Parser
21     ( Parser
22     , ParserResult(..)
23
24     , failP
25
26     , parse
27     , parseStr
28
29     , anyChar
30     , eof
31     , allowEOF
32     , satisfy
33     , char
34     , string
35     , (<|>)
36     , oneOf
37     , digit
38     , hexDigit
39     , notFollowedBy
40     , many
41     , many1
42     , count
43     , option
44     , sepBy
45     , sepBy1
46
47     , sp
48     , ht
49     , crlf
50     )
51     where
52
53 import           Control.Monad.State.Strict
54 import           Data.ByteString.Base (LazyByteString)
55 import           Data.ByteString.Lazy ()
56 import qualified Data.ByteString.Lazy.Char8 as B
57
58 -- |@'Parser' a@ is obviously a parser which parses and returns @a@.
59 newtype Parser a = Parser {
60       runParser :: State ParserState (ParserResult a)
61     }
62
63
64 data ParserState
65     = PST {
66         pstInput      :: LazyByteString
67       , pstIsEOFFatal :: !Bool
68       }
69     deriving (Eq, Show)
70
71
72 data ParserResult a = Success !a
73                     | IllegalInput -- 受理出來ない入力があった
74                     | ReachedEOF   -- 限界を越えて讀まうとした
75                       deriving (Eq, Show)
76
77
78 --  (>>=) :: Parser a -> (a -> Parser b) -> Parser b
79 instance Monad Parser where
80     p >>= f = Parser $! do saved <- get -- 失敗した時の爲に状態を保存
81                            result <- runParser p
82                            case result of
83                              Success a    -> runParser (f a)
84                              IllegalInput -> do put saved -- 状態を復歸
85                                                 return IllegalInput
86                              ReachedEOF   -> do put saved -- 状態を復歸
87                                                 return ReachedEOF
88     return x = x `seq` Parser $! return $! Success x
89     fail _   = Parser $! return $! IllegalInput
90
91 -- |@'failP'@ is just a synonym for @'Prelude.fail'
92 -- 'Prelude.undefined'@.
93 failP :: Parser a
94 failP = fail undefined
95
96 -- |@'parse' p bstr@ parses @bstr@ with @p@ and returns @(# result,
97 -- remaining #)@.
98 parse :: Parser a -> LazyByteString -> (# ParserResult a, LazyByteString #)
99 parse p input -- input は lazy である必要有り。
100     = p `seq`
101       let (result, state') = runState (runParser p) (PST input True)
102       in
103         result `seq` (# result, pstInput state' #) -- pstInput state' も lazy である必要有り。
104
105 -- |@'parseStr' p str@ packs @str@ and parses it.
106 parseStr :: Parser a -> String -> (# ParserResult a, LazyByteString #)
107 parseStr p input
108     = p `seq` -- input は lazy である必要有り。
109       parse p (B.pack input)
110
111
112 anyChar :: Parser Char
113 anyChar = Parser $!
114           do state@(PST input _) <- get
115              if B.null input then
116                  return ReachedEOF
117                else
118                  do put $! state { pstInput = B.tail input }
119                     return (Success $! B.head input)
120
121
122 eof :: Parser ()
123 eof = Parser $!
124       do PST input _ <- get
125          if B.null input then
126              return $! Success ()
127            else
128              return IllegalInput
129
130 -- |@'allowEOF' p@ makes @p@ treat reaching EOF a normal failure.
131 allowEOF :: Parser a -> Parser a
132 allowEOF f = f `seq`
133              Parser $! do saved@(PST _ isEOFFatal) <- get
134                           put $! saved { pstIsEOFFatal = False }
135
136                           result <- runParser f
137                          
138                           state <- get
139                           put $! state { pstIsEOFFatal = isEOFFatal }
140
141                           return result
142
143
144 satisfy :: (Char -> Bool) -> Parser Char
145 satisfy f = f `seq`
146             do c <- anyChar
147                if f c then
148                    return c
149                  else
150                    failP
151
152
153 char :: Char -> Parser Char
154 char c = c `seq` satisfy (== c)
155
156
157 string :: String -> Parser String
158 string str = str `seq`
159              do mapM_ char str
160                 return str
161
162
163 infixr 0 <|>
164
165 -- |This is the backtracking alternation. There is no non-backtracking
166 -- equivalent.
167 (<|>) :: Parser a -> Parser a -> Parser a
168 f <|> g
169     = f `seq` g `seq`
170       Parser $! do saved <- get -- 状態を保存
171                    result <- runParser f
172                    case result of
173                      Success a    -> return $! Success a
174                      IllegalInput -> do put saved -- 状態を復歸
175                                         runParser g
176                      ReachedEOF   -> if pstIsEOFFatal saved then
177                                          return ReachedEOF
178                                      else
179                                          do put saved
180                                             runParser g
181
182
183 oneOf :: [Char] -> Parser Char
184 oneOf = foldl (<|>) failP . map char
185
186
187 notFollowedBy :: Parser a -> Parser ()
188 notFollowedBy p = p `seq`
189                   (p >> failP) <|> return ()
190
191
192 digit :: Parser Char
193 digit = do c <- anyChar
194            if c >= '0' && c <= '9' then
195                return c
196              else
197                failP
198
199
200 hexDigit :: Parser Char
201 hexDigit = do c <- anyChar
202               if (c >= '0' && c <= '9') ||
203                  (c >= 'a' && c <= 'f') ||
204                  (c >= 'A' && c <= 'F') then
205                   return c
206                 else
207                   failP
208
209
210 many :: Parser a -> Parser [a]
211 many p = p `seq`
212          do x  <- p
213             xs <- many p
214             return (x:xs)
215          <|>
216          return []
217
218
219 many1 :: Parser a -> Parser [a]
220 many1 p = p `seq`
221           do x  <- p
222              xs <- many p
223              return (x:xs)
224
225
226 count :: Int -> Parser a -> Parser [a]
227 count 0 _ = return []
228 count n p = n `seq` p `seq`
229             do x  <- p
230                xs <- count (n-1) p
231                return (x:xs)
232
233 -- def may be a _|_
234 option :: a -> Parser a -> Parser a
235 option def p = p `seq`
236                p <|> return def
237
238
239 sepBy :: Parser a -> Parser sep -> Parser [a]
240 sepBy p sep = p `seq` sep `seq`
241               sepBy1 p sep <|> return []
242
243
244 sepBy1 :: Parser a -> Parser sep -> Parser [a]
245 sepBy1 p sep = p `seq` sep `seq`
246                do x  <- p
247                   xs <- many $! sep >> p
248                   return (x:xs)
249
250
251 sp :: Parser Char
252 sp = char ' '
253
254
255 ht :: Parser Char
256 ht = char '\t'
257
258
259 crlf :: Parser String
260 crlf = string "\x0d\x0a"