Executable                             
Relational Specifications of
Polymorphic Type Systems
using Prolog

Ki Yung  Ahn
kyagrd@gmail.com

kyagrd.github.io

( this slide is available online at http://slides.com/kyagrd/TIPERdundee )

Andrea Vezzosi
vezzosi (AT) chalmers (DOT) se
http://www.cse.chalmers.se/~vezzosi/

Static Types are Cool

  • (Connections to all the cool theories, fun for research)
  • Efficiency
    • provide basic information at compile time for compilers to optimize code generation
  • Safety
    • using type-safety to guarantee that program does not reach bad state, before running the program
    • provides basic safeguard while refactoring :
      when you change the type of a function, you can follow all the type errors to track where that change is being propagated without looking through whole source or running regression tests

Static Types are Scarce

  • Apart from a few exeptions such as
    F# (MS), Swift (Apple),
    Scala, Elm, PureScript (community based)
    that tries to benefit from type system research
     
  • Most of the recent major buzz langauges we hear
    about are untyped, especially on web/cloud platforms.
    e.g., Javascript, Python, Ruby, ...

however, in the real world ...

Why on earth there are so many

dynamically-typed untyped languages

and still more piling up every new year?

Langugae Construction tool-stack avialble today

We need a TIPER

Language System Front-end Construction tool-stack

  • Lexer generator
     
  • Parser generator
     
  • TIPER :
    Type Inference Prototyping Engine
                                                  from Relational specifications
                                                      of type systems

Outline

  • Motivation -- need a TIPER
     
  • why Relational Specification
     
  • Prolog Specifications of HM
     
  • HM + type constructor poly + kind poly
     
  • Plans and Ideas on the TIPER project

Relational Specifcation

  • It is the way how we usually
    define type systems on paper
  • Specification for type checking and
    type inference without duplication
  • Can be queried multiple ways on
    logic programming systems

Relational Specifcation

  • Type Checking

     
  • Type Inference

     
  • Type Inhabitation
     
?- type([], lam(x,var(x)), A->A).
true .
?- type([], lam(x,var(x)), T).
T = (_G123->_G123) .
?- type([], E,             A->A).
E = lam(_G234,var(_G234)) .

A functional specification would need several different functions for each functionality, which will inevitably cause duplication in the specification.

HM

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,X $ Y,        B ) :- type(C,X,A -> B), type(C,Y,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(poly(C,T),T1) :- copy_term(t(C,T),t(C,T1)).
instantiate(mono(T),T).

Type Constructor Polymorphism

(a.k.a. higher-kinded polymorphism)

Haskell supports parametric polymorphism over type constructors as well as types, historically motivated to support the monad class, which classifies over type constructors, but useful for defining generic form of datatypes even when type classes aren't involved.

  -- 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 [] a    -- varying number of children

HM + TC Poly + Kind Poly

kind(KC,var(Z),K1) :- first(Z:K,KC), instantiate(K,K1).
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), inst_type(KC,T,T1).
type(KC,C,lam(X,E), A->B) :- type(KC,[X:mono(A)|C],E,B),
                             kind(KC,A->B,o).
type(KC,C,X $ Y,       B) :- type(KC,C,X,A->B), type(KC,C,Y,A).
type(KC,C,let(X=E0,E1),T) :- type(KC,C,E0,A),
                             type(KC,[X:poly(C,A)|C],E1,T).

% first and instantiate are same as before in HM

% inst_type does what instantiate does but adds more
% kind assertions for freshly instantiated variables

We wanted to write a specification like this.

Unfortunately, this does not work
because Prolog is not perfect ...

STLC + Kind

kind(KC,var(Z),K) :- first(Z:K,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),      T) :- first(X:T,C).
type(KC,C,lam(X,E), A->B) :- type(KC,[X:A|C],E,B),
                             kind(KC,A->B,o).
type(KC,C,X $ Y,       B) :- type(KC,C,X,A->B), type(KC,C,Y,A).
?- type([], [], lam(x,var(x)), A->A).
ERROR: Out of local stack 
  Exception: (1,456,711) kind([], _G8740235, (_G8740238->
_G8740232->_G8740226->_G8740220-> ... -> ...)) ? abort
% Execution Aborted

HM + TC Poly + Kind Poly

A twist to make type & kind inference work in Prolog
using Definite Clause Grammar (DCG) rues as
a neat syntax for a writer monad that collects
kind assertions as a side-output to be called upon later.

kind(KC,var(Z),K1) :- first(Z:K,KC), instantiate(K,K1).
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), inst_type(KC,T,T1).
type(KC,C,lam(X,E), A->B) --> type(KC,[X:mono(A)|C],E,B),
                              [ kind(KC,A->B,o) ]. % delayed goal
type(KC,C,X $ Y,       B) --> type(KC,C,X,A->B), type(KC,C,Y,A).
type(KC,C,let(X=E0,E1),T) --> type(KC,C,E0,A),
                              type(KC,[X:poly(C,A)|C],E1,T).

HM + TC Poly + Kind Poly

?- phrase(type([],[],lam(x,var(x)), Gs).
T = (_G2662->_G2662),
Gs = [kind([], (_G2662->_G2662), o)] .

  Freeze the Prolog variables in types into
  variables for kind inference and also
  extend the kinding context with them

 

?- kind([t1:mono(K1)], (var(t1)->var(t1)), o).
K1 = o

For further details (including pattern matching, Mendler-style recursion)
see

1st stage of
type inference

2nd stage of
kind inference

pre-processing for 2nd stage

Lessons

  • Executable Relational Specifications are writable in Prolog
    (pure) logic programming + extra logical operations
     
  • Hacking in Prolog is fun experiment but not ideal as a tool
    We need to design and implement TIPER
     
  • Essential extra-logical features
    - variable test/comparison
    - fresh variable/atom generation
     
  • Undesirable extra-logical features
    - use of meta-interpreter
    Used for certain purposes such as handling delayed goals, but it is too powerful, not intending to support in TIPER

Contributions

  • This work is a pioneering case study on the subject matter of how relational specification of type systems can be practically beneficial.
    - we were able to obtain reference implementation of
      advanced type systems directly from the specifications
     
  • There are surprisingly few executable specifications of polymorphic type systems in LP/ATP.
    - few for HM (type polymorphism)
    - wasn't able to find any beyond type polymorphsm
     
  • Majority of related examples in ATP/ITP systems were about type inference algorithms, but not type system specification. There can be many variations of type inference algorithms for the same type system.

What's next?  TIPER

Type Inference Prototyping Engine                                            
from Relational specifications
of type systems                    

  1. Continue experimenting with Prolog on various features
    • to research what functionality is needed in TIPER
  2. Code generation for a target language of choice (Haskell)
    • build TIPER-u using microKanren as a backend
      microKanren is an eDSL for LP, being ported to increasing number of host languages including Haskell
  3. Study S-resolution in the context of TIPER development
    • also develop an eDSL for S-res based LP
  4. Change TIPER-s backend to S-resolution based eDSL

Executable Relational Specifications of Polymorphic Type Systems using Prolog

By 안기영 (Ahn, Ki Yung)

Executable Relational Specifications of Polymorphic Type Systems using Prolog

Talk @ Dundee, UK 2015-08-28

  • 2,926