SlideShare a Scribd company logo
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...
Template Haskell とか
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)
 )
Template Haskell とか
[   |
[   |
        [| 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
Ad

More Related Content

What's hot (18)

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 Clojure
Dmitry Buzdin
 
Introductionto fp with groovy
Introductionto fp with groovyIntroductionto fp with groovy
Introductionto fp with groovy
Isuru 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.3
Matthew 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 edition
osfameron
 
SPL - The Undiscovered Library - PHPBarcelona 2015
SPL - The Undiscovered Library - PHPBarcelona 2015SPL - The Undiscovered Library - PHPBarcelona 2015
SPL - The Undiscovered Library - PHPBarcelona 2015
Mark Baker
 
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
Michelangelo van Dam
 
Perl6 a whistle stop tour
Perl6 a whistle stop tourPerl6 a whistle stop tour
Perl6 a whistle stop tour
Simon Proctor
 
Perl6 a whistle stop tour
Perl6 a whistle stop tourPerl6 a whistle stop tour
Perl6 a whistle stop tour
Simon Proctor
 
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
OdessaJS Conf
 
Hammurabi
HammurabiHammurabi
Hammurabi
Mario Fusco
 
PHP Language Trivia
PHP Language TriviaPHP Language Trivia
PHP Language Trivia
Nikita Popov
 
Haskell in the Real World
Haskell in the Real WorldHaskell in the Real World
Haskell in the Real World
osfameron
 
Python Performance 101
Python Performance 101Python Performance 101
Python Performance 101
Ankur Gupta
 
GR8Conf 2011: Effective Groovy
GR8Conf 2011: Effective GroovyGR8Conf 2011: Effective Groovy
GR8Conf 2011: Effective Groovy
GR8Conf
 
여자개발자모임터 6주년 개발 세미나 - Scala Language
여자개발자모임터 6주년 개발 세미나 - Scala Language여자개발자모임터 6주년 개발 세미나 - Scala Language
여자개발자모임터 6주년 개발 세미나 - Scala Language
Ashal aka JOKER
 
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 Clojure
Dmitry Buzdin
 
Introductionto fp with groovy
Introductionto fp with groovyIntroductionto fp with groovy
Introductionto fp with groovy
Isuru 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.3
Matthew 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 edition
osfameron
 
SPL - The Undiscovered Library - PHPBarcelona 2015
SPL - The Undiscovered Library - PHPBarcelona 2015SPL - The Undiscovered Library - PHPBarcelona 2015
SPL - The Undiscovered Library - PHPBarcelona 2015
Mark Baker
 
Perl6 a whistle stop tour
Perl6 a whistle stop tourPerl6 a whistle stop tour
Perl6 a whistle stop tour
Simon Proctor
 
Perl6 a whistle stop tour
Perl6 a whistle stop tourPerl6 a whistle stop tour
Perl6 a whistle stop tour
Simon Proctor
 
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
OdessaJS Conf
 
PHP Language Trivia
PHP Language TriviaPHP Language Trivia
PHP Language Trivia
Nikita Popov
 
Haskell in the Real World
Haskell in the Real WorldHaskell in the Real World
Haskell in the Real World
osfameron
 
Python Performance 101
Python Performance 101Python Performance 101
Python Performance 101
Ankur Gupta
 
GR8Conf 2011: Effective Groovy
GR8Conf 2011: Effective GroovyGR8Conf 2011: Effective Groovy
GR8Conf 2011: Effective Groovy
GR8Conf
 
여자개발자모임터 6주년 개발 세미나 - Scala Language
여자개발자모임터 6주년 개발 세미나 - Scala Language여자개발자모임터 6주년 개발 세미나 - Scala Language
여자개발자모임터 6주년 개발 세미나 - Scala Language
Ashal aka JOKER
 

Viewers also liked (20)

実践・完全犯罪のつくり方
実践・完全犯罪のつくり方実践・完全犯罪のつくり方
実践・完全犯罪のつくり方
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 Effects
Hiromi 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
 
最終発表
最終発表最終発表
最終発表
Hiromi Ishii
 
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
 
実践・完全犯罪のつくり方
実践・完全犯罪のつくり方実践・完全犯罪のつくり方
実践・完全犯罪のつくり方
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 Effects
Hiromi 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
 
Ad

Similar to Template Haskell とか (20)

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 Moment
Sergio 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 slide
jonycse
 
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
jwausle
 
Functional perl
Functional perlFunctional perl
Functional perl
Errorific
 
Crafting Custom Interfaces with Sub::Exporter
Crafting Custom Interfaces with Sub::ExporterCrafting Custom Interfaces with Sub::Exporter
Crafting Custom Interfaces with Sub::Exporter
Ricardo Signes
 
GE8151 Problem Solving and Python Programming
GE8151 Problem Solving and Python ProgrammingGE8151 Problem Solving and Python Programming
GE8151 Problem Solving and Python Programming
Muthu Vinayagam
 
An Intro To ES6
An Intro To ES6An Intro To ES6
An Intro To ES6
FITC
 
Music as data
Music as dataMusic as data
Music as data
John Vlachoyiannis
 
Go ahead, make my day
Go ahead, make my dayGo ahead, make my day
Go ahead, make my day
Tor 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# 7
Paulo 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 World
BTI360
 
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 swift
Chiwon Song
 
Forget about loops
Forget about loopsForget about loops
Forget about loops
Dušan Kasan
 
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 Moment
Sergio 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 slide
jonycse
 
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
jwausle
 
Functional perl
Functional perlFunctional perl
Functional perl
Errorific
 
Crafting Custom Interfaces with Sub::Exporter
Crafting Custom Interfaces with Sub::ExporterCrafting Custom Interfaces with Sub::Exporter
Crafting Custom Interfaces with Sub::Exporter
Ricardo Signes
 
GE8151 Problem Solving and Python Programming
GE8151 Problem Solving and Python ProgrammingGE8151 Problem Solving and Python Programming
GE8151 Problem Solving and Python Programming
Muthu Vinayagam
 
An Intro To ES6
An Intro To ES6An Intro To ES6
An Intro To ES6
FITC
 
Go ahead, make my day
Go ahead, make my dayGo ahead, make my day
Go ahead, make my day
Tor 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# 7
Paulo 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 World
BTI360
 
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 swift
Chiwon Song
 
Forget about loops
Forget about loopsForget about loops
Forget about loops
Dušan Kasan
 
Ad

Template Haskell とか

  • 6. Template Haskell Haskell Q C preprocessor
  • 7. TH
  • 9. TH Haskell IO compile-time wxWidgets Network...
  • 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) )
  • 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
  翻译: