Skip to content

Instantly share code, notes, and snippets.

@tanakh
Last active February 17, 2020 12:46
Show Gist options
  • Star 8 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save tanakh/d7a089341a011118a1cd to your computer and use it in GitHub Desktop.
Save tanakh/d7a089341a011118a1cd to your computer and use it in GitHub Desktop.
Trifecta / Parsers
Use gist deck to view:
https://gistdeck.herokuapp.com/
-- デモでかいたやつ
import Text.Trifecta
import Control.Applicative
data Json
= JSObject [(String, Json)]
| JSArray [Json]
| JSString String
| JSNumber (Either Integer Double)
| JSBool Bool
| JSNull
deriving (Eq, Show)
json =
JSObject <$> braces (commaSep ((,) <$> stringLiteral <* symbol ":" <*> json)) <|>
JSArray <$> brackets (commaSep json) <|>
JSString <$> stringLiteral <|>
JSNumber <$> naturalOrDouble <|>
JSBool <$> (True <$ symbol "true" <|> False <$ symbol "false") <|>
JSNull <$ symbol "null"
main = parseTest (json <* eof) =<< getLine

自己紹介 / Self Introduction

  • Hideyuki Tanaka (@tanakh)

  • Preferred Infrastructure 勤務 / Working at Preferred Infrastructure Inc.

  • Haskell 愛好家 / I love Haskell

  • (宣伝)すごいHaskell楽しく学ぼう (Learn You a Haskell for Great Good in Japanese)

    • lyah
    • Buy NOW!

Trifecta とは / What is Trifecta?

  • Parser Combinator Library

  • Trifecta (三連単) of Parser

    • Iteratee
    • Parsec
    • Monoidal Parsing
  • 最近 version 1.0 が出た / Version 1.0 was released

    • 2010年から開発 / Since 2010
    • そろそろ安定しているのかなあ? / Seems to be stabled

Parser ライブラリ色々 / Other Parser Combinators

  • parsec

    • デファクト / defact standard
  • attoparsec

    • 最近よく使われる / Recently, most likely to use
    • bytestring ベースの実装でよくチューニングされており、 とにかく速い / It is EXTREAMLY fast!
  • binary, cereal

    • バイナリデータ向け / for Binary data
    • generic-deriving などにも対応していて、速度も速いので、 自分の定義したデータをバイナリにしたいときは便利 / Convenient for serializing user defined data-structures
  • iteratee および派生 (conduit など) / and others

    • 何かを入力して何かを出力する抽象化 / I/O abstraction
    • ちょっとレイヤーが違うかも / Lower layer
      • attoparsec-conduit とかある
  • peggy

    • DSL for PEG (Parsing Expression Grammers)
    • Template Haskell のコードを生成 / Generates Codes for TH

何が新しいのか(公式の主張) / What's new?

  • Parsec と Monoidal Parsing のよいところを融合 / Fuses advantages of parsec and monoids

  • Parsec は/is

    • 便利 / Convenient
  • Monoidal Parsing は/is

    • 並列 / Parallel
    • インクリメンタル / Incremental
    • (このへん正直あんまりわからない)

個人的に良いとこ / Other goodies

  • APIが洒落てる / Pretty API

    • トークンの扱いがいい感じ
    • ekmett プロダクトにはよくあること
  • CPS 変換済み / CPS'd impl

    • ekmett プロダクトにはよくあること
  • 標準的なAPIに従ってる / Support Standard APIs

    • Functor, Applicative, Monad, MonadPlus, Alternative, Monoid
    • ekmett プロダクトにはよくあること
  • 強いエラー報告機能 / Strong error diagnostics

    • あとで詳しく / Detail is later

Trifecta Parser is ...

標準的なコンビネータ

choice       :: Alternative m => [m a] -> m a
option       :: Alternative m => a -> m a -> m a
optional     :: Alternative f => f a -> f (Maybe a)
skipOptional :: Alternative m => m a -> m ()
between      :: Applicative m => m bra -> m ket -> m a -> m a
some         :: Alternative f => forall a. f a -> f [a]
many         :: Alternative f => forall a. f a -> f [a]
sepBy        :: Alternative m => m a -> m sep -> m [a]
sepBy1       :: Alternative m => m a -> m sep -> m [a]
sepEndBy1    :: Alternative m => m a -> m sep -> m [a]
sepEndBy     :: Alternative m => m a -> m sep -> m [a]
endBy1       :: Alternative m => m a -> m sep -> m [a]
endBy        :: Alternative m => m a -> m sep -> m [a]
count        :: Applicative m => Int -> m a -> m [a]
chainl       :: Alternative m => m a -> m (a -> a -> a) -> a -> m a
chainr       :: Alternative m => m a -> m (a -> a -> a) -> a -> m a
chainl1      :: Alternative m => m a -> m (a -> a -> a) -> m a
chainr1      :: Alternative m => m a -> m (a -> a -> a) -> m a
manyTill     :: Alternative m => m a -> m end -> m [a]
  • 実は、Alternativeさえあればいい / Only Alternative needed

いい感じの型クラス / Nice Type Class

class Alternative m => Parsing m where
  try :: m a -> m a
  (<?>) :: m a -> String -> m a
  skipMany :: m a -> m ()
  skipSome :: m a -> m ()
  unexpected :: String -> m a
  eof :: m ()

Token パーザのクラス / Token Parser Class

class CharParsing m => TokenParsing m where
  someSpace :: m ()
  nesting :: m a -> m a
  semi :: m Char
  highlight :: Highlight -> m a -> m a
  token :: m a -> m a

Incremental Parsing

data Step a
  = StepDone !Rope a
  | StepFail !Rope Doc
  | StepCont !Rope (Result a) (Rope -> Step a)

feed       :: Reducer t Rope => t -> Step r -> Step r
starve     :: Step a -> Result a
stepParser :: Parser a -> Delta -> ByteString -> Step a
stepResult :: Rope -> Result a -> Step a
stepIt     :: It Rope a -> Step a
  • 入力を少しずつ投入できる / feed inputs incrementaly
    • cf. Lazy Stringを取るインターフェース (parsecなど)
    • Iteratee的なインターフェースと親和性が良い / Convenient using with iteratees

Clang スタイルエラー報告 / Clang style error diagnostics

  • Clangのようないい感じのparse error表示機能 / Pretty good error report like Clang
    • エラー箇所をcaretで表示 / Show error point by caret
    • ターミナルへのカラー出力! / Color output!
expr   = term   `chainl1` addop
term   = factor `chainl1` mulop
factor = parens expr <|> integer

mulop  = (*) <$ symbol "*" <|> div <$ symbol "/"
addop  = (+) <$ symbol "+" <|> (-) <$ symbol "-"

main = parseTest expr =<< getLine
$ echo "1+2**3" | runhaskell trifecta-test.hs
(interactive):1:5: error: expected: "(", integer
1+2**3<EOF>
    ^

(Parsecの場合 / Parsec case)

import Text.Parsec
import qualified Text.Parsec.Token as P
import Text.Parsec.Language (haskellDef)
import Control.Applicative hiding ((<|>), many)

lexer       = P.makeTokenParser haskellDef    
      
parens      = P.parens lexer
integer     = P.integer lexer
symbol      = P.symbol lexer

expr   = term   `chainl1` addop
term   = factor `chainl1` mulop
factor = parens expr <|> integer

mulop  = (*) <$ symbol "*" <|> div <$ symbol "/"
addop  = (+) <$ symbol "+" <|> (-) <$ symbol "-"

main = parseTest (many expr <* eof) =<< getLine
$ echo "1+2**3" | runhaskell parsec-test.hs
parse error at (line 1, column 5):
unexpected "*"
expecting "(" or integer

parsers

  • パーザコンビネータの一般化 / Generalization of Parser Combinators

    • 基本的なAPIはparsecを踏襲 / Basically, parsec like API
  • trifectaparsers の型クラスのインスタンス / trifecta's parser is an instance of parser's class

    • 実は、さっきまでのドライバ周り以外のAPIはparsersのもの
  • parsec-parsers

    • parsecに対するparsersのインスタンス実装 / parsers instance of parsec
    • parsers で書けば、trifectaでもparsecでもパーズできる / parsers' parser can be parsed by BOTH trifecta and parsec!!

デモ / Demo

  • ライブコーディングの予定 / Now, I will be implement some parsers!
 (´・_・`)
 m____m カタカタ...
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment