SlideShare une entreprise Scribd logo
1  sur  101
invertible-syntax
  (TH                     )
           Hiromi Ishii
        a.k.a. @mr_konn
About myself...

• id:mr_konn / @mr_konn
• Template Haskell
• P Haskell
TOC

• invertible-syntax
•         JSON Parser Pretty Printer

• Inside invertible-syntax
• Real World Template Haskell
TOC

• invertible-syntax
•         JSON Parser Pretty Printer

• Inside invertible-syntax
• Real World Template Haskell
invertible-syntax
Haskeller
Haskeller
•
Haskeller
•
    • Web   JSON   YAML……
Haskeller
•
    • Web   JSON   YAML……

    •
Haskeller
•
    • Web        JSON   YAML……

    •
    • Java   C
Haskeller
•
    • Web        JSON   YAML……

    •
    • Java   C

•
•   Parser   Pretty Printer
•   Parser       Pretty Printer

    •   Parser
•   Parser       Pretty Printer

    •   Parser
        •                   (Parsec, Happy...)
•   Parser       Pretty Printer

    •   Parser
        •                   (Parsec, Happy...)

        •
•   Parser       Pretty Printer

    •   Parser
        •                   (Parsec, Happy...)

        •
    •   Pretty Printer
•   Parser       Pretty Printer

    •   Parser
        •                   (Parsec, Happy...)

        •
    •   Pretty Printer
        •                 ……      (Show, HughesPJ...)
•   Parser       Pretty Printer

    •   Parser
        •                   (Parsec, Happy...)

        •
    •   Pretty Printer
        •                 ……      (Show, HughesPJ...)

            •   ……
•   Parser       Pretty Printer

    •
        •   Don’t Repeat Yourself!
    •   Pretty Printer

    •
•
invertible-syntax
invertible-syntax

•   Parser       Pretty Printer

    •                 Syntax Description

    •   Applicative

•
    •   Parser     Pretty Printer
JSON
JSON
•            JSON

    •
    •
data Slot = Slot { key :: String, val :: JSON }
data JSON = Number !Integer
       | Null
       | Bool !Bool
       | Array ![JSON]
       | String String
       | Object ![Slot]
JSONPretty.hs
import Text.PrettyPrint.HughesPJ

pretty :: Printer JSON -- Printer a = a → Doc
pretty (Object jss) = braces $ hcat $ intersperse comma
                          $ map slot jss
pretty (Array jss) = brackets $ hcat $ intersperse comma
                           $ map pretty jss
pretty (String str) = doubleQuotes $ text str
pretty (Null)      = text "null"
pretty (Bool b)     = case b of
                  True → text "true"
                  False → text "false"
pretty (Number int) = integer int
slot s = doubleQuotes (text $ key s) <> colon <+> sub (val s)
JSONParsec.hs
import Text.Parsec

json, jsobj, ..., jsnumber :: Parser JSON
json = jsobj <|> jsarray <|> ... <|> jsbool <|> jsnumber
jsobj = Object <$> between (symbol "{") (symbol "}")
                   (term `sepBy` symbol ",")
  where
   term = Slot <$> str <* symbol ":" <*> json
jsarray = Array <$> between (symbol "[") (symbol "]")
                   (json `sepBy` symbol ",")
jsstring = String <$> str
jsnull = Null <$ symbol "null"
jsbool = Bool True             <$ symbol "true"
     <|> Bool False          <$ symbol "false"
jsnumber = Number . read <$> many1 digit

str = between (spaces *> char '"') (char '"' <* spaces)
         (many $ noneOf """)
JSONInvertible.hs
defineIsomorphisms ''JSON

json, jsobj, ..., jsnumber :: Syntax f   f JSON
json = jsobj <|> jsarray <|> ... <|> jsbool <|> jsnumber
jsobj = object <$> between (symbol "{") (symbol "}")
                 (term `sepBy` symbol ",")
  where
   term = slot <$> str <* skipSpace <* text ":" <*> json
jsarray = array <$> between (symbol "[") (symbol "]")
                 (json `sepBy` symbol ",")
jsstring = string <$> str
jsnull = null <$> symbol "null"
jsbool = bool . element True <$> symbol "true"
     <|> bool . element False <$> symbol "false"
jsnumber = number . numIso <$> many1 digit

str = between (optSpace *> text """) (text """ <* optSpace)
          (many (subset (/='"') <$> token))
numIso = Iso read’ show’
 where
   read' = liftM fst . listToMaybe . reads
   show' = return . show
• Syntax f f JSON
 • Syntax Description
 • pure token
• <$> <$ <*>
• defineIsomorphisms   ……

•
• (<$) (<$>)
• Iso
Inside
invertible-sytnax
Parser   Priner
Parser   Priner
• Iso :
Parser            Priner
• Iso :
  • data Iso a b = Iso (a→Maybe b) (b→Maybe a)
Parser            Priner
• Iso :
  • data Iso a b = Iso (a→Maybe b) (b→Maybe a)
  •
Parser            Priner
• Iso :
  • data Iso a b = Iso (a→Maybe b) (b→Maybe a)
  •
  • Iso Category
Parser            Priner
• Iso :
  • data Iso a b = Iso (a→Maybe b) (b→Maybe a)
  •
  • Iso Category
    •          id            (.)
Parser            Priner
• Iso :
  • data Iso a b = Iso (a→Maybe b) (b→Maybe a)
  •
  • Iso Category
    •          id            (.)

•          IsoFunctor
Iso                      1
        numIso = Iso read’ show’
         where
          read' = liftM fst . listToMaybe . reads
          show' = return . show


•
•              Control.Isomorphism.Partial.Unsafe

•
    •                        Iso
Iso                         2
•   import Control.Isomorphism.Partial
•   element :: α → Iso α ()
    •                  ()

•   subset :: (α → Bool) → Iso α α
    •
•   foldl :: Iso (α,β) α → Iso (α,[β]) α

•           (***), associate, iterate, unit       ……
IsoFunctor
• Functor       =

 • fmap :: (α→β) → f α → f β
 • α→β                Iso α β       …
    class IsoFunctor δ where
     (<$>) :: Iso α β → δ α → δ β


•
partial-isomorphisms
invertible-syntax
Applicative
invertible-syntax
Applicative
invertible-syntax
Applicative
•             (<*>)

• (<*>) :: δ (α → β) → δ α → δ β
• Iso α β           ……
    class IsoApplicative δ where
     (<*>) :: δ (Iso α β) → δ α → δ β


• Parser
 •                   Iso α β       α
Printer
instance IsoApplicative Printer where
 (<*>) pab pa b = ……
Printer
    instance IsoApplicative Printer where
     (<*>) pab pa b = ……

• (<*>) :: Printer (Iso α β) → Printer α → Printer β
   = ((Iso α β)→Doc) → (α→Doc) → β → Doc
Printer
     instance IsoApplicative Printer where
      (<*>) pab pa b = ……

• (<*>) :: Printer (Iso α β) → Printer α → Printer β
   = ((Iso α β)→Doc) → (α→Doc) → β → Doc

•β
Printer
     instance IsoApplicative Printer where
      (<*>) pab pa b = ……

• (<*>) :: Printer (Iso α β) → Printer α → Printer β
   = ((Iso α β)→Doc) → (α→Doc) → β → Doc

•β
 •                                      ……
Printer
      instance IsoApplicative Printer where
       (<*>) pab pa b = ……

• (<*>) :: Printer (Iso α β) → Printer α → Printer β
   = ((Iso α β)→Doc) → (α→Doc) → β → Doc

•β
  •                                      ……

•                          ……
•   Applicative
•        Applicative

    • Slot <$> key <*> val
•        Applicative

    • Slot <$> key <*> val
    • Slot :: String → JSON → (String, JSON)
•        Applicative

    • Slot <$> key <*> val
    • Slot :: String → JSON → (String, JSON)
     • slot :: Iso String (Iso JSON Slot)
•        Applicative

    • Slot <$> key <*> val
    • Slot :: String → JSON → (String, JSON)
     • slot :: Iso String (Iso JSON Slot)

     • slot <$> key :: δ (Iso JSON Slot)
……
……
• slot :: Iso (String, JSON) Slot
……
• slot :: Iso (String, JSON) Slot
 • slot <$> key <*> val :: δ Slot
                ……
……
• slot :: Iso (String, JSON) Slot
 • slot <$> key <*> val :: δ Slot
                ……

  • slot <$> (key <*> val)          ……
……
• slot :: Iso (String, JSON) Slot
 • slot <$> key <*> val :: δ Slot
                ……

  • slot <$> (key <*> val)          ……

  • (<*>) :: δ α → δ β → δ (α, β)
ProductFunctor
    class ProductFunctor δ where
     (<*>) :: δ α → δ β → δ (α, β)

    infix 5 <$>
    infixr 6 <*>


• Parser      Printer



•
Iso
null :: Iso () JSON
null = Iso to from
 where
  to _ = Just Null
  from Null = Just ()
  from _ = Nothing

number :: Iso Integer JSON
number = Iso to from
 where
  to = Just . Number
  from (Number int) = Just int
  from _         = Nothing

slot :: Iso (String, JSON) Slot
slot = Iso to from
 where
   to (a,b) = Just $ Slot a b
   from (Slot a b) = Just (a,b)
class Alternative δ where
         (<|>) :: δ α → δ α → δ α
         empty :: δ α


    •         Applicative      instance

•                         token

•                 pure

    •                 Syntax
class IsoFunctor δ where
 (<$>) :: Iso α β → δ α → δ β

class ProductFunctor δ where
 (<*>) :: δ α → δ β → δ (α, β)

class Alternative δ where
 (<|>) :: δ α → δ α → δ α
 empty :: δ α

class ( IsoFunctor δ, ProductFunctor δ
    , Alternative δ
    )    Syntax δ where
 pure :: α → δ α
 token :: δ Char
•
•
•   many, sepBy, chainl1, text, between
•
•   many, sepBy, chainl1, text, between
    •           +
•
•   many, sepBy, chainl1, text, between
    •           +

•   skipSpace, sepSpace, optSpace
•
•   many, sepBy, chainl1, text, between
    •           +

•   skipSpace, sepSpace, optSpace
    •
•
•   many, sepBy, chainl1, text, between
    •             +

•   skipSpace, sepSpace, optSpace
    •
    •   Printer
•
•   many, sepBy, chainl1, text, between
    •             +

•   skipSpace, sepSpace, optSpace
    •
    •   Printer

    •   sep           opt
• skipSpace   sepSpace optSpace

 •
 • “ntr”
read/show      invertible-syntax

  Parsec/HughesPJ (         )
•
• invertible-syntax   Parser Printer
  Naive

  •
  •            Proof of Concept
•   Parsec   HughesPJ   Syntax
•   Parsec   HughesPJ   Syntax



    •
•   Parsec   HughesPJ           Syntax



    •
        •               (<|>)
•   Parsec   HughesPJ           Syntax



    •
        •               (<|>)

    •
•   Parsec   HughesPJ           Syntax



    •
        •               (<|>)

    •
•
•   Parsec   HughesPJ           Syntax



    •
        •               (<|>)

    •
•
•
ADT Iso
defineIsomorphisms
Real World
Template Haskell
 defineIsomorphisms   TH
null :: Iso () JSON
null = Iso to from
 where
  to _ = Just Null
  from Null = Just ()
  from _ = Nothing

number :: Iso Integer JSON
number = Iso to from
 where
  to a = Just $ Number a
  from (Number int) = Just int
  from _         = Nothing

slot :: Iso (String, JSON) Slot
slot = Iso to from
 where
   to (a,b) = Just $ Slot a b
   from (Slot a b) = Just (a,b)
• data Hoge
•
  •                     Iso () Hoge

  •        Iso (a, (b, ...)) Hoge
• from
 • Just $     a b c ...

• to
 •
    Nothing
•
•
    • reify
•
    •                 ……   Exp

    •         ……   Type
TH


• Metaprogramming in Haskell
•
    •
        •   E    ,P         ,T      ,D           ,
            C         , B Body, L

        •   type HogeQ = Q Hoge
    •                                    (LamE       lamE   )

        •         Q

        •   lamE :: [PatQ] → ExpQ→ ExpQ
• defineIsomorphisms :: Name → Q [Dec]
 • data newtype
 defineIsomorphisms :: Name → Q [Dec]
 defineIsomorphisms d = do
  TyConI dec ← reify d
  cs     ← decConstructors dec
  mapM (defFromCon (wildcard cs)) cs

 decConstructors   :: Dec -> Q [Con]
 decConstructors   (DataD _ _ _ cs _) = return cs
 decConstructors   (NewtypeD _ _ _ c _)= return [c]
 decConstructors   _ = error “not supported!”
•   wildcard

    •   case { _ → Nothing }

•   defFromCon

    •   rename                             (         )

wildcard :: [Con] -> [MatchQ]
wildcard cs
 = if length cs > 1
   then [match (wildP) (normalB [| Nothing |]) []]
   else []

defFromCon :: [MatchQ] -> Con -> DecQ
defFromCon wc con
 = funD (rename (conName con))
    [clause [] (normalB (isoFromCon wc con)) []]
•
isoFromCon :: [MatchQ] -> Con -> ExpQ
                                                 Iso
isoFromCon wildcard con = do
  let c = conName con
  let fs = conFields con --
 let n   = length fs    --
 (ps, vs) ← genPE n       --
 v       ← newName "x"
 let f   = lamE [nested tupP ps] --
             [| Just $(foldl appE (conE c) vs) |]
 let g   = lamE [varP v]
         (caseE (varE v) $
           [ match (conP c ps) -- Con (a,(b,..) →
            (normalB [| Just $(nested tupE vs) |]) []
           ] ++ wildcard) -- case
 [| Iso $f $g |] --            from/to   λ     Iso
Any Questions?
Invertible-syntax 入門

Contenu connexe

Tendances

Functional Pe(a)rls - the Purely Functional Datastructures edition
Functional Pe(a)rls - the Purely Functional Datastructures editionFunctional Pe(a)rls - the Purely Functional Datastructures edition
Functional Pe(a)rls - the Purely Functional Datastructures editionosfameron
 
Introductionto fp with groovy
Introductionto fp with groovyIntroductionto fp with groovy
Introductionto fp with groovyIsuru Samaraweera
 
Tips and Tricks of Developing .NET Application
Tips and Tricks of Developing .NET ApplicationTips and Tricks of Developing .NET Application
Tips and Tricks of Developing .NET ApplicationJoni
 
Perl6 a whistle stop tour
Perl6 a whistle stop tourPerl6 a whistle stop tour
Perl6 a whistle stop tourSimon Proctor
 
Perl6 a whistle stop tour
Perl6 a whistle stop tourPerl6 a whistle stop tour
Perl6 a whistle stop tourSimon Proctor
 
Xlab #1: Advantages of functional programming in Java 8
Xlab #1: Advantages of functional programming in Java 8Xlab #1: Advantages of functional programming in Java 8
Xlab #1: Advantages of functional programming in Java 8XSolve
 
ITT 2015 - Saul Mora - Object Oriented Function Programming
ITT 2015 - Saul Mora - Object Oriented Function ProgrammingITT 2015 - Saul Mora - Object Oriented Function Programming
ITT 2015 - Saul Mora - Object Oriented Function ProgrammingIstanbul Tech Talks
 
Python Performance 101
Python Performance 101Python Performance 101
Python Performance 101Ankur Gupta
 
Scala vs Java 8 in a Java 8 World
Scala vs Java 8 in a Java 8 WorldScala vs Java 8 in a Java 8 World
Scala vs Java 8 in a Java 8 WorldBTI360
 
GR8Conf 2011: Effective Groovy
GR8Conf 2011: Effective GroovyGR8Conf 2011: Effective Groovy
GR8Conf 2011: Effective GroovyGR8Conf
 
Crafting Custom Interfaces with Sub::Exporter
Crafting Custom Interfaces with Sub::ExporterCrafting Custom Interfaces with Sub::Exporter
Crafting Custom Interfaces with Sub::ExporterRicardo Signes
 
Profiling and optimization
Profiling and optimizationProfiling and optimization
Profiling and optimizationg3_nittala
 
Functional Programming In Java
Functional Programming In JavaFunctional Programming In Java
Functional Programming In JavaAndrei Solntsev
 
Nik Graf - Get started with Reason and ReasonReact
Nik Graf - Get started with Reason and ReasonReactNik Graf - Get started with Reason and ReasonReact
Nik Graf - Get started with Reason and ReasonReactOdessaJS Conf
 
Functional Algebra: Monoids Applied
Functional Algebra: Monoids AppliedFunctional Algebra: Monoids Applied
Functional Algebra: Monoids AppliedSusan Potter
 
RxSwift 시작하기
RxSwift 시작하기RxSwift 시작하기
RxSwift 시작하기Suyeol Jeon
 
Exhibition of Atrocity
Exhibition of AtrocityExhibition of Atrocity
Exhibition of AtrocityMichael Pirnat
 

Tendances (20)

Functional Pe(a)rls - the Purely Functional Datastructures edition
Functional Pe(a)rls - the Purely Functional Datastructures editionFunctional Pe(a)rls - the Purely Functional Datastructures edition
Functional Pe(a)rls - the Purely Functional Datastructures edition
 
Introductionto fp with groovy
Introductionto fp with groovyIntroductionto fp with groovy
Introductionto fp with groovy
 
Tips and Tricks of Developing .NET Application
Tips and Tricks of Developing .NET ApplicationTips and Tricks of Developing .NET Application
Tips and Tricks of Developing .NET Application
 
Perl6 a whistle stop tour
Perl6 a whistle stop tourPerl6 a whistle stop tour
Perl6 a whistle stop tour
 
Perl6 a whistle stop tour
Perl6 a whistle stop tourPerl6 a whistle stop tour
Perl6 a whistle stop tour
 
groovy & grails - lecture 3
groovy & grails - lecture 3groovy & grails - lecture 3
groovy & grails - lecture 3
 
Xlab #1: Advantages of functional programming in Java 8
Xlab #1: Advantages of functional programming in Java 8Xlab #1: Advantages of functional programming in Java 8
Xlab #1: Advantages of functional programming in Java 8
 
ITT 2015 - Saul Mora - Object Oriented Function Programming
ITT 2015 - Saul Mora - Object Oriented Function ProgrammingITT 2015 - Saul Mora - Object Oriented Function Programming
ITT 2015 - Saul Mora - Object Oriented Function Programming
 
Rust ⇋ JavaScript
Rust ⇋ JavaScriptRust ⇋ JavaScript
Rust ⇋ JavaScript
 
Python Performance 101
Python Performance 101Python Performance 101
Python Performance 101
 
Scala vs Java 8 in a Java 8 World
Scala vs Java 8 in a Java 8 WorldScala vs Java 8 in a Java 8 World
Scala vs Java 8 in a Java 8 World
 
GR8Conf 2011: Effective Groovy
GR8Conf 2011: Effective GroovyGR8Conf 2011: Effective Groovy
GR8Conf 2011: Effective Groovy
 
Crafting Custom Interfaces with Sub::Exporter
Crafting Custom Interfaces with Sub::ExporterCrafting Custom Interfaces with Sub::Exporter
Crafting Custom Interfaces with Sub::Exporter
 
Profiling and optimization
Profiling and optimizationProfiling and optimization
Profiling and optimization
 
Functional programming in java
Functional programming in javaFunctional programming in java
Functional programming in java
 
Functional Programming In Java
Functional Programming In JavaFunctional Programming In Java
Functional Programming In Java
 
Nik Graf - Get started with Reason and ReasonReact
Nik Graf - Get started with Reason and ReasonReactNik Graf - Get started with Reason and ReasonReact
Nik Graf - Get started with Reason and ReasonReact
 
Functional Algebra: Monoids Applied
Functional Algebra: Monoids AppliedFunctional Algebra: Monoids Applied
Functional Algebra: Monoids Applied
 
RxSwift 시작하기
RxSwift 시작하기RxSwift 시작하기
RxSwift 시작하기
 
Exhibition of Atrocity
Exhibition of AtrocityExhibition of Atrocity
Exhibition of Atrocity
 

En vedette

ものまね鳥を愛でる 結合子論理と計算
ものまね鳥を愛でる 結合子論理と計算ものまね鳥を愛でる 結合子論理と計算
ものまね鳥を愛でる 結合子論理と計算Hiromi Ishii
 
実践・完全犯罪のつくり方
実践・完全犯罪のつくり方実践・完全犯罪のつくり方
実践・完全犯罪のつくり方Hiromi Ishii
 
(数式の入った)本をつくる
(数式の入った)本をつくる(数式の入った)本をつくる
(数式の入った)本をつくるHiromi Ishii
 
Alloy Analyzer のこと
Alloy Analyzer のことAlloy Analyzer のこと
Alloy Analyzer のことHiromi Ishii
 
Yesodを支える技術
Yesodを支える技術Yesodを支える技術
Yesodを支える技術Hiromi Ishii
 
アメブロの大規模システム刷新と それを支えるSpring
アメブロの大規模システム刷新と それを支えるSpringアメブロの大規模システム刷新と それを支えるSpring
アメブロの大規模システム刷新と それを支えるSpringTakuya Hattori
 
御清聴ありがとうございました
御清聴ありがとうございました御清聴ありがとうございました
御清聴ありがとうございましたHiromi Ishii
 
EPUBのナビゲーションを理解しよう
EPUBのナビゲーションを理解しようEPUBのナビゲーションを理解しよう
EPUBのナビゲーションを理解しようHiroshi Takase
 

En vedette (9)

ものまね鳥を愛でる 結合子論理と計算
ものまね鳥を愛でる 結合子論理と計算ものまね鳥を愛でる 結合子論理と計算
ものまね鳥を愛でる 結合子論理と計算
 
実践・完全犯罪のつくり方
実践・完全犯罪のつくり方実践・完全犯罪のつくり方
実践・完全犯罪のつくり方
 
(数式の入った)本をつくる
(数式の入った)本をつくる(数式の入った)本をつくる
(数式の入った)本をつくる
 
Alloy Analyzer のこと
Alloy Analyzer のことAlloy Analyzer のこと
Alloy Analyzer のこと
 
最終発表
最終発表最終発表
最終発表
 
Yesodを支える技術
Yesodを支える技術Yesodを支える技術
Yesodを支える技術
 
アメブロの大規模システム刷新と それを支えるSpring
アメブロの大規模システム刷新と それを支えるSpringアメブロの大規模システム刷新と それを支えるSpring
アメブロの大規模システム刷新と それを支えるSpring
 
御清聴ありがとうございました
御清聴ありがとうございました御清聴ありがとうございました
御清聴ありがとうございました
 
EPUBのナビゲーションを理解しよう
EPUBのナビゲーションを理解しようEPUBのナビゲーションを理解しよう
EPUBのナビゲーションを理解しよう
 

Similaire à Invertible-syntax 入門

Happy Go Programming
Happy Go ProgrammingHappy Go Programming
Happy Go ProgrammingLin Yo-An
 
ScotRuby - Dark side of ruby
ScotRuby - Dark side of rubyScotRuby - Dark side of ruby
ScotRuby - Dark side of rubyGautam Rege
 
Slides chapter3part1 ruby-forjavaprogrammers
Slides chapter3part1 ruby-forjavaprogrammersSlides chapter3part1 ruby-forjavaprogrammers
Slides chapter3part1 ruby-forjavaprogrammersGiovanni924
 
Building Interpreters with PyPy
Building Interpreters with PyPyBuilding Interpreters with PyPy
Building Interpreters with PyPyDaniel Neuhäuser
 
RedDot Ruby Conf 2014 - Dark side of ruby
RedDot Ruby Conf 2014 - Dark side of ruby RedDot Ruby Conf 2014 - Dark side of ruby
RedDot Ruby Conf 2014 - Dark side of ruby Gautam Rege
 
Programming Haskell Chapter8
Programming Haskell Chapter8Programming Haskell Chapter8
Programming Haskell Chapter8Kousuke Ruichi
 
C# 6 and 7 and Futures 20180607
C# 6 and 7 and Futures 20180607C# 6 and 7 and Futures 20180607
C# 6 and 7 and Futures 20180607Kevin Hazzard
 
Haskell for Scala-ists
Haskell for Scala-istsHaskell for Scala-ists
Haskell for Scala-istschriseidhof
 
sbt, history of JSON libraries, microservices, and schema evolution (Tokyo ver)
sbt, history of JSON libraries, microservices, and schema evolution (Tokyo ver)sbt, history of JSON libraries, microservices, and schema evolution (Tokyo ver)
sbt, history of JSON libraries, microservices, and schema evolution (Tokyo ver)Eugene Yokota
 
楽々Scalaプログラミング
楽々Scalaプログラミング楽々Scalaプログラミング
楽々ScalaプログラミングTomoharu ASAMI
 
Haskell for Scala-ists
Haskell for Scala-istsHaskell for Scala-ists
Haskell for Scala-istschriseidhof
 
Joshua Wehner - Tomorrows Programming Languages Today
Joshua Wehner - Tomorrows Programming Languages TodayJoshua Wehner - Tomorrows Programming Languages Today
Joshua Wehner - Tomorrows Programming Languages TodayRefresh Events
 
Writing your own programming language to understand Ruby better - Euruko 2011
Writing your own programming language to understand Ruby better - Euruko 2011Writing your own programming language to understand Ruby better - Euruko 2011
Writing your own programming language to understand Ruby better - Euruko 2011Plataformatec
 
A Few of My Favorite (Python) Things
A Few of My Favorite (Python) ThingsA Few of My Favorite (Python) Things
A Few of My Favorite (Python) ThingsMichael Pirnat
 
PostgreSQLからMongoDBへ
PostgreSQLからMongoDBへPostgreSQLからMongoDBへ
PostgreSQLからMongoDBへBasuke Suzuki
 
NUS iOS Swift Talk
NUS iOS Swift TalkNUS iOS Swift Talk
NUS iOS Swift TalkGabriel Lim
 

Similaire à Invertible-syntax 入門 (20)

Happy Go Programming
Happy Go ProgrammingHappy Go Programming
Happy Go Programming
 
ScotRuby - Dark side of ruby
ScotRuby - Dark side of rubyScotRuby - Dark side of ruby
ScotRuby - Dark side of ruby
 
Json the-x-in-ajax1588
Json the-x-in-ajax1588Json the-x-in-ajax1588
Json the-x-in-ajax1588
 
Slides chapter3part1 ruby-forjavaprogrammers
Slides chapter3part1 ruby-forjavaprogrammersSlides chapter3part1 ruby-forjavaprogrammers
Slides chapter3part1 ruby-forjavaprogrammers
 
Building Interpreters with PyPy
Building Interpreters with PyPyBuilding Interpreters with PyPy
Building Interpreters with PyPy
 
RedDot Ruby Conf 2014 - Dark side of ruby
RedDot Ruby Conf 2014 - Dark side of ruby RedDot Ruby Conf 2014 - Dark side of ruby
RedDot Ruby Conf 2014 - Dark side of ruby
 
Programming Haskell Chapter8
Programming Haskell Chapter8Programming Haskell Chapter8
Programming Haskell Chapter8
 
C# 6 and 7 and Futures 20180607
C# 6 and 7 and Futures 20180607C# 6 and 7 and Futures 20180607
C# 6 and 7 and Futures 20180607
 
P3 2018 python_regexes
P3 2018 python_regexesP3 2018 python_regexes
P3 2018 python_regexes
 
1 the ruby way
1   the ruby way1   the ruby way
1 the ruby way
 
Haskell for Scala-ists
Haskell for Scala-istsHaskell for Scala-ists
Haskell for Scala-ists
 
sbt, history of JSON libraries, microservices, and schema evolution (Tokyo ver)
sbt, history of JSON libraries, microservices, and schema evolution (Tokyo ver)sbt, history of JSON libraries, microservices, and schema evolution (Tokyo ver)
sbt, history of JSON libraries, microservices, and schema evolution (Tokyo ver)
 
楽々Scalaプログラミング
楽々Scalaプログラミング楽々Scalaプログラミング
楽々Scalaプログラミング
 
Haskell for Scala-ists
Haskell for Scala-istsHaskell for Scala-ists
Haskell for Scala-ists
 
Joshua Wehner - Tomorrows Programming Languages Today
Joshua Wehner - Tomorrows Programming Languages TodayJoshua Wehner - Tomorrows Programming Languages Today
Joshua Wehner - Tomorrows Programming Languages Today
 
Writing your own programming language to understand Ruby better - Euruko 2011
Writing your own programming language to understand Ruby better - Euruko 2011Writing your own programming language to understand Ruby better - Euruko 2011
Writing your own programming language to understand Ruby better - Euruko 2011
 
A Few of My Favorite (Python) Things
A Few of My Favorite (Python) ThingsA Few of My Favorite (Python) Things
A Few of My Favorite (Python) Things
 
PostgreSQLからMongoDBへ
PostgreSQLからMongoDBへPostgreSQLからMongoDBへ
PostgreSQLからMongoDBへ
 
Swift Study #2
Swift Study #2Swift Study #2
Swift Study #2
 
NUS iOS Swift Talk
NUS iOS Swift TalkNUS iOS Swift Talk
NUS iOS Swift Talk
 

Plus de Hiromi Ishii

Freer Monads, More Extensible Effects
Freer Monads, More Extensible EffectsFreer Monads, More Extensible Effects
Freer Monads, More Extensible EffectsHiromi Ishii
 
Lebesgue可測性に関するSoloayの定理と実数の集合の正則性
Lebesgue可測性に関するSoloayの定理と実数の集合の正則性Lebesgue可測性に関するSoloayの定理と実数の集合の正則性
Lebesgue可測性に関するSoloayの定理と実数の集合の正則性Hiromi Ishii
 
実数の集合はどこまで可測になれるか?
実数の集合はどこまで可測になれるか?実数の集合はどこまで可測になれるか?
実数の集合はどこまで可測になれるか?Hiromi Ishii
 
Lebesgue 可測性に関する Solovay-Shelah の結果に必要な記述集合論のごく基本的な事項
Lebesgue 可測性に関する Solovay-Shelah の結果に必要な記述集合論のごく基本的な事項Lebesgue 可測性に関する Solovay-Shelah の結果に必要な記述集合論のごく基本的な事項
Lebesgue 可測性に関する Solovay-Shelah の結果に必要な記述集合論のごく基本的な事項Hiromi Ishii
 
技術者が知るべき Gröbner 基底
技術者が知るべき Gröbner 基底技術者が知るべき Gröbner 基底
技術者が知るべき Gröbner 基底Hiromi Ishii
 
数学プログラムを Haskell で書くべき 6 の理由
数学プログラムを Haskell で書くべき 6 の理由数学プログラムを Haskell で書くべき 6 の理由
数学プログラムを Haskell で書くべき 6 の理由Hiromi Ishii
 
Algebraic DP: 動的計画法を書きやすく
Algebraic DP: 動的計画法を書きやすくAlgebraic DP: 動的計画法を書きやすく
Algebraic DP: 動的計画法を書きやすくHiromi Ishii
 
Yesod でブログエンジンをつくってみた
Yesod でブログエンジンをつくってみたYesod でブログエンジンをつくってみた
Yesod でブログエンジンをつくってみたHiromi Ishii
 
How wonderful to be (statically) typed 〜型が付くってスバラシイ〜
How wonderful to be (statically) typed 〜型が付くってスバラシイ〜How wonderful to be (statically) typed 〜型が付くってスバラシイ〜
How wonderful to be (statically) typed 〜型が付くってスバラシイ〜Hiromi Ishii
 

Plus de Hiromi Ishii (9)

Freer Monads, More Extensible Effects
Freer Monads, More Extensible EffectsFreer Monads, More Extensible Effects
Freer Monads, More Extensible Effects
 
Lebesgue可測性に関するSoloayの定理と実数の集合の正則性
Lebesgue可測性に関するSoloayの定理と実数の集合の正則性Lebesgue可測性に関するSoloayの定理と実数の集合の正則性
Lebesgue可測性に関するSoloayの定理と実数の集合の正則性
 
実数の集合はどこまで可測になれるか?
実数の集合はどこまで可測になれるか?実数の集合はどこまで可測になれるか?
実数の集合はどこまで可測になれるか?
 
Lebesgue 可測性に関する Solovay-Shelah の結果に必要な記述集合論のごく基本的な事項
Lebesgue 可測性に関する Solovay-Shelah の結果に必要な記述集合論のごく基本的な事項Lebesgue 可測性に関する Solovay-Shelah の結果に必要な記述集合論のごく基本的な事項
Lebesgue 可測性に関する Solovay-Shelah の結果に必要な記述集合論のごく基本的な事項
 
技術者が知るべき Gröbner 基底
技術者が知るべき Gröbner 基底技術者が知るべき Gröbner 基底
技術者が知るべき Gröbner 基底
 
数学プログラムを Haskell で書くべき 6 の理由
数学プログラムを Haskell で書くべき 6 の理由数学プログラムを Haskell で書くべき 6 の理由
数学プログラムを Haskell で書くべき 6 の理由
 
Algebraic DP: 動的計画法を書きやすく
Algebraic DP: 動的計画法を書きやすくAlgebraic DP: 動的計画法を書きやすく
Algebraic DP: 動的計画法を書きやすく
 
Yesod でブログエンジンをつくってみた
Yesod でブログエンジンをつくってみたYesod でブログエンジンをつくってみた
Yesod でブログエンジンをつくってみた
 
How wonderful to be (statically) typed 〜型が付くってスバラシイ〜
How wonderful to be (statically) typed 〜型が付くってスバラシイ〜How wonderful to be (statically) typed 〜型が付くってスバラシイ〜
How wonderful to be (statically) typed 〜型が付くってスバラシイ〜
 

Invertible-syntax 入門

  • 1. invertible-syntax (TH ) Hiromi Ishii a.k.a. @mr_konn
  • 2. About myself... • id:mr_konn / @mr_konn • Template Haskell • P Haskell
  • 3. TOC • invertible-syntax • JSON Parser Pretty Printer • Inside invertible-syntax • Real World Template Haskell
  • 4. TOC • invertible-syntax • JSON Parser Pretty Printer • Inside invertible-syntax • Real World Template Haskell
  • 8. Haskeller • • Web JSON YAML……
  • 9. Haskeller • • Web JSON YAML…… •
  • 10. Haskeller • • Web JSON YAML…… • • Java C
  • 11. Haskeller • • Web JSON YAML…… • • Java C •
  • 12.
  • 13. Parser Pretty Printer
  • 14. Parser Pretty Printer • Parser
  • 15. Parser Pretty Printer • Parser • (Parsec, Happy...)
  • 16. Parser Pretty Printer • Parser • (Parsec, Happy...) •
  • 17. Parser Pretty Printer • Parser • (Parsec, Happy...) • • Pretty Printer
  • 18. Parser Pretty Printer • Parser • (Parsec, Happy...) • • Pretty Printer • …… (Show, HughesPJ...)
  • 19. Parser Pretty Printer • Parser • (Parsec, Happy...) • • Pretty Printer • …… (Show, HughesPJ...) • ……
  • 20. Parser Pretty Printer • • Don’t Repeat Yourself! • Pretty Printer • •
  • 22. invertible-syntax • Parser Pretty Printer • Syntax Description • Applicative • • Parser Pretty Printer
  • 23. JSON
  • 24. JSON • JSON • • data Slot = Slot { key :: String, val :: JSON } data JSON = Number !Integer | Null | Bool !Bool | Array ![JSON] | String String | Object ![Slot]
  • 25. JSONPretty.hs import Text.PrettyPrint.HughesPJ pretty :: Printer JSON -- Printer a = a → Doc pretty (Object jss) = braces $ hcat $ intersperse comma $ map slot jss pretty (Array jss) = brackets $ hcat $ intersperse comma $ map pretty jss pretty (String str) = doubleQuotes $ text str pretty (Null) = text "null" pretty (Bool b) = case b of True → text "true" False → text "false" pretty (Number int) = integer int slot s = doubleQuotes (text $ key s) <> colon <+> sub (val s)
  • 26. JSONParsec.hs import Text.Parsec json, jsobj, ..., jsnumber :: Parser JSON json = jsobj <|> jsarray <|> ... <|> jsbool <|> jsnumber jsobj = Object <$> between (symbol "{") (symbol "}") (term `sepBy` symbol ",") where term = Slot <$> str <* symbol ":" <*> json jsarray = Array <$> between (symbol "[") (symbol "]") (json `sepBy` symbol ",") jsstring = String <$> str jsnull = Null <$ symbol "null" jsbool = Bool True <$ symbol "true" <|> Bool False <$ symbol "false" jsnumber = Number . read <$> many1 digit str = between (spaces *> char '"') (char '"' <* spaces) (many $ noneOf """)
  • 27. JSONInvertible.hs defineIsomorphisms ''JSON json, jsobj, ..., jsnumber :: Syntax f f JSON json = jsobj <|> jsarray <|> ... <|> jsbool <|> jsnumber jsobj = object <$> between (symbol "{") (symbol "}") (term `sepBy` symbol ",") where term = slot <$> str <* skipSpace <* text ":" <*> json jsarray = array <$> between (symbol "[") (symbol "]") (json `sepBy` symbol ",") jsstring = string <$> str jsnull = null <$> symbol "null" jsbool = bool . element True <$> symbol "true" <|> bool . element False <$> symbol "false" jsnumber = number . numIso <$> many1 digit str = between (optSpace *> text """) (text """ <* optSpace) (many (subset (/='"') <$> token)) numIso = Iso read’ show’ where read' = liftM fst . listToMaybe . reads show' = return . show
  • 28.
  • 29. • Syntax f f JSON • Syntax Description • pure token • <$> <$ <*>
  • 30. • defineIsomorphisms …… • • (<$) (<$>) • Iso
  • 32. Parser Priner
  • 33. Parser Priner • Iso :
  • 34. Parser Priner • Iso : • data Iso a b = Iso (a→Maybe b) (b→Maybe a)
  • 35. Parser Priner • Iso : • data Iso a b = Iso (a→Maybe b) (b→Maybe a) •
  • 36. Parser Priner • Iso : • data Iso a b = Iso (a→Maybe b) (b→Maybe a) • • Iso Category
  • 37. Parser Priner • Iso : • data Iso a b = Iso (a→Maybe b) (b→Maybe a) • • Iso Category • id (.)
  • 38. Parser Priner • Iso : • data Iso a b = Iso (a→Maybe b) (b→Maybe a) • • Iso Category • id (.) • IsoFunctor
  • 39. Iso 1 numIso = Iso read’ show’ where read' = liftM fst . listToMaybe . reads show' = return . show • • Control.Isomorphism.Partial.Unsafe • • Iso
  • 40. Iso 2 • import Control.Isomorphism.Partial • element :: α → Iso α () • () • subset :: (α → Bool) → Iso α α • • foldl :: Iso (α,β) α → Iso (α,[β]) α • (***), associate, iterate, unit ……
  • 41. IsoFunctor • Functor = • fmap :: (α→β) → f α → f β • α→β Iso α β … class IsoFunctor δ where (<$>) :: Iso α β → δ α → δ β •
  • 43.
  • 47. (<*>) • (<*>) :: δ (α → β) → δ α → δ β • Iso α β …… class IsoApplicative δ where (<*>) :: δ (Iso α β) → δ α → δ β • Parser • Iso α β α
  • 48. Printer instance IsoApplicative Printer where (<*>) pab pa b = ……
  • 49. Printer instance IsoApplicative Printer where (<*>) pab pa b = …… • (<*>) :: Printer (Iso α β) → Printer α → Printer β = ((Iso α β)→Doc) → (α→Doc) → β → Doc
  • 50. Printer instance IsoApplicative Printer where (<*>) pab pa b = …… • (<*>) :: Printer (Iso α β) → Printer α → Printer β = ((Iso α β)→Doc) → (α→Doc) → β → Doc •β
  • 51. Printer instance IsoApplicative Printer where (<*>) pab pa b = …… • (<*>) :: Printer (Iso α β) → Printer α → Printer β = ((Iso α β)→Doc) → (α→Doc) → β → Doc •β • ……
  • 52. Printer instance IsoApplicative Printer where (<*>) pab pa b = …… • (<*>) :: Printer (Iso α β) → Printer α → Printer β = ((Iso α β)→Doc) → (α→Doc) → β → Doc •β • …… • ……
  • 53.
  • 54. Applicative
  • 55. Applicative • Slot <$> key <*> val
  • 56. Applicative • Slot <$> key <*> val • Slot :: String → JSON → (String, JSON)
  • 57. Applicative • Slot <$> key <*> val • Slot :: String → JSON → (String, JSON) • slot :: Iso String (Iso JSON Slot)
  • 58. Applicative • Slot <$> key <*> val • Slot :: String → JSON → (String, JSON) • slot :: Iso String (Iso JSON Slot) • slot <$> key :: δ (Iso JSON Slot)
  • 60. …… • slot :: Iso (String, JSON) Slot
  • 61. …… • slot :: Iso (String, JSON) Slot • slot <$> key <*> val :: δ Slot ……
  • 62. …… • slot :: Iso (String, JSON) Slot • slot <$> key <*> val :: δ Slot …… • slot <$> (key <*> val) ……
  • 63. …… • slot :: Iso (String, JSON) Slot • slot <$> key <*> val :: δ Slot …… • slot <$> (key <*> val) …… • (<*>) :: δ α → δ β → δ (α, β)
  • 64. ProductFunctor class ProductFunctor δ where (<*>) :: δ α → δ β → δ (α, β) infix 5 <$> infixr 6 <*> • Parser Printer •
  • 65. Iso null :: Iso () JSON null = Iso to from where to _ = Just Null from Null = Just () from _ = Nothing number :: Iso Integer JSON number = Iso to from where to = Just . Number from (Number int) = Just int from _ = Nothing slot :: Iso (String, JSON) Slot slot = Iso to from where to (a,b) = Just $ Slot a b from (Slot a b) = Just (a,b)
  • 66. class Alternative δ where (<|>) :: δ α → δ α → δ α empty :: δ α • Applicative instance • token • pure • Syntax
  • 67.
  • 68. class IsoFunctor δ where (<$>) :: Iso α β → δ α → δ β class ProductFunctor δ where (<*>) :: δ α → δ β → δ (α, β) class Alternative δ where (<|>) :: δ α → δ α → δ α empty :: δ α class ( IsoFunctor δ, ProductFunctor δ , Alternative δ ) Syntax δ where pure :: α → δ α token :: δ Char
  • 69.
  • 70.
  • 71. • • many, sepBy, chainl1, text, between
  • 72. • • many, sepBy, chainl1, text, between • +
  • 73. • • many, sepBy, chainl1, text, between • + • skipSpace, sepSpace, optSpace
  • 74. • • many, sepBy, chainl1, text, between • + • skipSpace, sepSpace, optSpace •
  • 75. • • many, sepBy, chainl1, text, between • + • skipSpace, sepSpace, optSpace • • Printer
  • 76. • • many, sepBy, chainl1, text, between • + • skipSpace, sepSpace, optSpace • • Printer • sep opt
  • 77. • skipSpace sepSpace optSpace • • “ntr”
  • 78. read/show invertible-syntax Parsec/HughesPJ ( )
  • 79. • • invertible-syntax Parser Printer Naive • • Proof of Concept
  • 80.
  • 81. Parsec HughesPJ Syntax
  • 82. Parsec HughesPJ Syntax •
  • 83. Parsec HughesPJ Syntax • • (<|>)
  • 84. Parsec HughesPJ Syntax • • (<|>) •
  • 85. Parsec HughesPJ Syntax • • (<|>) • •
  • 86. Parsec HughesPJ Syntax • • (<|>) • • •
  • 87.
  • 90. Real World Template Haskell defineIsomorphisms TH
  • 91. null :: Iso () JSON null = Iso to from where to _ = Just Null from Null = Just () from _ = Nothing number :: Iso Integer JSON number = Iso to from where to a = Just $ Number a from (Number int) = Just int from _ = Nothing slot :: Iso (String, JSON) Slot slot = Iso to from where to (a,b) = Just $ Slot a b from (Slot a b) = Just (a,b)
  • 92. • data Hoge • • Iso () Hoge • Iso (a, (b, ...)) Hoge
  • 93. • from • Just $ a b c ... • to • Nothing •
  • 94. • reify • • …… Exp • …… Type
  • 96. • • E ,P ,T ,D , C , B Body, L • type HogeQ = Q Hoge • (LamE lamE ) • Q • lamE :: [PatQ] → ExpQ→ ExpQ
  • 97. • defineIsomorphisms :: Name → Q [Dec] • data newtype defineIsomorphisms :: Name → Q [Dec] defineIsomorphisms d = do TyConI dec ← reify d cs ← decConstructors dec mapM (defFromCon (wildcard cs)) cs decConstructors :: Dec -> Q [Con] decConstructors (DataD _ _ _ cs _) = return cs decConstructors (NewtypeD _ _ _ c _)= return [c] decConstructors _ = error “not supported!”
  • 98. wildcard • case { _ → Nothing } • defFromCon • rename ( ) wildcard :: [Con] -> [MatchQ] wildcard cs = if length cs > 1 then [match (wildP) (normalB [| Nothing |]) []] else [] defFromCon :: [MatchQ] -> Con -> DecQ defFromCon wc con = funD (rename (conName con)) [clause [] (normalB (isoFromCon wc con)) []]
  • 99. • isoFromCon :: [MatchQ] -> Con -> ExpQ Iso isoFromCon wildcard con = do let c = conName con let fs = conFields con -- let n = length fs -- (ps, vs) ← genPE n -- v ← newName "x" let f = lamE [nested tupP ps] -- [| Just $(foldl appE (conE c) vs) |] let g = lamE [varP v] (caseE (varE v) $ [ match (conP c ps) -- Con (a,(b,..) → (normalB [| Just $(nested tupE vs) |]) [] ] ++ wildcard) -- case [| Iso $f $g |] -- from/to λ Iso

Notes de l'éditeur

  1. \n
  2. \n
  3. \n
  4. &amp;#x307E;&amp;#x306B;&amp;#x3042;&amp;#x3044;&amp;#x307E;&amp;#x305B;&amp;#x3093;&amp;#x3067;&amp;#x3057;&amp;#x305F;&amp;#x3054;&amp;#x3081;&amp;#x3093;&amp;#x306A;&amp;#x3055;&amp;#x3044;&gt;&lt;\n&amp;#x6642;&amp;#x9593;&amp;#x304C;&amp;#x3042;&amp;#x3063;&amp;#x305F;&amp;#x3089;&amp;#x6614;&amp;#x306E;&amp;#x767A;&amp;#x8868;&amp;#x8CC7;&amp;#x6599;&amp;#x3064;&amp;#x304B;&amp;#x3044;&amp;#x3064;&amp;#x3064;&amp;#x9811;&amp;#x5F35;&amp;#x308A;&amp;#x307E;&amp;#x3059;&amp;#xFF01;\n
  5. \n
  6. \n
  7. \n
  8. \n
  9. \n
  10. \n
  11. \n
  12. \n
  13. \n
  14. \n
  15. \n
  16. \n
  17. \n
  18. \n
  19. \n
  20. \n
  21. \n
  22. \n
  23. \n
  24. \n
  25. \n
  26. \n
  27. \n
  28. \n
  29. \n
  30. \n
  31. \n
  32. \n
  33. \n
  34. \n
  35. \n
  36. \n
  37. &amp;#x8DB3;&amp;#x308A;&amp;#x306A;&amp;#x3044;&amp;#x3082;&amp;#x306E;&amp;#x3092; Unsafe import &amp;#x3057;&amp;#x3066;&amp;#x81EA;&amp;#x524D;&amp;#x3067;&amp;#x5B9A;&amp;#x7FA9;&amp;#x3059;&amp;#x308B;&amp;#x611F;&amp;#x3058;&amp;#x306B;&amp;#x306A;&amp;#x308A;&amp;#x307E;&amp;#x3059;\n
  38. \n
  39. \n
  40. \n
  41. \n
  42. \n
  43. \n
  44. \n
  45. \n
  46. \n
  47. \n
  48. \n
  49. \n
  50. \n
  51. \n
  52. \n
  53. \n
  54. \n
  55. \n
  56. \n
  57. \n
  58. \n
  59. &amp;#x30FB;null &amp;#x306F;&amp;#x5F15;&amp;#x6570;&amp;#x3092;&amp;#x53D6;&amp;#x308A;&amp;#x307E;&amp;#x305B;&amp;#x3093;&amp;#x304C;&amp;#x3001; Iso &amp;#x306F;&amp;#x95A2;&amp;#x6570;&amp;#x306A;&amp;#x306E;&amp;#x3067; () &amp;#x3092;&amp;#x6E21;&amp;#x3057;&amp;#x3066;&amp;#x3044;&amp;#x308B;(&amp;#x3060;&amp;#x304B;&amp;#x3089; &lt;$&gt; &amp;#x304C; &lt;$ &amp;#x306B;&amp;#x306A;&amp;#x3063;&amp;#x305F;)\n
  60. \n
  61. \n
  62. Stateful &amp;#x306A;&amp;#x3082;&amp;#x306E;&amp;#x306F;&amp;#x5F53;&amp;#x7136;&amp;#x7121;&amp;#x7406;\n
  63. Stateful &amp;#x306A;&amp;#x3082;&amp;#x306E;&amp;#x306F;&amp;#x5F53;&amp;#x7136;&amp;#x7121;&amp;#x7406;\n
  64. Stateful &amp;#x306A;&amp;#x3082;&amp;#x306E;&amp;#x306F;&amp;#x5F53;&amp;#x7136;&amp;#x7121;&amp;#x7406;\n
  65. Stateful &amp;#x306A;&amp;#x3082;&amp;#x306E;&amp;#x306F;&amp;#x5F53;&amp;#x7136;&amp;#x7121;&amp;#x7406;\n
  66. Stateful &amp;#x306A;&amp;#x3082;&amp;#x306E;&amp;#x306F;&amp;#x5F53;&amp;#x7136;&amp;#x7121;&amp;#x7406;\n
  67. Stateful &amp;#x306A;&amp;#x3082;&amp;#x306E;&amp;#x306F;&amp;#x5F53;&amp;#x7136;&amp;#x7121;&amp;#x7406;\n
  68. Stateful &amp;#x306A;&amp;#x3082;&amp;#x306E;&amp;#x306F;&amp;#x5F53;&amp;#x7136;&amp;#x7121;&amp;#x7406;\n
  69. \n
  70. &amp;#x30FB;&amp;#x8D64;&amp;#x304C; read/show&amp;#x3001;&amp;#x7DD1;&amp;#x304C; invetible-syntax&amp;#x3001;&amp;#x9752;&amp;#x304C; parsec/hughesPJ\n&amp;#x30FB;&amp;#x5DE6;&amp;#x304B;&amp;#x3089;&amp;#x9806;&amp;#x306B;JSON&amp;#x914D;&amp;#x5217;&amp;#x306E;&amp;#x30D1;&amp;#x30FC;&amp;#x30B9;(100&amp;#x8981;&amp;#x7D20;,500&amp;#x8981;&amp;#x7D20;)&amp;#x3001;JSON&amp;#x30C7;&amp;#x30FC;&amp;#x30BF;&amp;#x306E;Pretty Print (100, 500)\n
  71. \n
  72. &amp;#x30FB;&amp;#x4E0A;&amp;#x624B;&amp;#x304F;&amp;#x3044;&amp;#x304B;&amp;#x306A;&amp;#x304B;&amp;#x3063;&amp;#x305F;&amp;#x7406;&amp;#x7531;&amp;#x304C;&amp;#x308F;&amp;#x304B;&amp;#x3089;&amp;#x306A;&amp;#x3044;&amp;#x306E;&amp;#x3067;&amp;#x8AB0;&amp;#x304B;&amp;#x52A9;&amp;#x3051;&amp;#x3066;&amp;#x304F;&amp;#x3060;&amp;#x3055;&amp;#x3044;&amp;#xFF01;&amp;#xFF01;\n
  73. &amp;#x30FB;&amp;#x4E0A;&amp;#x624B;&amp;#x304F;&amp;#x3044;&amp;#x304B;&amp;#x306A;&amp;#x304B;&amp;#x3063;&amp;#x305F;&amp;#x7406;&amp;#x7531;&amp;#x304C;&amp;#x308F;&amp;#x304B;&amp;#x3089;&amp;#x306A;&amp;#x3044;&amp;#x306E;&amp;#x3067;&amp;#x8AB0;&amp;#x304B;&amp;#x52A9;&amp;#x3051;&amp;#x3066;&amp;#x304F;&amp;#x3060;&amp;#x3055;&amp;#x3044;&amp;#xFF01;&amp;#xFF01;\n
  74. &amp;#x30FB;&amp;#x4E0A;&amp;#x624B;&amp;#x304F;&amp;#x3044;&amp;#x304B;&amp;#x306A;&amp;#x304B;&amp;#x3063;&amp;#x305F;&amp;#x7406;&amp;#x7531;&amp;#x304C;&amp;#x308F;&amp;#x304B;&amp;#x3089;&amp;#x306A;&amp;#x3044;&amp;#x306E;&amp;#x3067;&amp;#x8AB0;&amp;#x304B;&amp;#x52A9;&amp;#x3051;&amp;#x3066;&amp;#x304F;&amp;#x3060;&amp;#x3055;&amp;#x3044;&amp;#xFF01;&amp;#xFF01;\n
  75. &amp;#x30FB;&amp;#x4E0A;&amp;#x624B;&amp;#x304F;&amp;#x3044;&amp;#x304B;&amp;#x306A;&amp;#x304B;&amp;#x3063;&amp;#x305F;&amp;#x7406;&amp;#x7531;&amp;#x304C;&amp;#x308F;&amp;#x304B;&amp;#x3089;&amp;#x306A;&amp;#x3044;&amp;#x306E;&amp;#x3067;&amp;#x8AB0;&amp;#x304B;&amp;#x52A9;&amp;#x3051;&amp;#x3066;&amp;#x304F;&amp;#x3060;&amp;#x3055;&amp;#x3044;&amp;#xFF01;&amp;#xFF01;\n
  76. &amp;#x30FB;&amp;#x4E0A;&amp;#x624B;&amp;#x304F;&amp;#x3044;&amp;#x304B;&amp;#x306A;&amp;#x304B;&amp;#x3063;&amp;#x305F;&amp;#x7406;&amp;#x7531;&amp;#x304C;&amp;#x308F;&amp;#x304B;&amp;#x3089;&amp;#x306A;&amp;#x3044;&amp;#x306E;&amp;#x3067;&amp;#x8AB0;&amp;#x304B;&amp;#x52A9;&amp;#x3051;&amp;#x3066;&amp;#x304F;&amp;#x3060;&amp;#x3055;&amp;#x3044;&amp;#xFF01;&amp;#xFF01;\n
  77. &amp;#x30FB;&amp;#x4E0A;&amp;#x624B;&amp;#x304F;&amp;#x3044;&amp;#x304B;&amp;#x306A;&amp;#x304B;&amp;#x3063;&amp;#x305F;&amp;#x7406;&amp;#x7531;&amp;#x304C;&amp;#x308F;&amp;#x304B;&amp;#x3089;&amp;#x306A;&amp;#x3044;&amp;#x306E;&amp;#x3067;&amp;#x8AB0;&amp;#x304B;&amp;#x52A9;&amp;#x3051;&amp;#x3066;&amp;#x304F;&amp;#x3060;&amp;#x3055;&amp;#x3044;&amp;#xFF01;&amp;#xFF01;\n
  78. \n
  79. \n
  80. \n
  81. partial-isomorphisms &amp;#x306F; Real World &amp;#x306A;&amp;#x306E;&amp;#x304B;&amp;#x3068;&amp;#x3044;&amp;#x3046;&amp;#x7A81;&amp;#x3063;&amp;#x8FBC;&amp;#x307F;&amp;#x306F;NG\n
  82. \n
  83. \n
  84. \n
  85. \n
  86. \n
  87. \n
  88. \n
  89. \n
  90. foldl appE (conE c) vs &amp;#x306F; appsE (conE c:vs) &amp;#x3068;&amp;#x3082;&amp;#x66F8;&amp;#x3051;&amp;#x308B;\n
  91. \n
  92. \n