SlideShare ist ein Scribd-Unternehmen logo
1 von 46
Downloaden Sie, um offline zu lesen
List-based Monadic Computations for
Dynamically Typed Languages
Wim Vanderbauwhede
School of Computing Science, University of Glasgow, UK
Overview
Program Composition in Dynamically
Typed Languages
Objects
Monads
Defining Karma
Karmic Types
Combining Functions using Functions
The Rules
Designing Karma
Syntactic Sugar
fold and chain
Karma Needs Dynamic Typing
Karmic Computations By Example
Maybe
State
Parsing
Conclusion
Dynamically Typed Languages
size proportional to
√
#projects on GitHub
Perl ...
Notorious
$_=’while(read+STDIN,$_,2048){$a=29;$b=73;
$c=142;$t=255;@t=map{$_%16or$t^=$c^=($m=
(11,10,116,100,11,122,20,100)[$_/16%8])&110;
$t^=(72,@z=(64,72,$a^=12*($_%16 -2?0:$m&17)),
$b^=$_%64?12:0,@z)[$_%8]}(16..271);
if((@a=unx"C*",$_)[20]&48){$h =5;$_=unxb24,
join"",@b=map{xB8,unxb8,chr($_^$a[--$h+84])}
@ARGV;s/...$/1$&/;$ d=unxV,xb25,$_;$e=256|
(ord$b[4])<‌<9|ord$b[3];$d=$d>‌>8^($f=$t&
($d>‌>12^$d>‌>4^$d^$d/8))<‌<17,$e=$e>‌>8^($t
&($g=($q=$e>‌>14&7^$e)^$q*8^$q<‌<6))<‌<9,$_=
$t[$_]^(($h>‌>=8)+=$f+(~$g&$t))for
@a[128..$#a]}print+x"C*",@a}’;s/x/pack+/g;
eval;
But I like Perl (*ducks*)
Program Composition
Most Dynamic Languages use an OOP approach to
structure/compose programs
But what if you don’t like object orientation?
Or what if it is simply not the best approach?
An alternative approach to program composition:
Functional Languages use composition of higher-order functions
In particular, Haskell uses monads ...
Haskell ...
Most empathically not
dynamically typed ...
Makes easy things hard ...
But I like Haskell (*ducks*)
Monads
a reputation of being esoteric
hard to understand
the province of academic
languages
(unknown poet, 21st century)
Monas Hieroglyphica,
(“The Hieroglyphic Monad”),
John Dee, Antwerp 1564
Monads in Dynamic Languages
Have been done many times for many languages
https://en.wikipedia.org/wiki/Monad(functional_programming)#Monads_in_other_languages
But have not found widespread adoption
So ...
The Claim
... are monads of practical use in day-to-day programming?
Yes!
Only we won’t call them monads ...
Karmic Computations
Karma is a Sanskrit word meaning action, work or deed.
A different approach from the many existing implementations of
monads in dynamic languages.
Based on types, lambda functions and higher-order functions.
Types and Notation
Haskell-style syntax for types:
A function g from a type a to a type b:
g :: a → b
A function s with two arguments and the result of type a:
s :: a → a → a
A function f from a type a to a type m b, i.e. a type m parametrised
on a type b:
f :: a → m b
A function h which takes as arguments two functions of type
a → b and b → c and returns a function of type a → m b:
h :: (a → b) → (b → c) → (a → m b)
Lambda Functions
Also knows as anonymous subroutines, i.e. functions without a
name.
They are expressions that can be assigned to variables.
Language Lambda Syntax
Haskell x y -> f x y
LiveScript (x,y) -> f x,y
Perl sub ($x,$y) { f $x,$y }
Python lambda x,y : f(x,y)
Ruby -> (x,y) { f x,y }
Higher-Order Functions
Functions that take other
functions as arguments and/or
return functions as results
Available in your favourite
dynamically type language: Ruby,
Python, LiveScript, JavaScript, ...
What is Karma?
A karmic computation consists of:
a given type m a;
the higher-order functions bind and wrap
and three rules governing those functions.
Karmic Types
A karmic type can be viewed as a “wrapper” around another type.
It does not have to have a particular structure, e.g. it can be an
object, or a list, or a map, or a function.
The key point is that the “karmic” type contains more information
than the “bare” type.
We will write m a as the karmic type constructor, regardless of
the structure of the type.
For example, in Ruby the following function f has a type
f :: a → m b, if g has type g :: a → b:
def f(x)
m.new( g(x) )
end
Combining Functions
using Functions
The purpose of the karmic computation is to combine functions that
operates on karmic types.
The bind function composes values of type m a with functions
from a to m b:
bind :: m a → (a → m b) → m b
The wrap function takes a given type a and returns m a:
wrap :: a → m a
With these two functions we can create expressions that consists of
combinations of functions.
The Rules
Three rules govern bind and wrap to ensure that the composition is
well-behaved:
1. bind (wrap x) f ≡ f x
2. bind m wrap ≡ m
3. bind (bind m f) g ≡ bind m (x -> bind (f x) g)
For reference, the rules in Ruby syntax:
1. bind(wrap(x),f) = f.call(x)
2. bind(m,wrap) = m
3. bind(bind(m,f),g) = bind(m,->(c){bind(f.call(x),g))})
Syntactic Sugar for Monads
In Haskell:
No sugar:
ex x =
x -> (bind (g x) (y -> (f (bind y (z -> wrap z)))))
Operator sugar:
ex x =
g x >‌>= y ->
f y >‌>= z ->
wrap z
Do-notation sugar:
ex x = do
y <- g x
z <- f y
wrap z
Syntactic Sugar for Karma
Our approach:
Use lists to combine computations
For example:
[
word,
maybe parens choice
natural,
[
symbol ’kind’,
symbol ’=’,
natural
]
]
Designing Karma
Grouping items in lists provides a natural sequencing
mechanism, and allows easy nesting.
In most dynamic languages, lists us the [...,...] syntax, it’s
portable and non-obtrusive.
We introduce a chain function to chain computations together.
Pass chain a list of functions and it will combine these functions
into a single expression.
Preliminary: fold
To define chain in terms of bind and wrap, we need the left fold
function (foldl).
foldl performs a left-to-right reduction of a list via iterative
application of a function to an initial value:
foldl :: (a → b → a) → a → [b] → [a]
A possible implementation e.g. in Perl would be
sub foldl ($f, $acc, @lst) {
for my $elt (@lst) {
$acc=$f->($acc,$elt)
}
return $acc
}
Defining chain
We can now define chain as
sub chain(@fs) {
sub($x) { foldl bind, wrap $x, @fs }
}
Or in Haskell syntax
chain fs = x -> foldl (>‌>=) (wrap x) fs
Karma Needs Dynamic Typing
The above definition of chain is valid in Haskell, but only if the
type signature is
chain :: [(a → m a)] → (a → m a)
But the type of bind is bind :: m a → (a → m b) → m b
the karmic type m b returned by bind does not have to be the same
as the karmic type argument m a.
every function in the list passed to chain should be allowed to have
a different type!
This is not allowed in a statically typed language like Haskell, so
only the restricted case of functions of type a → m a can be
used.
However, in a dynamically typed language there is no such
restriction, so we can generalise the type signature:
chain :: [(ai−1 → m ai )] → (a0 → m aN ) ∀i ∈ 1 .. N
Demonstrating Karma
Combining computations that can fail
Stateful computation
Parser combinators
Combining Fallible Computations (1)
Expressing failure
A Maybe class
class Maybe
attr_accessor :val,:ok
def initialize(value,status)
@val=value
@ok=status # true or false
end
end
For convenience: a fail instance
fail = Maybe.new(nil,false)
Assume f, g, h :: a → Maybe b
Combining Fallible Computations (2)
Without karma
v1 = f(x)
if (v1.ok)
v2=g(v1.val)
if (v2.ok)
v3 = h(v2.val)
if (v3.ok)
v3.val
else
fail
end
else
fail
end
else
fail
end
With karma:
comp = chain [
->(x) {f x},
->(y) {g y},
->(z) {h z}
]
v1=comp.call x
If f, g and h are defined as
lambda functions:
comp =
chain [ f,g,h ]
v1=comp.call x
bind and wrap for Maybe
For the Maybe karmic type, bind is defined as:
def bind(x,f)
if x.ok
f.call(x)
else
fail
end
end
and wrap as:
def wrap(x)
Maybe.new(x,true)
end
Stateful Computation
Using karma to perform stateful computations without actual
mutable state.
Example in LiveScript, because LiveScript has the option to force
immutable variables.
There is a growing interest in the use of immutable state in other
dynamic languages, in particular for web programming, because
immutable state greatly simplifies concurrent programming and
improves testability of code.
State Concept and API
We simulate state by combining functions that transform the
state, and applying the resulting function to an initial state
(approach borrowed from Haskell’s Control.State).
A small API to allow the functions in the list to access a shared
state:
get = -> ( (s) -> [s, s] )
put = (s) -> ( -> [[],s])
The get function reads the state, the put function writes an
updated state. Both return lambda functions.
A top-level function to apply the stateful computation to an initial
state:
res = evalState comp, init
where
evalState = (comp,init) -> comp!(init)
Trivial Interpreter:
Instructions
We want to interpret a list of instructions of type
type Instr = (String, ([Int] → Int, [a]))
For example
instrs = [
["v1",[set,[1]]],
["v2",[add,["v1",2]]],
["v2",[mul,["v2","v2"]]],
["v1",[add,["v1","v2"]]],
["v3",[mul,["v1","v2"]]]
]
where add, mul and set are functions of type [Int] → Int
The interpreter should return the final values for all variables.
The interpreter will need a context for the variables, we use a
simple map { String : Int } to store the values for each variable.
This constitutes the state of the computation.
Trivial Interpreter:
the Karmic Function
We write a function interpret_instr_st :: Instr → [[a], Ctxt]:
interpret_instr_st = (instr) ->
chain( [
get,
(ctxt) ->
[v,res] = interpret_instr(instr, ctxt)
put (insert v, res, ctxt)
] )
interpret_instr_st
gets the context from the state,
uses it to compute the instruction,
updates the context using the insert function and
puts the context back in the state.
Trivial Interpreter:
the Stateless Function
Using Ctxt as the type of the context, the type of interpret_instr is
interpret_instr :: Instr → Ctxt → (String, Int) and the
implementation is straightforward:
interpret_instr = (instr, ctxt) ->
[v,rhs] = instr # unpacking
[op,args] = rhs # unpacking
vals = map (‘get_val‘ ctxt), args
[v, op vals]
get_val looks up the value of a variable in the context; it is
backticked into an operator here to allow partial application.
bind and wrap for State
For the State karmic type, bind is defined as:
bind = (f,g) ->
(st) ->
[x,st_] = f st
(g x) st_
and wrap as
wrap = (x) -> ( (s) -> [x,s] )
modify: Modifying the State
The pattern of calling get to get the state, then computing using
the state and then updating the state using put is very common.
So we combine it in a function called modify:
modify = (f) ->
chain( [
get,
(s) -> put( f(s))
] )
Using modify we can rewrite interpret_instr_st as
interpret_instr_st = (instr) ->
modify (ctxt) ->
[v,res] = interpret_instr(instr, ctxt)
insert v, res, ctxt
mapM: a Dynamic chain
We could in principle use chain to write a list of computations on
each instruction:
chain [
interpret_instr_st instrs[0],
interpret_instr_st instrs[1],
interpret_instr_st instrs[2],
...
]
but clearly this is not practical as it is entirely static.
Instead, we use a monadic variant of the map function, mapM:
mapM :: Monad m ⇒ (a → m b) → [a] → m [b]
mapM applies the computations to the list of instructions (using
map) and then folds the resulting list using bind.
With mapM, we can simply write :
res = evalState (mapM interpret_instr_st, instrs), {}
Fortran ...
I like Fortran (*ducks*)
Parser Combinators
Or more precisely, I needed to
parse Fortran for source
transformations.
So I needed a Fortran parser ...
... in Perl (for reasons).
So I created a Perl version of
Haskell’s Parsec parser
combinator library ...
... using Karma.
Parser Combinator Basics
Each basic parser returns a function which operates on a string
and returns a result.
Parser :: String → Result
The result is a tuple containing the status, the remaining string
and the substring(s) matched by the parser.
type Result = (Status, String, [Match])
To create a complete parser, the basic parsers are combined
using combinators.
A combinator takes a list of parsers and returns a parsing
function similar to the basic parsers:
combinator :: [Parser] → Parser
Karmic Parser Combinators
For example, a parser for a Fortran-95 type declaration:
my $parser = chain [
identifier,
maybe parens choice
natural,
[
symbol ’kind’,
symbol ’=’,
natural
]
];
In dynamic languages the actual chain combinator can be
implicit, i.e. a bare list will result in calling of chain on the list.
For statically typed languages this is of course not possible as all
elements in a list must have the same type.
bind and wrap for Parser
For the Parser karmic type, bind is defined as (Perl):
sub bind($t, $p) {
my ($st_,$r_,$ms_) = @{$t};
if ($st_) {
($st,$r,$ms) = $p->($r_);
if ($st) {
(1,$r,[@{$ms_},@{$ms}]);
} else {
(0,$r,undef)
}
} else {
(0,$r_,undef)
}
and wrap as:
sub wrap($str){ (1,$str,undef) }
bind and wrap for Parser
For the Parser karmic type, bind is defined as (LiveScript):
bind = (t, p) ->
[st_,r_,ms_] = t
if st_ then
[st,r,ms] = p r_
if st then
[1,r,ms_ ++ ms]
else
[0,r,void]
else
[0,r_,void]
and wrap as:
wrap = (str) -> [1,str,void]
Final Example (1)
Parsers can combine several other parsers, and can be labeled:
my $f95_arg_decl_parser =
chain [
whiteSpace,
{TypeTup => $type_parser},
maybe [
comma,
$dim_parser
],
maybe [
comma,
$intent_parser
],
symbol ’::’,
{Vars => sepBy ’,’,word}
];
Final Example (2)
We can run this parser e.g.
my $var_decl =
"real(8), dimension(0:ip,-1:jp+1,kp) :: u,v"
my $res =
run $f95_arg_decl_parser, $var_decl;
This results in the parse tree:
{
’TypeTup’ => {
’Type’ => ’real’,
’Kind’ => ’8’
},
’Dim’ => [’0:ip’,’-1:jp+1’,’kp’],
’Vars’ => [’u’,’v’]
}
Parser Combinators Library
The Perl and LiveScript versions are on GitHub:
https:
//github.com/wimvanderbauwhede/Perl-Parser-Combinators
https:
//github.com/wimvanderbauwhede/parser-combinators-ls
The Perl library is actually used in a Fortran source compiler
https://github.com/wimvanderbauwhede/RefactorF4Acc
Conclusion
We have presented a design for list-based monadic
computations, which we call karmic computations.
Karmic computations
are equivalent to monadic computations in statically typed
languages such as Haskell,
but rely essentially on dynamic typing through the use of
heterogeneous lists.
The proposed list-based syntax
is easy to use,
results in concise, elegant and very readable code, and
is largely language-independent.
The proposed approach can be applied very widely, especially as
a design technique for libraries.
Thank you

Weitere ähnliche Inhalte

Was ist angesagt?

Real World Haskell: Lecture 3
Real World Haskell: Lecture 3Real World Haskell: Lecture 3
Real World Haskell: Lecture 3Bryan O'Sullivan
 
Scala categorytheory
Scala categorytheoryScala categorytheory
Scala categorytheoryKnoldus Inc.
 
The Functional Programming Triad of Folding, Scanning and Iteration - a first...
The Functional Programming Triad of Folding, Scanning and Iteration - a first...The Functional Programming Triad of Folding, Scanning and Iteration - a first...
The Functional Programming Triad of Folding, Scanning and Iteration - a first...Philip Schwarz
 
Real World Haskell: Lecture 7
Real World Haskell: Lecture 7Real World Haskell: Lecture 7
Real World Haskell: Lecture 7Bryan O'Sullivan
 
Real World Haskell: Lecture 1
Real World Haskell: Lecture 1Real World Haskell: Lecture 1
Real World Haskell: Lecture 1Bryan O'Sullivan
 
Big picture of category theory in scala with deep dive into contravariant and...
Big picture of category theory in scala with deep dive into contravariant and...Big picture of category theory in scala with deep dive into contravariant and...
Big picture of category theory in scala with deep dive into contravariant and...Piotr Paradziński
 
3 kotlin vs. java- what kotlin has that java does not
3  kotlin vs. java- what kotlin has that java does not3  kotlin vs. java- what kotlin has that java does not
3 kotlin vs. java- what kotlin has that java does notSergey Bandysik
 
Function Applicative for Great Good of Palindrome Checker Function - Polyglot...
Function Applicative for Great Good of Palindrome Checker Function - Polyglot...Function Applicative for Great Good of Palindrome Checker Function - Polyglot...
Function Applicative for Great Good of Palindrome Checker Function - Polyglot...Philip Schwarz
 
Introducing Assignment invalidates the Substitution Model of Evaluation and v...
Introducing Assignment invalidates the Substitution Model of Evaluation and v...Introducing Assignment invalidates the Substitution Model of Evaluation and v...
Introducing Assignment invalidates the Substitution Model of Evaluation and v...Philip Schwarz
 
Implicit conversion and parameters
Implicit conversion and parametersImplicit conversion and parameters
Implicit conversion and parametersKnoldus Inc.
 
Introduction to Functional Programming in JavaScript
Introduction to Functional Programming in JavaScriptIntroduction to Functional Programming in JavaScript
Introduction to Functional Programming in JavaScripttmont
 
Scala 3 enum for a terser Option Monad Algebraic Data Type
Scala 3 enum for a terser Option Monad Algebraic Data TypeScala 3 enum for a terser Option Monad Algebraic Data Type
Scala 3 enum for a terser Option Monad Algebraic Data TypePhilip Schwarz
 
Applicative Functor - Part 3
Applicative Functor - Part 3Applicative Functor - Part 3
Applicative Functor - Part 3Philip Schwarz
 
Strinng Classes in c++
Strinng Classes in c++Strinng Classes in c++
Strinng Classes in c++Vikash Dhal
 

Was ist angesagt? (20)

Clojure basics
Clojure basicsClojure basics
Clojure basics
 
Real World Haskell: Lecture 3
Real World Haskell: Lecture 3Real World Haskell: Lecture 3
Real World Haskell: Lecture 3
 
Scala categorytheory
Scala categorytheoryScala categorytheory
Scala categorytheory
 
The Functional Programming Triad of Folding, Scanning and Iteration - a first...
The Functional Programming Triad of Folding, Scanning and Iteration - a first...The Functional Programming Triad of Folding, Scanning and Iteration - a first...
The Functional Programming Triad of Folding, Scanning and Iteration - a first...
 
Real World Haskell: Lecture 7
Real World Haskell: Lecture 7Real World Haskell: Lecture 7
Real World Haskell: Lecture 7
 
Real World Haskell: Lecture 1
Real World Haskell: Lecture 1Real World Haskell: Lecture 1
Real World Haskell: Lecture 1
 
Monad Fact #4
Monad Fact #4Monad Fact #4
Monad Fact #4
 
Big picture of category theory in scala with deep dive into contravariant and...
Big picture of category theory in scala with deep dive into contravariant and...Big picture of category theory in scala with deep dive into contravariant and...
Big picture of category theory in scala with deep dive into contravariant and...
 
3 kotlin vs. java- what kotlin has that java does not
3  kotlin vs. java- what kotlin has that java does not3  kotlin vs. java- what kotlin has that java does not
3 kotlin vs. java- what kotlin has that java does not
 
Knolx session
Knolx sessionKnolx session
Knolx session
 
Compile time polymorphism
Compile time polymorphismCompile time polymorphism
Compile time polymorphism
 
Function Applicative for Great Good of Palindrome Checker Function - Polyglot...
Function Applicative for Great Good of Palindrome Checker Function - Polyglot...Function Applicative for Great Good of Palindrome Checker Function - Polyglot...
Function Applicative for Great Good of Palindrome Checker Function - Polyglot...
 
Introducing Assignment invalidates the Substitution Model of Evaluation and v...
Introducing Assignment invalidates the Substitution Model of Evaluation and v...Introducing Assignment invalidates the Substitution Model of Evaluation and v...
Introducing Assignment invalidates the Substitution Model of Evaluation and v...
 
Implicit conversion and parameters
Implicit conversion and parametersImplicit conversion and parameters
Implicit conversion and parameters
 
The string class
The string classThe string class
The string class
 
Introduction to Functional Programming in JavaScript
Introduction to Functional Programming in JavaScriptIntroduction to Functional Programming in JavaScript
Introduction to Functional Programming in JavaScript
 
Scala 3 enum for a terser Option Monad Algebraic Data Type
Scala 3 enum for a terser Option Monad Algebraic Data TypeScala 3 enum for a terser Option Monad Algebraic Data Type
Scala 3 enum for a terser Option Monad Algebraic Data Type
 
Applicative Functor - Part 3
Applicative Functor - Part 3Applicative Functor - Part 3
Applicative Functor - Part 3
 
Lambda Calculus
Lambda CalculusLambda Calculus
Lambda Calculus
 
Strinng Classes in c++
Strinng Classes in c++Strinng Classes in c++
Strinng Classes in c++
 

Ähnlich wie List-based Monadic Computations for Dynamic Languages

High-Performance Haskell
High-Performance HaskellHigh-Performance Haskell
High-Performance HaskellJohan Tibell
 
Composition birds-and-recursion
Composition birds-and-recursionComposition birds-and-recursion
Composition birds-and-recursionDavid Atchley
 
Functional Programming Concepts for Imperative Programmers
Functional Programming Concepts for Imperative ProgrammersFunctional Programming Concepts for Imperative Programmers
Functional Programming Concepts for Imperative ProgrammersChris
 
TI1220 Lecture 6: First-class Functions
TI1220 Lecture 6: First-class FunctionsTI1220 Lecture 6: First-class Functions
TI1220 Lecture 6: First-class FunctionsEelco Visser
 
Functional Programming by Examples using Haskell
Functional Programming by Examples using HaskellFunctional Programming by Examples using Haskell
Functional Programming by Examples using Haskellgoncharenko
 
Programming with effects - Graham Hutton
Programming with effects - Graham HuttonProgramming with effects - Graham Hutton
Programming with effects - Graham HuttonWen-Shih Chao
 
Programming in Scala - Lecture Four
Programming in Scala - Lecture FourProgramming in Scala - Lecture Four
Programming in Scala - Lecture FourAngelo Corsaro
 
Functional Programming in JavaScript
Functional Programming in JavaScriptFunctional Programming in JavaScript
Functional Programming in JavaScriptWill Livengood
 
Loops and functions in r
Loops and functions in rLoops and functions in r
Loops and functions in rmanikanta361
 
A brief introduction to apply functions
A brief introduction to apply functionsA brief introduction to apply functions
A brief introduction to apply functionsNIKET CHAURASIA
 
Functional programming ii
Functional programming iiFunctional programming ii
Functional programming iiPrashant Kalkar
 

Ähnlich wie List-based Monadic Computations for Dynamic Languages (20)

High-Performance Haskell
High-Performance HaskellHigh-Performance Haskell
High-Performance Haskell
 
Composition birds-and-recursion
Composition birds-and-recursionComposition birds-and-recursion
Composition birds-and-recursion
 
Functional Programming Concepts for Imperative Programmers
Functional Programming Concepts for Imperative ProgrammersFunctional Programming Concepts for Imperative Programmers
Functional Programming Concepts for Imperative Programmers
 
TI1220 Lecture 6: First-class Functions
TI1220 Lecture 6: First-class FunctionsTI1220 Lecture 6: First-class Functions
TI1220 Lecture 6: First-class Functions
 
Functional Programming by Examples using Haskell
Functional Programming by Examples using HaskellFunctional Programming by Examples using Haskell
Functional Programming by Examples using Haskell
 
Lecture 3
Lecture 3Lecture 3
Lecture 3
 
Programming with effects - Graham Hutton
Programming with effects - Graham HuttonProgramming with effects - Graham Hutton
Programming with effects - Graham Hutton
 
Programming in Scala - Lecture Four
Programming in Scala - Lecture FourProgramming in Scala - Lecture Four
Programming in Scala - Lecture Four
 
Functional Programming in JavaScript
Functional Programming in JavaScriptFunctional Programming in JavaScript
Functional Programming in JavaScript
 
Tutorial2
Tutorial2Tutorial2
Tutorial2
 
Functional object
Functional objectFunctional object
Functional object
 
Loops and functions in r
Loops and functions in rLoops and functions in r
Loops and functions in r
 
Frp2016 3
Frp2016 3Frp2016 3
Frp2016 3
 
MatlabIntro.ppt
MatlabIntro.pptMatlabIntro.ppt
MatlabIntro.ppt
 
Matlab intro
Matlab introMatlab intro
Matlab intro
 
MatlabIntro.ppt
MatlabIntro.pptMatlabIntro.ppt
MatlabIntro.ppt
 
MatlabIntro.ppt
MatlabIntro.pptMatlabIntro.ppt
MatlabIntro.ppt
 
MatlabIntro.ppt
MatlabIntro.pptMatlabIntro.ppt
MatlabIntro.ppt
 
A brief introduction to apply functions
A brief introduction to apply functionsA brief introduction to apply functions
A brief introduction to apply functions
 
Functional programming ii
Functional programming iiFunctional programming ii
Functional programming ii
 

Mehr von Wim Vanderbauwhede

Haku, a toy functional language based on literary Japanese
Haku, a toy functional language  based on literary JapaneseHaku, a toy functional language  based on literary Japanese
Haku, a toy functional language based on literary JapaneseWim Vanderbauwhede
 
A few thoughts on work life-balance
A few thoughts on work life-balanceA few thoughts on work life-balance
A few thoughts on work life-balanceWim Vanderbauwhede
 
It was finally Christmas: Perl 6 is here!
It was finally Christmas: Perl 6 is here!It was finally Christmas: Perl 6 is here!
It was finally Christmas: Perl 6 is here!Wim Vanderbauwhede
 
FPGAs as Components in Heterogeneous HPC Systems (paraFPGA 2015 keynote)
FPGAs as Components in Heterogeneous HPC Systems (paraFPGA 2015 keynote) FPGAs as Components in Heterogeneous HPC Systems (paraFPGA 2015 keynote)
FPGAs as Components in Heterogeneous HPC Systems (paraFPGA 2015 keynote) Wim Vanderbauwhede
 
Why I do Computing Science Research
Why I do Computing Science ResearchWhy I do Computing Science Research
Why I do Computing Science ResearchWim Vanderbauwhede
 
On the Capability and Achievable Performance of FPGAs for HPC Applications
On the Capability and Achievable Performance of FPGAs for HPC ApplicationsOn the Capability and Achievable Performance of FPGAs for HPC Applications
On the Capability and Achievable Performance of FPGAs for HPC ApplicationsWim Vanderbauwhede
 

Mehr von Wim Vanderbauwhede (8)

Haku, a toy functional language based on literary Japanese
Haku, a toy functional language  based on literary JapaneseHaku, a toy functional language  based on literary Japanese
Haku, a toy functional language based on literary Japanese
 
Frugal computing
Frugal computingFrugal computing
Frugal computing
 
A few thoughts on work life-balance
A few thoughts on work life-balanceA few thoughts on work life-balance
A few thoughts on work life-balance
 
Greener Search
Greener SearchGreener Search
Greener Search
 
It was finally Christmas: Perl 6 is here!
It was finally Christmas: Perl 6 is here!It was finally Christmas: Perl 6 is here!
It was finally Christmas: Perl 6 is here!
 
FPGAs as Components in Heterogeneous HPC Systems (paraFPGA 2015 keynote)
FPGAs as Components in Heterogeneous HPC Systems (paraFPGA 2015 keynote) FPGAs as Components in Heterogeneous HPC Systems (paraFPGA 2015 keynote)
FPGAs as Components in Heterogeneous HPC Systems (paraFPGA 2015 keynote)
 
Why I do Computing Science Research
Why I do Computing Science ResearchWhy I do Computing Science Research
Why I do Computing Science Research
 
On the Capability and Achievable Performance of FPGAs for HPC Applications
On the Capability and Achievable Performance of FPGAs for HPC ApplicationsOn the Capability and Achievable Performance of FPGAs for HPC Applications
On the Capability and Achievable Performance of FPGAs for HPC Applications
 

Kürzlich hochgeladen

Your Vision, Our Expertise: TECUNIQUE's Tailored Software Teams
Your Vision, Our Expertise: TECUNIQUE's Tailored Software TeamsYour Vision, Our Expertise: TECUNIQUE's Tailored Software Teams
Your Vision, Our Expertise: TECUNIQUE's Tailored Software TeamsJaydeep Chhasatia
 
Big Data Bellevue Meetup | Enhancing Python Data Loading in the Cloud for AI/ML
Big Data Bellevue Meetup | Enhancing Python Data Loading in the Cloud for AI/MLBig Data Bellevue Meetup | Enhancing Python Data Loading in the Cloud for AI/ML
Big Data Bellevue Meetup | Enhancing Python Data Loading in the Cloud for AI/MLAlluxio, Inc.
 
ARM Talk @ Rejekts - Will ARM be the new Mainstream in our Data Centers_.pdf
ARM Talk @ Rejekts - Will ARM be the new Mainstream in our Data Centers_.pdfARM Talk @ Rejekts - Will ARM be the new Mainstream in our Data Centers_.pdf
ARM Talk @ Rejekts - Will ARM be the new Mainstream in our Data Centers_.pdfTobias Schneck
 
online pdf editor software solutions.pdf
online pdf editor software solutions.pdfonline pdf editor software solutions.pdf
online pdf editor software solutions.pdfMeon Technology
 
AI Embracing Every Shade of Human Beauty
AI Embracing Every Shade of Human BeautyAI Embracing Every Shade of Human Beauty
AI Embracing Every Shade of Human BeautyRaymond Okyere-Forson
 
Cybersecurity Challenges with Generative AI - for Good and Bad
Cybersecurity Challenges with Generative AI - for Good and BadCybersecurity Challenges with Generative AI - for Good and Bad
Cybersecurity Challenges with Generative AI - for Good and BadIvo Andreev
 
Kubernetes go-live checklist for your microservices.pptx
Kubernetes go-live checklist for your microservices.pptxKubernetes go-live checklist for your microservices.pptx
Kubernetes go-live checklist for your microservices.pptxPrakarsh -
 
eAuditor Audits & Inspections - conduct field inspections
eAuditor Audits & Inspections - conduct field inspectionseAuditor Audits & Inspections - conduct field inspections
eAuditor Audits & Inspections - conduct field inspectionsNirav Modi
 
Generative AI for Cybersecurity - EC-Council
Generative AI for Cybersecurity - EC-CouncilGenerative AI for Cybersecurity - EC-Council
Generative AI for Cybersecurity - EC-CouncilVICTOR MAESTRE RAMIREZ
 
Deep Learning for Images with PyTorch - Datacamp
Deep Learning for Images with PyTorch - DatacampDeep Learning for Images with PyTorch - Datacamp
Deep Learning for Images with PyTorch - DatacampVICTOR MAESTRE RAMIREZ
 
Optimizing Business Potential: A Guide to Outsourcing Engineering Services in...
Optimizing Business Potential: A Guide to Outsourcing Engineering Services in...Optimizing Business Potential: A Guide to Outsourcing Engineering Services in...
Optimizing Business Potential: A Guide to Outsourcing Engineering Services in...Jaydeep Chhasatia
 
Introduction-to-Software-Development-Outsourcing.pptx
Introduction-to-Software-Development-Outsourcing.pptxIntroduction-to-Software-Development-Outsourcing.pptx
Introduction-to-Software-Development-Outsourcing.pptxIntelliSource Technologies
 
ERP For Electrical and Electronics manufecturing.pptx
ERP For Electrical and Electronics manufecturing.pptxERP For Electrical and Electronics manufecturing.pptx
ERP For Electrical and Electronics manufecturing.pptxAutus Cyber Tech
 
Leveraging DxSherpa's Generative AI Services to Unlock Human-Machine Harmony
Leveraging DxSherpa's Generative AI Services to Unlock Human-Machine HarmonyLeveraging DxSherpa's Generative AI Services to Unlock Human-Machine Harmony
Leveraging DxSherpa's Generative AI Services to Unlock Human-Machine Harmonyelliciumsolutionspun
 
JS-Experts - Cybersecurity for Generative AI
JS-Experts - Cybersecurity for Generative AIJS-Experts - Cybersecurity for Generative AI
JS-Experts - Cybersecurity for Generative AIIvo Andreev
 
20240330_고급진 코드를 위한 exception 다루기
20240330_고급진 코드를 위한 exception 다루기20240330_고급진 코드를 위한 exception 다루기
20240330_고급진 코드를 위한 exception 다루기Chiwon Song
 
Mastering Kubernetes - Basics and Advanced Concepts using Example Project
Mastering Kubernetes - Basics and Advanced Concepts using Example ProjectMastering Kubernetes - Basics and Advanced Concepts using Example Project
Mastering Kubernetes - Basics and Advanced Concepts using Example Projectwajrcs
 
OpenChain Webinar: Universal CVSS Calculator
OpenChain Webinar: Universal CVSS CalculatorOpenChain Webinar: Universal CVSS Calculator
OpenChain Webinar: Universal CVSS CalculatorShane Coughlan
 
Top Software Development Trends in 2024
Top Software Development Trends in  2024Top Software Development Trends in  2024
Top Software Development Trends in 2024Mind IT Systems
 

Kürzlich hochgeladen (20)

Your Vision, Our Expertise: TECUNIQUE's Tailored Software Teams
Your Vision, Our Expertise: TECUNIQUE's Tailored Software TeamsYour Vision, Our Expertise: TECUNIQUE's Tailored Software Teams
Your Vision, Our Expertise: TECUNIQUE's Tailored Software Teams
 
Big Data Bellevue Meetup | Enhancing Python Data Loading in the Cloud for AI/ML
Big Data Bellevue Meetup | Enhancing Python Data Loading in the Cloud for AI/MLBig Data Bellevue Meetup | Enhancing Python Data Loading in the Cloud for AI/ML
Big Data Bellevue Meetup | Enhancing Python Data Loading in the Cloud for AI/ML
 
ARM Talk @ Rejekts - Will ARM be the new Mainstream in our Data Centers_.pdf
ARM Talk @ Rejekts - Will ARM be the new Mainstream in our Data Centers_.pdfARM Talk @ Rejekts - Will ARM be the new Mainstream in our Data Centers_.pdf
ARM Talk @ Rejekts - Will ARM be the new Mainstream in our Data Centers_.pdf
 
online pdf editor software solutions.pdf
online pdf editor software solutions.pdfonline pdf editor software solutions.pdf
online pdf editor software solutions.pdf
 
AI Embracing Every Shade of Human Beauty
AI Embracing Every Shade of Human BeautyAI Embracing Every Shade of Human Beauty
AI Embracing Every Shade of Human Beauty
 
Cybersecurity Challenges with Generative AI - for Good and Bad
Cybersecurity Challenges with Generative AI - for Good and BadCybersecurity Challenges with Generative AI - for Good and Bad
Cybersecurity Challenges with Generative AI - for Good and Bad
 
Kubernetes go-live checklist for your microservices.pptx
Kubernetes go-live checklist for your microservices.pptxKubernetes go-live checklist for your microservices.pptx
Kubernetes go-live checklist for your microservices.pptx
 
eAuditor Audits & Inspections - conduct field inspections
eAuditor Audits & Inspections - conduct field inspectionseAuditor Audits & Inspections - conduct field inspections
eAuditor Audits & Inspections - conduct field inspections
 
Generative AI for Cybersecurity - EC-Council
Generative AI for Cybersecurity - EC-CouncilGenerative AI for Cybersecurity - EC-Council
Generative AI for Cybersecurity - EC-Council
 
Deep Learning for Images with PyTorch - Datacamp
Deep Learning for Images with PyTorch - DatacampDeep Learning for Images with PyTorch - Datacamp
Deep Learning for Images with PyTorch - Datacamp
 
Optimizing Business Potential: A Guide to Outsourcing Engineering Services in...
Optimizing Business Potential: A Guide to Outsourcing Engineering Services in...Optimizing Business Potential: A Guide to Outsourcing Engineering Services in...
Optimizing Business Potential: A Guide to Outsourcing Engineering Services in...
 
Introduction-to-Software-Development-Outsourcing.pptx
Introduction-to-Software-Development-Outsourcing.pptxIntroduction-to-Software-Development-Outsourcing.pptx
Introduction-to-Software-Development-Outsourcing.pptx
 
ERP For Electrical and Electronics manufecturing.pptx
ERP For Electrical and Electronics manufecturing.pptxERP For Electrical and Electronics manufecturing.pptx
ERP For Electrical and Electronics manufecturing.pptx
 
Leveraging DxSherpa's Generative AI Services to Unlock Human-Machine Harmony
Leveraging DxSherpa's Generative AI Services to Unlock Human-Machine HarmonyLeveraging DxSherpa's Generative AI Services to Unlock Human-Machine Harmony
Leveraging DxSherpa's Generative AI Services to Unlock Human-Machine Harmony
 
JS-Experts - Cybersecurity for Generative AI
JS-Experts - Cybersecurity for Generative AIJS-Experts - Cybersecurity for Generative AI
JS-Experts - Cybersecurity for Generative AI
 
20240330_고급진 코드를 위한 exception 다루기
20240330_고급진 코드를 위한 exception 다루기20240330_고급진 코드를 위한 exception 다루기
20240330_고급진 코드를 위한 exception 다루기
 
Program with GUTs
Program with GUTsProgram with GUTs
Program with GUTs
 
Mastering Kubernetes - Basics and Advanced Concepts using Example Project
Mastering Kubernetes - Basics and Advanced Concepts using Example ProjectMastering Kubernetes - Basics and Advanced Concepts using Example Project
Mastering Kubernetes - Basics and Advanced Concepts using Example Project
 
OpenChain Webinar: Universal CVSS Calculator
OpenChain Webinar: Universal CVSS CalculatorOpenChain Webinar: Universal CVSS Calculator
OpenChain Webinar: Universal CVSS Calculator
 
Top Software Development Trends in 2024
Top Software Development Trends in  2024Top Software Development Trends in  2024
Top Software Development Trends in 2024
 

List-based Monadic Computations for Dynamic Languages

  • 1. List-based Monadic Computations for Dynamically Typed Languages Wim Vanderbauwhede School of Computing Science, University of Glasgow, UK
  • 2. Overview Program Composition in Dynamically Typed Languages Objects Monads Defining Karma Karmic Types Combining Functions using Functions The Rules Designing Karma Syntactic Sugar fold and chain Karma Needs Dynamic Typing Karmic Computations By Example Maybe State Parsing Conclusion
  • 3. Dynamically Typed Languages size proportional to √ #projects on GitHub
  • 4. Perl ... Notorious $_=’while(read+STDIN,$_,2048){$a=29;$b=73; $c=142;$t=255;@t=map{$_%16or$t^=$c^=($m= (11,10,116,100,11,122,20,100)[$_/16%8])&110; $t^=(72,@z=(64,72,$a^=12*($_%16 -2?0:$m&17)), $b^=$_%64?12:0,@z)[$_%8]}(16..271); if((@a=unx"C*",$_)[20]&48){$h =5;$_=unxb24, join"",@b=map{xB8,unxb8,chr($_^$a[--$h+84])} @ARGV;s/...$/1$&/;$ d=unxV,xb25,$_;$e=256| (ord$b[4])<‌<9|ord$b[3];$d=$d>‌>8^($f=$t& ($d>‌>12^$d>‌>4^$d^$d/8))<‌<17,$e=$e>‌>8^($t &($g=($q=$e>‌>14&7^$e)^$q*8^$q<‌<6))<‌<9,$_= $t[$_]^(($h>‌>=8)+=$f+(~$g&$t))for @a[128..$#a]}print+x"C*",@a}’;s/x/pack+/g; eval; But I like Perl (*ducks*)
  • 5. Program Composition Most Dynamic Languages use an OOP approach to structure/compose programs But what if you don’t like object orientation? Or what if it is simply not the best approach? An alternative approach to program composition: Functional Languages use composition of higher-order functions In particular, Haskell uses monads ...
  • 6. Haskell ... Most empathically not dynamically typed ... Makes easy things hard ... But I like Haskell (*ducks*)
  • 7. Monads a reputation of being esoteric hard to understand the province of academic languages (unknown poet, 21st century) Monas Hieroglyphica, (“The Hieroglyphic Monad”), John Dee, Antwerp 1564
  • 8. Monads in Dynamic Languages Have been done many times for many languages https://en.wikipedia.org/wiki/Monad(functional_programming)#Monads_in_other_languages But have not found widespread adoption So ...
  • 9. The Claim ... are monads of practical use in day-to-day programming? Yes! Only we won’t call them monads ...
  • 10. Karmic Computations Karma is a Sanskrit word meaning action, work or deed. A different approach from the many existing implementations of monads in dynamic languages. Based on types, lambda functions and higher-order functions.
  • 11. Types and Notation Haskell-style syntax for types: A function g from a type a to a type b: g :: a → b A function s with two arguments and the result of type a: s :: a → a → a A function f from a type a to a type m b, i.e. a type m parametrised on a type b: f :: a → m b A function h which takes as arguments two functions of type a → b and b → c and returns a function of type a → m b: h :: (a → b) → (b → c) → (a → m b)
  • 12. Lambda Functions Also knows as anonymous subroutines, i.e. functions without a name. They are expressions that can be assigned to variables. Language Lambda Syntax Haskell x y -> f x y LiveScript (x,y) -> f x,y Perl sub ($x,$y) { f $x,$y } Python lambda x,y : f(x,y) Ruby -> (x,y) { f x,y }
  • 13. Higher-Order Functions Functions that take other functions as arguments and/or return functions as results Available in your favourite dynamically type language: Ruby, Python, LiveScript, JavaScript, ...
  • 14. What is Karma? A karmic computation consists of: a given type m a; the higher-order functions bind and wrap and three rules governing those functions.
  • 15. Karmic Types A karmic type can be viewed as a “wrapper” around another type. It does not have to have a particular structure, e.g. it can be an object, or a list, or a map, or a function. The key point is that the “karmic” type contains more information than the “bare” type. We will write m a as the karmic type constructor, regardless of the structure of the type. For example, in Ruby the following function f has a type f :: a → m b, if g has type g :: a → b: def f(x) m.new( g(x) ) end
  • 16. Combining Functions using Functions The purpose of the karmic computation is to combine functions that operates on karmic types. The bind function composes values of type m a with functions from a to m b: bind :: m a → (a → m b) → m b The wrap function takes a given type a and returns m a: wrap :: a → m a With these two functions we can create expressions that consists of combinations of functions.
  • 17. The Rules Three rules govern bind and wrap to ensure that the composition is well-behaved: 1. bind (wrap x) f ≡ f x 2. bind m wrap ≡ m 3. bind (bind m f) g ≡ bind m (x -> bind (f x) g) For reference, the rules in Ruby syntax: 1. bind(wrap(x),f) = f.call(x) 2. bind(m,wrap) = m 3. bind(bind(m,f),g) = bind(m,->(c){bind(f.call(x),g))})
  • 18. Syntactic Sugar for Monads In Haskell: No sugar: ex x = x -> (bind (g x) (y -> (f (bind y (z -> wrap z))))) Operator sugar: ex x = g x >‌>= y -> f y >‌>= z -> wrap z Do-notation sugar: ex x = do y <- g x z <- f y wrap z
  • 19. Syntactic Sugar for Karma Our approach: Use lists to combine computations For example: [ word, maybe parens choice natural, [ symbol ’kind’, symbol ’=’, natural ] ]
  • 20. Designing Karma Grouping items in lists provides a natural sequencing mechanism, and allows easy nesting. In most dynamic languages, lists us the [...,...] syntax, it’s portable and non-obtrusive. We introduce a chain function to chain computations together. Pass chain a list of functions and it will combine these functions into a single expression.
  • 21. Preliminary: fold To define chain in terms of bind and wrap, we need the left fold function (foldl). foldl performs a left-to-right reduction of a list via iterative application of a function to an initial value: foldl :: (a → b → a) → a → [b] → [a] A possible implementation e.g. in Perl would be sub foldl ($f, $acc, @lst) { for my $elt (@lst) { $acc=$f->($acc,$elt) } return $acc }
  • 22. Defining chain We can now define chain as sub chain(@fs) { sub($x) { foldl bind, wrap $x, @fs } } Or in Haskell syntax chain fs = x -> foldl (>‌>=) (wrap x) fs
  • 23. Karma Needs Dynamic Typing The above definition of chain is valid in Haskell, but only if the type signature is chain :: [(a → m a)] → (a → m a) But the type of bind is bind :: m a → (a → m b) → m b the karmic type m b returned by bind does not have to be the same as the karmic type argument m a. every function in the list passed to chain should be allowed to have a different type! This is not allowed in a statically typed language like Haskell, so only the restricted case of functions of type a → m a can be used. However, in a dynamically typed language there is no such restriction, so we can generalise the type signature: chain :: [(ai−1 → m ai )] → (a0 → m aN ) ∀i ∈ 1 .. N
  • 24. Demonstrating Karma Combining computations that can fail Stateful computation Parser combinators
  • 25. Combining Fallible Computations (1) Expressing failure A Maybe class class Maybe attr_accessor :val,:ok def initialize(value,status) @val=value @ok=status # true or false end end For convenience: a fail instance fail = Maybe.new(nil,false) Assume f, g, h :: a → Maybe b
  • 26. Combining Fallible Computations (2) Without karma v1 = f(x) if (v1.ok) v2=g(v1.val) if (v2.ok) v3 = h(v2.val) if (v3.ok) v3.val else fail end else fail end else fail end With karma: comp = chain [ ->(x) {f x}, ->(y) {g y}, ->(z) {h z} ] v1=comp.call x If f, g and h are defined as lambda functions: comp = chain [ f,g,h ] v1=comp.call x
  • 27. bind and wrap for Maybe For the Maybe karmic type, bind is defined as: def bind(x,f) if x.ok f.call(x) else fail end end and wrap as: def wrap(x) Maybe.new(x,true) end
  • 28. Stateful Computation Using karma to perform stateful computations without actual mutable state. Example in LiveScript, because LiveScript has the option to force immutable variables. There is a growing interest in the use of immutable state in other dynamic languages, in particular for web programming, because immutable state greatly simplifies concurrent programming and improves testability of code.
  • 29. State Concept and API We simulate state by combining functions that transform the state, and applying the resulting function to an initial state (approach borrowed from Haskell’s Control.State). A small API to allow the functions in the list to access a shared state: get = -> ( (s) -> [s, s] ) put = (s) -> ( -> [[],s]) The get function reads the state, the put function writes an updated state. Both return lambda functions. A top-level function to apply the stateful computation to an initial state: res = evalState comp, init where evalState = (comp,init) -> comp!(init)
  • 30. Trivial Interpreter: Instructions We want to interpret a list of instructions of type type Instr = (String, ([Int] → Int, [a])) For example instrs = [ ["v1",[set,[1]]], ["v2",[add,["v1",2]]], ["v2",[mul,["v2","v2"]]], ["v1",[add,["v1","v2"]]], ["v3",[mul,["v1","v2"]]] ] where add, mul and set are functions of type [Int] → Int The interpreter should return the final values for all variables. The interpreter will need a context for the variables, we use a simple map { String : Int } to store the values for each variable. This constitutes the state of the computation.
  • 31. Trivial Interpreter: the Karmic Function We write a function interpret_instr_st :: Instr → [[a], Ctxt]: interpret_instr_st = (instr) -> chain( [ get, (ctxt) -> [v,res] = interpret_instr(instr, ctxt) put (insert v, res, ctxt) ] ) interpret_instr_st gets the context from the state, uses it to compute the instruction, updates the context using the insert function and puts the context back in the state.
  • 32. Trivial Interpreter: the Stateless Function Using Ctxt as the type of the context, the type of interpret_instr is interpret_instr :: Instr → Ctxt → (String, Int) and the implementation is straightforward: interpret_instr = (instr, ctxt) -> [v,rhs] = instr # unpacking [op,args] = rhs # unpacking vals = map (‘get_val‘ ctxt), args [v, op vals] get_val looks up the value of a variable in the context; it is backticked into an operator here to allow partial application.
  • 33. bind and wrap for State For the State karmic type, bind is defined as: bind = (f,g) -> (st) -> [x,st_] = f st (g x) st_ and wrap as wrap = (x) -> ( (s) -> [x,s] )
  • 34. modify: Modifying the State The pattern of calling get to get the state, then computing using the state and then updating the state using put is very common. So we combine it in a function called modify: modify = (f) -> chain( [ get, (s) -> put( f(s)) ] ) Using modify we can rewrite interpret_instr_st as interpret_instr_st = (instr) -> modify (ctxt) -> [v,res] = interpret_instr(instr, ctxt) insert v, res, ctxt
  • 35. mapM: a Dynamic chain We could in principle use chain to write a list of computations on each instruction: chain [ interpret_instr_st instrs[0], interpret_instr_st instrs[1], interpret_instr_st instrs[2], ... ] but clearly this is not practical as it is entirely static. Instead, we use a monadic variant of the map function, mapM: mapM :: Monad m ⇒ (a → m b) → [a] → m [b] mapM applies the computations to the list of instructions (using map) and then folds the resulting list using bind. With mapM, we can simply write : res = evalState (mapM interpret_instr_st, instrs), {}
  • 36. Fortran ... I like Fortran (*ducks*)
  • 37. Parser Combinators Or more precisely, I needed to parse Fortran for source transformations. So I needed a Fortran parser ... ... in Perl (for reasons). So I created a Perl version of Haskell’s Parsec parser combinator library ... ... using Karma.
  • 38. Parser Combinator Basics Each basic parser returns a function which operates on a string and returns a result. Parser :: String → Result The result is a tuple containing the status, the remaining string and the substring(s) matched by the parser. type Result = (Status, String, [Match]) To create a complete parser, the basic parsers are combined using combinators. A combinator takes a list of parsers and returns a parsing function similar to the basic parsers: combinator :: [Parser] → Parser
  • 39. Karmic Parser Combinators For example, a parser for a Fortran-95 type declaration: my $parser = chain [ identifier, maybe parens choice natural, [ symbol ’kind’, symbol ’=’, natural ] ]; In dynamic languages the actual chain combinator can be implicit, i.e. a bare list will result in calling of chain on the list. For statically typed languages this is of course not possible as all elements in a list must have the same type.
  • 40. bind and wrap for Parser For the Parser karmic type, bind is defined as (Perl): sub bind($t, $p) { my ($st_,$r_,$ms_) = @{$t}; if ($st_) { ($st,$r,$ms) = $p->($r_); if ($st) { (1,$r,[@{$ms_},@{$ms}]); } else { (0,$r,undef) } } else { (0,$r_,undef) } and wrap as: sub wrap($str){ (1,$str,undef) }
  • 41. bind and wrap for Parser For the Parser karmic type, bind is defined as (LiveScript): bind = (t, p) -> [st_,r_,ms_] = t if st_ then [st,r,ms] = p r_ if st then [1,r,ms_ ++ ms] else [0,r,void] else [0,r_,void] and wrap as: wrap = (str) -> [1,str,void]
  • 42. Final Example (1) Parsers can combine several other parsers, and can be labeled: my $f95_arg_decl_parser = chain [ whiteSpace, {TypeTup => $type_parser}, maybe [ comma, $dim_parser ], maybe [ comma, $intent_parser ], symbol ’::’, {Vars => sepBy ’,’,word} ];
  • 43. Final Example (2) We can run this parser e.g. my $var_decl = "real(8), dimension(0:ip,-1:jp+1,kp) :: u,v" my $res = run $f95_arg_decl_parser, $var_decl; This results in the parse tree: { ’TypeTup’ => { ’Type’ => ’real’, ’Kind’ => ’8’ }, ’Dim’ => [’0:ip’,’-1:jp+1’,’kp’], ’Vars’ => [’u’,’v’] }
  • 44. Parser Combinators Library The Perl and LiveScript versions are on GitHub: https: //github.com/wimvanderbauwhede/Perl-Parser-Combinators https: //github.com/wimvanderbauwhede/parser-combinators-ls The Perl library is actually used in a Fortran source compiler https://github.com/wimvanderbauwhede/RefactorF4Acc
  • 45. Conclusion We have presented a design for list-based monadic computations, which we call karmic computations. Karmic computations are equivalent to monadic computations in statically typed languages such as Haskell, but rely essentially on dynamic typing through the use of heterogeneous lists. The proposed list-based syntax is easy to use, results in concise, elegant and very readable code, and is largely language-independent. The proposed approach can be applied very widely, especially as a design technique for libraries.