Type families and data kinds

Similar documents
GADTs. Wouter Swierstra. Advanced functional programming - Lecture 7. Faculty of Science Information and Computing Sciences

GADTs. Alejandro Serrano. AFP Summer School. [Faculty of Science Information and Computing Sciences]

GADTs. Wouter Swierstra and Alejandro Serrano. Advanced functional programming - Lecture 7. [Faculty of Science Information and Computing Sciences]

IA014: Advanced Functional Programming

Advanced Type System Features Tom Schrijvers. Leuven Haskell User Group

Lecture 8: Summary of Haskell course + Type Level Programming

Applicative, traversable, foldable

Advances in Programming Languages

Programming with Math and Logic

Type-indexed functions in Generic Haskell

Applicative, traversable, foldable

Lambda calculus. Wouter Swierstra and Alejandro Serrano. Advanced functional programming - Lecture 6

Harvard School of Engineering and Applied Sciences CS 152: Programming Languages

Programming in Omega Part 1. Tim Sheard Portland State University

Type Systems. Pierce Ch. 3, 8, 11, 15 CSE

CS 360: Programming Languages Lecture 12: More Haskell

GADTs. GADTs in Haskell

Informatics 1 Functional Programming Lecture 9. Algebraic Data Types. Don Sannella University of Edinburgh

Giving Haskell a Promotion

Haskell Introduction Lists Other Structures Data Structures. Haskell Introduction. Mark Snyder

CSCI-GA Scripting Languages

Typing Data. Chapter Recursive Types Declaring Recursive Types

Exercise 1 ( = 24 points)

Exercise 1 (2+2+2 points)

Background Type Classes (1B) Young Won Lim 6/14/18

Background Type Classes (1B) Young Won Lim 6/28/18

Typed Racket: Racket with Static Types

Programming Languages Fall 2014

CS 11 Haskell track: lecture 1

Simple Unification-based Type Inference for GADTs

Introduction to Typed Racket. The plan: Racket Crash Course Typed Racket and PL Racket Differences with the text Some PL Racket Examples

Exercise 1 ( = 22 points)

Introduction. Wouter Swierstra. Applied functional programming. Faculty of Science Information and Computing Sciences

CS 320: Concepts of Programming Languages

Type Processing by Constraint Reasoning

Applying Type-Level and Generic Programming in Haskell

Logic - CM0845 Introduction to Haskell

PROGRAMMING IN HASKELL. CS Chapter 6 - Recursive Functions

Exercise 1 ( = 18 points)

Pierce Ch. 3, 8, 11, 15. Type Systems

Testing. Wouter Swierstra and Alejandro Serrano. Advanced functional programming - Lecture 2. [Faculty of Science Information and Computing Sciences]

Optimising Functional Programming Languages. Max Bolingbroke, Cambridge University CPRG Lectures 2010

Haske k ll An introduction to Functional functional programming using Haskell Purely Lazy Example: QuickSort in Java Example: QuickSort in Haskell

Concepts of programming languages

CS 457/557: Functional Languages

n n Try tutorial on front page to get started! n spring13/ n Stack Overflow!

Solution sheet 1. Introduction. Exercise 1 - Types of values. Exercise 2 - Constructors

Simon Peyton Jones Microsoft Research. August 2012

Haskell Overview II (2A) Young Won Lim 8/9/16

Programming Languages

Coercion Quantification

An introduction introduction to functional functional programming programming using usin Haskell

CS 320: Concepts of Programming Languages

Trees. Solution: type TreeF a t = BinF t a t LeafF 1 point for the right kind; 1 point per constructor.

Functional Programming. Overview. Topics. Definition n-th Fibonacci Number. Graph

Advanced features of Functional Programming (Haskell)

CSC324- TUTORIAL 5. Shems Saleh* *Some slides inspired by/based on Afsaneh Fazly s slides

Simon Peyton Jones Microsoft Research August 2013

Programming with Universes, Generically

Programming Languages Lecture 14: Sum, Product, Recursive Types

Lecture 4: Higher Order Functions

Week 5 Tutorial Structural Induction

Haskell & functional programming, some slightly more advanced stuff. Matteo Pradella

CS 320 Homework One Due 2/5 11:59pm

Dynamic Types in GHC 8

CMSC 330: Organization of Programming Languages. Operational Semantics

The type checker will complain that the two branches have different types, one is string and the other is int

G Programming Languages Spring 2010 Lecture 6. Robert Grimm, New York University

Towards Reasoning about State Transformer Monads in Agda. Master of Science Thesis in Computer Science: Algorithm, Language and Logic.

The Typed Racket Guide

Haskell Overloading (1) LiU-FP2016: Lecture 8 Type Classes. Haskell Overloading (3) Haskell Overloading (2)

Types and Type Inference

Depending on Types. Stephanie Weirich University of Pennsylvania

Simon Peyton Jones Microsoft Research August 2012

Introduction to Haskell

Alonzo a Compiler for Agda

Data types à la carte

Introduction to Functional Programming in Haskell 1 / 56

CS 440: Programming Languages and Translators, Spring 2019 Mon

PROGRAMMING IN HASKELL. Chapter 2 - First Steps

Polymorphism Overview (1A) Young Won Lim 2/20/18

Outline. Introduction Concepts and terminology The case for static typing. Implementing a static type system Basic typing relations Adding context

More Lambda Calculus and Intro to Type Systems

Reasoning About Imperative Programs. COS 441 Slides 10

Haskell Type Constraints Unleashed

Adding GADTs to OCaml the direct approach

Shared Subtypes. Subtyping Recursive Parameterized Algebraic Data Types

CSCE 314 TAMU Fall CSCE 314: Programming Languages Dr. Flemming Andersen. Haskell Functions

Lecture #23: Conversion and Type Inference

Conversion vs. Subtyping. Lecture #23: Conversion and Type Inference. Integer Conversions. Conversions: Implicit vs. Explicit. Object x = "Hello";

Monads. Functional Programming (CS4011) Monads

CS 209 Functional Programming

Structural polymorphism in Generic Haskell

Introduction to Programming, Aug-Dec 2006

COMP 3141 Software System Design and Implementation

Static Contract Checking for Haskell

Typed Scheme: Scheme with Static Types

Improving Haskell Types with SMT

cs242 Kathleen Fisher Reading: Concepts in Programming Languages, Chapter 6 Thanks to John Mitchell for some of these slides.

Tracing Ambiguity in GADT Type Inference

Transcription:

Type families and data kinds AFP Summer School Wouter Swierstra 1

Today How do GADTs work? Kinds beyond * Programming with types 2

Calling functions on vectors Given two vectors xs : Vec a n and ys : Vec a m. Suppose I want to zip these vectors together using: zipvec :: Vec a n -> Vec b n -> Vec (a,b) n Question What happens when I call zipvec xs ys? 3

Calling functions on vectors Given two vectors xs : Vec a n and ys : Vec a m. Suppose I want to zip these vectors together using: zipvec :: Vec a n -> Vec b n -> Vec (a,b) n Question What happens when I call zipvec xs ys? I get a type error: n and m are not necessarily equal! 3

Comparing the length of vectors We can define a boolean function that checks when two vectors have the same length equallength :: Vec a m -> Vec b n -> Bool equallength Nil Nil = True equallength (Cons _ xs) (Cons _ ys) = equallength xs ys equallength = False 4

Comparing the length of vectors Such a function is not very useful Suppose I want to use this to check the lengths of my vectors: if equallength xs ys then zipvec xs ys else error "Wrong lengths" Question Will this type check? 5

Comparing the length of vectors Such a function is not very useful Suppose I want to use this to check the lengths of my vectors: if equallength xs ys then zipvec xs ys else error "Wrong lengths" Question Will this type check? No! Just because equallength xs ys returns True, does not guarantee that m and n are equal 5 How can we enforce that two types are indeed equal?

Equality type Just as we saw for the Sum type, we can introduce a GADT that represents a proof that two types are equal: data Equal :: * -> * -> * where Refl :: Equal a a 6

Equality type We can prove properties of our equality relation: refl :: Equal a a sym :: Equal a b -> Equal b a trans :: Equal a b -> Equal b c -> Equal a c 7

Equality type We can prove properties of our equality relation: refl :: Equal a a sym :: Equal a b -> Equal b a trans :: Equal a b -> Equal b c -> Equal a c Question How are these functions defined? 7

Equality type We can prove properties of our equality relation: refl :: Equal a a sym :: Equal a b -> Equal b a trans :: Equal a b -> Equal b c -> Equal a c Question How are these functions defined? What happens if you don t pattern match on the Refl constructor? 7

Equality type Instead of returning a boolean, we can now provide evidence that the length of two vectors is equal: eqlength :: Vec a m -> Vec b n -> Maybe (Equal m n) eqlength Nil Nil = Just Refl eqlength (Cons x xs) (Cons y ys) = case eqlength xs ys of Just Refl -> Just Refl Nothing -> Nothing eqlength = Nothing 8

Using equality test :: Vec a m -> Vec b (Succ n) -> Maybe (a,b) test xs ys = case eqlength xs ys Just Refl -> head (zipvec xs ys) _ -> Nothing Question Why does this type check? 9

Expressive power of equality The equality type can be used to encode other GADTs. Recall our expression example using phantom types: data Expr a = LitI Int LitB Bool IsZero (Expr Int) Plus (Expr Int) (Expr Int) If (Expr Bool) (Expr a) (Expr a) 10

Expressive power of equality We can use equality proofs and phantom types to implement GADTs: data Expr a = LitI (Equal a Int) Int LitB (Equal a Bool) Bool IsZero (Equal a Bool) (Equal b Int) Plus (Equal a Int) (Expr Int) (Expr Int) If (Expr Bool) (Expr a) (Expr a)... 11

Safe vs unsafe coercions Using our equality function we can safely coerce between types: coerce :: Equal a b -> a -> b coerce Refl x = x Question Why does this type check? 12

Safe vs unsafe coercions Using our equality function we can safely coerce between types: coerce :: Equal a b -> a -> b coerce Refl x = x Question Why does this type check? Question What about this definition: 12 coerce :: Equal a b -> a -> b coerce p x = x

Aside: irrefutable patterns Haskell also allows irrefutable patterns: lazyhead ~(x:xs) = x This does not force the list to weak head normal form. 13

Aside: irrefutable patterns In tandem with GADTs this is particularly dangerous: coercel :: Equal a b -> a -> b coercel ~Refl x = x Question How could this cause well-typed program to crash with a type error? 14

Aside: irrefutable patterns In tandem with GADTs this is particularly dangerous: coercel :: Equal a b -> a -> b coercel ~Refl x = x Question How could this cause well-typed program to crash with a type error? foo :: Bool -> Int foo b = coercel undefined b 14 Apparently unrelated language features may interact in unexpected ways!

System FC Haskell s core language, System FC, is a typed lambda calculus, extended with data types and pattern matching. One of its more distinct features is coercions and casts. Coercions play the same role as our Equal data type; If two types are coercible, one can be cast to the other: iszero :: (a ~ Int) => a -> Bool There is quite a lot of work necessary to guarantee that this does not accidentally make the type system unsound! 15 Pattern matching on GADTs introduces such coercions in the individual branches.

Problems with GADTs vappend :: Vec a n -> Vec a m -> Vec a??? To define this function, we needed to construct an explicit relation describing how to add two types, n and m. 16

Problems with GADTs tovec :: [a] -> Vec a??? To define this function, we needed to reify natural numbers on the type level defining a singleton type SNat. 17

Passing explicit Sums In the last lecture, we saw how to pass an explicit argument, explaining how to add two type-level natural numbers: data Sum :: * -> * -> * -> * where SumZero :: Sum Zero n n SumSucc :: Sum n m s -> Sum (Succ n) m (Succ s) But constructing this evidence by hand is tedious 18

Multi-parameter type classes One way to automate this, is through a multi-parameter type class class Summable a b c a b -> c where makesum :: Sum a b c instance Summable Zero n n where makesum = SumZero instance Summable n m s => Summable (Succ n) m (Succ s) where makesum = SumSucc makesum 19 append :: Sum n m s => Vec a n -> Vec a m -> Vec a s append = vappend makesum

Multi-parameter type classes Type classes define relations between types: Eq defines a subset of all types that support an equality function; MonadState defines a subset of pairs of types s and m, where m supports read/write operations on a state of type s. The Summable type class is special case of such relations it is really defining a function between types. 20

Multi-parameter type classes For some time, multi-parameter type classes with functional dependencies were the only way in Haskell to define such type-level computations. But there has been a flurry of research in the last decade exploring alternative language extensions.... the interaction of functional dependencies with other type-level features such as existentials and GADTs is not well understood and possibly problematic. Kiselyov, Peyton Jones, Shan in Fun with type families 21

Associated types and type families Type classes let you capture an interface such as monads (supporting return and bind), or monoids (supporting zero and addition). These interaces can describe functions. But what if we would like them to describe types. 22

Associated types Associated types let you declare a type in a class declaration: class Collects c where type Elem c -- Associated type synonym empty :: c insert :: Elem c -> c -> c tolist :: c -> [Elem c] Any instance of the Collects class must choose a type of elements, together with definitions for the functions. 23

Associated types examples instance Eq e => Collects [e] where type Elem [e] = e empty = []... instance Collects BitSet where type Elem BitSet = Char... 24

Addition through association We can use such associated types to replace the functional dependencies we saw previously: class Summable n m where type TheSum n m makesum :: Sum n m (TheSum n m) instance Summable Zero n where type TheSum Zero m = m... 25 instance Summable n m => Summable (Succ n) m where type TheSum (Succ n) m = Succ (TheSum n m)...

Associated types or multiparameter type? Both approaches are similar in expressive power. Multiparameter type classes are no longer fashionable mainly because they can make type class resolution unpredictable. Associated types have gained traction in other languages such as Apple s Swift. 26

Type families Associated types always require a class definition even if we re only interested in the types. Type families build upon the technology that associated types provide, enabling you to write: type family Sum n m type instance Sum Zero n = n type instance Sum (Succ n) m = Succ (Sum n m) This looks much more like regular programming 27

Type families If we piggyback on the associated type machinery, however, all our type families are open we can add bogus definitions: type instance Sum n Zero = Zero Furthermore, all our type level code is essentially untyped. type instance Sum Bool Int = Char 28

Closed type functions The more modern closed type families allow you to define a function between types using pattern matching: type family Count (f :: *) :: Nat where Count (a -> b) = 1 + (Count b) Count x = 1 GHC will try to match a given type against the patterns one by one, taking the first branch that matches successfully. This almost lets us program with types almost as if they were regular values. 29

Kinds So far we have seen that two different forms of kinds: all types have kind * given two kinds k1 and k2, we can form the kind k1 -> k2 corresponding to the type constructor taking something of kind k1 to produce a type of kind k2. 30

Kinds So far we have seen that two different forms of kinds: all types have kind * given two kinds k1 and k2, we can form the kind k1 -> k2 corresponding to the type constructor taking something of kind k1 to produce a type of kind k2. This is essentially the simply typed lambda calculus with one base type. As soon as we do richer programming with types, however, we would like stronger guarantees about the safety of the type level computations that we write. 30

Example data Apply f a = MkApply (f a) Question What is the kind of Apply? 31

Example data Apply f a = MkApply (f a) Question What is the kind of Apply? Many different answers exist: (* -> *) -> * -> * being the most obvious. But there s no reason that a must have kind *. You can make the case for kind polymorphism just as we have polymorphism in types (GHC supports this). 31

Promotion data Zero data Succ n data Nat = Zero Succ Nat How can we ensure all numbers in our types to be built from Zero and Succ? 32

Promotion Using the DataKinds language extension we can introduce new kinds and automatically promote data constructors into their type-level variants: {-# LANGUAGE DataKinds #-} data Nat = Zero Succ Nat This declaration introduces: a new kind Nat a type 'Zero :: Nat a type 'Succ :: Nat -> Nat 33 (This only works for algebraic data types, not for GADTs)

Example: booleans -- the usual definition of booleans data Bool = True False -- Not function on values not :: Bool -> Bool not True = False not False = True -- Not function on types type family Not (a :: Bool) :: Bool type instance Not True = False type instance Not False = True 34

Type-level literals GHC takes the idea of programming with types quite far. It has added support and syntax for: type-level strings; type-level lists; type-level integers; 35

Outlook generic programming: Reflecting types We can even use GADTs to reflect types themselves as data: data Type :: * -> * where INT :: Type Int BOOL :: Type Bool LIST :: Type a -> Type [a] PAIR :: Type a -> Type b -> Type (a,b) 36

Safe dynamically typed values We can define dynamically typed values by packing up a type representation with a value: data Dynamic :: * where Dyn :: Type a -> a -> Dynamic 37

Safe dynamically typed values We can define dynamically typed values by packing up a type representation with a value: data Dynamic :: * where Dyn :: Type a -> a -> Dynamic To unwrap these values safely, we check whether the types line up as expected: coerce :: Type a -> Dynamic -> Maybe a coerce t (Dyn t' x) = case eqtype t t' Just Refl -> Just x _ -> Nothnig 37

Generic programming We can also define new functions by induction on the type structure: f :: Type a ->... a... In this way, we can define our own versions of functions such as show, read, equality, etc. 38

Outlook: writing webserver with Servant Servant is a library for describing web APIs. From such a description, it will generate documentation, a simple webserver, etc. Instead of describing the APIs using Haskell values you describe the API as a (complex) Haskell type. type HackageAPI = "users" :> Get '[JSON] [UserSummary] :< > "user" :> Capture "username" Username :> Get '[JSON] UserDetailed :< > "packages" :> Get '[JSON] [Package] 39 And then generate any desired functionality from this description.

Recap: GADTs GADTs give you more power to define interesting types in Haskell. We can decorate our types with more specific information. But we still cannot do any interesting computation using types. 40

Recap: GADTs GADTs can be used to encode advanced properties of types in the type language. We end up mirroring expression-level concepts on the type level (e.g. natural numbers). GADTs can also represent data that is computationally irrelevant and just guides the type checker (equality proofs, evidence for addition). Such information could ideally be erased, but in Haskell, we can always cheat via undefined :: Equal Int Bool 41

Recap: type families Haskell has various different ways to program with types; We ll see numerous applications of these ideas next week, such as data type generic programming. But the value language and type language live in very different worlds 42