FSA 1: Crash Course in Functional Programming

Jan van Eijck

September 5, 2016

> module FSA1 where
> import Data.List

The contents below refer to chapters 1 and 2 of The Haskell Road. If this material is new to you, you should read up in the book, and carry out enough of the implementation exercises to make you familiar with the basics of Haskell.

Lazy lists

What happens here?

> sentence = "Sentences can go " ++ onAndOn
> onAndOn  = "on and " ++ onAndOn

Try this out with

take 65 sentence

Next consider:

> sentences = "Sentences can go on":
>                map (++ " and on") sentences

Try this out with

take 10 sentences

Review question Can you give your own definitions of map and take?

First Order logic formulas and functional programs

Example domain: the natural numbers

Example properties: being even, odd, prime, 3-fold, etc

> threefold :: Integer -> Bool
> threefold n = rem n 3 == 0

The lazy list of threefolds:

> threefolds = filter threefold [0..]                     

Review question Can you give your own definition of filter?

List Comprehensions

See list comprehension.

[ x | x <- [0..],  threefold x ]

is syntactic sugar for

filter threefold [0..]

The notation suggests a close connection with set comprehension:

\[ \{ x \mid x \in {\mathbb N}, P(x) \} \]

How to say things with predicate logic in Haskell

there is no largest natural number

there is a smallest natural number

Translations use any and all but they will run forever

> nats = [0..]
> 
> query1 = all (\ n -> any (\ m -> n < m) nats) nats
> 
> query2 = any (\ n -> all (\ m -> n <= m) nats) nats

We can make this look a bit more natural as follows:

> forall = flip all
> exist  = flip any         
> 
> query1' = forall nats (\ n -> exist nats (\ m -> n < m))
> 
> query2' = exist nats (\ n -> forall nats (\ m -> n <= m))

Review question Give your own definitions of all and any.

We can give alternative definitions of all, any in terms of foldr.

foldr :: (a -> b -> b) -> b -> [a] -> b 
foldr f z [] = z
foldr f z (x:xs) = f x (foldr f z xs)

Using this we get home-made definitions of all and any ...

> myall p = foldr (\ x b -> p x && b) True
> myany p = foldr (\ x b -> p x || b) False

The lab exercises for this week give further examples of the use of foldr.

Definition of being a prime number with a formula of predicate logic:

\[ P(n) :\equiv n \in {\mathbb N} \land n > 1 \land \forall d \in {\mathbb N} (1 < d < n \rightarrow \neg D(d,n)). \]

In words:

\(n\) is prime \(:\equiv\) \(n\) is a natural number and \(n > 1\) and for all natural numbers \(d\) with \(1 < d < n\) it holds that \(d\) does not divide \(n\).

To implement this, the first thing we need is the divide relation. Here it is:

> divide :: Integer -> Integer -> Bool
> divide n m = rem m n == 0

Next, we just write the definition, using the Haskell implementations of &&, all and not.

> isPrime :: Integer -> Bool
> isPrime n = n > 1 && all (\ d -> not (divide d n)) [2..n-1]

Of course, this is not efficient. But the point is that Haskell has counterparts all, not, any, &&, ||, etc, to express all the constructs of first order logic.

Review question Are you able to state the types and provide your own definitions of all, not, any, &&, || ?

Here is a slightly more efficient version of isPrime:

> isPrime' :: Integer -> Bool
> isPrime' n = all (\ x -> rem n x /= 0) xs
>   where xs = takeWhile (\ y -> y^2 <= n) [2..]

And the following is still better, for it tests only for divisibility by primes that you have already found before.

> prime :: Integer -> Bool
> prime n = n > 1 && all (\ x -> rem n x /= 0) xs
>   where xs = takeWhile (\ y -> y^2 <= n) primes
> primes :: [Integer]
> primes = 2 : filter prime [3..]

Review question Why do we need to give the starting value \(2\) explicitly?

If these examples use built-in functions that you are not familiar with, you should familiarize yourself with them. The best way to do this is by writing myfilter, mytakeWhile, and so on.

Also, make sure you understand the use of anonymous functions like (\ x -> rem n x /= 0) and (\ y -> y^2 <= n). Again, if you don't quite understand what these mean and how they are used, write some of your own.

The sieve of Eratosthenes.

> sieve :: [Integer] -> [Integer]
> sieve (n:ns) = n : sieve (filter (\m -> rem m n /= 0) ns)
> 
> eprimes = sieve [2..]

Try to understand why this works. If all else fails, take a sheet of paper, fill it with an initial segment of the natural numbers, and operate the sieve of Eratosthenes by hand. Or have a look at Sieve of Eratosthenes.

Exercises for Warming Up

The number 13 has the property that it is prime and its reversal, the number 31, is also prime. Find all primes < 10000 with this property.

> reversal :: Integer -> Integer
> reversal = read . reverse . show
> solution = takeWhile (< 10000) (filter (prime.reversal) primes)

Review question: the definition of reversal uses function composition. Can you guess the type and definition of (.)?

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

What is the definition of the least natural number that has a given natural number property? Start the search with \(0\).

Note: if no number satisfies the property, the query will run forever.

> least :: (Integer -> Bool) -> Integer
> least p = head (filter p nats)       
*FSA1> least (\n -> prime n && prime (n+2) &&  n > 10000)
10007

Alternative:

> least1 p = lst p 0
>      where lst p n = if p n then n else lst p (n+1)

A prime pair is a pair \((p,p+2)\) with the property that both \(p\) and \(p+2\) are primes. The first prime pair is (3,5). Implement a function for generating prime pairs, and use this to find the first 100 prime pairs.

> dif2 :: [Integer] -> [(Integer,Integer)]
> dif2 (p:q:rs) = if p + 2 == q then (p,q) : dif2 (q:rs)
>                 else dif2 (q:rs)
> primePairs = dif2 primes

 *Lecture1> take 100 primePairs
 [(3,5),(5,7),(11,13),(17,19),(29,31),(41,43),(59,61),(71,73),
 (101,103),(107,109),(137,139),(149,151),(179,181),(191,193),
 (197,199),(227,229),(239,241),(269,271),(281,283),(311,313),
 (347,349),(419,421),(431,433),(461,463),(521,523),(569,571),
 (599,601),(617,619),(641,643),(659,661),(809,811),(821,823),
 (827,829),(857,859),(881,883),(1019,1021),(1031,1033),
 (1049,1051),(1061,1063),(1091,1093),(1151,1153),(1229,1231),
 (1277,1279),(1289,1291),(1301,1303),(1319,1321),(1427,1429),
 (1451,1453),(1481,1483),(1487,1489),(1607,1609),(1619,1621),
 (1667,1669),(1697,1699),(1721,1723),(1787,1789),(1871,1873),
 (1877,1879),(1931,1933),(1949,1951),(1997,1999),(2027,2029),
 (2081,2083),(2087,2089),(2111,2113),(2129,2131),(2141,2143),
 (2237,2239),(2267,2269),(2309,2311),(2339,2341),(2381,2383),
 (2549,2551),(2591,2593),(2657,2659),(2687,2689),(2711,2713),
 (2729,2731),(2789,2791),(2801,2803),(2969,2971),(2999,3001),
 (3119,3121),(3167,3169),(3251,3253),(3257,3259),(3299,3301),
 (3329,3331),(3359,3361),(3371,3373),(3389,3391),(3461,3463),
 (3467,3469),(3527,3529),(3539,3541),(3557,3559),(3581,3583),
 (3671,3673),(3767,3769),(3821,3823)]

Review Question: Observe that it holds for all of these pairs \((x,x+2)\) except the first pair that \(x+1\) (the number in between) is divisible by \(3\). Why is this so?

Factorizing a number Trial and error. We cannot do better.

> factors :: Integer -> [Integer]
> factors n = let
>    ps = takeWhile (\m -> m^2 <= n) primes
>  in factors' n ps where
>     factors' 1 _ = []
>     factors' n [] = [n]
>     factors' n (p:ps)
>       | n `mod` p == 0 = p : factors' (n `div` p) (p:ps)
>       | otherwise      = factors' n ps

Use this to investigate the structure of \(p+1\), where \((p,p+2)\) is a prime pair.

> ppairs = map (\ (p,_) -> factors (p+1))  primePairs

A prime triple is a triple \((n,m,k)\) such that \(n < m < k\) and \(n,m,k\) are all prime, and \(n\) and \(k\) differ by six. The first prime triple is (5,7,11).

Implement a function for generating prime triples, and use this to find the first 100 prime triples.

> dif6 :: [Integer] -> [(Integer,Integer,Integer)]
> dif6 (p:q:r:ss) = if p + 6 == r then (p,q,r) : dif6 (q:r:ss)
>                   else dif6 (q:r:ss)
> 
> primeTriples = dif6 primes
> 
> sol2 = take 100 primeTriples

Implement a function nextPrime with the property that nextPrime n returns n when n is prime, and the next prime after n otherwise.

> nextPrime :: Integer -> Integer
> nextPrime n = if prime n then n else nextPrime (n+1)

A Mersenne number is a natural number of the form \(2^p -1\) where \(p\) is a prime number. A Mersenne prime is a Mersenne number that is itself prime. Write a function for generating Mersenne primes. How far do you get? Note: only 48 Mersenne primes are known. See here for details.

> mersenne :: [(Integer,Integer)]
> mersenne = [ (p,2^p -1) | p <- primes, prime (2^p - 1) ]

Using Haskell to refute a conjecture.

Write a Haskell function that can be used to refute the following conjecture. "If \(p_1, ..., p_n\) is a list of consecutive primes starting from \(2\), then \((p_1 \times \cdots \times p_n) + 1\) is also prime." This can be refuted by means of a counterexample, so your Haskell program should generate counterexamples. What is the smallest counterexample?

> counterexamples :: [([Integer],Integer)]
> counterexamples = [ (ps,product ps + 1) | 
>                          ps <- [ take n primes | n <- [2..] ],
>                          not $ prime (product ps + 1) ]

A Pythagorean triple is a triple of natural numbers \((x,y,z)\) with the property that \(x^2 + y^2 = z^2\). The smallest example is \((3,4,5)\). Implement a Haskell function that generates Pythagorean triples. Are there Pythagorean triples \((x,y,z)\) with \(x = y\)? If your answer is "Yes", give the smallest one. If your answer is "No", explain why this is impossible.

> pythTriples :: [(Integer,Integer,Integer)]
> pythTriples = filter (\ (x,y,z) -> x^2 + y^2 == z^2)  
>    [ (x,y,z) | z <- [1..], x <- [1..z], y <- [1..z], x < y ]
> -- [ (x,y,z) | z <- [1..], x <- [1..z], y <- [x+1..z] ]

Pythagorean triples \((x,y,z)\) with \(x = y\) are impossible because if \(2x^2 = z^2\), then \(z = x\sqrt{2}\), which means that \(z\) cannot be a natural number.

In the same way, we can generate Pythagorean quadruples, integer sequences \((x,y,z,u)\) with \(x^2 + y^2 + z^2 = u^2\).

> pythQuadruples :: [(Integer,Integer,Integer,Integer)]
> pythQuadruples = filter (\ (x,y,z,u) -> x^2 + y^2 + z^2 == u^2)  
>    [ (x,y,z,u) | u <- [1..], x <- [1..u], y <- [x..u], z <- [y..u] ]

Haskell Scripting

An example of Haskell scripting is given in Bird2hs.

This is a script for converting Bird literate Haskell format into plain Haskell.

You can use this as runhaskell Bird2hs < InFile.lhs > Outfile.hs. Or you can compile it with ghc --make Bird2hs.hs -o bird2hs, move bird2hs into your folder of executables, and run it with bird2hs < InFile.lhs > Outfile.hs.

Links

Lab 1: Further exercises.

Back to main coursepage