Functional Programming

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

Standard prelude. Appendix A. A.1 Classes

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

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

Maybe Monad (3B) Young Won Lim 1/3/18

Applicative, traversable, foldable

A Third Look At ML. Chapter Nine Modern Programming Languages, 2nd ed. 1

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

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

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

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

Monad Overview (3B) Young Won Lim 1/16/18

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

A general introduction to Functional Programming using Haskell

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

Functional Programming

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

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

Applicative, traversable, foldable

College Functors, Applicatives

CSCE 314 Programming Languages Functors, Applicatives, and Monads

Functional Programming TDA 452, DIT 142

CS 11 Haskell track: lecture 4. n This week: Monads!

Monads. Bonus lecture 2017 David Sands

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

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

Advanced Functional Programming

Lazy Functional Programming in Haskell

Monads in Haskell. Nathanael Schilling. December 12, 2014

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

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

Programming Languages

CS 457/557: Functional Languages

CS 209 Functional Programming

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

Higher Order Functions in Haskell

Functional Programming TDA 452, DIT 142

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

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

CIS552: Advanced Programming

INTRODUCTION TO HASKELL

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

CS 320: Concepts of Programming Languages

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

Lecture 4: Higher Order Functions

Monads seen so far: IO vs Gen

CSCE 314 Programming Languages

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)

GHCi: Getting started (1A) Young Won Lim 5/31/17

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

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

Shell CSCE 314 TAMU. Higher Order Functions

Lambda-termide redutseerimine

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

Haskell Monads CSC 131. Kim Bruce

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

PROGRAMMING IN HASKELL. Chapter 5 - List Comprehensions

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

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

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

Libraries (1A) Young Won Lim 6/5/17

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

Haskell through HUGS THE BASICS

Monads. Functional Programming (CS4011) Monads

Introduction to Haskell

Logic - CM0845 Introduction to Haskell

INTRODUCTION TO FUNCTIONAL PROGRAMMING

CPL 2016, week 10. Clojure functional core. Oleg Batrashev. April 11, Institute of Computer Science, Tartu, Estonia

Principles of Programming Languages (H)

Introduction to Haskell

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

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

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

The List Datatype. CSc 372. Comparative Programming Languages. 6 : Haskell Lists. Department of Computer Science University of Arizona

CSCE 314 Programming Languages

Monads. COS 441 Slides 16

EECS 700 Functional Programming

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.

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

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

PROGRAMMING IN HASKELL. CS Chapter 6 - Recursive Functions

Shell CSCE 314 TAMU. Functions continued

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

Parallel Haskell on MultiCores and Clusters

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

Programming Languages Fall 2013

A Second Look At ML. Chapter Seven Modern Programming Languages, 2nd ed. 1

COP4020 Programming Languages. Functional Programming Prof. Robert van Engelen

Haskell Revision and Exercises

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

Advanced Type System Features Tom Schrijvers. Leuven Haskell User Group

Exercises on ML. Programming Languages. Chanseok Oh

CS 320 Midterm Exam. Fall 2018

Functional Programming and Haskell

Box-and-arrow Diagrams

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

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

More on functional programming

Embedded Domain Specific Languages in Idris Lecture 3: State, Side Effects and Resources

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

Transcription:

Functional Programming Monadic Prelude Jevgeni Kabanov Department of Computer Science University of Tartu

Introduction Previously on Functional Programming Monadic laws Monad class (>>= and return) MonadPlus class (mzero and mplus) do-notation Maybe monad List monad State monad IO monad

Overview 1 List functions 2 Conditionals 3 Lifting 4 MonadPlus functions

Introduction Overview Monad power comes from very high degree of abstraction Haskell comes with a library of functions that are dened across all monads These functions correspond to control structures in most imperartive languages In fact given the do-notation and these functions we can program in Haskell using imperative approach

Introduction Overview Monad power comes from very high degree of abstraction Haskell comes with a library of functions that are dened across all monads These functions correspond to control structures in most imperartive languages In fact given the do-notation and these functions we can program in Haskell using imperative approach

Introduction Overview Monad power comes from very high degree of abstraction Haskell comes with a library of functions that are dened across all monads These functions correspond to control structures in most imperartive languages In fact given the do-notation and these functions we can program in Haskell using imperative approach

Introduction Overview Monad power comes from very high degree of abstraction Haskell comes with a library of functions that are dened across all monads These functions correspond to control structures in most imperartive languages In fact given the do-notation and these functions we can program in Haskell using imperative approach

Outline 1 List functions 2 Conditionals 3 Lifting 4 MonadPlus functions

sequence denition Monadic Prelude sequence_ :: Monad m ) [m a ]! m () sequence_ = foldr (>>) (return ()) sequence :: Monad m ) [m a ]! m [a ] sequence = foldr mcons (return [ ]) where mcons p q = p >>= x! q >>= y! return (x : y)

sequence example sequence Monads> sequence [print 1, print 2, print a ] 1 2 a *Monads> it [(),(),()] *Monads> sequence_ [print 1, print 2, print a ] 1 2 a *Monads> it ()

sequence sequence example 3 Prelude> sequence [Just 1, Just 2, Nothing, Just 3]

sequence sequence example 3 Prelude> sequence [Just 1, Just 2, Nothing, Just 3] Nothing Maybe is assymmetrical with respect to nothing!

mapm mapm denition mapm :: Monad m ) (a! m b)! [a ]! m [b ] mapm f as = sequence (map f as) mapm _ :: Monad m ) (a! m b)! [a ]! m () mapm _ f as = sequence_ (map f as)

mapm mapm example 1 Monads> mapm_ print [1,2,3,4,5] 1 2 3 4 5 mapm example 2 putstring :: [Char ]! IO () putstring s = mapm _ putchar s

form form denition form :: Monad m ) [a ]! (a! m b)! m [b ] form = ip mapm form _ :: Monad m ) [a ]! (a! m b)! m () form _ = ip mapm _ form _ example main = do form _ [1 : : 10] (i! print i )

lterm lterm denition lterm :: Monad m ) (a! m Bool)! [a ]! m [a ] lterm p [ ] = return [ ] lterm p (x : xs) = do b p x ys lterm p xs return (if b then (x : ys) else ys) lterm example main = do names getargs dirs lterm doesdirectoryexist names mapm _ putstrln dirs

foldm foldm denition foldl :: (a! b! a)! a! [b ]! a foldl f z [ ] = z foldl f z (x : xs) = foldl f (f z x ) xs foldm :: (Monad m) ) (a! b! m a)! a! [b ]! m a foldm f a [ ] = return a foldm f a (x : xs) = f a x >>= y! foldm f y xs Note that we lift the result of all functions under the monad.

foldm foldm explanation foldm f a1 [x1 ; x2 ; :::; xn ] = do a2 f a1 x1 a3 f a2 x2 ::: f an xn

foldm foldm example Monads> foldm (\a b -> putstrln (show a ++ "+" ++ show b ++ "=" ++ show (a+b))» return (a+b)) 0 [1..5] 0+1=1 1+2=3 3+3=6 6+4=10 10+5=15 Monads> it 15

foldm foldm example 2 data Sheep = Sheepfname :: String; mother :: Maybe Sheep; father :: Maybe Sheep g dolly :: Sheep dolly = let adam = Sheep "Adam" Nothing Nothing eve = Sheep "Eve" Nothing Nothing uranus = Sheep "Uranus" Nothing Nothing gaea = Sheep "Gaea" Nothing Nothing kronos = Sheep "Kronos" (Just gaea) (Just uranus) holly = Sheep "Holly" (Just eve) (Just adam) roger = Sheep "Roger" (Just eve) (Just kronos) molly = Sheep "Molly" (Just holly) (Just roger ) in Sheep "Dolly" (Just molly) Nothing

foldm foldm example 2 Output: tracefamily :: [(Sheep! Maybe Sheep)]! Sheep! Maybe Sheep tracefamily l s = foldm (ip ($)) s l paternalgrandmother = tracefamily [ father ; mother ] motherspaternalgrandfather = tracefamily [mother ; father ; father ] *Main> paternalgrandmother dolly Nothing *Main> motherspaternalgrandfather dolly Just "Kronos"

foldm Map denition data Map k a empty :: Map k a insert :: Ord k ) k! a! Map k a! Map k a lookup :: (Monad m; Ord k ) ) k! Map k a! m a tolist :: Map k a! [(k ; a)]

foldm foldm example 3 data Entry = Entryfkey :: String; value :: String g type Dict = Map String String addentry :: Dict! Entry! Dict addentry d e = insert (key e) (value e) d adddatafromfile :: Dict! Handle! IO Dict adddatafromfile dict hdl = do contents hgetcontents hdl entries return (map read (lines contents)) return (foldl (addentry) dict entries)

foldm foldm example 3 main :: IO () main = do les getargs handles mapm openforreading les dict foldm adddatafromfile empty handles print (tolist dict )

join join denition join :: (Monad m) ) m (m a)! m a join x = x >>= id Note that x >>= f = (join fmap f ) x. join example Monads> join (Just (Just a )) Just a Monads> join (return (putstrln "hello")) hello Monads> return (putstrln "hello") Monads> join [[1,2,3],[4,5]] [1,2,3,4,5]

Outline 1 List functions 2 Conditionals 3 Lifting 4 MonadPlus functions

when and unless denition when when :: (Monad m) ) Bool! m ()! m () when p s = if p then s else return () unless :: (Monad m) ) Bool! m ()! m () unless p s = when (: p) s when example Monads> mapm_ (\l -> when (not $ null l) (putstrln l)) ["","abc","def","","","ghi"] abc def ghi

Outline 1 List functions 2 Conditionals 3 Lifting 4 MonadPlus functions

liftm and liftm2 denition liftm liftm :: (Monad m) ) (a! b)! (m a! m b) liftm f = a! do fa 0 a; return (f a 0 )g liftm2 :: (Monad m) ) (a! b! c)! (m a! m b! m c) liftm2 f = a b! do fa 0 a; b 0 b; return (f a 0 b 0 )g Lifting allows to apply pure functions point-free to monadic values Together with monadic bind it constitutes a functional approach as apposed to the do-notation

liftm and liftm2 denition liftm liftm :: (Monad m) ) (a! b)! (m a! m b) liftm f = a! do fa 0 a; return (f a 0 )g liftm2 :: (Monad m) ) (a! b! c)! (m a! m b! m c) liftm2 f = a b! do fa 0 a; b 0 b; return (f a 0 b 0 )g Lifting allows to apply pure functions point-free to monadic values Together with monadic bind it constitutes a functional approach as apposed to the do-notation

liftm and liftm2 denition liftm liftm :: (Monad m) ) (a! b)! (m a! m b) liftm f = a! do fa 0 a; return (f a 0 )g liftm2 :: (Monad m) ) (a! b! c)! (m a! m b! m c) liftm2 f = a b! do fa 0 a; b 0 b; return (f a 0 b 0 )g Lifting allows to apply pure functions point-free to monadic values Together with monadic bind it constitutes a functional approach as apposed to the do-notation

liftm liftm example 1 getname :: String! Maybe String getname name = do let db = [("John"; "Smith, John"); ("Mike"; "Caine, Michael")] tempname lookup name db return (swapnames tempname) Can be rewritten as: getname name = do let db = ::: liftm swapnames (lookup name db)

liftm liftm example 2 adddatafromfile :: Dict! Handle! IO Dict adddatafromfile dict hdl = do contents hgetcontents hdl entries return (map read (lines contents)) return (foldl (addentry) dict entries) Can be rewritten as: adddatafromfile dict = liftm (foldl addentry dict map read lines) hgetcontents

liftm liftm2 example 1 What does this do? allcombinations :: (a! a! a)! [[a ]]! [a ] allcombinations fn [ ] = [ ] allcombinations fn (l : ls) = foldl (liftm2 fn) l ls

liftm liftm2 example 1 What does this do? allcombinations :: (a! a! a)! [[a ]]! [a ] allcombinations fn [ ] = [ ] allcombinations fn (l : ls) = foldl (liftm2 fn) l ls Output Main> allcombinations (+) [[0,1],[1,2,3]] [0+1,0+2,0+3,1+1,1+2,1+3] = [1,2,3,2,3,4] Main> allcombinations (*) [[0,1],[1,2],[3,5]] [0+1,0+2,0+3,1+1,1+2,1+3] = [0,0,0,0,3,5,6,10]

ap ap denition ap helps when both function and argument are in the monad. ap :: (Monad m) ) m (a! b)! m a! m b ap = liftm2 ($) Note that liftm2 f x y is equivalent to return f `ap` x `ap` y. Output Main> [(*2),(+3)] ap [0,1,2] [0,2,4,3,4,5] Main> (Just (*2)) ap (Just 3) Just 6

ap ap example words :: String! [String ] lookup :: (Eq a) ) a! [(a; b)]! Maybe b ap :: (Monad m) ) m (a! b)! m a! m b main = do let fns = [("double"; (2 )); ("halve"; (`div `2)); ("square"; (x! x x )); ("negate"; negate); ("incr"; (+1)); ("decr"; (+( 1)))] args getargs let val = read (args!! 0) cmds = map ((ip lookup) fns) (words (args!! 1)) print $ foldl (ip ap) (Just val) cmds

Outline 1 List functions 2 Conditionals 3 Lifting 4 MonadPlus functions

msum msum denition class Monad m ) MonadPlus m where mzero :: m a mplus :: m a! m a! m a msum :: MonadPlus m ) [m a ]! m a msum xs = foldr mplus mzero xs

msum msum example type Variable = String type Value = String type EnvironmentStack = [[(Variable; Value)]] lookupvar :: Variable! EnvironmentStack! Maybe Value lookupvar var stack = msum $ map (lookup var ) stack

guard guard denition guard :: MonadPlus m ) Bool! m () guard p = if p then return () else mzero guard example data Record = Recfname :: String; age :: Int g type DB = [Record ] getyoungerthan :: Int! DB! [Record ] getyoungerthan limit db = mapmaybe (r! do fguard (age r < limit ); return r g) db

List comprehensions Syntax 1 list = [r x1 <- xs1, x2 <- xs2,..., b1, b2,...] Syntax 2 list = do x1 <- xs1 x2 <- xs2... guard b1 guard b2... return r