Skip to content

Instantly share code, notes, and snippets.

@kanak
Created March 18, 2011 01:55
Show Gist options
  • Save kanak/875496 to your computer and use it in GitHub Desktop.
Save kanak/875496 to your computer and use it in GitHub Desktop.
Discrete Mathematics Using a Computer Chapter 09: Inductively Defined Sets Solutions
{- Discrete Mathematics Using a Computer
Chapter 09: Inductively Defined Sets
-}
module IndSet where
-- =============================================================================
-- 9.1: The Idea Behind Induction
{- Suppose we have know that:
0 in S
n in S => n + 1 in S
Together, they imply that every natural number is in S.
e.g. Proof: 3 is in S
0 in S
0 in S => 1 in S
1 in S (Modus Ponens)
1 in S => 2 in S
2 in S (Modus Ponens)
2 in S => 3 in S
Any finite number can be reached by applying the rule repeatedly
"Chain": (0 in S) -> (0 in S => 1 in S) -> (1 in S => 2 in S)
-}
-- Representing these chains
-- A chain implication as a function that returns the next element
-- Representing 1 in S => 2 in S
imp1 :: Integer -> Integer
imp1 1 = 2
imp1 _ = error "premise doesn't match"
imp2 :: Integer -> Integer
imp2 2 = 3
imp2 x = error "premise doesn't match"
s :: [Integer]
s = [1, imp1 (s !! 0), imp2 (s !! 1)] -- the entire set of elements
--------------------------------------------------------------------------------
-- Exercise 1,2,3,4: Is the following a chain:
imp3 3 = 4
ex1s = [1, imp1 (s !! 0), imp2 (s !! 1), imp3 (s !! 2)]
-- It is a chain because we have [1, 2, 3, 4]
ex2s = [1, imp2 (s !! 0), imp3 (s !! 1)]
-- No, because imp2 requires 2 to be in S, but only 1 is.
ex3s = [0, imp1 (s !! 0), imp3 (s !! 1)]
-- No because we have [0,1] but not [2,3]. imp3 requires 3 to be in s to work
ex4s = [0, imp1 (s !! 1), imp2 (s !! 0)]
-- No because imp2 requires 1 but we're passing it 0 as an argument.
--------------------------------------------------------------------------------
-- 9.1.1 Induction Rule
increment :: Integer -> Integer
increment = (+ 1)
s1 :: [Integer]
s1 = [0, increment (s !! 0), increment (s !! 1)]
-- but that's tedious
-- we can use DATA RECURSION to write
s2 :: [Integer]
s2 = 0 : map increment s2
-- *IndSet> s2 !! 50
-- 50
--------------------------------------------------------------------------------
-- Ex 5: Base case is 0 in n, induction rule is x in n => x + 1 in n
-- Fix the following so that 3 is in n
-- ex5fun x = x - 1
ex5fun x = x + 1 -- Fixed version
ex5n = 0 : map ex5fun ex5n
-- *IndSet> 3 `elem` ex5n
-- True
--------------------------------------------------------------------------------
-- Ex 6: based on the following, is 4 in S?
ex6fun = (+ 2)
ex6n = 1 : map ex6fun ex6n
-- No, 4 is not in S
-- 1 is in S, so 3 is in S, and 5 is in S ...
-- (all odd numbers are in)
--------------------------------------------------------------------------------
-- Ex 7: Fix this calculation of positive integers
-- ex7fun x = 0
ex7fun = (+ 1) -- fixed version
ex7n = 0 : map ex7fun ex7n
-- > take 10 ex7n
-- [0,1,2,3,4,5,6,7,8,9]
--------------------------------------------------------------------------------
-- Ex 8: Fix this calculation of positive multiples of 3
ex8fun = (* 3)
-- ex8n = map ex8fun ex8n
-- ex8n = 1 : map ex8fun ex8n -- Fixed version. actually this is the powers
ex8n = map ex8fun [1..]
-- =============================================================================
-- 9.2: Defining a set using induction
-- we can create sets inductively by specifying which elements are already inside
-- and how to create new elements based on ones we know are inside.
-- e.g. 1 in S, x in S => x + 1 in S gives us the natural numbers.
-- How to exclude elements that can't be constructed this way from the set?
-- Add a extremal clause that says that any element that can't be created by
-- finite application of the construction rules isn't in the set.
--------------------------------------------------------------------------------
-- Exercise 9: Is 82 in the following?
ex9 = 0 : map (+ 2) ex9
-- ex9 defines all the even numbers
-- So, after applying +2 41 times, we'll get to 82.
--------------------------------------------------------------------------------
-- Exercise 10: What set is defined by:
ex10 = 1 : map (* 3) ex10
-- the elements are [1, 3, 9, 27, ...]
-- the powers of 3
--------------------------------------------------------------------------------
-- 9.2.2 Set of Binary Machine Words
{- Inductive Definition:
1. Let BinDigit be the set {0,1}
2. Base case: x in BinDigit => x in BinWords
3. If x is a BinDigit and y is a BinWord, the concatenation xy is a binary word.
4. (Extremal clause): anything that can't be constructed in a finite number of
steps using 2 and 3 is not in the set.
-}
data Bin = Zero | One
deriving (Eq, Show, Ord)
type BinDigit = [Bin]
newBinDigit :: BinDigit -> [BinDigit]
newBinDigit xs = [Zero:xs, One:xs]
binaryWords = [Zero] : [One] : (concatMap newBinDigit binaryWords)
-- *IndSet> take 10 binaryWords
-- [[Zero],[One],[Zero,Zero],[One,Zero],[Zero,One],[One,One],[Zero,Zero,Zero],[One,Zero,Zero],[Zero,One,Zero],[One,One,Zero]]
--------------------------------------------------------------------------------
-- Exercise 11: Octal Numbers
--
octals = [0..7]
newOctalDigit :: [Integer] -> [[Integer]]
newOctalDigit xs = [x:xs | x <- octals]
octalWords = [[x] | x <- octals] ++ (concatMap newOctalDigit octalWords)
-- [[0],[1],[2],[3],[4],[5],[6],[7],[0,0],[1,0],[2,0],[3,0],[4,0],[5,0],[6,0],[7,0],[0,1],[1,1],[2,1],[3,1]]
-- =============================================================================
-- 7.3 Defining the Set of Integers
{- *WELL-FOUNDED*: set is infinite in only one direction
*COUNTABLE*: the set can be counted using natural numbers.
Are integers countable? Yes. Measure n then -n then n + 1 then - (n + 1) ...
-}
--------------------------------------------------------------------------------
-- Attempt 1 at building Integers
-- 0 in Z, x in Z => - x in Z. Nothing else is in Z
build :: a -> (a -> a) -> [a]
build a f = set
where set = a : map f set
builds :: a -> (a -> [a]) -> [a]
builds a f = set
where set = a : concatMap f set
nextInteger1 :: Integer -> Integer
nextInteger1 x = - x
integers1 :: [Integer]
integers1 = build 0 nextInteger1
--------------------------------------------------------------------------------
-- Ex 12: What are the first 10 elements of integers1?
-- build 0 nextInteger1
-- => 0 : map nextInteger1 (0:set)
-- => 0 : - 0 : map nextInteger1 (-0)
-- ... So it's all zeros
ex12 = take 10 integers1
--------------------------------------------------------------------------------
-- Attempt 2
-- 0 in Z, x in Z => x + 1 in Z, x - 1 in Z. nothing else is in Z
nextInteger2 x = [x + 1, x - 1]
integers2 = builds 0 nextInteger2
--------------------------------------------------------------------------------
-- Ex 13: What are the first 20 elements of integers2?
-- builds 0 nextIntegers2
-- [0] ++ [1, -1] ++ concatMap nextIntegers2 ([0] ++ [1, -1] ++ ...)
-- [0,1,-1] ++ [1,-1] ++ [2, -2] ++ [3, -3] ...
-- *IndSet> take 40 integers2
-- [0,1,-1,2,0,0,-2,3,1,1,-1,1,-1,-1,-3,4,2,2,0,2,0,0,-2,2,0,0,-2,0,-2,-2,-4,5,3,3,1,3,1,1,-1,3]
-- The problem (as they explain later) : is that each element is introduced multiple times
-- Want to introduce each element exactly once.
--------------------------------------------------------------------------------
-- Attempt 3
nextIntegers3 x = [x + 1, - (x + 1)]
integers3 = builds 0 nextIntegers3
-- Still introduces elements multiple times.
-- e.g. from 2 we get 3, -3
-- from -3 we get [2, -4]
-- Exercise 14
-- *IndSet> take 10 integers3
-- [0,1,-1,2,-2,0,0,3,-3,-1]
--------------------------------------------------------------------------------
-- Attempt 4
-- Intuitively, we want the negatives to go towards -ve infinity
-- we want the positives to go towards positive infinity
nextIntegers4 x
| x < 0 = x - 1
| otherwise = x + 1
integers4 = build 0 nextIntegers4
-- Exercise 15
-- but we get only positive numbers because by default, only 0 is in the set
-- since 0 is not less than 0, we keep adding to get positive numbers.
-- take 10 integers4
-- [0,1,2,3,4,5,6,7,8,9]
--------------------------------------------------------------------------------
-- Attempt 5
nextIntegers5 x
| x > 0 || x == 0 = [x + 1, -(x + 1)]
| otherwise = []
integers5 = builds 0 nextIntegers5
-- Exercise 16
-- 0 produces 1 and -1
-- 1 produces 2 and -2
-- -1 produces []
-- 2 produces 3 and -3
-- -2 produces []
-- and so on until we get all the integers.
-- basically what's happening here is we're "undoing" the absolute value
-- to get every integer.
-- ==============================================================================
-- Suggestions for Further Reading
-- Elements of Set Theory by Enderton: "good examples of inductively defined sets"
-- Axiomatic Set Theory by Suppes: "advanced treatment"
-- =============================================================================
-- Review Exercises Begin Here
--------------------------------------------------------------------------------
-- Exercise 17
nats = build 0 (1 +)
negs = build (-1) (1 -)
ints = nats ++ negs
{- Does this definition of ints enumerate the integers?
Yes nats covers all the non-negative integers, negs covers all the negative ones
Will you ever see the value -1?
No. Because we print all the non-negative integers before any of the negative ones
-}
--------------------------------------------------------------------------------
-- Exercise 18
twos = build 0 (2 *)
-- Does twos enumerate the set of even natural numbers?
-- No, it's all zeros.
--------------------------------------------------------------------------------
-- Exercise 19
-- What is wrong with the following definition of a stream of natural numbers?
nats19 = map (+ 1) nats19 ++ [0]
-- The base case is after the inductive case, which means that haskell will
-- try to keep applying the inductive step without terminating
-- so it returns bottom.
--------------------------------------------------------------------------------
-- Exercise 20
naturals (i:acc) = naturals (i + 1:i:acc)
nats20 = naturals [0]
-- Bottomless recursion:
-- naturals (0:[]) = naturals (1 : 0: [])
-- = naturals (2 : 1 : 0 : [])
-- ...
-- we should produce the stream outside the function call
--------------------------------------------------------------------------------
-- Exercise 21
{- Can we write a function that will take in a stream of naturals (appearing in
any order) and give the index of a particular number?
No. Imagine the stream defined as: [k, k + 1, ...] ++ [1..k] for some k
Then we can't find the index of any number 1 .. k because we the stream
tries to produce all natural numbers larger than k first.
-}
--------------------------------------------------------------------------------
-- Exercise 22: Using induction, define the set of roots of a given number n.
{- 1. n^1 is a root of n
2. n^(1/n) is a root => n^(1/(n + 1)) is a root
3. Anything that cannot be created by a finite number of applications of
rules 1 and 2 is not a root.
-}
--------------------------------------------------------------------------------
-- Exercise 23: Prove that n^3 is in P:
{- Definition: n^0 in P
n^m in P => n^(m + 1) in P
nothing else.
Proof: n^0 in P => n^1 in P => n^2 in P => n^3 in P.
(I've written in shorthand but in each step, we use Modus Ponens)
-}
--------------------------------------------------------------------------------
-- Exercise 24: When is 0 defined in the set below
{- Given a number n, the set N is defined as:
n in N
m in N => m - 2 in N.
nothing else.
0 is defined in the set if: 1) we set n = 0
2) n is a positive even number
Proof of 2: Suppose n is an positive even number
Then, n can be written as 2 * k where k > 0
Then, after k applications of rule 2, we get n - (2 * k) = n - n = 0
So n is in N
-}
--------------------------------------------------------------------------------
-- Exercise 25: What set is defined by:
{- Definition: 1 in S
n in S and n mod 2 = 0 => n + 1 in S
n in S and n mod 2 = 1 => n + 2 in S
This is the set of all odd numbers.
Proof is by induction
Base case: 1 in S, 1 is odd.
Inductive case: Assuming that every number before has been odd,
n mod 2 will be 1, so we use Rule 3 to add n + 2 into S
Since n is odd, n + 2 is also odd.
QED.
-}
--------------------------------------------------------------------------------
-- Exercise 26: Prove that 4 is in the set below.
{- Definition: 0 in S
n in S and n mod 2 = 0 => n + 2 in S
n in S and n mod 2 = 1 => n + 1 in S
Lemma: 2 in S
Proof: 0 in S, and 0 mod 2 = 0. So, 0 + 2 = 2 is in S.
Theorem: 4 in S
Proof: 2 in S, 2 mod 2 = 0. So, 2 + 2 = 4 is in S.
-}
--------------------------------------------------------------------------------
-- Exercise 27: Prove that "yyyy" is in YYS
{- Definition: "" in YYS
s in YYS => "yy" ++ s in YYS
nothing else
Lemma: yy in YYS
Proof: "" is in YYS. "" ++ "yy" = "yy". So "yy" is in YYS by rule 2
Theorem: yyyy is in YYS
Proof: yy is in YYS, and yyyy = "yy" ++ "yy"
-}
--------------------------------------------------------------------------------
-- Exercise 28: Using data recursion, define the set of strings containing the
-- letter "z"
{- I'm interpreting this to mean the set of strings containing ONLY "z"
Definition: "" in Zs
s in Zs => 'z':s in Zs
nothing else
-}
ex28 = "" : map ('z' :) ex28
--------------------------------------------------------------------------------
-- Exercise 29: Using induction, define the set of strings of spaces of length
-- less than or equal to length n, where n is a positive integer.
{- Definition: n is a parameter used in construction:
"" in Spaces
s in Spaces, length s < n => " ":s in Spaces
nothing else.
-}
--------------------------------------------------------------------------------
-- Exercise 30: Using recursion, define set of strings of spaces of length leq n
spaces :: Int -> [String]
spaces 0 = [""]
spaces n = take n (repeat ' ') : spaces (n - 1)
--------------------------------------------------------------------------------
-- Exercise 31: N - {2} is the set of all naturals except 2.
-- we can do this for all natural numbers.
-- make a set out of all these results.
{- Inductive Definition:
N - {0} is in SSN
if N - {m} is in SSN, N - {m + 1} is in SSN
Nothing else.
-}
--------------------------------------------------------------------------------
-- Exercise 32: Show that I - { - 3} is in SSI-
{- Definition of SSI-
1. I - { - 1} is in SSI-
2. I - {n} in SSI- => I - {n - 1} in SSI-
nothing else.
I - { -1} => I - { -2} => I - { - 3} is in SSI.
-}
--------------------------------------------------------------------------------
-- Exercise 33: Prove that -7 is in ONI
{- ONI: -1 in ONI
n in ONI => n - 2 in ONI
nothing else
-1 => -3 => -5 => -7 in ONI
-}
--------------------------------------------------------------------------------
-- Exercise 34: Define the set of negative integers using data recursion.
ni = -1 : map decrement ni
where decrement x = x - 1
-- *IndSet> take 10 ni
-- [-1,-2,-3,-4,-5,-6,-7,-8,-9,-10]
--------------------------------------------------------------------------------
-- Exercise 35: Will we ever see (1,2) in:
-- [(a, b) | a <- [0..], b <- [0..]]
-- No. Tries to produce all tuples (0, n) first. but there's infinite n
--------------------------------------------------------------------------------
-- Exercise 36: What set is given by:
{- 1 in S
n in S => n - n in S
nothing else.
1 in S => 1 - 1 = 0 in S.
0 - 0 = 0 in S.
So, only 0 and 1 are in S.
-}
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment