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

Similar documents
Informatics 1 Functional Programming Lectures 15 and 16. IO and Monads. Don Sannella University of Edinburgh

Informatics 1 Functional Programming 19 Tuesday 23 November IO and Monads. Philip Wadler University of Edinburgh

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

Standard prelude. Appendix A. A.1 Classes

Functional Programming

References. Monadic I/O in Haskell. Digression, continued. Digression: Creating stand-alone Haskell Programs

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

CSCE 314 Programming Languages. Interactive Programming: I/O

Applicative, traversable, foldable

CSCE 314 Programming Languages Functors, Applicatives, and Monads

Using Monads for Input and Output

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

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

Programming Languages

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

Applicative, traversable, foldable

Overview. Declarative Languages. General monads. The old IO monad. Sequencing operator example. Sequencing operator

More on functional programming

All About Monads A comprehensive guide to the theory and practice of monadic programming in Haskell Version 1.1.0

Introduction to Haskell

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

Monads and all that III Applicative Functors. John Hughes Chalmers University/Quviq AB

Monads. COS 441 Slides 16

PROGRAMMING IN HASKELL. Chapter 10 - Interactive Programming

INTRODUCTION TO HASKELL

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

Software System Design and Implementation

Programming in Haskell Aug Nov 2015

CS 457/557: Functional Languages

IO Monad (3D) Young Won Lim 1/18/18

Haskell Monads CSC 131. Kim Bruce

Monads in Haskell. Nathanael Schilling. December 12, 2014

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

CS 440: Programming Languages and Translators, Spring 2019 Mon 2/4

JVM ByteCode Interpreter

CS 320 Midterm Exam. Fall 2018

Monads. Functional Programming (CS4011) Monads

Haskell. COS 326 Andrew W. Appel Princeton University. a lazy, purely functional language. slides copyright David Walker and Andrew W.

I/O in Haskell. To output a character: putchar :: Char -> IO () e.g., putchar c. To output a string: putstr :: String -> IO () e.g.

Monadic Parsing. 1 Chapter 13 in the book Programming in Haskell (2nd ed.) by. 2 Chapters 10 and 16 in the book Real World Haskell by Bryan

CS 457/557: Functional Languages

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

It is better to have 100 functions operate one one data structure, than 10 functions on 10 data structures. A. Perlis

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

CS 320: Concepts of Programming Languages

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

Lambda-termide redutseerimine

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

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

Functional Programming for Logicians - Lecture 1

IO Monad (3C) Young Won Lim 8/23/17

EECS 700 Functional Programming

Principles of Programming Languages (H)

Topic of today: memoization. The string alignment problem. Optimality of an alignment. EDAN40: Functional Programming Assignment 2: String alignment

Lecture 4: Higher Order Functions

3. Functional Programming. Oscar Nierstrasz

Monad Background (3A) Young Won Lim 10/5/17

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

EDAF40. 2nd June :00-19:00. WRITE ONLY ON ONE SIDE OF THE PAPER - the exams will be scanned in and only the front/ odd pages will be read.

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

Types in Programming Languages Dynamic and Static Typing, Type Inference (CTM 2.8.3, EPL* 4) Abstract Data Types (CTM 3.7) Monads (GIH** 9)

A Study In Monads Leif Harald Karlsen Master s Thesis Autumn 2013

IO Monad (3C) Young Won Lim 1/6/18

INTRODUCTION TO FUNCTIONAL PROGRAMMING

CSC312 Principles of Programming Languages : Functional Programming Language. Copyright 2006 The McGraw-Hill Companies, Inc.

Box-and-arrow Diagrams

Advanced Functional Programming

A general introduction to Functional Programming using Haskell

PROGRAMMING IN HASKELL. Chapter 5 - List Comprehensions

INDEX. Symbols & Numbers. Learn You a Haskell for Great Good! 2011 by Miran Lipovača

Applicatives Comparisons (2C) Young Won Lim 3/6/18

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

Haskell An Introduction

1 Delimited continuations in Haskell

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

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

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

CS 209 Functional Programming

I/O in Purely Functional Languages. Stream-Based I/O. Continuation-Based I/O. Monads

Functional Programming TDA 452, DIT 142

Maybe Monad (3B) Young Won Lim 12/21/17

CIS552: Advanced Programming

Haskell Modules. Input and Output. Urtė Zubkaitė

College Functors, Applicatives

Introduction to Functional Programming and Haskell. Aden Seaman

CS 320: Concepts of Programming Languages

Principles of Programming Languages, 3

Haskell Revision and Exercises

Monads. Bonus lecture 2017 David Sands

CSCE 314 Programming Languages

Functional Programming TDA 452, DIT 142

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

Monads seen so far: IO vs Gen

An introduction introduction to functional functional programming programming using usin Haskell

PROGRAMMING IN HASKELL. CS Chapter 6 - Recursive Functions

CS 360: Programming Languages Lecture 10: Introduction to Haskell

GHCi: Getting started (1A) Young Won Lim 6/3/17

CS 11 Haskell track: lecture 1

COP4020 Programming Languages. Functional Programming Prof. Robert van Engelen

Programming with Math and Logic

Transcription:

Monad class EDAN40: Functional Programming Functors and Monads Jacek Malec Dept. of Computer Science, Lund University, Sweden April 23rd, 2018 Motivation: Separation of pure and impure code Properties of a particular kind of functions Introduction of state and its transformations Or simply: yet another type class For more material: see the course web. Jacek Malec, http://rss.cs.lth.se 1(41) Jacek Malec, http://rss.cs.lth.se 2(41) The functional IO problem Example: Lambda laughter IO has traditionally been included as side effects to ordinary functions: inputint :: Int then substituting equals for equals is no longer possible inputdiff = inputint - inputint probably not equal to zero Suppose the function: outputchar :: char -> () has the side effect of printing its argument. The expression (note: pseudo-haskell): outputchar h ; outputchar a ; outputchar h ; outputchar a Should then print the string "haha". Jacek Malec, http://rss.cs.lth.se 3(41) Jacek Malec, http://rss.cs.lth.se 4(41)

Lambda laughter, cont. Lambda laughter, cont. If we then try to catch the repetitive pattern by instead writing: let x = (outputchar h ; outputchar a ) in x; x then the laugh is on us (P. Wadler). It will print only "ha". Why? If we then try to catch the repetitive pattern by instead writing: let x = (outputchar h ; outputchar a ) in x; x then the laugh is on us (P. Wadler). It will print only "ha". Why? However, the following (note: pseudo-haskell): let f() = (outputchar h ; outputchar a ) in f(); f() will print the string "haha". Jacek Malec, http://rss.cs.lth.se 5(41) Jacek Malec, http://rss.cs.lth.se 5(41) The IO Monad The do-notation The type of IO activities: prompt :: IO () prompt = putstr ">:" The type of IO activities that return a value: getchar :: IO Char getline :: IO String Allows sequencing and naming the returned values: echoreverse :: IO () echoreverse = do aline <- getline putstrln (reverse aline) Jacek Malec, http://rss.cs.lth.se 6(41) Jacek Malec, http://rss.cs.lth.se 7(41)

return and let The return operation does the empty IO-activity: getint :: IO Int getint = do aline <- getline return (read aline :: Int) Local variables may be defined using let: echoreverse2 :: IO () echoreverse2 = do aline <- getline let thelinereversed = reverse aline putstrln (thelinereversed) Imperative style One can e.g. use the conditional clause: testpalindrome :: IO () testpalindrome = do prompt aline <- getline if (aline == (reverse aline)) then putstrln "Yes, a palindrome." else putstrln "No, no!" Jacek Malec, http://rss.cs.lth.se 8(41) Jacek Malec, http://rss.cs.lth.se 9(41) Loops done with recursion Monadic lambda laughter testpalindroms :: IO () testpalindroms = do prompt aline <- getline if (aline == "") then return () else do if (aline == (reverse aline)) then putstrln "Yes, a palindrome." else putstrln "No, no!" testpalindroms The IO monad gives type-safe laughters: laugh :: IO () laugh = let x = do putchar h ; putchar a in do x; x Jacek Malec, http://rss.cs.lth.se 10(41) Jacek Malec, http://rss.cs.lth.se 11(41)

IO-stripping Back door IO stripping is not allowed (at least officially:-) because if you could strip off side effects with: stripio :: IO a -> a then the following code inputint :: Int inputint = iostrip getint inputdiff = inputint - inputint In the module System.IO.Unsafe there actually is unsafeperformio :: IO a -> a behaving as expected. However: it is NOT type-safe; you could coerce any type to any other type using unsafeperformio! FORGET IT IMMEDIATELY! would violate equals for equals principle. Jacek Malec, http://rss.cs.lth.se 12(41) Jacek Malec, http://rss.cs.lth.se 13(41) Monad class (again) Composing functions Composing functions is simple: Motivation: Separation of pure and impure code Properties of a particular kind of functions Introduction of state and its transformations Or simply: yet another type class f :: a -> b g :: b -> c then g and f may be composed to g.f. But suppose: f :: a -> Maybe b g :: b -> Maybe c then how to compose g and f? And what will it mean? Jacek Malec, http://rss.cs.lth.se 14(41) Jacek Malec, http://rss.cs.lth.se 15(41)

Composing functions Functor (reminder) Yet another example: children :: Person -> [Person] grandchildren :: Person -> [Person] then almost grandchildren = children.children but not exactly. class Functor f where fmap :: (a -> b) -> f a -> f b Please note that instance Functor IO where fmap f action = do result <- action return (f result) Jacek Malec, http://rss.cs.lth.se 16(41) Jacek Malec, http://rss.cs.lth.se 17(41) More functors An example of its utility: import Data.Char import Data.List fmaptest = do line <- fmap (intersperse -. reverse. map toupper) getline putstrln line Jacek Malec, http://rss.cs.lth.se 18(41) More functors An example of its utility: import Data.Char import Data.List fmaptest = do line <- fmap (intersperse -. reverse. map toupper) getline putstrln line Slightly more complicated: ghci> let a = fmap (*) [1,2,3,4] ghci> :t a a :: [Integer -> Integer] ghci> fmap (\f -> f 9) a [9,18,27,36] Jacek Malec, http://rss.cs.lth.se 18(41)

Applicative functors class (Functor f) => Applicative f where pure :: a -> f a (<*>) :: f (a -> b) -> f a -> f b instance Applicative Maybe where pure = Just Nothing <*> _ = Nothing (Just f) <*> something = fmap f something Jacek Malec, http://rss.cs.lth.se 19(41) Applicative functors: examples ghci> Just (+3) <*> Just 9 Just 12 ghci> pure (+3) <*> Just 10 Just 13 ghci> pure (+3) <*> Just 9 Just 12 ghci> Just (++"hahah") <*> Nothing Nothing ghci> Nothing <*> Just "woot" Nothing ghci> pure (+) <*> Just 3 <*> Just 5 Just 8 ghci> pure (+) <*> Just 3 <*> Nothing Nothing ghci> pure (+) <*> Nothing <*> Just 5 Nothing Jacek Malec, http://rss.cs.lth.se 20(41) Some more... So we can apply: pure fn <*> x <*> y <*>... Considering that pure fn <*> x equals fmap fn x we can write instead fmap fn x <*> y <*>... or even more cleanly: (<$>) :: (Functor f) => (a -> b) -> f a -> f b fn <$> x = fmap fn x fn <$> x <*> y <*>... ghci> [(+),(*)] <*> [1,2] <*> [3,4] [4,5,5,6,3,4,6,8] Jacek Malec, http://rss.cs.lth.se 21(41) Rounding up instance Applicative [] where pure x = [x] fs <*> xs = [f x f <- fs, x <- xs] instance Applicative IO where pure = return a <*> b = do f <- a x <- b return (f x) Jacek Malec, http://rss.cs.lth.se 22(41)

The Monad class Just a word on return, again 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 -- Minimal complete definition: -- (>>=), return m >> k = m >>= \_ -> k fail s = error s return is a bad name! main = do s <- getline return () putstrln s works as charm! Operations >>= (bind) and >> are (by some) pronounced then. Jacek Malec, http://rss.cs.lth.se 23(41) Jacek Malec, http://rss.cs.lth.se 24(41) The MonadPlus class The identity monad class (Monad m) => MonadPlus m where mzero :: m a mplus :: m a -> m a -> m a Algebraically: a monoid data Id a = Id a instance Monad Id where return x = Id x (Id x) >>= f = f x Jacek Malec, http://rss.cs.lth.se 25(41) Jacek Malec, http://rss.cs.lth.se 26(41)

The List monad The Maybe monad instance Monad [] where return x = [x] xs >>= f = concat (map f xs) fail s = [] instance MonadPlus [ ] where mzero = [] mplus = (++) instance Monad Maybe where return x = Just x Just x >>= f = f x Nothing >>= f = Nothing instance MonadPlus Maybe where mzero = Nothing Nothing mplus ys = ys xs mplus ys = xs From the assignment (by atp08mla): singlewildcardmatch (wc:ps) (x:xs) = match wc ps xs >> Just [x] Jacek Malec, http://rss.cs.lth.se 27(41) Jacek Malec, http://rss.cs.lth.se 28(41) The do-notation List comprehensions do-expressions are just syntactic sugar for >>= or >>: echoreverse = do aline <- getline putstrln (reverse aline) is just echoreverse = getline >>= \aline -> putstrline (reverse aline) Reverse do-notation: list1 = [ (x,y) x<-[1..], y<-[1..x]] list2 = do x <- [1..] y <- [1..x] return (x,y) Jacek Malec, http://rss.cs.lth.se 29(41) Jacek Malec, http://rss.cs.lth.se 30(41)

Monad class Monadic Modularity A simple random number generator: Motivation: Separation of pure and impure code Properties of a particular kind of functions Introduction of state and its transformations Or simply: yet another type class g :: Integer -> (Float, Integer) g seed = (frominteger(newseed)/frominteger(m), newseed) where newseed = (seed*a) mod m a = 1812433253 m = 2^32 initialseed = 3121281023 Jacek Malec, http://rss.cs.lth.se 31(41) Jacek Malec, http://rss.cs.lth.se 32(41) Usage A generalisation attempt (a, s1) = g initialseed (b, s2) = g s1 (c, s3) = g s2 (xs, s4) = (values, last seeds) where (values, seeds) = (unzip.take 17.tail) (iterate (g.snd) (dummy, s3)) dummy = 45.0 newtype RandomGenerator a = Ran (Integer -> (a, Integer)) random = Ran g generate (Ran f) = (fst.f) initialseed Quite clumsy. Jacek Malec, http://rss.cs.lth.se 33(41) Jacek Malec, http://rss.cs.lth.se 34(41)

The Random monad type R = RandomGenerator instance Monad RandomGenerator where return :: a -> R a return x = Ran (\seed -> (x, seed)) (>>=) :: R a -> (a -> R b) -> R b (Ran g0) >>= f = Ran (\seed -> let (y, seed1) = g0 seed (Ran g1) = f y in g1 seed1) Using the random monad randoms3 = do a <- random b <- random c <- random return (a,b,c) result3 = generate randoms3 randomlist 0 = return [] randomlist n = do x <- random xs <- randomlist (n-1) return (x:xs) Jacek Malec, http://rss.cs.lth.se 35(41) Jacek Malec, http://rss.cs.lth.se 36(41) resultlist = generate (randomlist 17) do-notation, again The pattern randompair = do a <- random b <- random return (a,b) is equivalent to State transformation and value generation randompair = random >>= \a -> random >>= \b -> return (a,b) or randompair = random >>= (\a -> random >>= (\b -> return (a,b))) Jacek Malec, http://rss.cs.lth.se 37(41) Jacek Malec, http://rss.cs.lth.se 38(41)

Another state transformation example type Dictionary = [(String,String)] dictadd key value dict = (key, value):dict dictfind key dict = lookup key dict Passing state without side effects is clumsy: result1 = r where d1 = dictadd "no" "norway" [] d2 = dictadd "se" "sweden" d1 r1 = dictfind "fr" d2 d3 = dictadd "fr" "france" d2 r = dictfind "fr" d3 Jacek Malec, http://rss.cs.lth.se 39(41) The StateTransform monad newtype StateTransform s a = ST (s -> (s,a)) apply (ST f) = f instance Monad (StateTransform s) where return x = ST $ \s -> (s, x) x >>= f = ST $ \s0 -> let (s1,y) = apply x s0 in (apply (f y)) s1 stateupdate :: (s -> s) -> StateTransform s () stateupdate u = ST $ \s -> (u s, ()) statequery :: (s -> a) -> StateTransform s a statequery q = ST $ \s -> (s, q s) runst s t = apply t s Jacek Malec, http://rss.cs.lth.se 40(41) Dictionary example again Monad class type DictMonad = StateTransform Dictionary result2 = snd (runst [] dictm) where dictm :: DictMonad (Maybe String) dictm = do stateupdate (dictadd "no" "norway") stateupdate (dictadd "se" "sweden") r1 <- statequery (dictfind "fr") stateupdate (dictadd "fr" "france") r <- statequery (dictfind "fr") Motivation: Separation of pure and impure code Properties of a particular kind of functions Introduction of state and its transformations Or simply: yet another type class State passing becomes invisible: robustness. Jacek Malec, http://rss.cs.lth.se 41(41) Jacek Malec, http://rss.cs.lth.se 42(41)

Re: definition Kleisli triple 1 A type construction: for type a create Ma 2 A unit function a! Ma (return in Haskell) 3 A binding operation of polymorfic type Ma! (a! Mb)! Mb. Four stages (informally): 1 The monad-related structure on the first argument is "pierced" to expose any number of values in the underlying type a. 2 The given function is applied to all of those values to obtain values of type (M b). 3 The monad-related structure on those values is also pierced, exposing values of type b. 4 Finally, the monad-related structure is reassembled over all of the results, giving a single value of type (M b). Re: definition Monad axioms: 1 return acts as a neutral element of >>=. (return x) >>= f, fx m >>= return, m 2 Binding two functions in succession is the same as binding one function that can be determined from them. (m >>= f ) >>= g, m >>= x.(f x>>= g) Jacek Malec, http://rss.cs.lth.se 43(41) Jacek Malec, http://rss.cs.lth.se 44(41) Re: definition Example We can restate it in a cleaner way (Thomson). Define (>@>) :: Monad m => (a -> m b) -> (b -> m c) -> (a -> m c) f >@> g = \x -> (f x) >>= g Now, the monad axioms may be written as: return >@> f = f f >@> return = f (f >@> g) >@> h = f >@> (g >@> h) a = do x <- [3..4] [1..2] return (x, 42) is equivalent to a = [3..4] >>= (\x -> [1..2] >>= (\_ -> return (x, 42))) Thus, remembering that instance Monad [] where m >>= f = concatmap f m return x = [x] fail s = [] Jacek Malec, http://rss.cs.lth.se 45(41) Jacek Malec, http://rss.cs.lth.se 46(41)

Example, cont. The transformations may be reduced as follows: a = [3..4] >>= (\x -> [1..2] >>= (\_ -> return (x, 42))) a = [3..4] >>= (\x -> concatmap (\_ -> return (x, 42)) [1..2]) a = [3..4] >>= (\x -> [(x,42),(x,42)] ) a = concatmap (\x -> [(x,42),(x,42)] ) [3..4] a = [(3,42),(3,42),(4,42),(4,42)] Jacek Malec, http://rss.cs.lth.se 47(41)