Exploring Languages
with Interpreters
and Functional Programming

Chapter 16
Haskell Function Concepts

H. Conrad Cunningham

15 October 2018

Copyright (C) 2017, 2018, H. Conrad Cunningham

Acknowledgements: I originally created these slides in Fall 2017 to accompany what is now Chapter 16, Haskell Function Concepts, in the 2018 version of the textbook Exploring Languages with Interpreters and Functional Programming.

Browser Advisory: The HTML version of this document may require use of a browser that supports the display of MathML. A good choice as of October 2018 is a recent version of Firefox from Mozilla.

Code: The Haskell module for this chapter is in FunctionConcepts.hs.

Haskell Function Concepts

Lecture Goals

Strictness (1)

Strictness (2)

    two :: a -> Int 
    two x = 2  -- argument not evaluated

    reverse' :: [a] -> [a]  -- reverse
    reverse xs = rev xs []  -- must eval xs
                  where rev []     ys = ys 
                        rev (x:xs) ys = rev xs (x:ys)

Strictness (3)

    (++) :: [a] -> [a] -> [a] 
    [] ++ xs     = xs   -- 2nd arg not evaluated
    (x:xs) ++ ys = x:(xs ++ ys)

    (&&), (||) :: Bool -> Bool -> Bool 
    False && x = False  -- 2nd arg not evaluated 
    True  && x = x 

    False || x = x      -- 2nd arg not evaluated 
    True  || x = True

Currying/Partial Application (1)

    add :: (Int,Int) -> Int 
    add (x,y) = x + y 

    add' :: Int -> (Int -> Int) 
    add' x y  = x + y 

Currying/Partial Application (2)

    doublePos3 :: [Int] -> [Int]  -- Prelude map, filter
    doublePos3 xs = map ((*) 2) (filter ((<) 0) xs) 

Property of Extensionality

    f, g :: a -> a
    f x = some_expression
    g x = f x  -- one definition

    g = f      -- equivalent definition

Operator Section Motivation

Operator Section Definition

Operator section (syntactic sugar):

For infix operator \oplus and expression e:

  • (e \oplus) represents ((\oplus) e)

  • ( \oplus e) represents (flip ( \oplus) e)

Operator Section Examples

    sumCubes :: [Int] -> Int 
    sumCubes xs = sum' (map (^3) xs)

    sum' = foldl' (+) 0  -- sum 

Combinator Definition

Combinator:
function without any free variables
    flip' :: (a -> b -> c) -> b -> a -> c  -- flip in Prelude 
    flip' f x y = f y x                    -- C combinator

    const' :: a -> b -> a  -- const in Prelude
    const' k x = k         --   constant function constructor
                           --   K combinator

    id' :: a -> a          -- id in Prelude 
    id' x = x              --   identity function
                           --   I combinator

Tuple Selector Combinators

    fst' :: (a,b) -> a     -- fst in Prelude 
    fst' (x,_) = x 

    snd' :: (a,b) -> b     -- snd in Prelude 
    snd' (_,y) = y 

Reverse Using Combinator

    reverse' :: [a] -> [a]           -- reverse in Prelude
    reverse' = foldlX (flip (:)) [] -- foldl, flip

Curry and Uncurry Combinators

    curry' :: ((a, b) -> c) -> a -> b -> c -- curry in Prelude 
    curry' f x y =  f (x, y) 

    uncurry' :: (a -> b -> c) -> ((a, b) -> c) -- uncurry in Prelude 
    uncurry' f p =  f (fst p) (snd p) 

Fork and Cross Combinators

    fork :: (a -> b, a -> c) -> a -> (b,c)
    fork (f,g) x = (f x, g x)

    cross :: (a -> b, c -> d) -> (a,c) -> (b,d)
    cross (f,g) (x,y) = (f x, g y)

Functional Composition

    infixr 9 . 
    (.) :: (b -> c) -> (a -> b) -> (a -> c) 
    (f . g) x = f (g x) 
     f . (g . h) = (f . g) . h  -- associative
     id . f  = f . id           -- "id" is identity 

Pointful and Point-Free Styles

Pointful style — gives parameters explicitly

    doit x = f1 (f2 (f3 (f4 x))) 

Point-free style — leaves parameters implicit

    doit = f1 . f2 . f3 . f4 

Function Pipelines (1)

    count :: Int -> [[a]] -> Int 
    count n           -- point-free expression below defines pipeline
        | n >= 0    = length . filter (== n) . map length
        | otherwise = const 0   -- discard 2nd arg, return 0 

Function Pipelines (2)

    doublePos3 xs = map ((*) 2) (filter ((<) 0) xs) 

Above re-expressed in point-free style below

    doublePos4 :: [Int] -> [Int] 
    doublePos4 = map (2*) . filter (0<)

Function Pipelines (3)

    last' = head . reverse            -- last in Prelude
    init' = reverse . tail . reverse  -- init in Prelude

“Quick and dirty” function pipeline more efficient if implemented directly

    last2 :: [a] -> a    -- last in Prelude
    last2 [x]    = x 
    last2 (_:xs) = last2 xs 

    init2 :: [a] -> [a]  -- init in Prelude
    init2 [x]    = [] 
    init2 (x:xs) = x : init2 xs 

Function Pipelines (4)

    any', all' :: (a -> Bool) -> [a] -> Bool 
    any' p = or . map p   -- any in Prelude
    all' p = and . map p  -- all in Prelude

    elem', notElem' :: Eq a => a -> [a] -> Bool 
    elem'    = any . (==)  -- elem in Prelude
    notElem' = all . (/=)  -- notElem in Prelude
elem’ x xs
\Longrightarrow { expand elem’ }
(any . (==)) x xs
\Longrightarrow { expand composition }
any ((==) x) xs

Lambda Expression Motivation

    squareAll2 :: [Int] -> [Int] 
    squareAll2 xs = map sq xs 
                    where sq x = x * x 

Above from earlier can be re-expressed in point-free style

    squareAll3 :: [Int] -> [Int] 
    squareAll3 = map (\x -> x * x) 

Lambda Expression Examples

    import Data.List ( foldl' )
    length4 :: [a] -> Int   -- length in Prelude
    length4  = foldl' (\n _ -> n+1) 0

Application Operator $ (1)

Function application associates to left with highest binding power

    w + f x y * z 

    w + (((f x) y) * z) -- same as above

Sometimes want it to associate to right with lowest binding power

    infixr 0 $

    ($) :: (a -> b) -> a -> b 
    f $ x = f x

Application Operator $ (2)

For one-argument functions f, g, and h

    f $ g $ h $ z + 7

    (f (g (h (z+7))))  -- same as above

    (f . g . h) (z+7)  -- same as above

For two-argument functions f', g', and h'

    f' w $ g' x $ h' y $ z + 7

    ((f' w) ((g' x) ((h' y) (z+7)))) -- same as above

    (f' w . g' x . h' y) (z+7)

Application Operator $ (3)

    foldr (+) 0 $ map (2*) $ filter odd $ enumFromTo 1 20

Eager Evaluation

Eager Evaluation Using seq (1)

    seq :: a -> b -> b
    x `seq` y = y

Eager Evaluation Using seq (2)

    foldlP :: (a -> b -> a) -> a -> [b] -> a  -- foldl' in Data.List 
    foldlP f z []     = z                     -- optimized
    foldlP f z (x:xs) = y `seq` foldl' f y xs 
                        where y = f z x

Eager Evaluation Using $! (1)

    infixr 0 $! 
    ($!) :: (a -> b) -> a -> b 
    f $! x = x `seq` f x 
    foldlQ :: (a -> b -> a) -> a -> [b] -> a  -- foldl' in Data.List 
    foldlQ f z []     = z                     -- optimized
    foldlQ f z (x:xs) = (foldlQ f $! f z x) xs

Eager Evaluation Using $! (2)

    sum4 :: [Integer] -> Integer  -- sum in Prelude
    sum4 xs = sumIter xs 0        -- tail recursive
        where sumIter []     acc = acc
              sumIter (x:xs) acc = sumIter xs (acc+x)
    sum5 :: [Integer] -> Integer -- sum in Prelude
    sum5 xs = sumIter xs 0 
        where sumIter []     acc = acc
              sumIter (x:xs) acc = sumIter xs $! acc + x

Eager Evaluation Caution

Key Ideas

Source Code

The Haskell module for this chapter is in FunctionConcepts.hs.