Executable
Relational Specifications of Polymorphic Type Systems using Logic Programming
Ki Yung Ahn
Talk on 2016-01-08 hosted by PLASSE
at ERICA Campus, Hanyang University,
Ansan, Gyeonggi-do, Republic of Korea
best viewed using Chrome at https://slides.com/kyagrd/tiper-erica/
Outline
-
Motivation and Background
- Relational Specification
- Executable Specification
- Logic Programming
-
Type System Specification using Prolog
- Simply-Typed Lambda Calculus (STLC)
- Hindley--Milner Type System (HM)
- HM + Type-Constructor Poly. + Kind Poly.
-
TIPER Project
Motivation & Background
- Problems with Algorithmic/Functional description
- Relational Specification
- Executable Specification
- Logic Programming
Type System on paper
Type System implementation (algorithmic/functional description)
typeCheck :: (Ctx, Exp, Type) -> Bool
typeCheck(gamma, Var x, a) = (x,a) `elem` Gamma
typeCheck(gamma, App e1 e2, b) = case typeInfer(gamma,e1) of
Arr a b -> typeCheck(gamma,e2,a)
_ -> False
typeCheck(gamma, Abs x e, Arr a b) = typeCheck((x,a):gamma, e, b)
typeInfer :: (Ctx, Exp) -> Maybe Type
typeInfer(gamma, Var x) = lookup x gamma
typeInfer(gamma, App e1 e2) = case typeInfer(gamma,e1) of
Arr a b | typeCheck(gamma,e2,a) -> Just b
_ -> Nothing
typeInfer(gamma, Abs x e) = ... -- actually need some more magic here
(Var)
(Abs)
(App)
Type System on paper
Problems with Algorithmic/Functional description
(Var)
(Abs)
(App)
- Gap from original description on paper
- more details of data flow and computation steps - Duplication inevitable to support
both type checking and type inference
Type System on paper
Relational Specification
(Var)
(Abs)
(App)
- Reduces the gap from description on paper
- Single Source of Truth (Don't Repeat Yourself )
- Choice of tools for relational specification
- Inductive Definitions in Interactive Theorem Provers
- Logic Programming
- Constraint Solvers / Automated Theorem Provers
Executable Specification
Specifications for Prototyping / Development
of type system implementations should be
- executable on a machine (not just def. for proofs)
- able to inspect intermediate results
for debugging / error handling - Among the choices of tools
-Inductive Definitions in Interactive Theorem Provers
- Logic Programming
-Constraint Solvers / Automated Theorem Provers
Logic Programming
- Executable Relational Specification
- Semantics exist for LP languages
- incrementally builds up a substitution
- can inspect intermediate results (not a black box)
- Supports unification as a primitive operation
- unification is a basic building block
for type inference algorithms
- unification is a basic building block
Type System Specification
using Prolog
- Simply-Typed Lambda Calculus (STLC)
- Hindley--Milner Type System (HM)
- HM + Type Constructor Poly. + Kind Poly.
- Limitations of Prolog as a spec. lang. for type systems
Simply-Typed Lambda Calculus
:- set_prolog_flag(occurs_check,true).
:- op(500,yfx,$).
type(C,var(X), T) :- first(X:T,C).
type(C,lam(X,E),A -> B) :- type([X:A|C], E, B).
type(C,E1 $ E2, B) :- type(C,E1,A->B), type(C,E2,A).
first(K:V,[K1:V1|Xs]) :- K = K1, V = V1.
first(K:V,[K1:V1|Xs]) :- K\==K1, first(K:V, Xs).
Simply-Typed Lambda Calculus
:- set_prolog_flag(occurs_check,true).
:- op(500,yfx,$).
type(C,var(X), T) :- first(X:T,C).
type(C,lam(X,E),A -> B) :- type([X:A|C], E, B).
type(C,E1 $ E2, B) :- type(C,E1,A->B), type(C,E2,A).
first(K:V,[K1:V1|Xs]) :- K = K1, V = V1.
first(K:V,[K1:V1|Xs]) :- K\==K1, first(K:V, Xs).
?- type([], lam(x,var(x)), A->A). % type checking true . ?- type([], lam(x,var(x)), T). % type inference T = (_G123->_G123) . ?- type([], E, A->A). % type inhabitation E = lam(_G234,var(_G234)) .
HM = STLC + Type Poly.
:- set_prolog_flag(occurs_check,true).
:- op(500,yfx,$).
type(C,var(X), T1) :- first(X:T,C), instantiate(T,T1).
type(C,lam(X,E), A -> B) :- type([X:mono(A)|C],E,B).
type(C,E1 $ E2, B ) :- type(C,E1,A -> B), type(C,E2,A).
type(C,let(X=E0,E1), T ) :- type(C,E0,A), type([X:poly(C,A)|C],E1,T).
first(K:V,[K1:V1|Xs]) :- K = K1, V=V1.
first(K:V,[K1:V1|Xs]) :- K\==K1, first(K:V, Xs).
instantiate(mono(T),T).
instantiate(poly(C,T),T1) :- copy_term(t(C,T),t(C,T1)).
- Type binding X:A in STLC corresponds to X:mono(A) in HM
- poly(C,A) is a type scheme of A closed under the context C
- Instationation implemented by Prolog's built-in copy_term
HM = STLC + Type Poly.
:- set_prolog_flag(occurs_check,true).
:- op(500,yfx,$).
type(C,var(X), T1) :- first(X:T,C), instantiate(T,T1).
type(C,lam(X,E), A -> B) :- type([X:mono(A)|C],E,B).
type(C,E1 $ E2, B ) :- type(C,E1,A -> B), type(C,E2,A).
type(C,let(X=E0,E1), T ) :- type(C,E0,A), type([X:poly(C,A)|C],E1,T).
first(K:V,[K1:V1|Xs]) :- K = K1, V=V1.
first(K:V,[K1:V1|Xs]) :- K\==K1, first(K:V, Xs).
instantiate(mono(T),T).
instantiate(poly(C,T),T1) :- copy_term(t(C,T),t(C,T1)).
?- copy_term(t([],A->B), t([],T)). T = (_G993->_G994). % fresh vars: _G993 for A, _G994 for B ?- copy_term(t([x:A],A->B), t([x:A],T)). T = (A->_G1024). % fresh vars: _G1024 for B only
Type Constructor Polymorphism
(a.k.a. higher-kinded polymorphism)
-- Tree :: (* -> *) -> * -> *
data Tree c a
= Leaf a -- Leaf :: Tree c a
| Node (c (Tree c a)) -- Node :: (c(Tree c a)) -> Tree c a
type BinTree a = Tree Pair a -- two children on each node
type Pair t = (t,t)
type RoseTree a = Tree List a -- varying number of children
type List a = [a]
- HM only supports type polymorphism such as (1) but
not higher-kinded poly. such as (2) supported in Haskell
HM + TyCon Poly.
:- set_prolog_flag(occurs_check,true).
:- op(500,yfx,$).
kind(KC, var(X), K) :- first(X:T,KC).
kind(KC, F $ G, K2) :- kind(KC,F,K1->K2), kind(KC,G,K1).
kind(KC, A -> B, o) :- kind(KC,A,o), kind(KC,B,o).
type(KC,C,var(X), T1) :- first(X:T,C), instantiate(T,T1).
type(KC,C,lam(X,E), A -> B) :- type([X:mono(A)|C],E,B), kind(KC,A->B,o).
type(KC,C,E1 $ E2, B ) :- type(KC,C,E1,A -> B), type(KC,C,E2,A).
type(KC,C,let(X=E0,E1), T ) :- type(KC,C,E0,A), type(KC,[X:poly(C,A)|C],E1,T).
first(K:V,[K1:V1|Xs]) :- K = K1, V=V1.
first(K:V,[K1:V1|Xs]) :- K\==K1, first(K:V, Xs).
instantiate(mono(T),T).
instantiate(poly(C,T),T1) :- copy_term(t(C,T),t(C,T1)).
?- type(KC,[],lam(x,var(x)),T).
KC = [_G1578:_G1581|_G1584],
T = (var(_G1578)->var(_G1578)) .
% OK, got the most general type at first :)
?- type(KC,[],lam(x,lam(y,var(x))),T). KC = [_G1598:_G1601|_G1604], T = (var(_G1598)->var(_G1598)->var(_G1598)) ; KC = [_G1598:_G1601, _G1598:_G1612|_G1618], T = (var(_G1598)->var(_G1598)->var(_G1598)) ; KC = [_G1598:_G1601, _G1598:_G1612|_G1618], T = (var(_G1598)->var(_G1598)->var(_G1598)) ; KC = [_G1598:_G1601, _G1609:_G1612|_G1618], T = (var(_G1609)->var(_G1598)->var(_G1609))
% Well, the most general type in 4th solution :(
(a specification which kind of works but not really ...)
It gets even more unpleasant for HM + TyCon Poly + Kind Poly
Workaround for extensions of HM
- The Problem happens when
- Calling the kind goals invoked from the type goals
- A Workaround
- Delay kind goals until type goals are resolved
- we used Definite Clause Grammar (DCG) to collect kind goals during type inference to call them later
- For further details see
Ki Yung Ahn and Andrea Vezzosi. Executable Relational Specifications of Polymorphic Type Systems using Prolog, to appear in FLOPS 2016
- Prolog has features to exploit for workarounds but it is not ideal as a specification language for type systems
Type
Inference
Prototyping
Engines from
Relational Specifications of
Type Systems
Project Plan & Progress
What is TIPER?
Lex/Yacc : Parsers
TIPER : Type Systems
the missing automation tool
in langauge frontend construction
Does the World need TIPER?
YES! YES! YES!
Lack of automated tools for type systems
High development cost to adopt innovations from type theory & PL research
Inflexible and Verbose static type systems in mainstream langauges
Static Types are
considered harmful and
Dynamic Languages rule!
Oops, too painful to refactor/API-update
without static types
Okay, let's add static types
Flow type checker for JavaScript, TypeScript, mypy, Typed Clojure, Typed Lua, ... ..., and all those fancy projects on gradual typing
Plans for TIPER
- Project homepage
- Features to support
- Polymorphisms over Type / Type Constructor / Kind
- Extensible Records with Row Polymorphism
- First-Class Polymorphism and Modules
- Some FL features such as Type Classes and GADTs
- Some OOPL features such as subtyping
- Architecture
- Prolog-like syntax frontend
- parser integration & error handling
- portable backend of eDSL for LP (e.g. microKanren)
- Theories to investigate
- search strategies
- resolution semantics (coinductive)
Progress / Ongoing Work
- Exploring microKanren
- STLC, HM, HM+TC Poly, HM+TC Poly+Kind Poly are ported into an Haskell impl. of microKanren
- see https://github.com/kyagrd/ukanren for details
- Ingredients for Extensible Records
- (open-ended) set unification and map unification
- see my gh-repo ExtensibleRecordsWithSetMembLP
Executable Relational Specifications of Polymorphic Type Systems using Logic Programming
By 안기영 (Ahn, Ki Yung)
Executable Relational Specifications of Polymorphic Type Systems using Logic Programming
A declarative and machine executable specification of the Hindley–Milner type system (HM) can be formulated using a logic programming language. Modern functional language implementations such as the GHC supports more advanced polymorphism beyond HM. We progressively extended the HM specification to include more features using Prolog. We will contemplate on the lessons from this case study and introduce the plans and progress of the TIPER project to push this idea further towards a more practical language design/implementation tool.
- 2,560