Advanced Functional Programming

Slides:



Advertisements
Similar presentations
Types and Programming Languages Lecture 13 Simon Gay Department of Computing Science University of Glasgow 2006/07.
Advertisements

Functional Programming Lecture 10 - type checking.
ML Lists.1 Standard ML Lists. ML Lists.2 Lists A list is a finite sequence of elements. [3,5,9] ["a", "list" ] [] Elements may appear more than once [3,4]
ML Lists.1 Standard ML Lists. ML Lists.2 Lists  A list is a finite sequence of elements. [3,5,9] ["a", "list" ] []  Elements may appear more than once.
Type Checking, Inference, & Elaboration CS153: Compilers Greg Morrisett.
ML Lists.1 Standard ML Lists. ML Lists.2 Lists  A list is a finite sequence of elements. [3,5,9] ["a", "list" ] []  ML lists are immutable.  Elements.
Kathleen Fisher cs242 Reading: “A history of Haskell: Being lazy with class”,A history of Haskell: Being lazy with class Section 6.4 and Section 7 “Monads.
Exercises – don’t use built in functions for these as we want the practice Write a recursive function to add up all the numbers in a list "flatten" a list.
ML: a quasi-functional language with strong typing Conventional syntax: - val x = 5; (*user input *) val x = 5: int (*system response*) - fun len lis =
A Type System for MetaML MetaML types as an Omega program Lecture 12.
A Lightning Tour of Haskell Lecture 1, Designing and Using Combinators John Hughes.
Tim Sheard Oregon Graduate Institute Lecture 6: Monads and Interpreters CSE 510 Section FSC Winter 2004 Winter 2004.
CS 312 Spring 2004 Lecture 18 Environment Model. Substitution Model Represents computation as doing substitutions for bound variables at reduction of.
Advanced Programming Handout 12 Higher-Order Types (SOE Chapter 18)
CS 312 Spring 2002 Lecture 16 The Environment Model.
Cse536 Functional Programming 1 6/23/2015 Lecture #17, Dec. 1, 2004 Todays Topics – Higher Order types »Type constructors that take types as arguments.
Chapter 5 Polymorphic and Higher-Order Functions.
CS510AP Quick Check Monads. QuickCheck Quick check is a Haskell library for doing random testing. You can read more about quickcheck at –
Type Classes with Functional Dependencies Mark P Jones, Oregon Graduate Institute The theory of relational databases meets.
Tim Sheard Oregon Graduate Institute Lecture 6: Monadic Staging of the RE language CSE 510 Section FSC Winter 2004 Winter 2004.
CS321 Functional Programming 2 © JAS Type Checking Polymorphism in Haskell is implicit. ie the system can derive the types of all objects. This.
Advanced Functional Programming Tim Sheard 1 Lecture 14 Advanced Functional Programming Tim Sheard Oregon Graduate Institute of Science & Technology Lecture.
Advanced Functional Programming Tim Sheard 1 Lecture 6 Functional Programming Tim Sheard & Mark Jones Monads & Interpreters.
Arvind Computer Science and Artificial Intelligence Laboratory M.I.T. L06-1 September 26, 2006http:// Type Inference September.
CSE 230 The -Calculus. Background Developed in 1930’s by Alonzo Church Studied in logic and computer science Test bed for procedural and functional PLs.
Advanced Functional Programming Tim Sheard 1 Lecture 18 Advanced Functional Programming Tim Sheard Oregon Graduate Institute of Science & Technology Lecture.
0 Odds and Ends in Haskell: Folding, I/O, and Functors Adapted from material by Miran Lipovaca.
CS 2104 – Prog. Lang. Concepts Functional Programming II Lecturer : Dr. Abhik Roychoudhury School of Computing From Dr. Khoo Siau Cheng’s lecture notes.
1 CS 457/557: Functional Languages Lists and Algebraic Datatypes Mark P Jones Portland State University.
Advanced Functional Programming Tim Sheard 1 Lecture 17 Advanced Functional Programming Tim Sheard Oregon Graduate Institute of Science & Technology Lecture:
Eight languages Eight weeks How I designed and implemented a teaching OO language in 4 days.
Advanced Functional Programming Tim Sheard 1 Lecture 6 Advanced Functional Programming Tim Sheard Oregon Graduate Institute of Science & Technology Lecture.
Advanced Functional Programming Tim Sheard 1 Lecture 17 Advanced Functional Programming Tim Sheard Oregon Graduate Institute of Science & Technology Lecture.
Simon Peyton Jones, Stephanie Weirich, Richard Eisenberg, Dimitrios Vytiniotis Microsoft Research University of Pennsylvania April 2016.
Arvind Computer Science and Artificial Intelligence Laboratory M.I.T. L05-1 September 21, 2006http:// Types and Simple Type.
© M. Winter COSC 4P41 – Functional Programming Some functions id :: a -> a id x = x const :: a -> b -> a const k _ = k ($) :: (a -> b) -> a -> b.
Lesson 10 Type Reconstruction
CS5205: Foundation in Programming Languages Type Reconstruction
Set Comprehensions In mathematics, the comprehension notation can be used to construct new sets from old sets. {x2 | x  {1...5}} The set {1,4,9,16,25}
Set Comprehensions In mathematics, the comprehension notation can be used to construct new sets from old sets. {x2 | x  {1...5}} The set {1,4,9,16,25}
Functional Programming
CSE341: Programming Languages Lecture 11 Type Inference
PROGRAMMING IN HASKELL
ML: a quasi-functional language with strong typing
Functional Programming Lecture 12 - more higher order functions
A lightening tour in 45 minutes
Tim Sheard Oregon Graduate Institute
Advanced Functional Programming
Programming Languages and Compilers (CS 421)
Lecture 18 Infinite Streams and
Advanced Functional Programming
Advanced Functional Programming
CSE341: Programming Languages Lecture 11 Type Inference
CSE341: Programming Languages Lecture 11 Type Inference
SUNY-Buffalo Zhi Yang Courtesy of Greg Morrisett
Advanced Functional Programming
CSCE 314: Programming Languages Dr. Dylan Shell
PROGRAMMING IN HASKELL
CS 457/557: Functional Languages Folds
Functional Programming
CSCE 314: Programming Languages Dr. Dylan Shell
CSE341: Programming Languages Lecture 11 Type Inference
Programming Languages
PROGRAMMING IN HASKELL
PROGRAMMING IN HASKELL
CSE341: Programming Languages Lecture 11 Type Inference
PROGRAMMING IN HASKELL
PROGRAMMING IN HASKELL
CSE341: Programming Languages Lecture 11 Type Inference
Advanced Functional Programming
Presentation transcript:

Advanced Functional Programming Tim Sheard Oregon Graduate Institute of Science & Technology Lecture 5: Algorithms for Hindley-Milner type Inference

Type inference and Hindley-Milner How is type inference done? Structural recursion over a term. Uses an environment which maps variables to their types Returns a computation in a monad type infer :: Exp -> Env -> M Type What does the Env look like partial function from Name -> Scheme Scheme is an encoding of a Hindley-Milner polymorphic type. All the forall's to the outermost position. Often implemented as a list

The Inference Monad newtype IM a x = Ck (Int -> (ST a (x, String, Int))) instance Functor (IM a) where fmap f (Ck g) = Ck h where h n = do { (x, out, n') <- g n ; return (f x,out,n') } instance Monad (IM a) where return x = Ck h where h n = return (x, "", n) (Ck g) >>= f = Ck ff where ff n = do { (a, out1, n1) <- g n ; let (Ck h) = f a ; (y, out2, n2) <- h n1 ; return (y, out1 ++ out2, n2)}

Interface to IM readVar :: STRef a b -> IM a b readVar ref = Ck f where f n = do { z <- readSTRef ref ; return (z, "", n) } newVar :: x -> IM a (STRef a x) newVar init = Ck f where f n = do { z <- newSTRef init writeVar :: STRef a b -> b -> IM a () writeVar ref value = Ck f where f n = do { z <- writeSTRef ref value nextN :: IM a Int nextN = Ck f where f n = return (n, "", n+1)

Escaping the monad Since the monad is a variant of the state monad we need to escape from it: runIM :: (forall a . IM a c) -> Int -> (c,String,Int) runIM w n = let (Ck f) = w in runST (f n) force :: (forall a . IM a c) -> c force w = case (runIM w) 0 of (x, _, _) -> x Note the use of Rank 2 polymorphism

Representing Types data Type a = Tunit | Tarrow (Type a) (Type a) | Ttuple [ Type a ] | Tdata String [ Type a ] | Tgen Int | Tvar (STRef a (Maybe (Type a))) data Scheme a = Sch [Int] (Type a) forall a,b . (a,b) = Sch [1,2] (Ttuple [ Tgen 1, Tgen 2 ])

Handling Errors class Error a b where occursCk :: Type a -> Type a -> IM a b nameMtch:: Type a -> Type a -> IM a b shapeMtch:: Type a -> Type a -> IM a b tupleLenMtch:: Type a -> Type a -> IM a b

Unification unify tA tB = do { t1 <- prune1 tA ; t2 <- prune1 tB unify :: Error a [String] => Type a -> Type a -> IM a [String] unify tA tB = do { t1 <- prune1 tA ; t2 <- prune1 tB ; case (t1,t2) of (Tvar r1,Tvar r2) -> -- Both are Variables if r1==r2 then return [] else do { writeVar r1 (Just t2); return []} (Tvar r1,_) -> -- One is a Variable do { b <- occursIn1 r1 t2 ; if b then occursCk t1 t2 else do { writeVar r1 (Just t2) ; return [] } } (_,Tvar r2) -> unify t2 t1

Unification 2 ; case (t1,t2) of . . . (Tgen s, Tgen t) -> if s==t then return [] else (nameMtch t1 t2) (Tarrow x y,Tarrow m n) -> do { cs1 <- unify x m ; cs2 <- unify y n ; return (cs1 ++ cs2) } (Ttuple xs, Ttuple ys) -> if (length xs) == (length ys) then do { xss <- sequence (fmap (uncurry unify) (zip xs ys)) ; return (concat xss) } else tupleLenMtch t1 t2 (_,_) -> (shapeMtch t1 t2)

Operations on Types prune1 (typ @ (Tvar ref)) = do { m <- readVar ref ; case m of Just t -> do { newt <- prune1 t ; writeVar ref (Just newt) ; return newt } Nothing -> return typ prune1 typ = return typ Tvar(Just _ ) Tuple[ X, Y] Tvar(Just _ ) Tuple[ X, Y]

Does a ref occur in a type? occursIn1 r t = do { t2 <- prune1 t ; case t2 of Tunit -> return False Tarrow x y -> do { b1 <- occursIn1 r x ; b2 <- occursIn1 r y ; return ((||) b1 b2 ) } Ttuple xs -> do { bs <- sequence (map (occursIn1 r) xs) ; return (or bs)} Tdata name xs -> Tgen s -> return False Tvar z -> return(r == z) }

Generalizing We need to look through a type, and replace all generalizable TVar's with consistent Tgen's A TVar is generalizable if its isn't bound to something. I.e. Tvar ref and do { x <- readVar ref ; case x of Nothing -> .... and its not mentioned in the outer environment. Keep a list of pairs, pairing known generalizable Tvar's and their unique Int

Finding unique Ints genVar :: Tref a -> [(Tref a,Int)] -> IM a (Type a,[(Tref a,Int)]) genVar r [] = do { n <- nextN ; return (Tgen n,[(r,n)]) } genVar r (ps @ ((p @ (r1,n)):more)) = if r1==r then return (Tgen n,ps) else do { (t,ps2) <- genVar r more ; return (t,p:ps2)} Note we return the new extended list as well as the type (Tgen n) that corresponds to the Tvar reference

Putting it all together gen :: (Tref a -> IM a Bool) -> Type a -> [(Tref a,Int)] -> IM a (Type a,[(Tref a,Int)]) gen pred t pairs = do { t1 <- prune1 t ; case t1 of Tvar r -> do { b <- pred r ; if b then genVar r pairs else return(t1,pairs)} Tgen n -> return(t1,pairs) Tunit -> return(t1,pairs) Tarrow x y -> do { (x',p1) <- gen pred x pairs ; (y',p2) <- gen pred y p1 ; return (Tarrow x' y',p2)} Ttuple ts -> do { (ts',p) <- thread pred ts pairs ; return (Ttuple ts',p) } Tdata c ts -> do { (ts',p) <- thread pred ts pairs ; return (Tdata c ts',p) } }

Finishing up generalization thread p [] pairs = return ([],pairs) thread p (t:ts) pairs = do { (t',p1) <- gen p t pairs ; (ts',p2) <- thread p ts p1 ; return(t':ts',p2) } generalize :: (Tref a -> IM a Bool) -> Type a -> IM a (Scheme a) generalize p t = do { (t',pairs) <- gen p t [] ; return(Sch (map snd pairs) t')

Instantiation g (x::a) = let f :: forall b . b -> (a,b) freshVar = do { r <- newVar Nothing ; return (Tvar r) } -- Sch [1] (Tarrow (Tgen 1) (Ttuple [Tvar a, Tgen 1])) instantiate (Sch ns t) = do { ts <- sequence(map (\ _ -> freshVar) ns) ; let sub = zip ns ts ; subGen sub t } g (x::a) = let f :: forall b . b -> (a,b) f = \ y -> (x,y) w1 = f "z" w2 = f True in (x,f)

Substituting (Tgen n) for T subGen sub t = do { t2 <- prune1 t ; case t2 of Tunit -> return Tunit Tarrow x y -> do { b1 <- subGen sub x ; b2 <- subGen sub y ; return (Tarrow b1 b2)} Ttuple xs -> do { bs <- sequence (map (subGen sub) xs) ; return (Ttuple bs)} Tdata name xs -> ; return (Tdata name bs)} Tgen s -> return(find s sub) Tvar z -> return(Tvar z) }

Note the pattern Before we do a case analysis we always prune. gen pred t pairs = do { t1 <- prune1 t ; case t1 of . . . occursIn1 r t = do { t2 <- prune1 t ; case t2 of . . . unify tA tB = do { t1 <- prune1 tA ; t2 <- prune1 tB ; case (t1,t2) of . . . subGen sub t = ; case t2 of Tvar(Just _ ) Tuple[ X, Y] Tvar(Just _ ) Tuple[ X, Y]

Type inference Representing programs data Exp = App Exp Exp | Abs String Exp | Var String | Tuple [ Exp] | Const Int | Let String Exp Exp

infer :: Error a [String] => Exp -> [(String,Scheme a)] -> IM a (Type a) infer e env = case e of Var s -> instantiate (find s env) App f x -> do { ftyp <- infer f env ; xtyp <- infer x env ; result <- freshVar ; unify (Tarrow xtyp result) ftyp ; return result } Abs x e -> do { xtyp <- freshVar ; etyp <- infer e ((x,Sch [] xtyp):env) ; return(Tarrow xtyp etyp)

Let inference Let bound variables can be given polymorphic types if their type doesn't mention any type variables in an outer scope. generic :: [(n,Scheme a)] -> Tref a -> IM a Bool generic [] r = return True generic ((name,Sch _ typ):more) r = do { b <- occursIn1 r typ ; if b then return False else generic more r } g x = let f = ((\ y -> (x,y)) :: C1 -> (A1,C1)) w1 = f "z" w2 = f True in (x,f) {g::E1, x::A1, f::B1}

inference continued infer e env = case e of . . . Tuple es -> do { ts' <- sequence(map (\ e -> infer e env) es) ; return(Ttuple ts') } Const n -> return(Tdata "Int" []) Let x e b -> do { xtyp <- freshVar ; etyp <- infer e ((x,Sch [] xtyp):env) ; unify xtyp etyp ; schm <- generalize (generic env) etyp ; btyp <- infer b ((x,schm):env) ; return btyp

Poly morphic recursion f :: [a] -> Int f [] = 0 f (x:xs) = 1 + f xs + (f (map g xs)) where g x = [x]