Advanced Functional Programming

Similar documents
Advanced Programming Handout 7. Monads and Friends (SOE Chapter 18)

Software System Design and Implementation

CSCE 314 Programming Languages Functors, Applicatives, and Monads

CS 457/557: Functional Languages

Lecture 19: Functions, Types and Data Structures in Haskell

Overloading, Type Classes, and Algebraic Datatypes

JVM ByteCode Interpreter

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

College Functors, Applicatives

Programming Languages Fall 2013

A general introduction to Functional Programming using Haskell

Monads and all that I. Monads. John Hughes Chalmers University/Quviq AB

CS 320: Concepts of Programming Languages

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

An introduction introduction to functional functional programming programming using usin Haskell

CSCE 314 Programming Languages

Programming in Omega Part 1. Tim Sheard Portland State University

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

Type system. Type theory. Haskell type system. EDAN40: Functional Programming Types and Type Classes (revisited)

Advances in Programming Languages

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

CS 457/557: Functional Languages

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

Exercise 1 ( = 24 points)

Programming with Math and Logic

Applicative, traversable, foldable

Applicative, traversable, foldable

Idris: Implementing a Dependently Typed Programming Language

CS 209 Functional Programming

f() ! " Run a higher-priority task? ! " Yield the processor to another task because our ! " Use the processor for some other activity while

CS 410/510: Advanced Programming

10/21/08. Monads for functional programming uses! Kathleen Fisher!

Monads seen so far: IO vs Gen

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

Functional Programming

Witnessing Purity, Constancy and Mutability APLAS Ben Lippmeier Australian National University 2009/12/14

Types and Type Inference

GADTs. GADTs in Haskell

Advanced Functional Programming

Programming Language Concepts, CS2104 Lecture 7

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

Functional Programming - 2. Higher Order Functions

Structural polymorphism in Generic Haskell

CSc 372 Comparative Programming Languages

Monad (3A) Young Won Lim 8/9/17

Part 0. A (Not So) Brief Introduction to Haskell

CS 360: Programming Languages Lecture 12: More Haskell

CS 440: Programming Languages and Translators, Spring 2019 Mon

Type Processing by Constraint Reasoning

CSc 372. Comparative Programming Languages. 8 : Haskell Function Examples. Department of Computer Science University of Arizona

CS 320: Concepts of Programming Languages

Lecture 4: Higher Order Functions

Monad (1A) Young Won Lim 6/26/17

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

These notes are intended exclusively for the personal usage of the students of CS352 at Cal Poly Pomona. Any other usage is prohibited without

Type checking by theorem proving in IDRIS

CSE 3302 Programming Languages Lecture 8: Functional Programming

State Monad (3D) Young Won Lim 9/25/17

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

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

INTRODUCTION TO HASKELL

Monads. Functional Programming (CS4011) Monads

Principles of Programming Languages

Haskell Types, Classes, and Functions, Currying, and Polymorphism

Types and Type Inference

Haskell: From Basic to Advanced. Part 2 Type Classes, Laziness, IO, Modules

Generic Programming With Dependent Types: II

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

Type-indexed functions in Generic Haskell

Exercise 1 ( = 18 points)

Monad Background (3A) Young Won Lim 11/8/17

Handout 2 August 25, 2008

Parsing. Zhenjiang Hu. May 31, June 7, June 14, All Right Reserved. National Institute of Informatics

MoreIntro_annotated.v. MoreIntro_annotated.v. Printed by Zach Tatlock. Oct 04, 16 21:55 Page 1/10

Course year Typeclasses and their instances

Introduction to Functional Programming in Haskell 1 / 56

Monad Background (3A) Young Won Lim 11/20/17

Monads. COS 441 Slides 16

Questions & Answers 28 Sept.

PROGRAMMING IN HASKELL. Chapter 2 - First Steps

Programming Paradigms

MoreIntro.v. MoreIntro.v. Printed by Zach Tatlock. Oct 07, 16 18:11 Page 1/10. Oct 07, 16 18:11 Page 2/10. Monday October 10, 2016 lec02/moreintro.

Monad Background (3A) Young Won Lim 11/18/17

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

Functional Programming Mid-term exam Tuesday 3/10/2017

Monad (1A) Young Won Lim 6/9/17

Exercise 1 (2+2+2 points)

Structures in Coq January 27th 2014

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

CSci 450: Org. of Programming Languages Overloading and Type Classes

Background Operators (1E) Young Won Lim 7/7/18

Box-and-arrow Diagrams

Overview. Declarative Languages D7012E. Overloading. Overloading Polymorphism Subtyping

A Lazy Language Needs a Lazy Type System: Introducing Polymorphic Contexts

State Monad (3D) Young Won Lim 8/31/17

A Pragmatic Case For. Static Typing

Introduction to ML. Based on materials by Vitaly Shmatikov. General-purpose, non-c-like, non-oo language. Related languages: Haskell, Ocaml, F#,

Monad class. Example: Lambda laughter. The functional IO problem. EDAN40: Functional Programming Functors and Monads

Haskell Refresher Informatics 2D

Advanced features of Functional Programming (Haskell)

Transcription:

Advanced Functional Programming Tim Sheard Portland State University Lecture 2: More about Type Classes Implementing Type Classes Higher Order Types Multi-parameter Type Classes Tim Sheard 1

Implementing Type Classes I know of two methods for implementing type classes Using the Dictionary Passing Transform Passing runtime representation of type information. Tim Sheard 2

class Equal a where equal :: a -> a -> Bool Source & 2 strategies data EqualL a = EqualL { equalm :: a -> a -> Bool } equalx :: Rep a -> a -> a -> Bool class Nat a where inc :: a -> a dec :: a -> a zero :: a -> Bool data NatL a = NatL { incm :: a -> a, decm :: a -> a, zerom :: a -> Bool } incx :: Rep a -> a -> a decx :: Rep a -> a -> a zerox :: Rep a -> a -> Bool f0 :: (Equal a, Nat a) => a -> a f0 x = if zero x && equal x x then inc x else dec x f1 :: EqualL a -> NatL a -> a -> a f1 el nl x = if zerom nl x && equalm el x x then incm nl x else decm nl x f2 :: Rep a -> a -> a f2 r x = if zerox r x && equalx r x x then incx r x else decx r x Tim Sheard 3

Dictionary passing instances instance Equal Int where equal x y = x==y instance_l1 :: EqualL Int instance_l1 = EqualL {equalm = equal } where equal x y = x==y instance Nat Int where inc x = x+1 dec x = x+1 zero 0 = True zero n = False instance_l2 :: NatL Int instance_l2 = NatL {incm=inc,decm=dec,zerom=zero} where inc x = x+1 dec x = x+1 zero 0 = True zero n = False Tim Sheard 4

Instance declarations data N = Z S N instance Equal N where equal Z Z = True equal (S x) (S y) = equal x y equal = False instance Nat N where inc x = S x dec (S x) = x zero Z = True zero (S _) = False Tim Sheard 5

Become record definitions instance_l3 :: EqualL N instance_l3 = EqualL { equalm = equal } where equal Z Z = True equal (S x) (S y) = equal x y equal = False instance_l4 :: NatL N instance_l4 = NatL {incm = inc, decm = dec, zerom = zero } where inc x = S x dec (S x) = x zero Z = True zero (S _) = False Tim Sheard 6

Dependent classes instance Equal a => Equal [a] where equal [] [] = True equal (x:xs) (y:ys) = equal x y && equal xs ys equal = False instance Nat a => Nat [a] where inc xs = map inc xs dec xs = map dec xs zero xs = all zero xs Tim Sheard 7

become functions between records instance_l5 :: EqualL a -> EqualL [a] instance_l5 lib = EqualL { equalm = equal } where equal [] [] = True equal (x:xs) (y:ys) = equalm lib x y && equal xs ys equal = False instance_l6 :: NatL a -> NatL [a] instance_l6 lib = NatL { incm = inc, decm =dec, zerom = zero } where inc xs = map (incm lib) xs dec xs = map (decm lib) xs zero xs = all (zerom lib) xs Tim Sheard 8

In run-time type passing Collect all the instances together to make one function which has an extra arg which is the representation of the type this function is specialized on. incx (Int p) x = to p (inc (from p x)) where inc x = x+1 incx (N p) x = to p (inc (from p x)) where inc x = S x incx (List a p) x = to p (inc (from p x)) where inc xs = map (incx a) xs decx (Int p) x = to p (dec (from p x)) where dec x = x+1 decx (N p) x = to p (dec (from p x)) where dec x = S x decx (List a p) x = to p (dec (from p x)) where dec xs = map (decx a) xs zerox (Int p) x = zero (from p x) where zero 0 = True zero n = False zerox (N p) x = zero (from p x) where zero Z = True zero (S _) = False zerox (List a p) x = zero (from p x) where zero xs = all (zerox a) xs Tim Sheard 9

data Proof a b = Ep{from :: a->b, to:: b->a} data Rep t = Int (Proof t Int) Char (Proof t Char) Unit (Proof t ()) forall a b. Arr (Rep a) (Rep b) (Proof t (a->b)) forall a b. Prod (Rep a) (Rep b) (Proof t (a,b)) forall a b. Sum (Rep a) (Rep b) (Proof t (Either a b)) N (Proof t N) forall a. List (Rep a) (Proof t [a]) Tim Sheard 10

Note how recursive calls at different types are calls to the runtime passing versions with new type-rep arguments. equalx (Int p) x y = h equal p x y where equal x y = x==y equalx (N p) x y = h equal p x y where equal Z Z = True equal (S x) (S y) = equal x y equal = False equalx (List a p) x y = h equal p x y where equal [] [] = True equal (x:xs) (y:ys) = equalx a x y && equal xs ys equal = False h equal p x y = equal (from p x) (from p y) Tim Sheard 11

Higher Order types Type constructors are higher order since they take types as input and return types as output. Some type constructors (and also some class definitions) are even higher order, since they take type constructors as arguments. Haskell s Kind system A Kind is haskell s way of typing types Ordinary types have kind * Int :: * [ String ] :: * Type constructors have kind * -> * Tree :: * -> * [] :: * -> * (,) :: * -> * -> * Tim Sheard 12

The Functor Class class Functor f where fmap :: (a -> b) -> (f a -> f b) Note how the class Functor requires a type constructor of kind * -> * as an argument. The method fmap abstracts the operation of applying a function on every parametric Argument. Type T a = a a a x x x fmap f (f x) (f x) (f x) Tim Sheard 13

More than just types Laws for Functor. Most class definitions have some implicit laws that all instances should obey. The laws for Functor are: fmap id = id fmap (f. g) = fmap f. fmap g Tim Sheard 14

Built in Higher Order Types Special syntax for built in type constructors (->) :: * -> * -> * [] :: * -> * (,) :: * -> * -> * (,,) :: * -> * -> * -> * type Arrow = (->) Int Int type List = [] Int type Pair = (,) Int Int type Triple = (,,) Int Int Int Tim Sheard 15

Instances of class functor data Tree a = Leaf a Branch (Tree a) (Tree a) instance Functor Tree where fmap f (Leaf x) = Leaf (f x) fmap f (Branch x y) = Branch (fmap f x) (fmap f y) instance Functor ((,) c) where fmap f (x,y) = (x, f y) Tim Sheard 16

More Instances instance Functor [] where fmap f [] = [] fmap f (x:xs) = f x : fmap f xs instance Functor Maybe where fmap f Nothing = Nothing fmap f (Just x) = Just (f x) Tim Sheard 17

Other uses of Higher order T.C. s data Tree t a = Tip a Node (t (Tree t a)) t1 = Node [Tip 3, Tip 0] Main> :t t1 t1 :: Tree [] Int data Bin x = Two x x t2 = Node (Two(Tip 5) (Tip 21)) Main> :t t2 t2 :: Tree Bin Int Tim Sheard 18

What is the kind of Tree? Tree is a binary type constructor It s kind will be something like:? ->? -> * The first argument to Tree is itself a type constructor, the second is just an ordinary type. Tree :: ( * -> *) -> * -> * Tim Sheard 19

Another Higher Order Class class Monad m where (>>=) :: m a -> (a -> m b) -> m b (>>) :: m a -> m b -> m b return :: a -> m a fail :: String -> m a p >> q = p >>= \ _ -> q fail s = error s We pronounce >>= as bind and >> as sequence Note m is a type constructor Tim Sheard 20

Default methods Note that Monad has two default definitions p >> q = p >>= \ _ -> q fail s = error s These are the definitions that are usually correct, so when making an instance of class Monad, only two defintions (>>=> and (return) are usually given. Tim Sheard 21

Do notation shorthand The Do notation is shorthand for the infix operator >>= do e => e do { e1 ; e2; ; en} => e1 >> do { e2 ; ;en} do { x <- e; f} => e >>= (\ x -> f) where x is a variable do { pat <- e1 ; e2 ; ; en } => let ok pat = do { e2; ; en } ok _ = fail some error message in e1 >>= ok Tim Sheard 22

Monad s and Actions We ve always used the do notation to indicate an impure computation that performs an actions and then returns a value. We can use monads to invent our own kinds of actions. To define a new monad we need to supply a monad instance declaration. Example: The action is potential failure instance Monad Maybe where Just x >>= k = k x Nothing >>= k = Nothing return = Just Tim Sheard 23

Example find :: Eq a => a -> [(a,b)] -> Maybe b find x [] = Nothing find x ((y,a):ys) = if x == y then Just a else find x ys test a c x = do { b <- find a x; return (c+b) } What is the type of test? What does it return if the find fails? Tim Sheard 24

Multi-parameter Type Classes A relationship between two types class (Monad m,same ref) => Mutable ref m where put :: ref a -> a -> m () get :: ref a -> m a new :: a -> m (ref a) class Same ref where same :: ref a -> ref a -> Bool Tim Sheard 25

An Instance instance Mutable (STRef a) (ST a) where put = writestref get = readstref new = newstref instance Same (STRef a) where same x y = x==y Tim Sheard 26

Another Instance instance Mutable IORef IO where new = newioref get = readioref put = writeioref instance Same IORef where same x y = x==y Tim Sheard 27

Another Multi-parameter Type Class class Name term name where isname :: term -> Maybe name fromname :: name -> term type Var = String data Term0 = Add0 Term0 Term0 Const0 Int Lambda0 Var Term0 App0 Term0 Term0 Var0 Var instance Name Term0 Var where isname (Var0 s) = Just s isname _ = Nothing fromname s = Var0 s Tim Sheard 28

Yet Another class Mult a b c where times :: a -> b -> c instance Mult Int Int Int where times x y = x * y instance Ix a => Mult Int (Array a Int) (Array a Int) where times x y = fmap (*x) y Tim Sheard 29

An Example Use Unification of types is used for type inference. data (Mutable ref m ) => Type ref m = Tvar (ref (Maybe (Type ref m))) Tgen Int Tarrow (Type ref m) (Type ref m) Ttuple [Type ref m] Tcon String [Type ref m] Tim Sheard 30

Questions What are the types of the constructors Tvar :: Tgen :: Tarrow :: Tim Sheard 31

Useful Function Run down a chain of Type TVar references making them all point to the last item in the chain. Tvar(Just _ ) Tvar(Just _ ) Tvar(Just _ ) Tvar(Just _ ) Tvar(Just _ ) Tvar(Just _ ) Tuple[ X, Y] Tuple[ X, Y] Tim Sheard 32

Prune prune :: (Monad m, Mutable ref m) => Type ref m -> m (Type ref m) prune (typ @ (Tvar ref)) = do { m <- get ref ; case m of Just t -> do { newt <- prune t ; put ref (Just newt) ; return newt } Nothing -> return typ} prune x = return x Tim Sheard 33

Does a reference occur in a type? occursin :: Mutable ref m => ref (Maybe (Type ref m)) -> Type ref m -> m Bool occursin ref1 t = do { t2 <- prune t ; case t2 of Tvar ref2 -> return (same ref1 ref2) Tgen n -> return False Tarrow a b -> do { x <- occursin ref1 a ; if x then return True else occursin ref1 b } Ttuple xs -> do { bs <- sequence(map (occursin ref1) xs) ; return(any id bs)} Tcon c xs -> do { bs <- sequence(map (occursin ref1) xs) ; return(any id bs) } } Tim Sheard 34

Unify unify :: Mutable ref m => (Type ref m -> Type ref m -> m [String]) -> Type ref m -> Type ref m -> m [String] unify occursaction x y = do { t1 <- prune x ; t2 <- prune y ; case (t1,t2) of (Tvar r1,tvar r2) -> if same r1 r2 then return [] else do { put r1 (Just t2); return []} (Tvar r1,_) -> do { b <- occursin r1 t2 ; if b then occursaction t1 t2 else do { put r1 (Just t2) ; return [] } } Tim Sheard 35

Unify continued unify occursaction x y = do { t1 <- prune x ; t2 <- prune y ; case (t1,t2) of... (_,Tvar r2) -> unify occursaction t2 t1 (Tgen n,tgen m) -> if n==m then return [] else return ["generic error"] (Tarrow a b,tarrow x y) -> do { e1 <- unify occursaction a x ; e2 <- unify occursaction b y ; return (e1 ++ e2) } (_,_) -> return ["shape match error"] } Tim Sheard 36

Generic Monad Functions sequence :: Monad m => [m a] -> m [a] sequence = foldr mcons (return []) where mcons p q = do { x <- p ; xs <- q ; return (x:xs) } mapm :: Monad m => (a -> m b) -> [a] -> m [b] mapm f as = sequence (map f as) Tim Sheard 37