]> gitweb @ CieloNegro.org - Lucu.git/blob - Network/HTTP/Lucu/Parser.hs
9a36ad5d83978048d3414b26090146db576a9562
[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     , choice
37     , oneOf
38     , digit
39     , hexDigit
40     , notFollowedBy
41     , many
42     , manyChar
43     , many1
44     , count
45     , option
46     , sepBy
47     , sepBy1
48
49     , sp
50     , ht
51     , crlf
52     )
53     where
54
55 import           Control.Monad.State.Strict
56 import qualified Data.ByteString.Lazy as Lazy (ByteString)
57 import qualified Data.ByteString.Lazy.Char8 as B hiding (ByteString)
58 import qualified Data.Foldable as Fold
59 import           Data.Int
60 import qualified Data.Sequence as Seq
61 import           Data.Sequence (Seq, (|>))
62
63 -- |@'Parser' a@ is obviously a parser which parses and returns @a@.
64 newtype Parser a = Parser {
65       runParser :: State ParserState (ParserResult a)
66     }
67
68
69 data ParserState
70     = PST {
71         pstInput      :: Lazy.ByteString
72       , pstIsEOFFatal :: !Bool
73       }
74     deriving (Eq, Show)
75
76
77 data ParserResult a = Success !a
78                     | IllegalInput -- 受理出來ない入力があった
79                     | ReachedEOF   -- 限界を越えて讀まうとした
80                       deriving (Eq, Show)
81
82
83 --  (>>=) :: Parser a -> (a -> Parser b) -> Parser b
84 instance Monad Parser where
85     p >>= f = Parser $! do saved <- get -- 失敗した時の爲に状態を保存
86                            result <- runParser p
87                            case result of
88                              Success a    -> runParser (f a)
89                              IllegalInput -> do put saved -- 状態を復歸
90                                                 return IllegalInput
91                              ReachedEOF   -> do put saved -- 状態を復歸
92                                                 return ReachedEOF
93     return !x = Parser $! return $! Success x
94     fail _    = Parser $! return $! IllegalInput
95
96 -- |@'failP'@ is just a synonym for @'Prelude.fail'
97 -- 'Prelude.undefined'@.
98 failP :: Parser a
99 failP = fail undefined
100
101 -- |@'parse' p bstr@ parses @bstr@ with @p@ and returns @(# result,
102 -- remaining #)@.
103 parse :: Parser a -> Lazy.ByteString -> (# ParserResult a, Lazy.ByteString #)
104 parse !p input -- input は lazy である必要有り。
105     = let (!result, state') = runState (runParser p) (PST input True)
106       in
107         (# result, pstInput state' #) -- pstInput state' も lazy である必要有り。
108
109 -- |@'parseStr' p str@ packs @str@ and parses it.
110 parseStr :: Parser a -> String -> (# ParserResult a, Lazy.ByteString #)
111 parseStr !p input -- input は lazy である必要有り。
112     = parse p (B.pack input)
113
114
115 anyChar :: Parser Char
116 anyChar = Parser $!
117           do state@(PST input _) <- get
118              if B.null input then
119                  return ReachedEOF
120                else
121                  do put $! state { pstInput = B.tail input }
122                     return (Success $! B.head input)
123
124
125 eof :: Parser ()
126 eof = Parser $!
127       do PST input _ <- get
128          if B.null input then
129              return $! Success ()
130            else
131              return IllegalInput
132
133 -- |@'allowEOF' p@ makes @p@ treat reaching EOF a normal failure.
134 allowEOF :: Parser a -> Parser a
135 allowEOF !f
136     = Parser $! do saved@(PST _ isEOFFatal) <- get
137                    put $! saved { pstIsEOFFatal = False }
138
139                    result <- runParser f
140                          
141                    state <- get
142                    put $! state { pstIsEOFFatal = isEOFFatal }
143
144                    return result
145
146
147 satisfy :: (Char -> Bool) -> Parser Char
148 satisfy !f
149     = do c <- anyChar
150          if f c then
151              return c
152            else
153              failP
154
155
156 char :: Char -> Parser Char
157 char !c = satisfy (== c)
158
159
160 string :: String -> Parser String
161 string !str
162     = let bs  = B.pack str
163           len = B.length bs
164       in
165         Parser $!
166         do st <- get
167            let (bs', rest) = B.splitAt len $ pstInput st
168                st'         = st { pstInput = rest }
169            if B.length bs' < len then
170                return ReachedEOF
171              else
172                if bs == bs' then
173                    do put st'
174                       return $ Success str
175                else
176                    return IllegalInput
177
178
179 infixr 0 <|>
180
181 -- |This is the backtracking alternation. There is no non-backtracking
182 -- equivalent.
183 (<|>) :: Parser a -> Parser a -> Parser a
184 (!f) <|> (!g)
185     = Parser $! do saved  <- get -- 状態を保存
186                    result <- runParser f
187                    case result of
188                      Success a    -> return $! Success a
189                      IllegalInput -> do put saved -- 状態を復歸
190                                         runParser g
191                      ReachedEOF   -> if pstIsEOFFatal saved then
192                                          do put saved
193                                             return ReachedEOF
194                                      else
195                                          do put saved
196                                             runParser g
197
198
199 choice :: [Parser a] -> Parser a
200 choice = foldl (<|>) failP
201
202
203 oneOf :: [Char] -> Parser Char
204 oneOf = foldl (<|>) failP . map char
205
206
207 notFollowedBy :: Parser a -> Parser ()
208 notFollowedBy !p
209     = Parser $! do saved  <- get -- 状態を保存
210                    result <- runParser p
211                    case result of
212                      Success _    -> do put saved -- 状態を復歸
213                                         return IllegalInput
214                      IllegalInput -> do put saved -- 状態を復歸
215                                         return $! Success ()
216                      ReachedEOF   -> do put saved -- 状態を復歸
217                                         return $! Success ()
218
219
220 digit :: Parser Char
221 digit = do c <- anyChar
222            if c >= '0' && c <= '9' then
223                return c
224              else
225                failP
226
227
228 hexDigit :: Parser Char
229 hexDigit = do c <- anyChar
230               if (c >= '0' && c <= '9') ||
231                  (c >= 'a' && c <= 'f') ||
232                  (c >= 'A' && c <= 'F') then
233                   return c
234                 else
235                   failP
236
237
238 many :: forall a. Parser a -> Parser [a]
239 many !p = Parser $!
240           do state <- get
241              let (# result, state' #) = many' state Seq.empty
242              put state'
243              return result
244     where
245       many' :: ParserState -> Seq a -> (# ParserResult [a], ParserState #)
246       many' !st !soFar
247           = case runState (runParser p) st of
248               (Success a,  st') -> many' st' (soFar |> a)
249               (IllegalInput, _) -> (# Success (Fold.toList soFar), st #)
250               (ReachedEOF  , _) -> if pstIsEOFFatal st then
251                                        (# ReachedEOF, st #)
252                                    else
253                                        (# Success (Fold.toList soFar), st #)
254
255 manyChar :: Parser Char -> Parser Lazy.ByteString
256 manyChar !p = Parser $!
257               do state <- get
258                  case scan' state 0 of
259                    Success len
260                        -> do let (bs, rest) = B.splitAt len (pstInput state)
261                                  state'     = state { pstInput = rest }
262                              put state'
263                              return $ Success bs
264                    ReachedEOF
265                        -> if pstIsEOFFatal state then
266                               return ReachedEOF
267                           else
268                               error "internal error"
269                    _   -> error "internal error"
270     where
271       scan' :: ParserState -> Int64 -> ParserResult Int64
272       scan' !st !soFar
273           = case runState (runParser p) st of
274               (Success _   , st') -> scan' st' (soFar + 1)
275               (IllegalInput, _  ) -> Success soFar
276               (ReachedEOF  , _  ) -> if pstIsEOFFatal st then
277                                          ReachedEOF
278                                      else
279                                          Success soFar
280
281
282 many1 :: Parser a -> Parser [a]
283 many1 !p = do x  <- p
284               xs <- many p
285               return (x:xs)
286
287
288 count :: Int -> Parser a -> Parser [a]
289 count !n !p = Parser $! count' n p Seq.empty
290
291 -- This implementation is rather ugly but we need to make it
292 -- tail-recursive to avoid stack overflow.
293 count' :: Int -> Parser a -> Seq a -> State ParserState (ParserResult [a])
294 count' 0  _  !soFar = return $! Success $! Fold.toList soFar
295 count' !n !p !soFar = do saved  <- get
296                          result <- runParser p
297                          case result of
298                            Success a    -> count' (n-1) p (soFar |> a)
299                            IllegalInput -> do put saved
300                                               return IllegalInput
301                            ReachedEOF   -> do put saved
302                                               return ReachedEOF
303
304
305 -- def may be a _|_
306 option :: a -> Parser a -> Parser a
307 option def !p = p <|> return def
308
309
310 sepBy :: Parser a -> Parser sep -> Parser [a]
311 sepBy !p !sep = sepBy1 p sep <|> return []
312
313
314 sepBy1 :: Parser a -> Parser sep -> Parser [a]
315 sepBy1 !p !sep
316     = do x  <- p
317          xs <- many $! sep >> p
318          return (x:xs)
319
320
321 sp :: Parser Char
322 sp = char ' '
323
324
325 ht :: Parser Char
326 ht = char '\t'
327
328
329 crlf :: Parser String
330 crlf = string "\x0d\x0a"