Practical Type Inference for the GADT Type System A Doctoral Dissertation Defense Chuan-kai Lin Advisor: Tim Sheard Department of Computer Science Portland State University

June 1, 2010

Chuan-kai Lin

Practical Type Inference for the GADT Type System

1 / 75

Practical Type Inference for the GADT Type System

Chuan-kai Lin

Practical Type Inference for the GADT Type System

2 / 75

Practical Type Inference for the GADT Type System (Oh no, not one of those again!!)

Chuan-kai Lin

Practical Type Inference for the GADT Type System

3 / 75

Practical Type Inference for the GADT Type System (Oh no, not one of those again!!)

Introduction What are types, and What are they good for?

Chuan-kai Lin

Practical Type Inference for the GADT Type System

4 / 75

Programs

Types

Type Rules

[] [1,2,3] [True] [3,True] . . .

[Int] [Bool] Bool .. . L

Type Checker Y/N Chuan-kai Lin

Practical Type Inference for the GADT Type System

5 / 75

The ADT type system cannot describe fine-grained program properties. Hence: the GADT type system. 5M 2L 1S

7M 4M



6S

AVL Balance Factors





3S







M

S

L

 

Chuan-kai Lin

Practical Type Inference for the GADT Type System

6 / 75

Counting (Tree Height) with Types

Chuan-kai Lin

data Z data S n

Peano encoding of 0 Peano encoding of 1+n

Z S S S S

type-level encoding type-level encoding type-level encoding type-level encoding type-level encoding .. .

Z (S Z) (S (S Z)) (S (S (S Z))) .. .

Practical Type Inference for the GADT Type System

of of of of of

0 1 2 3 4

7 / 75

Generalized Algebraic Data Types (GADTs) data Avl n Tip :: MNode :: SNode :: LNode ::

where Avl Z Avl (S n) → Int → Avl n → Avl (S (S n)) Avl n → Int → Avl n → Avl (S n) Avl n → Int → Avl (S n) → Avl (S (S n))

The LNode data constructor combines an integer with A left subtree of height n and

L

A right subtree of height 1+n=(S n) To build an AVL tree of height 2+n=(S (S n)). Chuan-kai Lin

Practical Type Inference for the GADT Type System

8 / 75

tree :: Avl (S (S (S (S Z)))) 5M tree = MNode (LNode 2L 7M Tip 2 (MNode   4M 6S (SNode Tip 3 Tip) 4 Tip))   3S    5 (MNode (SNode Tip 6 Tip) 7 Tip)  

Chuan-kai Lin

Practical Type Inference for the GADT Type System

9 / 75

tree :: Avl (S (S (S (S Z)))) 5M tree = MNode (LNode 2L 7M Tip 2 (MNode   4M 6S (SNode Tip 3 Tip) 4 Tip))   3S    5 (MNode (SNode Tip 6 Tip) 7 Tip)  

I’m sorry, Dave. I’m afraid I can’t do that. Chuan-kai Lin

Practical Type Inference for the GADT Type System

10 / 75

tree :: Avl (S (S (S (S Z)))) 5M tree = MNode (LNode 2L 7M (SNode Tip 1 Tip) 2 (MNode  1S 4M 6S (SNode Tip 3 Tip) 4 Tip))   3S    5 (MNode (SNode Tip 6 Tip) 7 Tip)  

Everything is going extremely well. Chuan-kai Lin

Practical Type Inference for the GADT Type System

11 / 75

The GADT type system can also describe properties of functions over generalized algebraic data types. X

Y Y

X

rotl A B

A

B

C

C

rotl :: forall n. Avl n → Int → Avl (S (S n)) → E (Avl (S (S n))) (Avl (S (S (S n))))

Chuan-kai Lin

Practical Type Inference for the GADT Type System

12 / 75

Type Checking for the rotl Function rotl :: forall n. Avl n → Int → Avl (S (S n)) → E (Avl (S (S n))) (Avl (S (S (S n)))) rotl u v w = case w of SNode a x b → R (MNode (LNode u LNode a x b → L (SNode (SNode u MNode k y c → case k of SNode a x b → L (SNode (SNode LNode a x b → L (SNode (MNode MNode a x b → L (SNode (SNode

v a) x b) v a) x b) u v a) x (SNode b y c)) u v a) x (SNode b y c)) u v a) x (LNode b y c))

Everything is going extremely well. Chuan-kai Lin

Practical Type Inference for the GADT Type System

13 / 75

The introduction so far focuses on type checking — Given a program, a context, and a type, determine if the program has the given type in the context. This dissertation is about type inference — Given a program and a context, determine if the program has a type in the context (and find the type if it exists). Type inference is a lot harder than type checking.

Chuan-kai Lin

Practical Type Inference for the GADT Type System

14 / 75

Type Inference for the rotl Function rotl u v w = case w of SNode a x b → R (MNode (LNode u LNode a x b → L (SNode (SNode u MNode k y c → case k of SNode a x b → L (SNode (SNode LNode a x b → L (SNode (MNode MNode a x b → L (SNode (SNode

v a) x b) v a) x b) u v a) x (SNode b y c)) u v a) x (SNode b y c)) u v a) x (LNode b y c))

Avl n → Int → Avl (S (S n)) → E (Avl (S (S n))) (Avl (S (S (S n))))

Everything is going extremely well. Chuan-kai Lin

Practical Type Inference for the GADT Type System

15 / 75

Previous Work The GADT type inference problem has been vigorously studied in past five years, but without much progress. Pottier & Régis-Gianas, Stratified Inference, POPL 2006 Peyton Jones et al., Wobbly Types, ICFP 2006 Schrijvers et al., OutsideIn, ICFP 2009 Stuckey & Sulzmann, GRDT Inference, 2005 Sulzmann et al., Herbrand Constraint Abduction, 2008

Current state: sound & complete with type annotations, extremely ineffective without type annotations Chuan-kai Lin

Practical Type Inference for the GADT Type System

16 / 75

Why GADT Type Inference? — A (Flying) Car Analogy —

Chuan-kai Lin

Practical Type Inference for the GADT Type System

17 / 75

Because it is at times quite convenient

Chuan-kai Lin

Practical Type Inference for the GADT Type System

18 / 75

And it can be really educational

Chuan-kai Lin

Practical Type Inference for the GADT Type System

19 / 75

But we must resist the easy way out

Chuan-kai Lin

Practical Type Inference for the GADT Type System

20 / 75

Thesis Statement Designing a practical GADT type inference algorithm leads to new discoveries about the GADT type system. These discoveries, in turn, advance the state of the art in the design of GADT type inference algorithms.

Chuan-kai Lin

Practical Type Inference for the GADT Type System

21 / 75

A Crash Course on Generalized Algebraic Data Types (in two slides)

Chuan-kai Lin

Practical Type Inference for the GADT Type System

22 / 75

Example: Length-Indexed Lists data Z data S n

(i.e., 0) (i.e., 1+n)

length zero data L n a where length increment Nil :: forall a. L Z a Cons :: forall n a. a → L n a → L (S n) a Nil :: L Z Int Cons 3 Nil :: L (S Z) Int Cons 5 (Cons 3 Nil) :: L (S (S Z)) Int

Chuan-kai Lin

Practical Type Inference for the GADT Type System

(length 0) (length 1) (length 2)

23 / 75

Pattern-Matching Length-Indexed Lists data L n a where Cons :: forall n a. a → L n a → L (S n) a isNat :: forall m. L m Int → L m Bool isNat xs = case xs of branch body, type L Z Bool Nil → Nil Cons y ys → Cons (y >= 0) (isNat ys) branch body, type L (S n) Bool

Chuan-kai Lin

Practical Type Inference for the GADT Type System

24 / 75

Pattern-Matching Length-Indexed Lists data L n a where Cons :: forall n a. a → L n a → L (S n) a isNat :: forall m. L m Int → L m Bool isNat xs = case xs of scrutinee, type L m Int Nil → Nil Cons y ys → Cons (y >= 0) (isNat ys) pattern, type L (S n) a

Chuan-kai Lin

Practical Type Inference for the GADT Type System

25 / 75

Pattern-Matching Length-Indexed Lists data L n a where Cons :: forall n a. a → L n a → L (S n) a isNat :: forall m. L m Int → L m Bool isNat xs = case xs of scrutinee, type L m Int Nil → Nil Cons y ys → Cons (y >= 0) (isNat ys) pattern, type L (S n) a U(L m Int ∼ L (S n) a) = [m 7→ S n, a 7→ Int] GADT type refinement

Chuan-kai Lin

Practical Type Inference for the GADT Type System

26 / 75

Pattern-Matching Length-Indexed Lists case expression type data L n a where Cons :: forall n a. a → L n a → L (S n) a isNat :: forall m. L m Int → L m Bool isNat xs = case xs of scrutinee, type L m Int Nil → Nil Cons y ys → Cons (y >= 0) (isNat ys) pattern, type L (S n) a

branch body, type L (S n) Bool

U(L m Int ∼ L (S n) a) = [m 7→ S n, a 7→ Int] GADT type refinement

Chuan-kai Lin

Practical Type Inference for the GADT Type System

27 / 75

Contribution #1 Finding a new answer to the question “What makes GADT type inference so hard?”

Chuan-kai Lin

Practical Type Inference for the GADT Type System

28 / 75

Background Previous work points out three technical difficulties with the GADT type inference problem: 1

Some programs lack principal types

2

Different case branches may have different types

3

Many programs use polymorphic recursion

Presumably, without these three technical difficulties, GADT type inference would be easy.

Chuan-kai Lin

Practical Type Inference for the GADT Type System

29 / 75

Methodology Apply existing inference algorithms to programs that 1

Contain GADT pattern-matching branches,

2

Have no type annotations,

3

Have principal (i.e., most-general) types,

4

Do not require GADT type refinements, and

5

Do not require polymorphic recursion.

Type inference failure indicates unforeseen difficulties.

Chuan-kai Lin

Practical Type Inference for the GADT Type System

30 / 75

GADT Type Inference Test #1 tail :: forall n a. L (S n) a → L n a tail xs = case xs of Cons y ys → ys

Stratified Type Inference Wobbly Types OutsideIn Herbrand Constraint Abduction Omega Implementation (Sheard)

Chuan-kai Lin

Practical Type Inference for the GADT Type System

7 7 7 7 3

31 / 75

GADT Type Inference Test #2 null :: forall null xs = case Nil → Cons y ys →

n a. L n a → Bool xs of True False

Stratified Type Inference Wobbly Types OutsideIn Herbrand Constraint Abduction Omega Implementation (Sheard)

Chuan-kai Lin

Practical Type Inference for the GADT Type System

7 7 7 3 7

32 / 75

The Contribution There is an unforeseen difficulty in the GADT type inference problem: case scrutinee type inference. tail xs = case xs of Cons y ys → ys xs :: L n a ? xs :: L (S n) a ? xs :: L (S Z) a ? .. .

Understanding scrutinee type properties is the key. Chuan-kai Lin

Practical Type Inference for the GADT Type System

33 / 75

Contribution #2 Generalized Existential Types in GADT Pattern-Matching Branches

Chuan-kai Lin

Practical Type Inference for the GADT Type System

34 / 75

Background Existential types (Läufer & Odersky) are type variables in a constructor type that are not in the range type. type existential type data F a where App :: forall a b. (b → a) → b → F a case e :: App f x App f x App f x

App (mod 3) 5, or App ord ’c’? F Int of → x 7 (b escapes from the branch) → f 3 7 (b is instantiated to Int) → f x 3 (no escape, no instantiation)

ñ Chuan-kai Lin

Practical Type Inference for the GADT Type System

35 / 75

A GADT pattern can introduce type variables that behave like (but are not) existential types. data Term a where no existential types RepInt :: Int → Term Int RepPair :: forall u v. u → v → Term (u,v) inc1 :: forall a. Term a → Term a inc1 e = case e of allows inc1 (RepPair True 3) RepInt i → RepInt i RepPair x y → RepPair (x+1) y Danger, Will Robinson! {x :: u, y :: v}, type refinement [a 7→ (u,v)]

Chuan-kai Lin

Practical Type Inference for the GADT Type System

36 / 75

The Contribution Generalized existential types are pattern type variables that receive no information from the scrutinee type. type generalized existential type data T a where C :: forall b. b → T [b] case e :: T u of C x → x C x → x+3 C x → 3

7 7 3

(b escapes from the branch) (b is instantiated to Int) (no escape, no instantiation)

ñ Chuan-kai Lin

Practical Type Inference for the GADT Type System

37 / 75

The Contribution Generalized existential types are evolutionary: An existential type is a generalized existential type. Generalized existential types are also revolutionary: Existential types are intrinsic to a data constructor. Generalized existentials are extrinsic to a pattern (they depend on the type of the scrutinee, i.e., the context where the pattern appears).

Chuan-kai Lin

Practical Type Inference for the GADT Type System

38 / 75

Contribution #3 Inferring Valid Scrutinee Types: Avoiding Generalized-Existential-Type Violations

Chuan-kai Lin

Practical Type Inference for the GADT Type System

39 / 75

Background Existing algorithms infer scrutinee types first and catch generalized-existential-type violations later. À Looks like a GADT type argument data T a where C :: forall b. b → T [b] case e of C x → x+3

Á I should infer scrutinee type as T a  Generalized existential type instantiation

à I’m sorry, Dave. I’m afraid I can’t do that. Chuan-kai Lin

Practical Type Inference for the GADT Type System

40 / 75

The Contribution A type inference algorithm should work backward to avoid generalized-existential-type violations. Á b better not be generalized existential data T a where C :: forall b. b → T [b] case e of C x → x+3

 I should infer scrutinee type as T [Int] À Type variable b is instantiated to Int

à Everything is going extremely well. Chuan-kai Lin

Practical Type Inference for the GADT Type System

41 / 75

Contribution #4 Inferring Better Scrutinee Types: Beyond the Myth of Most-General Types

Chuan-kai Lin

Practical Type Inference for the GADT Type System

42 / 75

Background How do programmers choose a type for a program? id :: forall a. a → a id :: forall a. [a] → [a] id :: [Int] → [Int]

(best, most-general) (not as good) (even worse)

id x = x

A more-general type allows the program to appear in a wider range of contexts and is thus more preferable.

Chuan-kai Lin

Practical Type Inference for the GADT Type System

43 / 75

The Contribution A good scrutinee type should closely match all branch pattern types in the case expression. pattern type for the Cons branch data L n a where Cons :: forall n a. a → L n a → L (S n) a head :: forall n. L n Int → Int head :: forall n a. L n a → a head :: forall n a. L (S n) a → a

(bad) (good, most-general) (even better!)

head xs = case xs of prevents divergence from head Nil Cons y ys → y

Chuan-kai Lin

Practical Type Inference for the GADT Type System

44 / 75

The Contribution Choosing scrutinee type specificity is a trade-off. A more general scrutinee type provides: More reusable case expressions More opportunities for pattern-matching failures

A more specific scrutinee type provides: Less reusable case expressions Fewer opportunities for pattern-matching failures

Chuan-kai Lin

Practical Type Inference for the GADT Type System

45 / 75

The Contribution A type inference algorithm should specialize a scrutinee type to match the pattern types in the case expression. data Vec n a where Vec0 :: Vec Z a Vec1 :: a → Vec (S Z) a Vec2 :: a → a → Vec (S (S Z)) a  Specialize type to Vec (S n) Int case vec of Vec1 x → x À Infer scrutinee type Vec n a Vec2 x y → x+y Á Infer scrutinee type Vec n Int

Chuan-kai Lin

Practical Type Inference for the GADT Type System

46 / 75

Contribution #5 Reconciling Types in Different Branches Using GADT Type Refinements

Chuan-kai Lin

Practical Type Inference for the GADT Type System

47 / 75

Background Conflicting branch body types in a case expression is a major technical difficulty in GADT type inference. data L n a where Nil :: forall a. L Z a Cons :: forall n a. a → L n a → L (S n) a head3 :: forall m. L m Int → L m Int head3 xs = case xs of [m 7→ Z], type L Z Int Nil → Nil Cons y ys → Cons 3 ys [m 7→ S n], type L (S n) Int

Chuan-kai Lin

Practical Type Inference for the GADT Type System

48 / 75

Background Previously inferred type information: à Nil pattern type, [m 7→ Z] data L n a where Ä Cons pattern type, [m 7→ S n] Nil :: forall a. L Z a Cons :: forall n a. a → L n a → L (S n) a  Infer scrutinee type L m Int head3 xs = case xs of À Infer body type L Z b Nil → Nil Cons y ys → Cons 3 ys Á Infer body type L (S n) Int

Chuan-kai Lin

Practical Type Inference for the GADT Type System

49 / 75

À Nil branch body type L Z b  Scrutinee type L m Int

Á Cons branch body type L (S n) Int

à Nil branch type refinement [m 7→ Z]

Ä Cons branch type refinement [m 7→ S n]

Å Fresh type variable u

Refinements

Branch Types

Branch

m

u

Nil Cons

Z

L Z b L (S n) Int

S n

Goal: infer u using the type refinements on m

Chuan-kai Lin

Practical Type Inference for the GADT Type System

50 / 75

The Contribution I developed two tactics that extract type information from inconsistent columns in the branch type table: 1

Destruct common top-level type constructors

2

Apply type refinements from the refinement table

These tactics enable type inference for case expressions whose pattern-matching branches have different types.

Chuan-kai Lin

Practical Type Inference for the GADT Type System

51 / 75

Branch Nil Cons

Refinements

Branch Types

m

u

Z S n

L Z b L (S n) Int

Tactic #1: destruct type constructor L ρ = [u 7→ L r s] Refinements Branch Nil Cons

Chuan-kai Lin

Branch Types

m

r

s

Z S n

Z S n

b Int

Practical Type Inference for the GADT Type System

52 / 75

Refinements Branch Nil Cons

Branch Types

m

r

s

Z S n

Z S n

b Int

Tactic #2: apply GADT type refinement to r ρ = [u 7→ L m s, r 7→ m] Branch Nil Cons

Chuan-kai Lin

Refinements

Branch Types

m

s

Z S n

b Int

Practical Type Inference for the GADT Type System

53 / 75

Branch Nil Cons

Refinements

Branch Types

m

s

Z S n

b Int

Last resort: unify each remaining branch type column ρ = [u 7→ L m Int, r 7→ m, s 7→ Int] head3 :: L m Int → L m Int

Everything is going extremely well. Chuan-kai Lin

Practical Type Inference for the GADT Type System

54 / 75

Hold on a sec. . . Did we really infer a type for head3 without type annotations?!?

Chuan-kai Lin

Practical Type Inference for the GADT Type System

55 / 75

Summary of Contributions data L n a where Nil :: forall a. L Z a Cons :: forall n a. a → L n a → L (S n) a head3 xs = case xs of Nil → Nil Cons y ys → Cons 3 ys head3 :: L m Int → L m Int

Everything is going extremely well. Chuan-kai Lin

Practical Type Inference for the GADT Type System

56 / 75

Evaluation Algorithm P for GADT Type Inference

Chuan-kai Lin

Practical Type Inference for the GADT Type System

57 / 75

The Plain GADT Type System Type polymorphism [Milner, 1978] Polymorphic recursion [Mycroft, 1984] Generalized Algebraic Data Types No support for type annotations Type Checking

Type Inference

Previous Work

Chuan-kai Lin

We Are Here

Practical Type Inference for the GADT Type System

58 / 75

Algorithm P Type inference for the plain GADT type system Type polymorphism [Milner, 1978] Polymorphic recursion [Mycroft, 1984] Generalized Algebraic Data Types (this work) Haskell Implementation (848 LoC) All systems are functional. Chuan-kai Lin

Practical Type Inference for the GADT Type System

59 / 75

Benchmark I collected a suite of 30 well-typed plain GADT programs from the following application domains: Dimensional types Generic N-way zip Functional reactive programming Type equality witnesses Shape-indexed binary-tree paths Color-indexed red-black trees

Chuan-kai Lin

Length-indexed lists Tagless term interpreters Monad libraries Integer ordering witnesses Balance-indexed AVL trees

Practical Type Inference for the GADT Type System

60 / 75

AVL Tree Left-Rotation rotl u v w = case w of SNode a x b → R (MNode (LNode u LNode a x b → L (SNode (SNode u MNode k y c → case k of SNode a x b → L (SNode (SNode LNode a x b → L (SNode (MNode MNode a x b → L (SNode (SNode

v a) x b) v a) x b) u v a) x (SNode b y c)) u v a) x (SNode b y c)) u v a) x (LNode b y c))

Avl n → Int → Avl (S (S n)) → E (Avl (S (S n))) (Avl (S (S (S n))))

Everything is going extremely well. Chuan-kai Lin

Practical Type Inference for the GADT Type System

61 / 75

Length-Indexed List Zip zipWith f a b = case a of Nil → case b of Nil → Nil Cons x xs → case b of Cons y ys → Cons (f x y) (zipWith f xs ys)

forall a b c d. (a → b → c) → L d a → L d b → L d c

Everything is going extremely well. Chuan-kai Lin

Practical Type Inference for the GADT Type System

62 / 75

Tagless Term Interpreter eval4 x = case x of RepInt i → i RepBool b → b RepCond u a b → case eval4 u of True → eval4 a False → eval4 b RepSnd u → case eval4 u of { (x, y) → y } RepPair a b → (eval4 a, eval4 b) forall a. Term a → a

Everything is going extremely well. Chuan-kai Lin

Practical Type Inference for the GADT Type System

63 / 75

Trivial Arrow Evaluation data FunDesc a b where FDI :: forall a. FunDesc a a FDC :: forall a b. b → FunDesc a b FDG :: forall a b. (a → b) → FunDesc a b fdFun FDI FDC FDG

e = case e of → λx → x b → λx → b f → f forall a b. FunDesc a b → a → b

Everything is going extremely well. Chuan-kai Lin

Practical Type Inference for the GADT Type System

64 / 75

Integer Ordering Witness data Nat n where Zn :: Nat Z Sn :: Nat n → Nat (S n) data NatLeq m n where LeZ :: NatLeq Z b NatLeq a b → NatLeq (S a) (S b) leq_o k = case k of Zn → LeZ Sn n → LeS (leq_o n)

I’m sorry, Dave. I’m afraid I can’t do that. Chuan-kai Lin

Practical Type Inference for the GADT Type System

65 / 75

Benchmark Results Algorithm P infers types for 25 out of 30 programs in the benchmark suite. The OutsideIn algorithm1 infers types for 1 out of 30 programs in the benchmark suite. The Wobbly Types algorithm2 infers types for 0 out of 30 programs in the benchmark suite. 1. Schrijvers et al., ICFP 2009

Chuan-kai Lin

2. Peyton Jones et al., ICFP 2006

Practical Type Inference for the GADT Type System

66 / 75

Closing Remarks

Chuan-kai Lin

Practical Type Inference for the GADT Type System

67 / 75

Topics Covered in This Talk GADT Type System Properties: Generalized existential types Specificity criterion for scrutinee types

GADT Type Inference Techniques: Generalized existential type elimination Scrutinee type specialization Branch type reconciliation tactics

Chuan-kai Lin

Practical Type Inference for the GADT Type System

68 / 75

The Key Lesson

There are two reasons to specialize a scrutinee type: 1

Eliminate generalized existential types to allow escape and instantiation of pattern-type variables, and

2

Exclude data constructors to reduce opportunities for runtime pattern-matching failures.

A more general scrutinee type is not necessarily better.

Chuan-kai Lin

Practical Type Inference for the GADT Type System

69 / 75

From the Dissertation

Pointwise Type Information Flow in GADT Patterns: Characterizes the principle of orthogonal design Sufficiently expressive for most GADT applications Excludes a specific class of pathological programs Makes GADT programs easier to understand Formalized by pointwise unifiers and pointwise unification

Chuan-kai Lin

Practical Type Inference for the GADT Type System

70 / 75

From the Dissertation

The GADT Branch Reachability Requirement: Requires every branch to be potentially reachable Interacts with local let definitions in perplexing ways Causes GADT type systems to lose type preservation Requires type consistency constraints in Algorithm P Lesson: restricted type system ; simple type inference

Chuan-kai Lin

Practical Type Inference for the GADT Type System

71 / 75

Thesis Statement Designing a practical GADT type inference algorithm leads to new discoveries about the GADT type system. These discoveries, in turn, advance the state of the art in the design of GADT type inference algorithms.

Chuan-kai Lin

Practical Type Inference for the GADT Type System

72 / 75

Future Work More work is needed to enable Algorithm P to: Infer types for more programs Support additional type system features Provide more useful error messages More work is also needed to formally describe and to verify the soundness of Algorithm P. I think you know what the problem is just as well as I do.

Chuan-kai Lin

Practical Type Inference for the GADT Type System

73 / 75

Acknowledgments Research Advising: Tim Sheard & Andrew P. Black Faculty members at PSU Computer Science Moral Support: Wife & Family Friends at PSU Computer Science Financial Backing: National Science Foundation

Chuan-kai Lin

Practical Type Inference for the GADT Type System

74 / 75

Thank You! Chuan-kai Lin

Practical Type Inference for the GADT Type System

75 / 75

Practical Type Inference for the GADT Type System - A ...

Department of Computer Science. Portland State University. June 1, 2010. Chuan-kai Lin. Practical Type Inference for the GADT Type System. 1 / 75 ...

1MB Sizes 0 Downloads 190 Views

Recommend Documents

Practical Type Inference for the GADT Type System
opportunity to develop my interests in computer science and to pursue graduate ...... algebraic data types that I made in the course of this dissertation research. Here ..... APP This rule types a function application by typing the function (f) and i

Practical Type Inference for the GADT Type System
Portland State University ... opportunity to develop my interests in computer science and to pursue graduate ..... 7.13 Type inference for reified state monad (1).

Nullable Type Inference - OCaml
Dec 11, 2002 - Imperative programming languages, such as C or Java deriva- tives, make abundant ... In languages using the ML type discipline, the option type type α option ..... //docs.hhvm.com/manual/en/hack.nullable.php. [3] Facebook ...

Nullable Type Inference - OCaml
Dec 11, 2002 - [1] Apple (2014): Swift, a new programming language for iOS and. OS X. Available at https://developer.apple.com/swift. [2] Facebook (2014): ...

Type Inference Algorithms: A Survey
An overview of type inference for a ML-like language can be found ..... this convention early on because it was built into some of the Coq libraries we used in our.

Polymorphism, subtyping and type inference in MLsub - ML Family ...
Sep 3, 2015 - Polymorphism, subtyping and type inference in. MLsub. Stephen Dolan and Alan Mycroft ... We have two tricks for getting around the difficulties: • Define types properly. • Only use half of them. 2 ... Any two types have a greatest c

Metadata Type System: Integrate Presentation, Data ...
based metadata extraction scripts, or mashups, to collect. 3. Page 3 of 10. dynamicExploratoryBrowsingInterfaces.pdf. dynamicExploratoryBrowsingInterfaces.

Polymorphism, subtyping and type inference in MLsub - ML Family ...
Sep 3, 2015 - Polymorphism, subtyping and type inference in. MLsub. Stephen Dolan and Alan Mycroft ... We have two tricks for getting around the difficulties: • Define types properly. • Only use half of them. 2 ... Any two types have a greatest c

11 reserves ring type station type
OCELLUS. OUTPOST. 15 Lambda Aurigae. X. N. N. N. BD+49 1280. FEDERATION. DEMOCRACY. AGR/IND. Yimakuapa. X. Y. N. N. DINDA [15]. FEDERATION.

material-schematic-hydraulic-system-caterpillar-d10t-track-type ...
material-schematic-hydraulic-system-caterpillar-d10t-track-type-tractor.pdf. material-schematic-hydraulic-system-caterpillar-d10t-track-type-tractor.pdf. Open.

Granville - Production Type
Carraque Scones. Charming fast horse. Milton S. Hershey Candy .... Granville harbour hosts a small maritime emergency rescue team. The number of rocks and.

struct tag-name { data-type member1; data-type ...
3. The tag name such as book_bank can be used to declare structure variables of its type .... static struct student s2,s3={“bbb”,”00CS002”,20,90,30}; s2=s1 ...

Name BP ACC Damage Type Attack Type Energy ...
A Pokémon with Solar Power receives a permanent +3 boost to its Special Attack as .... If the user moves after the target, the power of the user's next move is ...

Type I and Type II Fractional Brownian Motions
Benoit Mandelbrot (commodity and asset prices). Consider a stationary .... What matters, in the choice of linear representation, is how best to represent the joint distribution of the (finite) ... Frequency Domain Simulation: When ut is i.i.d. ...

A Piecewise Linear Chaotic Map For Baptista-Type ...
of cryptographic schemes, namely, public-key schemes and ... elliptic curve cryptography (ECC) are classified as public-key ..... Statistical properties of digital.

A Fast Bresenham Type Algorithm For Drawing Circles
once the points are determined they may be translated relative to any center that is not the origin ( , ). ... Thus we define a function which we call the V+.3?=I

Simplified conditions for type-I and type-II monoids
Abstract. In a previous paper, we obtained conditions on a monoid M for its prefix expansion to be either a left restriction monoid (in which case M must be either 'type-I' or 'type-II') or a left ample monoid (M is 'type-Ia' or 'type-. IIa'). In the

BDE Type Taxonomy - GitHub
Dec 4, 2015 - bslmf::IsFundamental baltzo::Loader bslma::DeallocatorGuard bslma::DestructorProctor utility meta- function protocol bdlt::Date bslstl::StringRef.

manual-caterpillar-monitoring-display-system-advisor-track-type ...
STMG 790 - 3 - Text Reference. 10/04. Page 3 of 92. manual-caterpillar-monitoring-display-system-advisor-track-type-tractors-bulldozer.pdf.

E-Type
Subject: Design and Analysis of Algorithm. Assignment No : 1. E-Type. E.1.1. Define the following asymptotic notation: a)Big Oh b)Big Omega c)Theta d)Little Oh ...

Granville - Production Type
of Chausey, which includes a small harbour, .... carried out and extensions were made to the hippodrome, telephone lines were ..... of Production Systems SAS.

Generality and Reuse in a Common Type System for ...
Compare project, an evaluation platform for many existing NLP tools in the biomedical ... clinical use cases. The design attempts to follow best practices for UIMA type systems, .... It should be noted that this type only deals with relationships ...

Solid Type System Runtime Checks and Unit Tests - GitHub
insufficient type information! Return type should be something like ... type is. // ProteinFail \/ Future[List[FacebookLike]]. Unwrap? ... case \/(result) => s"Dude, eat proteins, or you won't do like me: $result" .... Thank you! goo.gl/U0WYAB · PDF.