SlideShare une entreprise Scribd logo
1  sur  35
Template Haskell
         konn
Template Haskell
Template Haskell

 Haskell
Template Haskell

 Haskell
Template Haskell

 Haskell




           Q
Template Haskell

 Haskell




           Q

 C preprocessor
TH
TH

Haskell
TH

     Haskell




IO

     compile-time wxWidgets Network...
RandomDef.hs
{-# LANGUAGE TemplateHaskell #-}
module Main where
import Language.Haskell.TH
import System.Random

$( do rnd <- runIO $ randomRIO (0,1)
     let nm = mkName (["a", "b"] !! rnd)
     m <- [d| main = $(varE $ mkName "a") |]
     t <- valD (varP nm) (normalB [| putStrLn " ( ´ `) " |]) []
     return (t:m)
 )
RandomDef.hs
{-# LANGUAGE TemplateHaskell #-}
module Main where
import Language.Haskell.TH
import System.Random IO

$( do rnd <- runIO $ randomRIO (0,1)
     let nm = mkName (["a", "b"] !! rnd)
     m <- [d| main = $(varE $ mkName "a") |]
     t <- valD (varP nm) (normalB [| putStrLn " ( ´ `) " |]) []
     return (t:m)
 )
Splice(                     )
{-# LANGUAGE TemplateHaskell #-}
module Main where
import Language.Haskell.TH
import System.Random

$( do rnd <- runIO $ randomRIO (0,1)
     let nm = mkName (["a", "b"] !! rnd)
     m <- [d| main = $(varE $ mkName "a") |]
     t <- valD (varP nm) (normalB [| putStrLn " ( ´ `) " |]) []
     return (t:m)
 )
Splice
Splice
(Q   )
Splice
  (Q        )

splice

         splice
Splice
      (Q        )

    splice

             splice




“                     ”
{-# LANGUAGE TemplateHaskell #-}
module Main where
import Language.Haskell.TH
import System.Random

$( do rnd <- runIO $ randomRIO (0,1)
     let nm = mkName (["a", "b"] !! rnd)
     m <- [d| main = $(varE $ mkName "a") |]
     t <- valD (varP nm) (normalB [| putStrLn " ( ´ `) " |]) []
     return (t:m)
 )
[   |
[   |
        [| putStrLn “hogehoge” |]
[   |
        [| putStrLn “hogehoge” |]
        [t| String |]
[   |
        [| putStrLn “hogehoge” |]
        [t| String |]
          [d| main = putStrLn |]
[   |
        [| putStrLn “hogehoge” |]
        [t| String |]
          [d| main = putStrLn |]
        [$ident| function f() {..} |]
[   |
              [| putStrLn “hogehoge” |]
              [t| String |]
                [d| main = putStrLn |]
              [$ident| function f() {..} |]
        DSL
[   |
              [| putStrLn “hogehoge” |]
              [t| String |]
                [d| main = putStrLn |]
              [$ident| function f() {..} |]
        DSL
[   |
                [| putStrLn “hogehoge” |]
                [t| String |]
                  [d| main = putStrLn |]
                [$ident| function f() {..} |]
          DSL


        )JavaScript                 (
splice
[d| main = $(varE $ mkName "a") |]

                       splice

                [d| main = ‘a |]         TH
   a

                                `a

            ``String
{-# LANGUAGE TemplateHaskell #-}
module Main where
import Language.Haskell.TH
import System.Random

$( do rnd <- runIO $ randomRIO (0,1)
     let nm = mkName (["a", "b"] !! rnd)
     m <- [d| main = $(varE $ mkName "a") |]
     t <- valD (varP nm) (normalB [| putStrLn " ( ´ `) " |]) []
     return (t:m)
 )
valD (varP nm) (normalB [| putStrLn " ( ´ `) " |]) []

          [d| $(varP nm) = putStrLn “ ( ´ `) ” |]

                        ……                ……

                ghci

   > runQ [d| main = putStrLn “hoge” |]
Sucks



GHC

 TH                Ver.UP
      (ex. HOC )
lib2 =
   let
      l=LetS[ValD(VarP $ mkName"it")(NormalB(f"be"))[]]
      f=VarE . mkName
   in
      DoE [ l, l, l, NoBindS $ f"oh",l,
      NoBindS $ InfixE(Just$ f"speaking")(f"words")(Just $ f "wisdom"),l]
lib2 =
   let
      l=LetS[ValD(VarP $ mkName"it")(NormalB(f"be"))[]]
      f=VarE . mkName
   in
      DoE [ l, l, l, NoBindS $ f"oh",l,
      NoBindS $ InfixE(Just$ f"speaking")(f"words")(Just $ f "wisdom"),l]
lib2 =
   let
      l=LetS[ValD(VarP $ mkName"it")(NormalB(f"be"))[]]
      f=VarE . mkName
   in
      DoE [ l, l, l, NoBindS $ f"oh",l,
      NoBindS $ InfixE(Just$ f"speaking")(f"words")(Just $ f "wisdom"),l]

                            do let it = be
                              let it = be
                              let it = be
                              oh
                              let it = be
                              speaking `words` wisdom
                              let it = be
reify




        IO   reify

  Q

Contenu connexe

Tendances

Haste (Same Language, Multiple Platforms) and Tagless Final Style (Same Synta...
Haste (Same Language, Multiple Platforms) and Tagless Final Style (Same Synta...Haste (Same Language, Multiple Platforms) and Tagless Final Style (Same Synta...
Haste (Same Language, Multiple Platforms) and Tagless Final Style (Same Synta...takeoutweight
 
Refactoring to Macros with Clojure
Refactoring to Macros with ClojureRefactoring to Macros with Clojure
Refactoring to Macros with ClojureDmitry Buzdin
 
Introductionto fp with groovy
Introductionto fp with groovyIntroductionto fp with groovy
Introductionto fp with groovyIsuru Samaraweera
 
PHP 7 – What changed internally?
PHP 7 – What changed internally?PHP 7 – What changed internally?
PHP 7 – What changed internally?Nikita Popov
 
New SPL Features in PHP 5.3
New SPL Features in PHP 5.3New SPL Features in PHP 5.3
New SPL Features in PHP 5.3Matthew Turland
 
Is Haskell an acceptable Perl?
Is Haskell an acceptable Perl?Is Haskell an acceptable Perl?
Is Haskell an acceptable Perl?osfameron
 
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
 
SPL - The Undiscovered Library - PHPBarcelona 2015
SPL - The Undiscovered Library - PHPBarcelona 2015SPL - The Undiscovered Library - PHPBarcelona 2015
SPL - The Undiscovered Library - PHPBarcelona 2015Mark Baker
 
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
 
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
 
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
 
PHP Language Trivia
PHP Language TriviaPHP Language Trivia
PHP Language TriviaNikita Popov
 
Haskell in the Real World
Haskell in the Real WorldHaskell in the Real World
Haskell in the Real Worldosfameron
 
Python Performance 101
Python Performance 101Python Performance 101
Python Performance 101Ankur Gupta
 
GR8Conf 2011: Effective Groovy
GR8Conf 2011: Effective GroovyGR8Conf 2011: Effective Groovy
GR8Conf 2011: Effective GroovyGR8Conf
 
여자개발자모임터 6주년 개발 세미나 - Scala Language
여자개발자모임터 6주년 개발 세미나 - Scala Language여자개발자모임터 6주년 개발 세미나 - Scala Language
여자개발자모임터 6주년 개발 세미나 - Scala LanguageAshal aka JOKER
 

Tendances (19)

Haste (Same Language, Multiple Platforms) and Tagless Final Style (Same Synta...
Haste (Same Language, Multiple Platforms) and Tagless Final Style (Same Synta...Haste (Same Language, Multiple Platforms) and Tagless Final Style (Same Synta...
Haste (Same Language, Multiple Platforms) and Tagless Final Style (Same Synta...
 
Refactoring to Macros with Clojure
Refactoring to Macros with ClojureRefactoring to Macros with Clojure
Refactoring to Macros with Clojure
 
Introductionto fp with groovy
Introductionto fp with groovyIntroductionto fp with groovy
Introductionto fp with groovy
 
PHP 7 – What changed internally?
PHP 7 – What changed internally?PHP 7 – What changed internally?
PHP 7 – What changed internally?
 
New SPL Features in PHP 5.3
New SPL Features in PHP 5.3New SPL Features in PHP 5.3
New SPL Features in PHP 5.3
 
Is Haskell an acceptable Perl?
Is Haskell an acceptable Perl?Is Haskell an acceptable Perl?
Is Haskell an acceptable Perl?
 
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
 
SPL - The Undiscovered Library - PHPBarcelona 2015
SPL - The Undiscovered Library - PHPBarcelona 2015SPL - The Undiscovered Library - PHPBarcelona 2015
SPL - The Undiscovered Library - PHPBarcelona 2015
 
Spl Not A Bridge Too Far phpNW09
Spl Not A Bridge Too Far phpNW09Spl Not A Bridge Too Far phpNW09
Spl Not A Bridge Too Far phpNW09
 
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
 
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
 
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
 
Hammurabi
HammurabiHammurabi
Hammurabi
 
PHP Language Trivia
PHP Language TriviaPHP Language Trivia
PHP Language Trivia
 
Haskell in the Real World
Haskell in the Real WorldHaskell in the Real World
Haskell in the Real World
 
Python Performance 101
Python Performance 101Python Performance 101
Python Performance 101
 
GR8Conf 2011: Effective Groovy
GR8Conf 2011: Effective GroovyGR8Conf 2011: Effective Groovy
GR8Conf 2011: Effective Groovy
 
여자개발자모임터 6주년 개발 세미나 - Scala Language
여자개발자모임터 6주년 개발 세미나 - Scala Language여자개발자모임터 6주년 개발 세미나 - Scala Language
여자개발자모임터 6주년 개발 세미나 - Scala Language
 

En vedette

実践・完全犯罪のつくり方
実践・完全犯罪のつくり方実践・完全犯罪のつくり方
実践・完全犯罪のつくり方Hiromi Ishii
 
ものまね鳥を愛でる 結合子論理と計算
ものまね鳥を愛でる 結合子論理と計算ものまね鳥を愛でる 結合子論理と計算
ものまね鳥を愛でる 結合子論理と計算Hiromi Ishii
 
(数式の入った)本をつくる
(数式の入った)本をつくる(数式の入った)本をつくる
(数式の入った)本をつくるHiromi Ishii
 
Alloy Analyzer のこと
Alloy Analyzer のことAlloy Analyzer のこと
Alloy Analyzer のことHiromi Ishii
 
技術者が知るべき Gröbner 基底
技術者が知るべき Gröbner 基底技術者が知るべき Gröbner 基底
技術者が知るべき Gröbner 基底Hiromi Ishii
 
御清聴ありがとうございました
御清聴ありがとうございました御清聴ありがとうございました
御清聴ありがとうございましたHiromi Ishii
 
最近のHaskellマップ
最近のHaskellマップ最近のHaskellマップ
最近のHaskellマップMitsutoshi Aoe
 
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
 
Yesod でブログエンジンをつくってみた
Yesod でブログエンジンをつくってみたYesod でブログエンジンをつくってみた
Yesod でブログエンジンをつくってみたHiromi Ishii
 
Lebesgue 可測性に関する Solovay-Shelah の結果に必要な記述集合論のごく基本的な事項
Lebesgue 可測性に関する Solovay-Shelah の結果に必要な記述集合論のごく基本的な事項Lebesgue 可測性に関する Solovay-Shelah の結果に必要な記述集合論のごく基本的な事項
Lebesgue 可測性に関する Solovay-Shelah の結果に必要な記述集合論のごく基本的な事項Hiromi Ishii
 
Freer Monads, More Extensible Effects
Freer Monads, More Extensible EffectsFreer Monads, More Extensible Effects
Freer Monads, More Extensible EffectsHiromi Ishii
 
実数の集合はどこまで可測になれるか?
実数の集合はどこまで可測になれるか?実数の集合はどこまで可測になれるか?
実数の集合はどこまで可測になれるか?Hiromi Ishii
 
Lebesgue可測性に関するSoloayの定理と実数の集合の正則性
Lebesgue可測性に関するSoloayの定理と実数の集合の正則性Lebesgue可測性に関するSoloayの定理と実数の集合の正則性
Lebesgue可測性に関するSoloayの定理と実数の集合の正則性Hiromi Ishii
 
Algebraic DP: 動的計画法を書きやすく
Algebraic DP: 動的計画法を書きやすくAlgebraic DP: 動的計画法を書きやすく
Algebraic DP: 動的計画法を書きやすくHiromi Ishii
 
GHC 6.12.1 マルチコア対応ランタイムシステムについて
GHC 6.12.1 マルチコア対応ランタイムシステムについてGHC 6.12.1 マルチコア対応ランタイムシステムについて
GHC 6.12.1 マルチコア対応ランタイムシステムについてMitsutoshi Aoe
 
これから Haskell を書くにあたって
これから Haskell を書くにあたってこれから Haskell を書くにあたって
これから Haskell を書くにあたってTsuyoshi Matsudate
 
Yesodを支える技術
Yesodを支える技術Yesodを支える技術
Yesodを支える技術Hiromi Ishii
 
数学プログラムを Haskell で書くべき 6 の理由
数学プログラムを Haskell で書くべき 6 の理由数学プログラムを Haskell で書くべき 6 の理由
数学プログラムを Haskell で書くべき 6 の理由Hiromi Ishii
 
Ruby を用いた超絶技巧プログラミング(夏のプログラミングシンポジウム 2012)
Ruby を用いた超絶技巧プログラミング(夏のプログラミングシンポジウム 2012)Ruby を用いた超絶技巧プログラミング(夏のプログラミングシンポジウム 2012)
Ruby を用いた超絶技巧プログラミング(夏のプログラミングシンポジウム 2012)mametter
 

En vedette (20)

実践・完全犯罪のつくり方
実践・完全犯罪のつくり方実践・完全犯罪のつくり方
実践・完全犯罪のつくり方
 
ものまね鳥を愛でる 結合子論理と計算
ものまね鳥を愛でる 結合子論理と計算ものまね鳥を愛でる 結合子論理と計算
ものまね鳥を愛でる 結合子論理と計算
 
(数式の入った)本をつくる
(数式の入った)本をつくる(数式の入った)本をつくる
(数式の入った)本をつくる
 
Alloy Analyzer のこと
Alloy Analyzer のことAlloy Analyzer のこと
Alloy Analyzer のこと
 
技術者が知るべき Gröbner 基底
技術者が知るべき Gröbner 基底技術者が知るべき Gröbner 基底
技術者が知るべき Gröbner 基底
 
御清聴ありがとうございました
御清聴ありがとうございました御清聴ありがとうございました
御清聴ありがとうございました
 
最近のHaskellマップ
最近のHaskellマップ最近のHaskellマップ
最近のHaskellマップ
 
How wonderful to be (statically) typed 〜型が付くってスバラシイ〜
How wonderful to be (statically) typed 〜型が付くってスバラシイ〜How wonderful to be (statically) typed 〜型が付くってスバラシイ〜
How wonderful to be (statically) typed 〜型が付くってスバラシイ〜
 
Yesod でブログエンジンをつくってみた
Yesod でブログエンジンをつくってみたYesod でブログエンジンをつくってみた
Yesod でブログエンジンをつくってみた
 
Lebesgue 可測性に関する Solovay-Shelah の結果に必要な記述集合論のごく基本的な事項
Lebesgue 可測性に関する Solovay-Shelah の結果に必要な記述集合論のごく基本的な事項Lebesgue 可測性に関する Solovay-Shelah の結果に必要な記述集合論のごく基本的な事項
Lebesgue 可測性に関する Solovay-Shelah の結果に必要な記述集合論のごく基本的な事項
 
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の定理と実数の集合の正則性
 
Algebraic DP: 動的計画法を書きやすく
Algebraic DP: 動的計画法を書きやすくAlgebraic DP: 動的計画法を書きやすく
Algebraic DP: 動的計画法を書きやすく
 
GHC 6.12.1 マルチコア対応ランタイムシステムについて
GHC 6.12.1 マルチコア対応ランタイムシステムについてGHC 6.12.1 マルチコア対応ランタイムシステムについて
GHC 6.12.1 マルチコア対応ランタイムシステムについて
 
これから Haskell を書くにあたって
これから Haskell を書くにあたってこれから Haskell を書くにあたって
これから Haskell を書くにあたって
 
最終発表
最終発表最終発表
最終発表
 
Yesodを支える技術
Yesodを支える技術Yesodを支える技術
Yesodを支える技術
 
数学プログラムを Haskell で書くべき 6 の理由
数学プログラムを Haskell で書くべき 6 の理由数学プログラムを Haskell で書くべき 6 の理由
数学プログラムを Haskell で書くべき 6 の理由
 
Ruby を用いた超絶技巧プログラミング(夏のプログラミングシンポジウム 2012)
Ruby を用いた超絶技巧プログラミング(夏のプログラミングシンポジウム 2012)Ruby を用いた超絶技巧プログラミング(夏のプログラミングシンポジウム 2012)
Ruby を用いた超絶技巧プログラミング(夏のプログラミングシンポジウム 2012)
 

Similaire à Template Haskell とか

Are we ready to Go?
Are we ready to Go?Are we ready to Go?
Are we ready to Go?Adam Dudczak
 
Codementor Office Hours with Eric Chiang: Stdin, Stdout: pup, Go, and life at...
Codementor Office Hours with Eric Chiang: Stdin, Stdout: pup, Go, and life at...Codementor Office Hours with Eric Chiang: Stdin, Stdout: pup, Go, and life at...
Codementor Office Hours with Eric Chiang: Stdin, Stdout: pup, Go, and life at...Arc & Codementor
 
Five Languages in a Moment
Five Languages in a MomentFive Languages in a Moment
Five Languages in a MomentSergio Gil
 
Beginning Haskell, Dive In, Its Not That Scary!
Beginning Haskell, Dive In, Its Not That Scary!Beginning Haskell, Dive In, Its Not That Scary!
Beginning Haskell, Dive In, Its Not That Scary!priort
 
python beginner talk slide
python beginner talk slidepython beginner talk slide
python beginner talk slidejonycse
 
Frege is a Haskell for the JVM
Frege is a Haskell for the JVMFrege is a Haskell for the JVM
Frege is a Haskell for the JVMjwausle
 
Functional perl
Functional perlFunctional perl
Functional perlErrorific
 
Crafting Custom Interfaces with Sub::Exporter
Crafting Custom Interfaces with Sub::ExporterCrafting Custom Interfaces with Sub::Exporter
Crafting Custom Interfaces with Sub::ExporterRicardo Signes
 
GE8151 Problem Solving and Python Programming
GE8151 Problem Solving and Python ProgrammingGE8151 Problem Solving and Python Programming
GE8151 Problem Solving and Python ProgrammingMuthu Vinayagam
 
An Intro To ES6
An Intro To ES6An Intro To ES6
An Intro To ES6FITC
 
Go ahead, make my day
Go ahead, make my dayGo ahead, make my day
Go ahead, make my dayTor Ivry
 
Tuga IT 2017 - What's new in C# 7
Tuga IT 2017 - What's new in C# 7Tuga IT 2017 - What's new in C# 7
Tuga IT 2017 - What's new in C# 7Paulo Morgado
 
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
 
Mirror, mirror on the wall: Building a new PHP reflection library (DPC 2016)
Mirror, mirror on the wall: Building a new PHP reflection library (DPC 2016)Mirror, mirror on the wall: Building a new PHP reflection library (DPC 2016)
Mirror, mirror on the wall: Building a new PHP reflection library (DPC 2016)James Titcumb
 
Mirror, mirror on the wall - Building a new PHP reflection library (Nomad PHP...
Mirror, mirror on the wall - Building a new PHP reflection library (Nomad PHP...Mirror, mirror on the wall - Building a new PHP reflection library (Nomad PHP...
Mirror, mirror on the wall - Building a new PHP reflection library (Nomad PHP...James Titcumb
 
Kotlin For Android - Functions (part 3 of 7)
Kotlin For Android - Functions (part 3 of 7)Kotlin For Android - Functions (part 3 of 7)
Kotlin For Android - Functions (part 3 of 7)Gesh Markov
 
Perl6 Regexen: Reduce the line noise in your code.
Perl6 Regexen: Reduce the line noise in your code.Perl6 Regexen: Reduce the line noise in your code.
Perl6 Regexen: Reduce the line noise in your code.Workhorse Computing
 
20191116 custom operators in swift
20191116 custom operators in swift20191116 custom operators in swift
20191116 custom operators in swiftChiwon Song
 
Forget about loops
Forget about loopsForget about loops
Forget about loopsDušan Kasan
 

Similaire à Template Haskell とか (20)

Are we ready to Go?
Are we ready to Go?Are we ready to Go?
Are we ready to Go?
 
Codementor Office Hours with Eric Chiang: Stdin, Stdout: pup, Go, and life at...
Codementor Office Hours with Eric Chiang: Stdin, Stdout: pup, Go, and life at...Codementor Office Hours with Eric Chiang: Stdin, Stdout: pup, Go, and life at...
Codementor Office Hours with Eric Chiang: Stdin, Stdout: pup, Go, and life at...
 
Five Languages in a Moment
Five Languages in a MomentFive Languages in a Moment
Five Languages in a Moment
 
Beginning Haskell, Dive In, Its Not That Scary!
Beginning Haskell, Dive In, Its Not That Scary!Beginning Haskell, Dive In, Its Not That Scary!
Beginning Haskell, Dive In, Its Not That Scary!
 
python beginner talk slide
python beginner talk slidepython beginner talk slide
python beginner talk slide
 
Frege is a Haskell for the JVM
Frege is a Haskell for the JVMFrege is a Haskell for the JVM
Frege is a Haskell for the JVM
 
Functional perl
Functional perlFunctional perl
Functional perl
 
Crafting Custom Interfaces with Sub::Exporter
Crafting Custom Interfaces with Sub::ExporterCrafting Custom Interfaces with Sub::Exporter
Crafting Custom Interfaces with Sub::Exporter
 
GE8151 Problem Solving and Python Programming
GE8151 Problem Solving and Python ProgrammingGE8151 Problem Solving and Python Programming
GE8151 Problem Solving and Python Programming
 
An Intro To ES6
An Intro To ES6An Intro To ES6
An Intro To ES6
 
Music as data
Music as dataMusic as data
Music as data
 
Go ahead, make my day
Go ahead, make my dayGo ahead, make my day
Go ahead, make my day
 
Tuga IT 2017 - What's new in C# 7
Tuga IT 2017 - What's new in C# 7Tuga IT 2017 - What's new in C# 7
Tuga IT 2017 - What's new in C# 7
 
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
 
Mirror, mirror on the wall: Building a new PHP reflection library (DPC 2016)
Mirror, mirror on the wall: Building a new PHP reflection library (DPC 2016)Mirror, mirror on the wall: Building a new PHP reflection library (DPC 2016)
Mirror, mirror on the wall: Building a new PHP reflection library (DPC 2016)
 
Mirror, mirror on the wall - Building a new PHP reflection library (Nomad PHP...
Mirror, mirror on the wall - Building a new PHP reflection library (Nomad PHP...Mirror, mirror on the wall - Building a new PHP reflection library (Nomad PHP...
Mirror, mirror on the wall - Building a new PHP reflection library (Nomad PHP...
 
Kotlin For Android - Functions (part 3 of 7)
Kotlin For Android - Functions (part 3 of 7)Kotlin For Android - Functions (part 3 of 7)
Kotlin For Android - Functions (part 3 of 7)
 
Perl6 Regexen: Reduce the line noise in your code.
Perl6 Regexen: Reduce the line noise in your code.Perl6 Regexen: Reduce the line noise in your code.
Perl6 Regexen: Reduce the line noise in your code.
 
20191116 custom operators in swift
20191116 custom operators in swift20191116 custom operators in swift
20191116 custom operators in swift
 
Forget about loops
Forget about loopsForget about loops
Forget about loops
 

Template Haskell とか

  • 6. Template Haskell Haskell Q C preprocessor
  • 7. TH
  • 9. TH Haskell IO compile-time wxWidgets Network...
  • 10.
  • 11. RandomDef.hs {-# LANGUAGE TemplateHaskell #-} module Main where import Language.Haskell.TH import System.Random $( do rnd <- runIO $ randomRIO (0,1) let nm = mkName (["a", "b"] !! rnd) m <- [d| main = $(varE $ mkName "a") |] t <- valD (varP nm) (normalB [| putStrLn " ( ´ `) " |]) [] return (t:m) )
  • 12. RandomDef.hs {-# LANGUAGE TemplateHaskell #-} module Main where import Language.Haskell.TH import System.Random IO $( do rnd <- runIO $ randomRIO (0,1) let nm = mkName (["a", "b"] !! rnd) m <- [d| main = $(varE $ mkName "a") |] t <- valD (varP nm) (normalB [| putStrLn " ( ´ `) " |]) [] return (t:m) )
  • 13. Splice( ) {-# LANGUAGE TemplateHaskell #-} module Main where import Language.Haskell.TH import System.Random $( do rnd <- runIO $ randomRIO (0,1) let nm = mkName (["a", "b"] !! rnd) m <- [d| main = $(varE $ mkName "a") |] t <- valD (varP nm) (normalB [| putStrLn " ( ´ `) " |]) [] return (t:m) )
  • 16. Splice (Q ) splice splice
  • 17. Splice (Q ) splice splice “ ”
  • 18. {-# LANGUAGE TemplateHaskell #-} module Main where import Language.Haskell.TH import System.Random $( do rnd <- runIO $ randomRIO (0,1) let nm = mkName (["a", "b"] !! rnd) m <- [d| main = $(varE $ mkName "a") |] t <- valD (varP nm) (normalB [| putStrLn " ( ´ `) " |]) [] return (t:m) )
  • 19.
  • 20. [ |
  • 21. [ | [| putStrLn “hogehoge” |]
  • 22. [ | [| putStrLn “hogehoge” |] [t| String |]
  • 23. [ | [| putStrLn “hogehoge” |] [t| String |] [d| main = putStrLn |]
  • 24. [ | [| putStrLn “hogehoge” |] [t| String |] [d| main = putStrLn |] [$ident| function f() {..} |]
  • 25. [ | [| putStrLn “hogehoge” |] [t| String |] [d| main = putStrLn |] [$ident| function f() {..} |] DSL
  • 26. [ | [| putStrLn “hogehoge” |] [t| String |] [d| main = putStrLn |] [$ident| function f() {..} |] DSL
  • 27. [ | [| putStrLn “hogehoge” |] [t| String |] [d| main = putStrLn |] [$ident| function f() {..} |] DSL )JavaScript (
  • 28. splice [d| main = $(varE $ mkName "a") |] splice [d| main = ‘a |] TH a `a ``String
  • 29. {-# LANGUAGE TemplateHaskell #-} module Main where import Language.Haskell.TH import System.Random $( do rnd <- runIO $ randomRIO (0,1) let nm = mkName (["a", "b"] !! rnd) m <- [d| main = $(varE $ mkName "a") |] t <- valD (varP nm) (normalB [| putStrLn " ( ´ `) " |]) [] return (t:m) )
  • 30. valD (varP nm) (normalB [| putStrLn " ( ´ `) " |]) [] [d| $(varP nm) = putStrLn “ ( ´ `) ” |] …… …… ghci > runQ [d| main = putStrLn “hoge” |]
  • 31. Sucks GHC TH Ver.UP (ex. HOC )
  • 32. lib2 = let l=LetS[ValD(VarP $ mkName"it")(NormalB(f"be"))[]] f=VarE . mkName in DoE [ l, l, l, NoBindS $ f"oh",l, NoBindS $ InfixE(Just$ f"speaking")(f"words")(Just $ f "wisdom"),l]
  • 33. lib2 = let l=LetS[ValD(VarP $ mkName"it")(NormalB(f"be"))[]] f=VarE . mkName in DoE [ l, l, l, NoBindS $ f"oh",l, NoBindS $ InfixE(Just$ f"speaking")(f"words")(Just $ f "wisdom"),l]
  • 34. lib2 = let l=LetS[ValD(VarP $ mkName"it")(NormalB(f"be"))[]] f=VarE . mkName in DoE [ l, l, l, NoBindS $ f"oh",l, NoBindS $ InfixE(Just$ f"speaking")(f"words")(Just $ f "wisdom"),l] do let it = be let it = be let it = be oh let it = be speaking `words` wisdom let it = be
  • 35. reify IO reify Q

Notes de l'éditeur