Recursion on Lists

recommended: or, all, filter, partition, group, foldr, splitAll challenging: insertEverywhere, permutations, transpose, maximum segment sum

Implementing Functions from Data.List

Write the following functions using direct recursion. If no type signature is given, also give the type of the function.

product :: Num a => [a] -> a

The product function computes the product of a finite list of numbers.

concat

Concatenate a list of lists into a single list

concat []       = []
concat (xs:xss) = xs ++ concat xss

and :: [Bool] -> Bool

and returns the conjunction of a Boolean list.

and []     = True
and (x:xs) = x && and xs

or :: [Bool] -> Bool

or returns the disjunction of a Boolean list.

all

Applied to a predicate and a list, all determines if all elements of the list satisfy the predicate. For example,

all _ []     = True
all p (x:xs) = p x && all p xs

map :: (a -> b) -> [a] -> [b]

map _ []     = []
map f (x:xs) = f x : map f xs

intersperse

The intersperse function takes an element and a list and `intersperses’ that element between the elements of the list. For example,

intersperse ',' "abcde" == "a,b,c,d,e"

concatMap

Map a function over a list and concatenate the results.

unlines :: [String] -> String

unlines is an inverse operation to lines. It joins lines, after appending a terminating newline to each.

filter :: (a -> Bool) -> [a] -> [a]

filter, applied to a predicate and a list, returns the list of those elements that satisfy the predicate; i.e.,

filter p xs = [ x | x <- xs, p x]

partition

The partition function takes a predicate a list and returns the pair of lists of elements which do and do not satisfy the predicate, respectively; i.e.,

partition p xs == (filter p xs, filter (not . p) xs)

partition _ []                 = ([],[])
partition p (x:xs) | p x       = let (ts,fs) = partition p xs in (x:ts,  fs)
                   | otherwise = let (ts,fs) = partition p xs in (  ts,x:fs)

unzip :: [(a, b)] -> ([a], [b])

unzip transforms a list of pairs into a list of first components and a list of second components.

insert :: Ord a => a -> [a] -> [a]

The insert function takes an element and a (sorted) list and inserts the element into the list at the last position where it is still less than or equal to the next element.

insert q [] = [q]
insert q (x:xs) | q > x     = x : insert q xs
                | otherwise = q : x : xs

sort :: Ord a => [a] -> [a]

The sort function implements a sorting algorithm.

sort []     = []
sort (x:xs) = insert x (sort xs)

take

take i returns the first i elements from the input list. If the list has fewer than i elements, the entire input list is returned.

take          :: Int -> [a] -> [a]
take 0 _      = []
take n []     = []
take n (x:xs) = x : take (n-1) xs

takeWhile :: (a -> Bool) -> [a] -> [a]

takeWhile, applied to a predicate p and a list xs, returns the longest prefix (possibly empty) of xs of elements that satisfy p:

takeWhile _ []                 = []
takeWhile p (x:xs) | p x       = x : takeWhile p xs
                   | otherwise = []

group

The group function takes a list and returns a list of lists such that the concatenation of the result is equal to the argument. Moreover, each sublist in the result contains only equal elements. For example,

group "Mississippi" = ["M","i","ss","i","ss","i","pp","i"]

group []     = []
group (x:xs) = case group xs of
                 []                        -> [[x]]
                 (ys@(y:_):rs) | x == y    ->      (x:ys) : rs
                               | otherwise -> [x] :    ys : rs

remSuccessiveduplicates

The function remSuccessiveDuplicates removes succesive repeated elements from a list. For example

remSuccessiveduplicates [1, 2, 2, 3, 2, 4] == [1, 2, 3, 2, 4]

remSuccessiveduplicates []                   = []
remSuccessiveduplicates [x]                  = [x]
remSuccessiveduplicates (x:y:xs) | x == y    = remsuccessiveduplicates (y:xs)
                                 | otherwise = x : remsuccessiveduplicates (y:xs)

nub

The nub function removes duplicate elements from a list. In particular, it keeps only the first occurrence of each element. (The name nub means `essence’.)

nub l                   = nub' l [] where
    nub' [] _           = []
    nub' (x:xs) seen
        | x `elem` seen   = nub' xs seen
        | otherwise     = x : nub' xs (x:seen)

union :: Eq a => [a] -> [a] -> [a]

The union function returns the list union of the two lists. For example,

"dog" `union` "cow" == "dogcw"

Duplicates, and elements of the first list, are removed from the the second list, but if the first list contains duplicates, so will the result.

intersect :: Eq a => [a] -> [a] -> [a]

The intersect function takes the list intersection of two lists. For example,

[1,2,3,4] `intersect` [2,4,6,8] == [2,4]

If the first list contains duplicates, so will the result.

[1,2,2,3,4] `intersect` [6,4,4,2] == [2,2,4]

maybeLast :: [a] -> Maybe a

Extract the last element of a list. Returns Nothing if the list is empty.

maybeLast []     = Nothing
maybeList (x:xs) = case maybeList xs of
                     Nothing -> Just x
                     jl      -> jl

insertEverywhere

insertEverywhere x ys “inserts” x at every position in the list ys. I.e.:

insertEverywhere 10 [1..5] == [[10,1,2,3,4,5],[1,10,2,3,4,5],[1,2,10,3,4,5],[1,2,3,10,4,5],[1,2,3,4,10,5],[1,2,3,4,5,10]]

insertEverywhere             :: a -> [a] -> [[a]]
insertEverywhere x []        = [[x]]
insertEverywhere x xs@(y:ys) = (x:xs) : map (y:) (insertEverywhere x ys)

permutations :: [a] -> [[a]]

The permutations function returns the list of all permutations of the argument. E.g.:

permutations "abc" == ["abc","bac","bca","acb","cab","cba"]

Note that it is ok if your solution returns the permutations in any order. E.g.

permutations "abc" == ["abc","bac","cba","bca","cab","acb"]

is also correct.

permutations        :: [a] -> [[a]]
permutations []     = [[]]
permutations (x:xs) = concatMap (insertEverywhere x) $ permutations xs

foldr :: (a -> b -> b) -> b -> [a] -> b

The function foldr takes a function ‘f’ and an unit element ‘z’ and “combines” all elements in the list using the function ‘f’, and starting from value ‘z’.

Your implementation should satisfy:

foldr _ z []     = z
foldr f z (x:xs) = f x (foldr f z xs)

scanr :: (a -> b -> b) -> b -> [a] -> [b]

scanr is similar to foldr but returns a list of successive reduced values from the right:

scanr f z [x_1, x_2, .., x_n] == [x_1 `f` .., .., x_(n-1) `f` z ,x_n `f` z,z]

That is, it also returns all intermediate answers of a foldr. Note in particular that

head (scanr f z xs) == foldr f z xs.

scanr _ z []     = [z]
scanr f z (x:xs) = let rs@(r:_) = scanr f z xs
                   in f x r : rs

run length encoding: encode

The function encode computes the run-length encoding of a list. That is, the list is mapped to a list of pairs whose first element says how many times the second component of the pair appears in adjacent positions in the list. For example:

encode [1, 2, 2, 3, 2, 4] == [(1, 1),(2, 2),(1, 3),(1, 2),(1, 4)]

encode        :: Eq a => [a] -> [(Int,a)]
encode []     = []
encode (x:xs) = case encode xs of
                  []                       -> [(1,x)]
                  r@((i,y):ys) | x == y    -> (i+1,x) : ys
                               | otherwise -> (1,x)   : r

run length encoding: decode

Given a run length encoded list, decode produces the original input list, e.g. from the example above:

decode [(1, 1),(2, 2),(1, 3),(1, 2),(1, 4)] == [1, 2, 2, 3, 2, 4]

decode :: [(Int,a)] -> [a]
decode = concatMap (\(i,x) -> replicate i x)
  where
    replicate 0 _ = []
    replicate i x = x : replicate (i-1) x
    -- replicate is actually already defined in the Prelude.

splitAll :: Int -> [a] -> [[a]]

The splitAll function divides the given list in sublists, where the sublists have the given length. Only the last list might be shorter. For example,

splitAll 3 [1..11] == [[1,2,3],[4,5,6],[7,8,9],[10,11]]

Hint: Try to think of a simpler problem first, and write a helper function that solves this simpler problem.

-- | splitAt splits off the first i elements. Returns all elements in
-- the first list if there are fewer than i elements.
splitAt          :: Int -> [a] -> ([a],[a])
splitAt 0 xs     = ([],xs)
splitAt i []     = ([],[])
splitAt i (x:xs) = let (ys,rest) = splitAt (i-1) xs
                   in (x:ys,rest)

splitAll      :: Int -> [a] -> [[a]]
splitAll i xs = case splitAt i xs of
                  (ys,[])   -> [ys]
                  (ys,rest) -> ys : splitAll i rest

zipWith :: (a -> b -> c) -> [a] -> [b] -> [c]

zipWith combines two lists into a single list, by pairwise applying the given function. I.e. if f is the supplied function, and x and y are the \(i^\mathrm{th}\) elements in the first and second list, respectively, the \(^i\mathrm{th}\) element in the output list is f x y. If the lists have different length, the lengths are truncated to the shortest list. For example:

zipWith f (x:xs) (y:ys) = (f x y) : zipWith f xs ys
zipWith _ _      _      = []

transpose :: [[a]] -> [[a]]

Transposes a matrix (represented by a list of equally long lists). That is, the function transpose :: [[a]] -> [[a]] which maps the \(i^\mathrm{th}\) element of the \(j^\mathrm{th}\) list to the \(j^\mathrm{th}\) element of the \(i^\mathrm{th}\) list.

Hint: make use of the function zipWith.

-- The main work is done here; we consider the first row separately,
-- transpose the rest of the matrix (without its first row), and then
-- cons the elements from the first row onto the result.
--
-- If there are no rows left we generate sufficiently many (infinitely
-- many) empty rows that this consing/combining described above is
-- successful. The zipWith function will just truncate the empty
-- leftover rows generated.
transpose' (xs:xss) = zipWith (:) xs (transpose' xss)
transpose' []       = repeat []

-- The above function transpose' transposes non-empty matrices. But
-- when the matrix empty at the very start we get this infinite list
-- of empty lists instead. We should fix that:
transpose [] = []
transpose xs = transpose' xs

Maximum Segment Sum

Given a list of numbers, we define a segment as a contiguous sublist. For example [2,3,4] is a segment of l=[1,2,3,4,5,6] but [2,4,6] is not a segment of l. The sum of a segment is the value we obtain by summing all values in a segment, and the maximum segment sum of l is the maximum sum over all possible segments of l.

  1. Write the function segments that computes all segments of a list by combine existing functions from Data.List (which you have re-implemented in the exercises above)

    segments :: [Int] -> [[Int]]
    segments = ([] :) . concatMap (tail . List.inits) . List.tails
  2. implement maximumSegmentSum using a combination of existing List functions.

    maxSegSumSpec = maximum . map sum . segments
  3. The above implementation is simple, but actually very slow (\(O(n^3)\) time). With a bit of work we can derive a linear time implementation instead!

    Write, using direct recursion, a function maxPrefixSum that computes the maximum among all prefixes of a list.

    maxPrefixSum        :: [Int] -> Int
    maxPrefixSum []     = 0
    maxPrefixSum (x:xs) = 0 `max` (x + maxPrefixSum xs)
  4. Implement a function maximumSegSum with direct recursion.

    maxSegSum []     = 0
    maxSegSum (x:xs) = maxSegSum xs `max` (x + maxPrefixSum xs)
  5. Hopefully you can notice some commonality in the implementation of maxPrefixSum and maxSegSum. Exploit that to obtain a linear time implementation maxSegSum for the maximum segment sum.

    Hint: Write a function maxPrefixAndSegSum : [Int] -> (Int,Int) that simultaneously computes the maximum prefix sum and the maximum segment sum. I.e. Your function should satisfy the specification:

    maxPrefixAndSegSum xs = (maxPrefixSum xs, maxSegSum xs)
    maxPrefixAndSegSum        :: [Int] -> (Int,Int)
    maxPrefixAndSegSum []     = (0,0)
    maxPrefixAndSegSum (x:xs) = let (maxPrefix,maxSeg) = maxPrefixAndSegSum xs
                                    candidatePrefix    = x + maxPrefix
                                in (0       `max` candidatePrefix
                                   , maxSeg `max` candidatePrefix
                                   )
    
    maxSegSum :: [Int] -> Int
    maxSegSum = snd . maxPrefixAndSegSum

Counting Trues

Let countTrues :: [Bool] -> [int] be a function such that countTrues bs computes, for each prefix of the list bs, the number of True s in the list.

  1. Write countTrues using direct recursion.

    Hint: Take another look at your implementation of inits first.

    countTrues            :: [Bool] -> [Int]
    countTrues []         = [0]
    countTrues (True:bs)  = 0 : map (+1) (countTrues bs)
    countTrues (False:bs) = 0 : countTrues bs
  2. Write countTrues using a combination of existing functions.

    countTrues    :: [Bool] -> [Int]
    countTrues bs = map (length . filter (== True)) . inits $ bs
    
    -- note that we can eta-reduce to
    countTrues :: [Bool] -> [Int]
    countTrues = map (length . filter (== True)) . inits
  3. Write countTrues using an accumulator so that your implementation runs in linear time.

    countTrues :: [Bool] -> [Int]
    countTrues = count [0]
      where
        -- invariant: count acc xs == (reverse acc) ++ countTrues xs
        count acc          []        = reverse acc
        count acc@(cur:_) (True:bs)  = count (cur+1 : acc) bs
        count acc@(cur:_) (False:bs) = count (cur   : acc) bs
  4. Write an alternative implementation of countTrues (not using an accumulator) that also runs in linear time.

    countTrues :: [Bool] -> [Int]
    countTrues = reverse . count . reverse
      where
        count []         = [0]
        count (True :bs) = let res@(cur:_) = count bs in cur + 1 : res
        count (False:bs) = let res@(cur:_) = count bs in cur     : res