LoginSignup
3

More than 5 years have passed since last update.

Parsecのソースちら見(3)

Posted at

結局まだパーサー1個も出てきてないので、後一回必要。
http://www.facebook.com/hiratara/posts/539308276101182

プリミティブのパーサとしてはtokenPrimExが用意されてる。パーサの材料は原始的な感じで、エラー時の文字列生成に使うshowToken、エラー時に表示する(他にも使える)ソースのポジションを適切に更新するnextpos、ユーザが定義した状態を更新するJust nextState、そして実際にトークンの是非を判断するtestの4つとなる。これらを矛盾しないように適切に定義して渡せばOK。ソースは長く見えるけど当たり前のことしかやってない。ユーザ状態の更新の有無で定義を2つに分けてるけど、これはなぜ必要なんだろう。インライン展開する際のパフォーマンスの都合?

Text-Parsec-Prim.html
tokenPrimEx :: (Stream s m t)
            => (t -> String)      
            -> (SourcePos -> t -> s -> SourcePos)
            -> Maybe (SourcePos -> t -> s -> u -> u)
            -> (t -> Maybe a)     
            -> ParsecT s u m a
{-# INLINE tokenPrimEx #-}
tokenPrimEx showToken nextpos Nothing test
  = ParsecT $ \(State input pos user) cok cerr eok eerr -> do
      r <- uncons input
      case r of
        Nothing -> eerr $ unexpectError "" pos
        Just (c,cs)
         -> case test c of
              Just x -> let newpos = nextpos pos c cs
                            newstate = State cs newpos user
                        in seq newpos $ seq newstate $
                           cok x newstate (newErrorUnknown newpos)
              Nothing -> eerr $ unexpectError (showToken c) pos
tokenPrimEx showToken nextpos (Just nextState) test
  = ParsecT $ \(State input pos user) cok cerr eok eerr -> do
      r <- uncons input
      case r of
        Nothing -> eerr $ unexpectError "" pos
        Just (c,cs)
         -> case test c of
              Just x -> let newpos = nextpos pos c cs
                            newUser = nextState pos c cs user
                            newstate = State cs newpos newUser
                        in seq newpos $ seq newstate $
                           cok x newstate $ newErrorUnknown newpos
              Nothing -> eerr $ unexpectError (showToken c) pos

後必要なのはKleene closure(任意個の繰り返し)を作るためのmanyAccum。入力を消費して成功した場合、walk関数で繰り返しパーサを適用し、ユーザが定義したaccを使って結果を集める。繰り返しの停止に使えるのは入力を消費せずに失敗した場合なので、tryともうまく組み合わせる必要がある。入力を消費して失敗した場合には元々のエラー報告用の継続に処理を進めて素直にエラーを発生させる。

ミソは入力を消費せずに成功した場合で、この時は無限ループになる可能性があるのでエラーに落とし込んでいる。後、一度もwalkせずに繰り返しが終了した場合は、結局入力を消費しなかったことになるのでcokではなくeokの継続で処理を続けなければいけないことにも注意。

Text-Parsec-Prim.html
manyAccum :: (a -> [a] -> [a])
          -> ParsecT s u m a
          -> ParsecT s u m [a]
manyAccum acc p =
    ParsecT $ \s cok cerr eok eerr ->
    let walk xs x s' err =
            unParser p s'
              (seq xs $ walk $ acc x xs)  -- consumed-ok
              cerr                        -- consumed-err
              manyErr                     -- empty-ok
              (\e -> cok (acc x xs) s' e) -- empty-err
    in unParser p s (walk []) cerr manyErr (\e -> eok [] s e)

この辺まで事前知識を持ってからsatisfyのコードを読むと、すんなり読めるだろう。

Text-Parsec-Char.html
satisfy :: (Stream s m Char) => (Char -> Bool) -> ParsecT s u m Char
satisfy f           = tokenPrim (\c -> show [c])
                                (\pos c _cs -> updatePosChar pos c)
                                (\c -> if f c then Just c else Nothing)

Parsecのコード読むのはこの程度にしようかなと思うのだけど、最後に解せないとこが1つ。tokensだけはtokenPrimExmanyAccumも使ってない。歴史的経緯なのか、理由があるのか・・・。

Register as a new user and use Qiita more conveniently

  1. You get articles that match your needs
  2. You can efficiently read back useful information
  3. You can use dark theme
What you can do with signing up
3