SlideShare a Scribd company logo
1 of 53
Download to read offline
MP	in	Clojure
~	herding	cats	with	clj	~
Self-introduction
	/laʒenɔʁɛ̃k/	カマイルカlagénorhynque
(defprofile lagénorhynque
:name "Kent OHASHI"
:languages [Clojure Haskell Python Scala
English français Deutsch русский]
:interests [programming language-learning mathematics]
:contributing [github.com/japan-clojurians/clojure-site-ja])
Clojure	×	MP
Contents
1.	 What	is	MP?
2.	 Why	MP	in	Clojure?
3.	 How	MP	in	Clojure?
4.	 Examples
What	is	MP?
programming	with	monads
cf.	FP	=	functional	programming
MP	=	monadic	programming
de nition	of	Monad	in	Haskell
GHC.Base#Monad
class Applicative m => Monad m where
(>>=) :: forall a b. m a -> (a -> m b) -> m b
(>>) :: forall a b. m a -> m b -> m b
m >> k = m >>= _ -> k
{-# INLINE (>>) #-}
return :: a -> m a
return = pure
fail :: String -> m a
fail s = errorWithoutStackTrace s
monads	in	Haskell
型クラス	Monad	のインスタンス
>>=	:	m a -> (a -> m b) -> m b
return	:	a -> m a
モナド則( )を満たす
シンプルで合成可能な構造	→	様々な形で利⽤可能
do	記法というシンタックスシュガー
monad	laws
e.g.	
※	#渋⾕	java	なので⼀応	Java	の例から^_^;
java.util.Optional
jshell> Optional<Integer> a = Optional.of(2)
a ==> Optional[2]
jshell> Optional<Integer> b = Optional.of(3)
b ==> Optional[3]
jshell> a.flatMap( x -> // with `flatMap` & `map`
...> b.map( y ->
...> x * y
...> )
...> )
$3 ==> Optional[6]
e.g.	scala.Option
scala> val a = Some(2)
a: Some[Int] = Some(2)
scala> val b = Some(3)
b: Some[Int] = Some(3)
scala> a.flatMap { x => // with `flatMap` & `map`
| b.map { y =>
| x * y
| }
| }
res0: Option[Int] = Some(6)
scala> for { // with `for` expression
| x <- a
| y <- b
| } yield x * y
res1: Option[Int] = Some(6)
e.g.	Prelude.Maybe
> a = Just 2
> b = Just 3
> :{ -- with `>>=` & `return`
| a >>= x ->
| b >>= y ->
| return $ x * y
| :}
Just 6
> :{ -- with `do` notation
| do
| x <- a
| y <- b
| return $ x * y
| :}
Just 6
e.g.	cats.monad.maybe
user=> (require '[cats.core :as m]
#_=> '[cats.monad.maybe :as maybe])
nil
user=> (def a (maybe/just 2))
#'user/a
user=> (def b (maybe/just 3))
#'user/b
user=> (m/>>= a (fn [x] ; with `>>=` & `return`
#_=> (m/>>= b (fn [y]
#_=> (m/return (* x y))))))
#<Just 6>
user=> (m/mlet [x a ; with `mlet` macro
#_=> y b]
#_=> (m/return (* x y)))
#<Just 6>
Why	MP	in	Clojure?
MP	in	Clojure
Clojureでは
モナドは必須の機能ではないが……
静的型付け&純粋関数型の⾔語ではないが……
シンプルで汎⽤的なDSL構築フレームワーク
Haskellなどで有⽤なアイディアが活かせる
⇒	Clojureでも	MP	してみよう	(*> ᴗ •*)ゞ
How	MP	in	Clojure?
MP	libraries	in	Clojure
clojure/algo.monads
Macros	for	defining	monads,	and
definition	of	the	most	common
monads
funcool/cats
Category	Theory	and	Algebraic
abstractions	for	Clojure	and
ClojureScript.
how	to	support	MP	in	Clojure
feature algo.monads cats
Monad	type	class plain	Map	data protocol
do	notation macro macro
context	inference (n/a) protocol
anatomy	of	algo.monads
user=> (require '[clojure.algo.monads :as m])
nil
user=> (m/domonad m/maybe-m
#_=> [x 2
#_=> y 3]
#_=> (* x y))
6
macroexpand-1
clojure.algo.monads/with-monad	?
user=> (macroexpand-1
#_=> '(m/domonad m/maybe-m
#_=> [x 2
#_=> y 3]
#_=> (* x y)))
(clojure.algo.monads/with-monad m/maybe-m
(m-bind 2 (fn [x]
(m-bind 3 (fn [y]
(m-result (* x y)))))))
macroexpand-1	once	more
clojure.algo.monads/maybe-m	?
user=> (macroexpand-1 *1)
(clojure.core/let [name__3075__auto__ m/maybe-m
m-bind (:m-bind name__3075__auto__)
m-result (:m-result name__3075__auto__)
m-zero (:m-zero name__3075__auto__)
m-plus (:m-plus name__3075__auto__)]
(clojure.tools.macro/with-symbol-macros
(m-bind 2 (fn [x]
(m-bind 3 (fn [y]
(m-result (* x y))))))))
clojure.algo.monads/maybe-m
just	a	keyword-function	Map
user=> clojure.algo.monads/maybe-m
{:m-zero nil,
:m-plus #object[clojure.algo.monads$fn__3167$m_plus_maybe__3172 0x77a7
:m-result #object[clojure.algo.monads$fn__3167$m_result_maybe__3168 0x
:m-bind #object[clojure.algo.monads$fn__3167$m_bind_maybe__3170 0x142d
user=> (class clojure.algo.monads/maybe-m)
clojure.lang.PersistentArrayMap
strategy	in	algo.monads
1.	 :m-bind,	:m-result	をkey、対応する関数を
valueとしたMapを⽤意
2.	 マクロによってMapから取り出した関数	m-bind,
m-result	の組み合わせに変換
anatomy	of	cats
user=> (require '[cats.core :as m]
#_=> '[cats.monad.maybe :as maybe])
nil
user=> (m/mlet [x (maybe/just 2)
#_=> y (maybe/just 3)]
#_=> (m/return (* x y)))
#<Just 6>
macroexpand-1
cats.core/bind	?
without	explicit	monad	context?
user=> (macroexpand-1
#_=> '(m/mlet [x (maybe/just 2)
#_=> y (maybe/just 3)]
#_=> (m/return (* x y))))
(cats.core/bind (maybe/just 2) (clojure.core/fn [x]
(cats.core/bind (maybe/just 3) (clojure.core/fn [y]
(do (m/return (* x y)))))))
cats.core/bind
cats.context/infer	?
can	infer	monad	context?
user=> (source cats.core/bind)
(defn bind
;; (docstring here)
[mv f]
(let [ctx (ctx/infer mv)]
(p/-mbind ctx mv (fn [v]
(ctx/with-context ctx
(f v))))))
nil
cats.context/infer
cats.protocols/Contextual	?
user=> (source cats.context/infer)
(defn infer
;; (docstring here)
;; (0-arity pattern here)
([v]
(cond ; blank lines omitted
(not (nil? *context*))
*context*
(satisfies? p/Contextual v)
(p/-get-context v)
:else
(throw-illegal-argument
(str "No context is set and it can not be automatically "
"resolved from provided value")))))
nil
cats.protocols/Contextual
-get-context	method
user=> (source cats.protocols/Contextual)
(defprotocol Contextual
"Abstraction that establishes a concrete type as a member of a contex
A great example is the Maybe monad type Just. It implements
this abstraction to establish that Just is part of
the Maybe monad."
(-get-context [_] "Get the context associated with the type."))
nil
cats.core/bind	(again)
cats.protocols/-mbind	?
user=> (source cats.core/bind)
(defn bind
;; (docstring here)
[mv f]
(let [ctx (ctx/infer mv)]
(p/-mbind ctx mv (fn [v]
(ctx/with-context ctx
(f v))))))
nil
cats.protocols/Monad
-mreturn	&	-mbind	methods
user=> (source cats.protocols/Monad))
(defprotocol Monad
"The Monad abstraction."
(-mreturn [m v])
(-mbind [m mv f]))
nil
cats.core/bind	( nally)
cats.context/with-context	?
user=> (source cats.core/bind)
(defn bind
;; (docstring here)
[mv f]
(let [ctx (ctx/infer mv)]
(p/-mbind ctx mv (fn [v]
(ctx/with-context ctx
(f v))))))
nil
cats.context/with-context
dynamic	Var	*context*
user=> (source cats.context/with-context)
(defmacro with-context
"Set current context to specific monad."
[ctx & body]
`(do
(when-not (context? ~ctx)
(throw-illegal-argument
"The provided context does not implements Context."))
(binding [*context* ~ctx]
~@body)))
nil
user=> (source cats.context/*context*)
(def ^:dynamic *context* nil)
nil
strategy	in	cats
1.	 Monad	プロトコル(-mreturn,	-mbind)を実装した
コンテキストオブジェクトを⽤意
2.	 Monad	値は	Contextual	プロトコルによってコン
テキストオブジェクトを取り出せる
3.	 マクロで関数	bind,	return	の組み合わせに変換
4.	 bind	は第1引数の	Monad	値からコンテキストオブ
ジェクトを取り出す(コンテキストの推論)
5.	 with-context	で⼀度推論したコンテキストオブ
ジェクトを動的スコープで再利⽤
Examples
example	code	repositories
cf.	
lagenorhynque/mp-in-clojure
lagenorhynque/mp-in-haskell
using	monads:
safe	RPN	calculator
from	Learn	You	a	Haskell	for	Great	Good!
10.1	Reverse	Polish	Notation	Calculator
14.6	Making	a	Safe	RPN	Calculator
RPN:	reverse	Polish	notation
↓	with	parentheses
↓	evaluate
8	6	1	-	*	2	+
((8	(6	1	-)	*)	2	+)
42
without	monads
naïve	implementation
(defn- folding-function [[x y & ys :as xs] s]
(cond
(and x y (= s "*")) (conj ys (* y x))
(and x y (= s "+")) (conj ys (+ y x))
(and x y (= s "-")) (conj ys (- y x))
:else (conj xs (Double/parseDouble s))))
(defn solve-rpn [s]
(as-> s v
(str/split v #"s+")
(reduce folding-function () v)
(first v)))
;; valid RPN
user=> (solve-rpn "8 6 1 - * 2 +")
42.0
;; unsupported operator
user=> (solve-rpn "8 6 1 - * 2 /")
NumberFormatException For input string: "/" sun.misc.FloatingDecimal.r
;; invalid number
user=> (solve-rpn "8 6 1 - * a +")
NumberFormatException For input string: "a" sun.misc.FloatingDecimal.r
;; invalid RPN
user=> (solve-rpn "8 6 1 - * 2")
2.0
with	Maybe	monad
valid	⇒	just	x	;	invalid	⇒	nothing
lift-m	for	lifting	conj	function
(defn- read-maybe [s]
(try
(maybe/just (Double/parseDouble s))
(catch NumberFormatException _
(maybe/nothing))))
(defn- folding-function' [[x y & ys :as xs] s]
(cond
(and x y (= s "*")) (maybe/just (conj ys (* y x)))
(and x y (= s "+")) (maybe/just (conj ys (+ y x)))
(and x y (= s "-")) (maybe/just (conj ys (- y x)))
:else ((m/lift-m 1 #(conj xs %))
(read-maybe s))))
reduce	with	monadic	function	using	foldm
length	of	result	sequence	≠	1	⇒	nothing
MonadZero
cf.	MonadPlus,	Alternative
(defn solve-rpn' [s]
(m/mlet [result (m/foldm folding-function'
()
(str/split s #"s+"))
:when (= (count result) 1)]
(m/return (first result))))
;; valid RPN
user=> (solve-rpn' "8 6 1 - * 2 +")
#<Just 42.0>
;; unsupported operator
user=> (solve-rpn' "8 6 1 - * 2 /")
#<Nothing>
;; invalid number
user=> (solve-rpn' "8 6 1 - * a +")
#<Nothing>
;; invalid RPN
user=> (solve-rpn' "8 6 1 - * 2")
#<Nothing>
making	monads:
probability	distribution
from	Learn	You	a	Haskell	for	Great	Good!
14.8	Making	Monads
probability	distribution
e.g.	6-sided	die
n p
1 1/6
2 1/6
3 1/6
4 1/6
5 1/6
6 1/6
implementing	Prob	monad
define	the	data	type	Prob
(deftype Prob [v]
p/Contextual
(-get-context [_] context)
p/Extract
(-extract [_] v)
p/Printable
(-repr [_]
(str "#<Prob " (pr-str v) ">"))
Object
(equals [this obj]
(= (.v this) (.v obj))))
define	the	context	object	for	Prob
(def context
(reify
;; (other protocol implementations here)
p/Monad
(-mreturn [m v]
(p/-pure m v))
(-mbind [_ mv f]
(assert (prob? mv)
(str "Context mismatch: " (p/-repr mv)
" is not allowed to use with prob context."))
(->Prob (for [[x p] (p/-extract mv)
[y q] (p/-extract (f x))]
[y (* p q)])))
;; (below omitted)
define	factory/conversion	functions
(defn uniform [s] ; sequence
(let [n (count s)] ; -> Prob value of uniform distribution
(->> s
(map (fn [x] [x (/ 1 n)]))
->Prob)))
(defn prob->dist [prob] ; Prob value -> Map of distribution
(letfn [(add-prob [d [x p]]
(update d x (fnil #(+ % p) 0)))]
(reduce add-prob {} (p/-extract prob))))
sum	of	2	dice
user=> (def die (range 1 (inc 6)))
#'user/die
user=> (def prob
#_=> (m/mlet [d1 (uniform die)
#_=> d2 (uniform die)]
#_=> (m/return (+ d1 d2))))
#'user/prob
user=> prob
#<Prob ([2 1/36] [3 1/36] [4 1/36] [5 1/36] [6 1/36] [7 1/36] [3 1/36]
user=> (prob->dist prob)
{7 1/6, 4 1/12, 6 5/36, 3 1/18, 12 1/36, 2 1/36, 11 1/18,
9 1/9, 5 1/9, 10 1/12, 8 5/36}
Monty	Hall	problem
user=> (def doors #{:a :b :c})
#'user/doors
user=> (prob->dist
#_=> (m/mlet [prize (uniform doors)
#_=> choice (uniform doors)]
#_=> (m/return (if (= choice prize)
#_=> :win
#_=> :lose))))
{:win 1/3, :lose 2/3}
user=> (prob->dist
#_=> (m/mlet [prize (uniform doors)
#_=> choice (uniform doors)
#_=> opened (uniform (disj doors prize choice))
#_=> choice' (uniform (disj doors opened choice))]
#_=> (m/return (if (= choice' prize)
#_=> :win
#_=> :lose))))
{:lose 1/3, :win 2/3}
Vive	les	S-expressions	!
Long	live	S-expressions!
Further	Reading
	/	
	/	
clojure/algo.monads
khinsen/monads-in-clojure
funcool/cats
独習	Scalaz learning	Scalaz
猫番 herding	cats
モナド	(プログラミング)	-	Wikipedia
/	
第14章	もうちょっとだけモナド	/	For	a	Few
Monads	More
10.1	逆ポーランド記法電卓	/	
14.6	安全な逆ポーランド記法電卓を作ろう	/
Making	a	Safe	RPN	Calculator
14.8	モナドを作る	/	
『すごいHaskellたのしく学ぼう!』 Learn	You	a
Haskell	for	Great	Good!
Reverse	Polish
Notation	Calculator
Making	Monads
cf.	
Haskell	の	Monad	とは⾔語内DSLのフレームワー
クである
Functor,	Applicative,	Monadのシンプルな定式化
継承によらないポリモーフィズム実現⼿法
思ったほど怖くない!	Haskell	on	JVM	超⼊⾨
MP	in	Scala
MP	in	Haskell
Free	Monads	Getting	Started

More Related Content

What's hot

"Немного о функциональном программирование в JavaScript" Алексей Коваленко
"Немного о функциональном программирование в JavaScript" Алексей Коваленко"Немного о функциональном программирование в JavaScript" Алексей Коваленко
"Немного о функциональном программирование в JavaScript" Алексей Коваленко
Fwdays
 

What's hot (20)

Are we ready to Go?
Are we ready to Go?Are we ready to Go?
Are we ready to Go?
 
Python легко и просто. Красиво решаем повседневные задачи
Python легко и просто. Красиво решаем повседневные задачиPython легко и просто. Красиво решаем повседневные задачи
Python легко и просто. Красиво решаем повседневные задачи
 
Introduction to python
Introduction to pythonIntroduction to python
Introduction to python
 
Swiftの関数型っぽい部分
Swiftの関数型っぽい部分Swiftの関数型っぽい部分
Swiftの関数型っぽい部分
 
Functional Programming Patterns (BuildStuff '14)
Functional Programming Patterns (BuildStuff '14)Functional Programming Patterns (BuildStuff '14)
Functional Programming Patterns (BuildStuff '14)
 
"Немного о функциональном программирование в JavaScript" Алексей Коваленко
"Немного о функциональном программирование в JavaScript" Алексей Коваленко"Немного о функциональном программирование в JavaScript" Алексей Коваленко
"Немного о функциональном программирование в JavaScript" Алексей Коваленко
 
The Easy-Peasy-Lemon-Squeezy, Statically-Typed, Purely Functional Programming...
The Easy-Peasy-Lemon-Squeezy, Statically-Typed, Purely Functional Programming...The Easy-Peasy-Lemon-Squeezy, Statically-Typed, Purely Functional Programming...
The Easy-Peasy-Lemon-Squeezy, Statically-Typed, Purely Functional Programming...
 
Python Functions (PyAtl Beginners Night)
Python Functions (PyAtl Beginners Night)Python Functions (PyAtl Beginners Night)
Python Functions (PyAtl Beginners Night)
 
Python
PythonPython
Python
 
All Aboard The Scala-to-PureScript Express!
All Aboard The Scala-to-PureScript Express!All Aboard The Scala-to-PureScript Express!
All Aboard The Scala-to-PureScript Express!
 
4. Обработка ошибок, исключения, отладка
4. Обработка ошибок, исключения, отладка4. Обработка ошибок, исключения, отладка
4. Обработка ошибок, исключения, отладка
 
OpenGurukul : Language : PHP
OpenGurukul : Language : PHPOpenGurukul : Language : PHP
OpenGurukul : Language : PHP
 
Kotlin, why?
Kotlin, why?Kotlin, why?
Kotlin, why?
 
OpenGurukul : Language : C++ Programming
OpenGurukul : Language : C++ ProgrammingOpenGurukul : Language : C++ Programming
OpenGurukul : Language : C++ Programming
 
Python for data science by www.dmdiploma.com
Python for data science by www.dmdiploma.comPython for data science by www.dmdiploma.com
Python for data science by www.dmdiploma.com
 
C++11
C++11C++11
C++11
 
Hands on Session on Python
Hands on Session on PythonHands on Session on Python
Hands on Session on Python
 
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
 
The best language in the world
The best language in the worldThe best language in the world
The best language in the world
 
MTL Versus Free
MTL Versus FreeMTL Versus Free
MTL Versus Free
 

Viewers also liked (6)

Scala製機械学習サーバ「Apache PredictionIO」
Scala製機械学習サーバ「Apache PredictionIO」Scala製機械学習サーバ「Apache PredictionIO」
Scala製機械学習サーバ「Apache PredictionIO」
 
AtCoderで始めるテスト駆動開発
AtCoderで始めるテスト駆動開発AtCoderで始めるテスト駆動開発
AtCoderで始めるテスト駆動開発
 
Clojure web dev history
Clojure web dev historyClojure web dev history
Clojure web dev history
 
Non-Functional Programming in Scala
Non-Functional Programming in ScalaNon-Functional Programming in Scala
Non-Functional Programming in Scala
 
Javaでマサカリ投げてみた
Javaでマサカリ投げてみたJavaでマサカリ投げてみた
Javaでマサカリ投げてみた
 
Scala警察のすすめ
Scala警察のすすめScala警察のすすめ
Scala警察のすすめ
 

Similar to MP in Clojure

Functions in python
Functions in pythonFunctions in python
Functions in python
Ilian Iliev
 
INFORMATIVE ESSAYThe purpose of the Informative Essay assignme.docx
INFORMATIVE ESSAYThe purpose of the Informative Essay assignme.docxINFORMATIVE ESSAYThe purpose of the Informative Essay assignme.docx
INFORMATIVE ESSAYThe purpose of the Informative Essay assignme.docx
carliotwaycave
 
Refactoring to Macros with Clojure
Refactoring to Macros with ClojureRefactoring to Macros with Clojure
Refactoring to Macros with Clojure
Dmitry Buzdin
 

Similar to MP in Clojure (20)

하스켈 프로그래밍 입문 4
하스켈 프로그래밍 입문 4하스켈 프로그래밍 입문 4
하스켈 프로그래밍 입문 4
 
NativeBoost
NativeBoostNativeBoost
NativeBoost
 
functions
functionsfunctions
functions
 
Dnipro conf
Dnipro confDnipro conf
Dnipro conf
 
The Trailblazer Ride from the If Jungle into a Civilised Railway Station - Or...
The Trailblazer Ride from the If Jungle into a Civilised Railway Station - Or...The Trailblazer Ride from the If Jungle into a Civilised Railway Station - Or...
The Trailblazer Ride from the If Jungle into a Civilised Railway Station - Or...
 
Lecture#6 functions in c++
Lecture#6 functions in c++Lecture#6 functions in c++
Lecture#6 functions in c++
 
Learn Matlab
Learn MatlabLearn Matlab
Learn Matlab
 
PythonOOP
PythonOOPPythonOOP
PythonOOP
 
ClojureScript loves React, DomCode May 26 2015
ClojureScript loves React, DomCode May 26 2015ClojureScript loves React, DomCode May 26 2015
ClojureScript loves React, DomCode May 26 2015
 
documents.pub_new-features-in-java-8-it-jpoialjavanaitedwien15java8pdf-java-8...
documents.pub_new-features-in-java-8-it-jpoialjavanaitedwien15java8pdf-java-8...documents.pub_new-features-in-java-8-it-jpoialjavanaitedwien15java8pdf-java-8...
documents.pub_new-features-in-java-8-it-jpoialjavanaitedwien15java8pdf-java-8...
 
Wien15 java8
Wien15 java8Wien15 java8
Wien15 java8
 
Boosting Developer Productivity with Clang
Boosting Developer Productivity with ClangBoosting Developer Productivity with Clang
Boosting Developer Productivity with Clang
 
Functions in python
Functions in pythonFunctions in python
Functions in python
 
Do snow.rwn
Do snow.rwnDo snow.rwn
Do snow.rwn
 
Clojure basics
Clojure basicsClojure basics
Clojure basics
 
INFORMATIVE ESSAYThe purpose of the Informative Essay assignme.docx
INFORMATIVE ESSAYThe purpose of the Informative Essay assignme.docxINFORMATIVE ESSAYThe purpose of the Informative Essay assignme.docx
INFORMATIVE ESSAYThe purpose of the Informative Essay assignme.docx
 
Functors, applicatives, monads
Functors, applicatives, monadsFunctors, applicatives, monads
Functors, applicatives, monads
 
Refactoring to Macros with Clojure
Refactoring to Macros with ClojureRefactoring to Macros with Clojure
Refactoring to Macros with Clojure
 
Functional Smalltalk
Functional SmalltalkFunctional Smalltalk
Functional Smalltalk
 
CS4200 2019 | Lecture 4 | Syntactic Services
CS4200 2019 | Lecture 4 | Syntactic ServicesCS4200 2019 | Lecture 4 | Syntactic Services
CS4200 2019 | Lecture 4 | Syntactic Services
 

More from Kent Ohashi

More from Kent Ohashi (20)

インターフェース定義言語から学ぶモダンなWeb API方式: REST, GraphQL, gRPC
インターフェース定義言語から学ぶモダンなWeb API方式: REST, GraphQL, gRPCインターフェース定義言語から学ぶモダンなWeb API方式: REST, GraphQL, gRPC
インターフェース定義言語から学ぶモダンなWeb API方式: REST, GraphQL, gRPC
 
Team Geek Revisited
Team Geek RevisitedTeam Geek Revisited
Team Geek Revisited
 
Scala vs Clojure?: The Rise and Fall of Functional Languages in Opt Technologies
Scala vs Clojure?: The Rise and Fall of Functional Languages in Opt TechnologiesScala vs Clojure?: The Rise and Fall of Functional Languages in Opt Technologies
Scala vs Clojure?: The Rise and Fall of Functional Languages in Opt Technologies
 
Clojureコレクションで探るimmutableでpersistentな世界
Clojureコレクションで探るimmutableでpersistentな世界Clojureコレクションで探るimmutableでpersistentな世界
Clojureコレクションで探るimmutableでpersistentな世界
 
英語学習者のためのフランス語文法入門: フランス語完全理解(?)
英語学習者のためのフランス語文法入門: フランス語完全理解(?)英語学習者のためのフランス語文法入門: フランス語完全理解(?)
英語学習者のためのフランス語文法入門: フランス語完全理解(?)
 
JavaからScala、そしてClojureへ: 実務で活きる関数型プログラミング
JavaからScala、そしてClojureへ: 実務で活きる関数型プログラミングJavaからScala、そしてClojureへ: 実務で活きる関数型プログラミング
JavaからScala、そしてClojureへ: 実務で活きる関数型プログラミング
 
実用のための語源学入門
実用のための語源学入門実用のための語源学入門
実用のための語源学入門
 
メタプログラミング入門
メタプログラミング入門メタプログラミング入門
メタプログラミング入門
 
労働法の世界
労働法の世界労働法の世界
労働法の世界
 
Clojureで作る"simple"なDSL
Clojureで作る"simple"なDSLClojureで作る"simple"なDSL
Clojureで作る"simple"なDSL
 
RDBでのツリー表現入門
RDBでのツリー表現入門RDBでのツリー表現入門
RDBでのツリー表現入門
 
GraphQL入門
GraphQL入門GraphQL入門
GraphQL入門
 
Everyday Life with clojure.spec
Everyday Life with clojure.specEveryday Life with clojure.spec
Everyday Life with clojure.spec
 
たのしい多言語学習
たのしい多言語学習たのしい多言語学習
たのしい多言語学習
 
Ductモジュール入門
Ductモジュール入門Ductモジュール入門
Ductモジュール入門
 
Clojure REPL: The Good Parts
Clojure REPL: The Good PartsClojure REPL: The Good Parts
Clojure REPL: The Good Parts
 
"Simple Made Easy" Made Easy
"Simple Made Easy" Made Easy"Simple Made Easy" Made Easy
"Simple Made Easy" Made Easy
 
Clojurian Conquest
Clojurian ConquestClojurian Conquest
Clojurian Conquest
 
ClojurianからみたElixir
ClojurianからみたElixirClojurianからみたElixir
ClojurianからみたElixir
 
GraphQL API in Clojure
GraphQL API in ClojureGraphQL API in Clojure
GraphQL API in Clojure
 

Recently uploaded

CALL ON ➥8923113531 🔝Call Girls Kakori Lucknow best sexual service Online ☂️
CALL ON ➥8923113531 🔝Call Girls Kakori Lucknow best sexual service Online  ☂️CALL ON ➥8923113531 🔝Call Girls Kakori Lucknow best sexual service Online  ☂️
CALL ON ➥8923113531 🔝Call Girls Kakori Lucknow best sexual service Online ☂️
anilsa9823
 
+971565801893>>SAFE AND ORIGINAL ABORTION PILLS FOR SALE IN DUBAI AND ABUDHAB...
+971565801893>>SAFE AND ORIGINAL ABORTION PILLS FOR SALE IN DUBAI AND ABUDHAB...+971565801893>>SAFE AND ORIGINAL ABORTION PILLS FOR SALE IN DUBAI AND ABUDHAB...
+971565801893>>SAFE AND ORIGINAL ABORTION PILLS FOR SALE IN DUBAI AND ABUDHAB...
Health
 
CALL ON ➥8923113531 🔝Call Girls Badshah Nagar Lucknow best Female service
CALL ON ➥8923113531 🔝Call Girls Badshah Nagar Lucknow best Female serviceCALL ON ➥8923113531 🔝Call Girls Badshah Nagar Lucknow best Female service
CALL ON ➥8923113531 🔝Call Girls Badshah Nagar Lucknow best Female service
anilsa9823
 
TECUNIQUE: Success Stories: IT Service provider
TECUNIQUE: Success Stories: IT Service providerTECUNIQUE: Success Stories: IT Service provider
TECUNIQUE: Success Stories: IT Service provider
mohitmore19
 

Recently uploaded (20)

The Real-World Challenges of Medical Device Cybersecurity- Mitigating Vulnera...
The Real-World Challenges of Medical Device Cybersecurity- Mitigating Vulnera...The Real-World Challenges of Medical Device Cybersecurity- Mitigating Vulnera...
The Real-World Challenges of Medical Device Cybersecurity- Mitigating Vulnera...
 
The Ultimate Test Automation Guide_ Best Practices and Tips.pdf
The Ultimate Test Automation Guide_ Best Practices and Tips.pdfThe Ultimate Test Automation Guide_ Best Practices and Tips.pdf
The Ultimate Test Automation Guide_ Best Practices and Tips.pdf
 
Reassessing the Bedrock of Clinical Function Models: An Examination of Large ...
Reassessing the Bedrock of Clinical Function Models: An Examination of Large ...Reassessing the Bedrock of Clinical Function Models: An Examination of Large ...
Reassessing the Bedrock of Clinical Function Models: An Examination of Large ...
 
A Secure and Reliable Document Management System is Essential.docx
A Secure and Reliable Document Management System is Essential.docxA Secure and Reliable Document Management System is Essential.docx
A Secure and Reliable Document Management System is Essential.docx
 
Shapes for Sharing between Graph Data Spaces - and Epistemic Querying of RDF-...
Shapes for Sharing between Graph Data Spaces - and Epistemic Querying of RDF-...Shapes for Sharing between Graph Data Spaces - and Epistemic Querying of RDF-...
Shapes for Sharing between Graph Data Spaces - and Epistemic Querying of RDF-...
 
Software Quality Assurance Interview Questions
Software Quality Assurance Interview QuestionsSoftware Quality Assurance Interview Questions
Software Quality Assurance Interview Questions
 
CALL ON ➥8923113531 🔝Call Girls Kakori Lucknow best sexual service Online ☂️
CALL ON ➥8923113531 🔝Call Girls Kakori Lucknow best sexual service Online  ☂️CALL ON ➥8923113531 🔝Call Girls Kakori Lucknow best sexual service Online  ☂️
CALL ON ➥8923113531 🔝Call Girls Kakori Lucknow best sexual service Online ☂️
 
+971565801893>>SAFE AND ORIGINAL ABORTION PILLS FOR SALE IN DUBAI AND ABUDHAB...
+971565801893>>SAFE AND ORIGINAL ABORTION PILLS FOR SALE IN DUBAI AND ABUDHAB...+971565801893>>SAFE AND ORIGINAL ABORTION PILLS FOR SALE IN DUBAI AND ABUDHAB...
+971565801893>>SAFE AND ORIGINAL ABORTION PILLS FOR SALE IN DUBAI AND ABUDHAB...
 
CALL ON ➥8923113531 🔝Call Girls Badshah Nagar Lucknow best Female service
CALL ON ➥8923113531 🔝Call Girls Badshah Nagar Lucknow best Female serviceCALL ON ➥8923113531 🔝Call Girls Badshah Nagar Lucknow best Female service
CALL ON ➥8923113531 🔝Call Girls Badshah Nagar Lucknow best Female service
 
Steps To Getting Up And Running Quickly With MyTimeClock Employee Scheduling ...
Steps To Getting Up And Running Quickly With MyTimeClock Employee Scheduling ...Steps To Getting Up And Running Quickly With MyTimeClock Employee Scheduling ...
Steps To Getting Up And Running Quickly With MyTimeClock Employee Scheduling ...
 
W01_panagenda_Navigating-the-Future-with-The-Hitchhikers-Guide-to-Notes-and-D...
W01_panagenda_Navigating-the-Future-with-The-Hitchhikers-Guide-to-Notes-and-D...W01_panagenda_Navigating-the-Future-with-The-Hitchhikers-Guide-to-Notes-and-D...
W01_panagenda_Navigating-the-Future-with-The-Hitchhikers-Guide-to-Notes-and-D...
 
Try MyIntelliAccount Cloud Accounting Software As A Service Solution Risk Fre...
Try MyIntelliAccount Cloud Accounting Software As A Service Solution Risk Fre...Try MyIntelliAccount Cloud Accounting Software As A Service Solution Risk Fre...
Try MyIntelliAccount Cloud Accounting Software As A Service Solution Risk Fre...
 
Unlocking the Future of AI Agents with Large Language Models
Unlocking the Future of AI Agents with Large Language ModelsUnlocking the Future of AI Agents with Large Language Models
Unlocking the Future of AI Agents with Large Language Models
 
How To Troubleshoot Collaboration Apps for the Modern Connected Worker
How To Troubleshoot Collaboration Apps for the Modern Connected WorkerHow To Troubleshoot Collaboration Apps for the Modern Connected Worker
How To Troubleshoot Collaboration Apps for the Modern Connected Worker
 
Microsoft AI Transformation Partner Playbook.pdf
Microsoft AI Transformation Partner Playbook.pdfMicrosoft AI Transformation Partner Playbook.pdf
Microsoft AI Transformation Partner Playbook.pdf
 
TECUNIQUE: Success Stories: IT Service provider
TECUNIQUE: Success Stories: IT Service providerTECUNIQUE: Success Stories: IT Service provider
TECUNIQUE: Success Stories: IT Service provider
 
Unveiling the Tech Salsa of LAMs with Janus in Real-Time Applications
Unveiling the Tech Salsa of LAMs with Janus in Real-Time ApplicationsUnveiling the Tech Salsa of LAMs with Janus in Real-Time Applications
Unveiling the Tech Salsa of LAMs with Janus in Real-Time Applications
 
Learn the Fundamentals of XCUITest Framework_ A Beginner's Guide.pdf
Learn the Fundamentals of XCUITest Framework_ A Beginner's Guide.pdfLearn the Fundamentals of XCUITest Framework_ A Beginner's Guide.pdf
Learn the Fundamentals of XCUITest Framework_ A Beginner's Guide.pdf
 
Diamond Application Development Crafting Solutions with Precision
Diamond Application Development Crafting Solutions with PrecisionDiamond Application Development Crafting Solutions with Precision
Diamond Application Development Crafting Solutions with Precision
 
Short Story: Unveiling the Reasoning Abilities of Large Language Models by Ke...
Short Story: Unveiling the Reasoning Abilities of Large Language Models by Ke...Short Story: Unveiling the Reasoning Abilities of Large Language Models by Ke...
Short Story: Unveiling the Reasoning Abilities of Large Language Models by Ke...
 

MP in Clojure