Skip to content

Instantly share code, notes, and snippets.

@kanak
Created March 22, 2011 04:01
Show Gist options
  • Save kanak/880757 to your computer and use it in GitHub Desktop.
Save kanak/880757 to your computer and use it in GitHub Desktop.
Discrete Mathematics Using a Computer Chapter 11: Functions Notes and Solutions
{- Discrete Mathematics Using a Computer
Chapter 11: Functions
-}
module Functions where
import Data.Tuple (swap)
-- =============================================================================
-- 11.1 The Graph of a Function
{- This perspective views a function as a special type of relation:
Let A and B be sets.
A relation f :: A -> B is called a function if it satisfies:
forall x in A, forall y1 in B, forall y2 in B:
(x,y1) in f and (x,y2) in f => y1 == y2
So the only restriction is that an argument is mapped into at most one value.
Note: also needs to map every item in the domain to some value.
- this is addressed in the total vs partial function section
-}
type Relation a b = [(a,b)] -- same as before
type Function a b = ([a], [b], [(a,b)])
-- let's have functions carry the domain, codomains along with the mapping.
isFunction :: (Eq a, Eq b) => Function a b -> Bool
isFunction (_, _, maps) = isFunction' maps
where isFunction' :: (Eq a, Eq b) => Relation a b -> Bool
isFunction' [] = True
isFunction' ((a,_):xs) = all ((/= a) . fst) xs && isFunction' xs
-- Thanks to luite and sm on the #haskell forum for helping me debug:
-- null [x | x@(a,_) <- xs] && isFunction xs
-- The problem is that a is not pattern matched with the "a" from the function argument
-- Instead it is a fresh "a".
eg86 = isFunction ([1], [1..5], [(1,4), (1,5)]) -- False: 1 is mapped to two different values
eg87 = isFunction ([1,2,3], [1..5], [(1,2), (2,2), (3,4)]) -- True: each item in domain mapped to exactly one value
{- DEFINITION: Function application
An application of the function f :: A -> B to the argument x :: A is written
f(x) or f x and its value is y if (x,y) in f, undefined otherwise.
More succinctly: f x = y <=> (x,y) in f
Note: "bottom" ( _|_) is shorthand for undefined
-}
apply :: (Eq a, Eq b) => Function a b -> a -> Maybe b
apply (_, _, maps) x = apply' maps x
where apply' [] _ = Nothing
apply' ((x,y):xs) a
| x == a = Just y
| otherwise = apply' xs a
egF1 = ([1..4], [1..5], [(1,2), (2,3), (3,4), (4,5)]) -- a subset of the +1 function
egF2 = ([0,1], [0,1], [(0, 0), (-1, 1), (1, 1)]) -- a subset of the sqrt function
egK1 = apply egF1 1 -- Just 2
egK2 = apply egF1 5 -- Nothing
{- DEFINITION: Domain, Image
domain f = {x | exists y. (x,y) in f}
image f = {y | exists x. (x,y) in f}
-}
domain :: Function a b -> [a]
domain (dom, _, _) = dom
codomain, image :: Function a b -> [b]
codomain (_, c, _) = c
image (_, _, maps) = map snd maps
{- DEFINITION: codomain
It is the B in the f :: A -> B notation.
It is a superset of the image.
-}
{- Function Graph
similar to digraph. draw domain on one side, codomain on another
use arrows to connect items in the domain with their values.
-}
-- =============================================================================
-- 11.2 Functions in Programming
-- Here, we view functions as algorithms because that allows us to take into
-- account things like complexity of functions.
--------------------------------------------------------------------------------
-- 11.2.1 Inductively Defined Functions
{- DEFIN{- Discrete Mathematics Using a Computer
Chapter 11: Functiosn
-}
module Functions where
import Data.Tuple (swap)
-- =============================================================================
-- 11.1 The Graph of a Function
{- This perspective views a function as a special type of relation:
Let A and B be sets.
A relation f :: A -> B is called a function if it satisfies:
forall x in A, forall y1 in B, forall y2 in B:
(x,y1) in f and (x,y2) in f => y1 == y2
So the only restriction is that an argument is mapped into at most one value.
Note: also needs to map every item in the domain to some value.
- this is addressed in the total vs partial function section
-}
type Relation a b = [(a,b)] -- same as before
type Function a b = ([a], [b], [(a,b)])
-- let's have functions carry the domain, codomains along with the mapping.
isFunction :: (Eq a, Eq b) => Function a b -> Bool
isFunction (_, _, maps) = isFunction' maps
where isFunction' :: (Eq a, Eq b) => Relation a b -> Bool
isFunction' [] = True
isFunction' ((a,_):xs) = all ((/= a) . fst) xs && isFunction' xs
-- Thanks to luite and sm on the #haskell forum for helping me debug:
-- null [x | x@(a,_) <- xs] && isFunction xs
-- The problem is that a is not pattern matched with the "a" from the function argument
-- Instead it is a fresh "a".
eg86 = isFunction ([1], [1..5], [(1,4), (1,5)]) -- False: 1 is mapped to two different values
eg87 = isFunction ([1,2,3], [1..5], [(1,2), (2,2), (3,4)]) -- True: each item in domain mapped to exactly one value
{- DEFINITION: Function application
An application of the function f :: A -> B to the argument x :: A is written
f(x) or f x and its value is y if (x,y) in f, undefined otherwise.
More succintly: f x = y <=> (x,y) in f
Note: "bottom" ( _|_) is shorthand for undefined
-}
apply :: (Eq a, Eq b) => Function a b -> a -> Maybe b
apply (_, _, maps) x = apply' maps x
where apply' [] _ = Nothing
apply' ((x,y):xs) a
| x == a = Just y
| otherwise = apply' xs a
egF1 = ([1..4], [1..5], [(1,2), (2,3), (3,4), (4,5)]) -- a subset of the +1 function
egF2 = ([0,1], [0,1], [(0, 0), (-1, 1), (1, 1)]) -- a subset of the sqrt function
egK1 = apply egF1 1 -- Just 2
egK2 = apply egF1 5 -- Nothing
{- DEFINITION: Domain, Image
domain f = {x | exists y. (x,y) in f}
image f = {y | exists x. (x,y) in f}
-}
domain :: Function a b -> [a]
domain (dom, _, _) = dom
codomain, image :: Function a b -> [b]
codomain (_, c, _) = c
image (_, _, maps) = map snd maps
{- DEFINITION: codomain
It is the B in the f :: A -> B notation.
It is a superset of the image.
-}
{- Function Graph
similar to digraph. draw domain on one side, codomain on another
use arrows to connect items in the domain with their values.
-}
-- =============================================================================
-- 11.2 Functions in Programming
-- Here, we view functions as algorithms because that allows us to take into
-- account things like complexity of functions.
--------------------------------------------------------------------------------
-- 11.2.1 Inductively Defined Functions
{- DEFINTION: Inductively Defined Function
Suppose "h" is a nonrecursive function. Then, the function f of the form:
f 0 = k
f n = h (f (n - 1))
is said to be inductively defined.
--------------------
-- Example: length
length [] = 0
length (x:xs) = 1 + length (xs)
Here, [] plays the role of 0, k = 0, h is the (1 +) function
--------------------
-- Example: and
and [] = True
and (x:xs) = x && and xs
Again, [] plays the role of 0, k = True, h is the (x &&) function.
-}
--------------------------------------------------------------------------------
-- 11.2.2 Primitive Recursion
{- DEFINITION: Primitive Recursive Function
A function f is primitive recursive if its definition has the following form:
f 0 x = g x
f (k + 1) x = h (f k x) k x
Where: g and h are primitive recursive.
NOTE: this is definition is incomplete because it talks about how to compose
existing primitive recusive functions (g and h) to get a new one (f), but doesn't
talk about where g and h come from in the first place. In other words, we have no
"base case".
I went to wikipedia and there are several basic primitive recursive functions:
1. Constant function
2. Successor Function
3. "Projection Function"
-}
{- Example: Square
square x = f 0 x
where f 0 x = g x
g x = x * x
Note: requires us to prove that x * x is a primitive recursive function.
LEMMA: Addition is primitive recursive.
PROOF: Adapted from wikipedia
Suppose addition is defined as:
0 + x = 0 clause 1
(k + 1) + x = k + (1 + x) clause 2
So, g = const 0, which is a basic primitive recursive function.
h r k x = Successor(r) where r = k + x, and successor is primitive recursive.
Hence, addition is primitive recursive.
LEMMA: Multiplication is primitive recursive.
PROOF: Define multiplication as:
0 * x = 0 clause 1
(k + 1) * x = Add(x, k * x) clause 2
So, clause 1 uses const 0 function, which is primitive recursive
clause 2 uses Add, which we proved is primitive recursive above.
Hence, multiplication is primitive recursive.
Theorem: g x = x * x is primitive recursive
Proof: It's just multiplication.
--------------------
Example: Factorial
factorial k = f k undefined
where f 0 x = 1
f (k + 1) x = (k + 1) * (f k x)
Note: passing undefined to f because we ignore 2nd argument everywhere.
Clause 1 uses const 1, which is primitive recursive
Clause 2 uses successor and multiplication which are both primitive recursive.
--------------------
Example: Not primitive recursive
f 0 = 0
f 1 = 1
f x = if even x then 1 + f (x `div` 2) else f x
Not primitive recursive because it calls itself with the same arguments when x is even.
So i guess we can't compose this function out of any primitive recursive functions.
-}
--------------------------------------------------------------------------------
-- 11.2.3 Computational complexity
-- space and time complexity
-- can have simply defined but expensive computations: e.g. ackermann function.
--------------------------------------------------------------------------------
-- 11.2.4 State
{- Suppose we have a "function" that takes in an integer and multiplies it by the
hour of the day.
Then, calling this function with the same argument at different hours can give
different results.
We can describe this as a pure computation by having State of the system be an
argument to it: f :: State -> Integer -> Integer. Now, if we call it with the
same state, it returns the same value.
Problem: If we're using state frequently, can have explicit state arguments everywhere
Also problem: We need to thread the state correctly between stateful functions, since
putStrLn "hello" followed by putStrLn "World" is different from putStrLn "world" then
putStrLn "world". (This wasn't mentioned in the book, but SPJ talks about it in Awkward Squad
paper).
Solution: Imperative languages make state implicit and take care of threading.
but can't do simple equational reasoning anymore
Solution: Haskell uses monads to enable us to describe computations and thread states.
-}
-- =============================================================================
-- 11.3 Higher Order Functions
{- DEFINITION: FIRST ORDER FUNCTION, HIGHER ORDER FUNCTION.
First order function: Takes in ordinary (non-function arguments) and result.
Higher order function: Either takes in a function argument, or produces a function
result (or both).
e.g. length is first order
e.g. map, filter, fold are higher order.
-}
--------------------------------------------------------------------------------
-- Functions that take functions as arguments:
myMap :: (a -> b) -> [a] -> [b]
myMap f = foldr ((:) . f) []
myFilter :: (a -> Bool) -> [a] -> [a]
myFilter p = foldr ifConj []
where ifConj elt acc
| p elt = elt : acc
| otherwise = acc
-- map takes in a function and applies it to a list.
-- filter takes in a predicate and uses it to remove items from a list.
--------------------------------------------------------------------------------
-- Functions that return functions as arguments.
ident, double :: Int -> Int
ident 1 = 1
ident 2 = 2
double 1 = 2
double 2 = 4
multBy :: Int -> (Int -> Int)
multBy 1 = ident
multBy 2 = double
-- here, multby is returning a function that performs the actual multiplication.
{- Evaluating multby 2 1
= (multby 2) 1 -- multby is a fn of one argument
= double 1
= 2
-}
-- less tedious way to write the same:
multBy' :: Int -> (Int -> Int)
multBy' x = (* x)
--------------------------------------------------------------------------------
-- Multiple Arguments as Tuples
{- Our functions have the signature f :: A -> B
So how to represent addition, which would require two arguments?
Answer: bundle them up into a single argument.
Instead of saying 1 + 2, we'd say (+ bundle<1,2>)
In haskell, we can bundle things together using tuples.
-}
myAdd :: Num a => (a,a) -> a
myAdd (a,b) = a + b
-- of course this is cheating because it assumes we have a magical + that can accept
-- two arguments.
-- but if we built a list that looked like [((0,1), 1), ((0,2), 2)] etc then we would
-- have the function we desired
-- Note we have to be clever in constructing the list: can't do all zeros first then ones
-- otherwise the function will never terminate.
-- same idea when we want to return multiple values.
--------------------------------------------------------------------------------
-- Multiple Arguments with Higher Order Functions
{- An alternative way to have multiple arguments would be to return a function
that consumes the remaining arguments.
i.e. 1 + 2 is actually doing (1 +) and applying 2 to the result.
1 + would be the function that adds 1 to its argument.
This method is called currying.
-}
-- =============================================================================
-- 10.4 Total and Partial Functions
{- Let f :: A -> B be a function.
If domain f == A, then the function is total.
If domain f PROPERSUBSET A, the function is partial.
e.g. sqrt :: Integer -> Integer is partial because for example, sqrt 2 is
not an integer so we sqrt would have to map 2 to undefined.
e.g. 1+ :: Natural -> Natural is total because we have a value for every
Natural Number.
-}
isTotal :: (Eq a) => Function a b -> Bool
isTotal (dom, _, maps) = all doesMap dom
where doesMap x = not $ null [y | (y,_) <- maps, y == x]
isPartial :: (Eq a) => Function a b -> Bool
isPartial src = not $ isTotal src
-- example: suppose f maps numbers to characters. source of 1 is from 1 to 5
egK3 = ([1..4], "abcd", zip [1..4] "abcd") -- note no mapping provided for 5.
egK3Total = isTotal egK3 -- expect False
-- the following is partial because it "returns bottom" for every possible value
-- in the domain
infinite_loop :: a -> a
infinite_loop x = infinite_loop x
--------------------------------------------------------------------------------
-- Discussion of the halting problem
-- Want to write a function with the following signature:
wouldHalt :: (Integer -> Integer) -> Integer -> Bool
-- It takes in a function and an argument and returns True if the function halts
-- on the argument.
wouldHalt f x = if f x == f x then True else False
-- this is a terrible idea because if f x actually goes into an infinite loop,
-- then wouldHalt never gets to return.
-- So, we can't actually execute the function. we have to analyze its definition.
-- Can this be done? No.
{- THEOREM: Halting Problem is Undecidable
i.e. there is no function would Halt such that for all f and x:
wouldHalt f x = True if f x terminates, False otherwise.
Proof: Define a function paradox :: Integer -> Integer as follows.
paradox x = if wouldHalt paradox x then paradox x else 1
Now, either wouldHalt paradox x returns True or it returns False.
Case: wouldHalt paradox x = True
Then, we run paradox x. So, we've entered an infinite loop and don't actually
halt. But wouldHalt claimed we would. So this is a contradiction.
Case: wouldHalt paradox x = False
Then, we return 1 and we've halted. But wouldHalt claimed we wouldn't halt,
so this is a paradox.
Since we get a contradiction regardless of what wouldHalt does, wouldHalt cannot exist.
(Thank you Alonzo Church and Alan Turing)
-}
-- =============================================================================
{- Exercises
Ex 1: Are the following functions partial and total?
isPartial [1,2,3] [(1, 2), (2, 3), (3, undefined)]
Partial because 3 is not mapped to a defined value.
-- TODO: my isPartial returns true because it doesn't check that the value is
something other than undefined.
Book has its isPartial take in the codomain as well.
isPartial [1,2] [(1,2), (2,3)]
False. because every element in domain is mapped to unique value.
--------------------------------------------------------------------------------
Ex 2: Are the follwoing functions?
isFunction [(1,2), (2,2)]
yes.
isFunction [(1,2), (2,2), (3,2), (3,1)]
no. 3 is mapped to two values.
isFunction [(1,2), (2,2), (3,2)]
yes.
--------------------------------------------------------------------------------
Ex 3: what is the value of mystery x?
mystery :: Int -> Int
mystery x = if mystery x == 2 then 1 else 3
value of mystery x is bottom because it is not a terminating recursion.
--------------------------------------------------------------------------------
Ex 4: what is the value of mystery2 x?
mystery2 :: Int -> Int
mystery2 x = if x == 20 then 2 + mystery2 x else 3
mystery2 x = 22 if x is 20
3 otherwise
-}
-- =============================================================================
-- 11.5 Function Composition
{- Definition:
Suppose f :: B -> C and g :: A -> B. Then (f o g) is a function
A -> C such that (f o g) x = f (g x)
Think of composition producing a pipeline. First messages are sent to g,
then the results are piped to f.
THEOREM: composition is associative.
i.e. f o (g o h) is the same as (f o g) o h
PROOF: Direct Proof
Suppose h :: A -> B, g :: B -> C, f :: C -> D
Then, g o h :: A -> C
is the same as g (h x)
f o (g o h) :: A -> D
is the same as f (g (h x))
Similarly,
f o g :: B -> D
is the same as f (g x)
(f o g) o h :: A -> D
is the same as (f o g) (h x)
= f (g (h x))
This means we can omit all parentheses.
-}
compose :: (Eq a, Eq b, Eq c) => Function b c -> Function a b -> Function a c
compose f1@(dom1, cod1, maps1) f2@(dom2, cod2, maps2) =
(dom2, cod1, concat [apply' f1 x | x <- maps2])
where apply' rel (a,b) = case apply rel b of
Nothing -> []
Just c -> [(a,c)]
-- example:
egKFn1 = ([1..4], [1..5], [(1,2), (2,3), (3,4), (4,5)])
egKFn2 = ([1..4], [1..10], [(1,2), (2,4), (3,6), (4,8)])
composed = egKFn2 `compose` egKFn1
-- *Functions> composed
-- ([1,2,3,4],[1,2,3,4,5,6,7,8,9,10],[(1,4),(2,6),(3,8)])
--------------------------------------------------------------------------------
-- Exercises
-- Ex 5: What are the values of:
increment = (1 +)
ex5a = map (increment . increment . increment) [1,2,3]
-- we do 1+ three times i.e. do 3+
-- answer: [4,5,6]
ex5b = map ((+ 2) . (* 2) ) [1,2,3]
-- double and add 2
-- answer: 4, 6, 8
-- Exercise 6: Work out the type and graph of f . g
ex6f = ([1,2,3], ["cat", "dog", "mouse"], [(1, "cat"), (2, "dog"), (3, "mouse")])
ex6g = ("abc", [1,2,3], [('a', 1), ('b', 2), ('c', 2), ('d', 3)])
-- f :: Integer -> String
-- g :: Char -> Integer
-- f . g :: Integer -> String
-- specifically,
-- f . g = [('a', "cat"), ('b', "dog"), ('c', "dog"), ('d', "mouse")]
ex6verify = compose ex6f ex6g
-- *Functions> ex6verify
-- [('a',"cat"),('b',"dog"),('c',"dog"),('d',"mouse")]
-- Exercise 7: what does the following expression do?
ex7 xs = ((map (1+)) . (map snd)) xs
{- What is the type of ex7?
map snd :: [(a,b)] -> [b]
map 1+ :: Num a => [a] -> [a]
So, [b] and [a] must be the same.
So xs must have the type Num a => (z, a) -- z is any type
So, ex7s :: Num b => [(a,b)] -> [b]
What does the function do?
It takes in a list of tuples.
It returns a new list where 1 is added to the second item in the tuple.
*Functions> :t ex7
ex7 :: Num b => [(a, b)] -> [b]
NOTE: we can merge the two maps together using the following rule
(map f) . (map g) = map (f . g)
so, ex7 = map ((1+ ) . snd)
-}
-- Ex 8: What is the value of:
ex8 = (fst . snd . fst) ((1, (2,3)), 4)
-- (fst . snd . fst) ((1, (2,3)), 4)
-- = (fst . snd) (fst ((1, (2,3)), 4))
-- = (fst . snd) (1, (2,3))
-- = fst (snd (1, (2,3)))
-- = fst (2,3)
-- = 2
-- *Functions> ex8
-- 2
-- =============================================================================
-- 11.6 Properties of Functions
{- Definition: Surjective Function (Onto)
f :: A -> B is surjective if its codomain is the same as its image
alternatively, forall b in B, exists a in A such that (a,b) in f
-}
isSurjective :: (Eq a, Eq b) => Function a b -> Bool
isSurjective (_, codomain, maps) = codomain `setEq` (map snd maps)
subset :: (Eq a) => [a] -> [a] -> Bool
subset set1 = all ((flip elem) set1)
setEq :: (Eq a) => [a] -> [a] -> Bool
setEq s1 s2 = subset s1 s2 && subset s2 s1
egNotSurj = isSurjective ([1,2,3], "abcd", zip [1,2,3] "abcd") -- nothing maps to d
egSurj = isSurjective ([1,2,3], "abc", zip [1,2,3] "abc")
fnDouble = ([1..10], [1..10], [(x, x * 2) | x <- [1..10], x * 2 < 10])
-- Not surjective because odd numbers in 1..10 are not mapped to
--------------------------------------------------------------------------------
-- Exercise 9, 10, 11: Are the following surjective
ex9a = isSurjective ([1,2,3], [4,5], [(1,4), (2,5), (3,4)])
-- True: both 4 and 5 are mapped to
ex9b = isSurjective ([1,2,3], [4,5], [(1,4), (2,4), (3,4)])
-- False: nothing maps to 5
ex10a = isSurjective ([1,2], [2,3,4], [(1,2), (2,3)])
-- false: 4 is not mapped into
ex10b = isSurjective ([1,2,3], [1,2], [(1,1), (2,1), (3,2)])
-- true
{- 11a : map increment :: [Int] -> [Int]
LEMMA: If f :: A -> B is total and injective, then f-1 :: B -> A
defined as forall (x,y) in f, (y,x) in f-1
is a surjective function
PROOF:
Since f is total, every x is mapped to some y.
=> f-1 is surjective
Since f is injective, no distinct x are mapped to the same y.
=> f-1 is a function because no distinct y map to the same x.
THEOREM: map increment is surjective
PROOF: the inverse of the increment function is the decrement function.
The decrement function is total over the integers.
It is also injective since subtraction is unique.
The inverse of (map f) is just (map f-1).
if the g is total, then map g is total (it can produce values for any input list)
map g is also injective if g is injective
So, (map decrement) is total and injective which means (map increment) is surjective.
-}
{- 11b : take 0 :: [a] -> [a]
take 0 just produces the empty list for all inputs.
So, it is not surjective.
e.g. if we're talking about [Bool], take0 doesn't map anything to
[True] and [False].
-}
{- 11c : drop 0 :: [a] -> [a]
Returns the input list unchanged.
So, every item in codomain can be produced just by passing it as the argument
to drop0.
Hence, surjective.
-}
{- 11d : (++) xs :: [a] -> [a]
Not surjective because any list that doesn't have xs as a suffix can't be
produced.
-}
--------------------------------------------------------------------------------
{- DEFINITION: Injective Function
(which i already used above haha)
f :: A -> B is injective if:
forall x, x' in A, x != x' => f x != f x'
This means that each item in A is mapped to a distinct item in B.
-}
isInjective :: (Eq a, Eq b) => Function a b -> Bool
isInjective (_, _, []) = True
isInjective (dom, cod, ((_,b):xs)) = null [x | (x,y) <- xs, y == b] && isInjective (dom, cod, xs)
eg121 = ([1,2], [3,4,5], [(1,3), (2,5)])
eg122 = ([1,2,3], [4,5], [(1,4), (2,5), (3,5)]) -- note: 2 and 3 both map to 5
-- *Functions> isInjective eg121
-- True
-- *Functions> isInjective eg122
-- False
-- Exercise 12, 13: Are the following injective?
ex12a = isInjective ([1,2,3], [2,4], [(1,2), (2,4), (3,2)])
-- false because 1 and 3 map to 2
ex12b = isInjective ([1,2,3], [2,3,4], [(1,2), (2,4)])
-- true
ex13a = isInjective ([1,2], [1,2,3], [(1,2), (2,3)])
-- true
ex13b = isInjective ([1,2,3], [1,2], [(1,1), (2,2)])
-- true
-- Exercise 14: Suppose f :: A -> B, A has more elements than B, can f be injective?
{- Claim: If f is total, then no. If f is partial and maps at most |b| elements, then yes.
Proof: Direct proof, using the pigeon hole principle.
Let m be |B|, n be |A|. x <= n be the number of elements mapped
Case: m < x (Special case: x = n gives total function)
By pigeon hole principle, at least one item of B just be mapped to more than one
item from A.
Case : x <= m (A is a partial function)
We can map each of the x elements from A into a unique element from B without overlap.
So we can definitely have injection.
-}
-- =============================================================================
-- 11.7 Bijective Functions
{- DEFINITION: Bijection
A function is bijective if it is surjective and injective.
Since it is surjective, every item in the codomain is mapped into.
Since it is injective, every item in domain is mapped to a distinct item.
LEMMA: If f :: A -> B is total and bijective, |A| = |B|
Proof: Direct Proof
Since f is total, every element from A is mapped to something.
Since f is injective, every element is mapped to a distinct element.
So, |B| >= |A| by pigeon hole principle.
Since f is surjective, every element in B is mapped into.
So, |B| == |A|
-}
isBijective :: (Eq a, Eq b) => Function a b -> Bool
isBijective fn = isInjective fn && isSurjective fn && isTotal fn
--------------------------------------------------------------------------------
{- Definition: Permutation
A permutation is a bijective function f :: A -> A
Theorem: Identity function is a permutation.
Proof:
Since id x = x forall x :: a, id is total, injective, surjective
So, id is bijective.
Since id :: a -> a, it is a permutation
Theorem: If f and g are permutations, (f . g) is also a permutation.
Proof:
Since f :: a -> a and g :: a -> a, f . g :: a -> a
It has the required signature.
Proof strategy: we have to show that composition retains the surj, inj and total
properties that were present at the beginning.
Theorem: If f and g are bijective (and total), f . g is also bijective (and total).
Proof: Consider an arbitrary element x in domain of g.
Lemma: If f and g are total, f . g is total
Proof: Consider an arbitrary x :: a TODO: This assumes domain is nonempty
Since g is total, g x is a defined value.
So, f (g x) is itself a defined value.
So, f . g is total
Since f is surjective and g was surjective, f . g is itself surjective.
-> Since f is surjective, if we can produce every element in domain of f,
we are guaranteed to be able to produce every possible output of f
-> Since g is surjective, we can produce every element in domain of f.
-> So, f . g is surjective.
Since f and g are injective, f . g is itself injective.
-> Consider x != x'.
-> g x != g x' since g is injective.
-> Also, y != y' => f y != f y' since f is injective
-> So, f (g x) != f (g y) when x != y
-> So f . g is injective.
So, if f and g are bijective and total, the composition is a total bijection.
-}
isPermutation :: (Eq a) => Function a a -> Bool
isPermutation fn@(dom, co, maps)= dom `setEq` co && isBijective fn
ex16 = isPermutation ([1,2,3], [1,2,3], [(1,3), (2,1), (3,2)])
-- domain same as codomain
-- surjective since mappings to 1,2,3
-- injective since everything maps to distinct element
-- total since have maps from 1,2,3
-- so permutation.
ex17a = isPermutation ([1,2,3], [1,2,3], [(1,2), (2,3)])
-- 3 is not mapped to anything so not total. so not permutation
ex17b = isPermutation ([1,2,3], [1,2,3], [(1,2), (2,3), (3,1)])
-- True. Since clearly surj, inj and total.
-- Ex 18 is (1+) a permutation?
-- Domain is same as codomain
-- Total since every integer has a mapping
-- Injective since 1 + x = 1 + y => x = y
-- Surjective since for arbitrary y in domain, x = y - 1 is mapped into it
-- So is a permutation.
-- Ex 19: Show that composition of surjective functions is surjective
-- I proved a theorem for which this was a lemma above.
--------------------------------------------------------------------------------
-- Inverse Function
-- Definition: (already defined above)
inverse :: Function a b -> Function b a
inverse (dom, c, rels) = (c, dom, map swap rels)
{- Exercise 20: If f :: A -> A is a permutation. Is f-1 a permutation?
Theorem: The inverse of a permutation is also a permutation.
Proof: Have to show total, injective, surjective.
Since f is total, every x is mapped to a valid y.
=> f-1 is surjective
Since f is surjective, for all y in codomain, exists x such that f x = y
=> f-1 is total
Since f is injective, (x,y) and (x', y) in f implies x == x'
=> if (y, x) and (y,x') in f-1, x == x'
=> f-1 is an injective function
Taken together, f-1 is a total injective surjective function
aka permutation
-}
-- =============================================================================
-- 11.8 Cardinality of Sets
{- Definition: Cardinality
A set S is finite iff there is a natural number n such that there is a bijection
mapping the natural numbers {0,1, ..., n -1} to S.
The "cardinality" of S is n, and it is written |S|
-}
{- Definition: Infinite set
Set A is infinite if there exists an injective function f :: A -> B such that
B is a proper subset of A.
Note: the definition is slightly tricky. We take a proper subset of A, but
we're still able to map each element of A into a distinct element of B!!
e.g. Let N' = [2,...] i.e. naturals except 1
Then f :: N -> N', f x = 1 + x is an injective function:
if 1 + x = 1 + x', x == x'
Since we have this injection, f is infinite.
e.g. Let Bool' = [False]. Do we have an injection from Bool to Bool'?
Let's map False to False. Then don't have anything to map True to
(note: we're implicitly assuming things have to be total)
If we map True to False, then don't have anything to map False to.
So, not an injection, so Bool is not infinite.
-}
{- Definition: Same cardinality
Two sets A and B have the same cardinality if there is a bijection f :: A -> B
Example: ["cat", "dog"] has same cardinality as [True, False]
[(cat, True), (dog, False)] is a bijection
Example: Naturals has same cardinality as Integers
N = 0 1 2 3 4 5 6
Z = 0 -1 1 -2 2 -3 3
(we spiral out of Z). This is a bijection:
f :: Z -> N
f x = 2 * x if x > 0
-2 * x + 1 otherwise
-}
{- Definition: Countable
A set is countable if there is a bijection between it and the naturals.
-}
{- Exercise 21 : Why can't a finite set have an injection to its proper subset?
Proof: Suppose the set A is finite.
Then, there exists an N such that there is a bijection between
A and [0, ... , N - 1]
Let B be a proper subset of A.
Then, exists x in A such that x not in B.
So, can have a bijection between M and B, M < N
Proof: Suppose 'a' is in A but not in B.
If 'a' is mapped to k, and 'z' is mapped to N - 1
Then, map 'a' to N - 1 and 'z' to k
Now, even [0, ... , N - 2] is a bijection with B.
So, the size of B is M, M < N
By pigeon hole principle, we can't have an injection between A and B
because there are fewer elements in B. (M vs N)
-}
{- Exercise 22: Suppose your manager gave you the task of writing a program that determines
whether an arbitrary set was finite or infinite. Would you accept it? Why or why not?
DO NOT ACCEPT THE JOB!
Theorem: Halting Problem is reducible to this problem.
Proof:
Suppose you wrote cardinality :: Set -> Integer | Infinite.
Suppose it is computable.
Suppose steps f x is a function that produces a set of reduction steps while computing
f x.
In particular, if steps f x is finite, f must terminate on input x.
Then, we have an oracle for the halting problem:
willHalt f x = number (steps f x) != 'infinity'
This is a contradiction!
-}
{- Exercise 23: Suppose your manager asked you two write a program that decided whether a
function was a bijection. How would you respond?
Appropriate response: THIS CANNOT BE DONE
Suppose isBijection is computable.
Then I can ask you whether a set has a bijection with Naturals (telling me its countably
infinite), and if it isn't, i can ask you if it has a bijection with [1..N].
So, I have the cardinality function from before.
And we know how that went.
-}
--------------------------------------------------------------------------------
{- Rational Numbers are countable:
Enumerate rationals in thie following manner:
(1,1)
(1,2) (2,1)
(1,3) (2,2) (3,1)
(1,4) (2,3) (3,2)
Each row in this sequence is finite, so we can print it completely before
going to the next line. So, we can reach each rational in a finite number of steps.
Hence, countable.
-}
--------------------------------------------------------------------------------
{- Real Numbers are Uncountable
We just learned the unnerving fact that cardinality can be the same even when
one set has fewer elements. e.g. Naturals and Naturals except 1 have same cardinality
So, the only way we can say that something is bigger than naturals is to show that
there is no possible bijection between it and the naturals.
Proof Sketch: Reals are strictly larger than Naturals
Actually, we'll show that there are more reals between [0,1] than all naturals.
Suppose there is an enumeration. Then we can make a table where di_j means the jth
digit of the ith real number in the iteration.
It looks like:
. d00 d01 d02 d03 ...
. d10 d11 d12 d13 ...
. d20 d21 d22 d23 ...
Where the leading dot is because we're talking out reals between 0 and 1.
Now we'll construct a new real number between 0 and 1.
The new real will be dy0 dy1 dy2 ...
To make it different from the first real in the enumeration, it is enough to make the
dy0 different from d00.
So let's say dy0 = 0 if dx0 != 0, otherwise dy0 = 1
We can keep doing this for every single digit.
We now have a number that is different from every single one in the enumeration.
We didn't need to know any details about how the enumeration was done.
(Thank you Georg Cantor)
-}
-- =============================================================================
-- Review Exercises begin here.
{- Ex 25: Program has an expression (f . g) x
1) If g goes into an infinite loop, does that mean entire expression is bottom?
No. F could produce a value without knowing its arguments:
e.g. f _ = 2.
2) If f goes into an infinite loop, does that mean entire expression is bottom?
Yes. f _ is bottom so f (g x) is itself bottom.
-}
{- Ex 26: Which of the following are true?
1) If f and g are surjective, f o g is surjective.
True: can produce every possible input for f because g is surjective.
so, can produce every possible output of f, which is the entire codomain.
SO, fog is surjective.
2) If f and g are injective, f o g is injective.
True: Proof is by contradiction.
Suppose x != x' but fog x == fog x'
Since fog x == fog x' and f is injective, we must have g x == g x'
But g is injective so x != x' => g x != g x'
Contradiction.
3) If fog if bijective, f is surjective and g is injective.
Suppose f :: B -> C, g :: A -> B
Since fog is bijective
1. fog is surjective: image of fog is C
=> Image of f is C
=> f is surjective
2. fog is injective: x != x' => fog x != fog x'
Since f is a function, f x produces exactly one value.
So, g x != g x' if fog x and fog x' are different
Since x != x' => g x != g x', g is injective.
4) If fog is bijective, gof is bijective
Proved earlier, but I assumed total as well. I think the book implicitly makes
the same assumption.
-}
--------------------------------------------------------------------------------
-- Exercise 27
ex27f = ([1,2,3], [4,5,6], [(1,4), (2,6), (3,5)])
ex27g = ([4,5,6], [1,2,3], [(4,1), (5,1), (6,2)])
ex27_a = apply (ex27g `compose` ex27f) 1
-- g (f 1) = g (4) = 1
ex27_b = apply (ex27g `compose` ex27f) 3
-- g (f 3) = g (5) = 1
ex27_c = apply (ex27f `compose` ex27g) 4
-- f (g 4) = f (1) = 4
ex27_d = apply (ex27f `compose` ex27g) 5
-- f (g 5) = f (1) = 4
--------------------------------------------------------------------------------
-- Exercise 28, 29: State properties of following functions
ex28f = ([3,4,5], [3,4,5], [(3,4), (4,5), (5,3)])
-- permutation
ex28g = ([0,1,2], [0,1,2], [(0,0), (1,1), (2,2)])
-- permutation
ex28h = ([3,4,5], [3,4,5], [(4,3), (5,4), (3,5)])
-- permutation
ex29f = ("xyz", [7,8,9,10], [('x', 8), ('y', 10), ('z', 7)])
-- total, injection, not surjection
ex29g = ([7..10], "xyz", [(7,'x'), (8, 'x'), (9, 'x'), (10, 'x')])
-- total, not injection, not surjection
ex29h = ([7..10], [7..10], [(7,10), (8, 7), (9, 8), (10, 9)])
-- permutation
--------------------------------------------------------------------------------
-- Exercise 30: Are the following functions?
ex30a = isFunction ([1..5], [1..5], [(1,2), (2,3), (3,3), (3,4), (4,4), (4,5)])
-- No because 3 and 4 are mapped into multiple objects
ex30b = isFunction ([1..5], [1..5], [(1,2), (2,1), (3,4), (4,4), (5,3)])
-- Is a function.
ex30c = isFunction ([1..5], [1..5], [(1,2), (2,3), (3,4), (4,1)])
-- 5 is not mapped to anything. So it's not a total function.
--------------------------------------------------------------------------------
-- Ex 31: Which of the following are partial functions?
-- If there was a clause f x = undefined, I just didn't add (x,undefined) to the list
-- of relations.
ex31a = ([1..3], [1..3], [(2,1), (3,2)])
-- partial because 1 is not mapped to anything
ex31b = ([1..3], [1..3], [(1,3), (2,2), (3,1)])
-- total
ex31c = ([1..3], [1..3], [])
-- partial
--------------------------------------------------------------------------------
-- Ex 32:
ex32f = ([1,2,3], [7,8,9,10], [(1,7), (2,8), (3,9)])
ex32g = ([7,8,9,10], [1,2,3], [(7,1), (8,2), (9,3), (10,1)])
ex32h = ([1,2,3], [1,2,3], [(1,3), (2,2), (3,1)])
ex32_a = isSurjective $ ex32h `compose` ex32h
-- h is a permutation so hoh is also a permutation. so it is surjective
ex32_b = isSurjective $ ex32f `compose` ex32g
-- image of g is: {1,2,3} that is domain of f. f is not surjective
-- hence fog not surjective
ex32_c = isSurjective $ ex32g `compose` ex32f
-- image of f is: {7,8,9}
-- Using that, g can produce: {1,2,3}, which is the codomain
-- Hence, surjective.
ex32_d = isSurjective $ ex32h `compose` ex32f
-- image of f is: {7,8,9}
-- h isn't even defined over this domain!
-- so not surjective
ex32_e = isSurjective $ ex32g `compose` ex32h
-- domain of g is different than image of h
-- so the function produces undefined
-- so not surjective
--------------------------------------------------------------------------------
-- Ex 33: Which are injective?
ex33f = ([1,2,3], [4,5,6], [(1,4), (2,5), (3,5)])
ex33g = ([4,5,6], [1,2,3], [(4,1), (5,2), (6,3)])
ex33h = ([4,5,6], [1,2,3], [(4,1), (5,1), (6,1)])
ex33_a = isInjective ex33f
-- 2 and 3 map to 5 so no.
ex33_b = isInjective ex33g
-- yes
ex33_c = isInjective ex33h
-- no. everything maps to 1.
--------------------------------------------------------------------------------
-- Ex 34: Which are bijections?
ex34f = ([6,7,8,9], [1,2,3], [(6,1), (7,2), (8,3), (9,3)])
ex34g = ([1,2,3], [1,2,3], [(1,3), (2,2), (3,1)])
ex34h = ([1,2,3], [6,7,8,9], [(1,6), (2,7), (3,8)])
ex34_a = isBijective $ ex34g `compose` ex34g
-- g is a permutation so gog is also a permutation.
-- so it is bijective
ex34_b = isBijective $ ex34h `compose` ex34f
-- image of f is {1,2,3}
-- using {1,2,3}, h can produce {6,7,8} but not 9
-- so not surjective
ex34_c = isBijective $ ex34f `compose` ex34h
-- image of h is {6,7,8}
-- using {6,7,8}, f can produce {1,2,3}
-- that is the codomain of (hof)
-- the resulting mapping is [(6,6), (7,7), (8,8)]
-- so injective.
-- hence bijective.
--------------------------------------------------------------------------------
-- Ex 35: Which are partial?
ex35a True = False
ex35a False = ex35a False
-- ex35a produces bottom on False so partial
ex35b True = True
ex35b False = True
-- no bottom produced. so total
--------------------------------------------------------------------------------
-- Ex 36: writing isFunction. Did this at the top of document.
--------------------------------------------------------------------------------
-- Ex 37: writing isInjection. Also done at the top
--------------------------------------------------------------------------------
-- Ex 38: Can we determine if a function is surjective without knowing the codomain?
-- No. Because you need to check that the image is equal to the codomain.
ITION: Inductively Defined Function
Suppose "h" is a non-recursive function. Then, the function f of the form:
f 0 = k
f n = h (f (n - 1))
is said to be inductively defined.
--------------------
-- Example: length
length [] = 0
length (x:xs) = 1 + length (xs)
Here, [] plays the role of 0, k = 0, h is the (1 +) function
--------------------
-- Example: and
and [] = True
and (x:xs) = x && and xs
Again, [] plays the role of 0, k = True, h is the (x &&) function.
-}
--------------------------------------------------------------------------------
-- 11.2.2 Primitive Recursion
{- DEFINITION: Primitive Recursive Function
A function f is primitive recursive if its definition has the following form:
f 0 x = g x
f (k + 1) x = h (f k x) k x
Where: g and h are primitive recursive.
NOTE: this is definition is incomplete because it talks about how to compose
existing primitive recursive functions (g and h) to get a new one (f), but doesn't
talk about where g and h come from in the first place. In other words, we have no
"base case".
I went to wikipedia and there are several basic primitive recursive functions:
1. Constant function
2. Successor Function
3. "Projection Function"
-}
{- Example: Square
square x = f 0 x
where f 0 x = g x
g x = x * x
Note: requires us to prove that x * x is a primitive recursive function.
LEMMA: Addition is primitive recursive.
PROOF: Adapted from wikipedia
Suppose addition is defined as:
0 + x = 0 clause 1
(k + 1) + x = k + (1 + x) clause 2
So, g = const 0, which is a basic primitive recursive function.
h r k x = Successor(r) where r = k + x, and successor is primitive recursive.
Hence, addition is primitive recursive.
LEMMA: Multiplication is primitive recursive.
PROOF: Define multiplication as:
0 * x = 0 clause 1
(k + 1) * x = Add(x, k * x) clause 2
So, clause 1 uses const 0 function, which is primitive recursive
clause 2 uses Add, which we proved is primitive recursive above.
Hence, multiplication is primitive recursive.
Theorem: g x = x * x is primitive recursive
Proof: It's just multiplication.
--------------------
Example: Factorial
factorial k = f k undefined
where f 0 x = 1
f (k + 1) x = (k + 1) * (f k x)
Note: passing undefined to f because we ignore 2nd argument everywhere.
Clause 1 uses const 1, which is primitive recursive
Clause 2 uses successor and multiplication which are both primitive recursive.
--------------------
Example: Not primitive recursive
f 0 = 0
f 1 = 1
f x = if even x then 1 + f (x `div` 2) else f x
Not primitive recursive because it calls itself with the same arguments when x is even.
So i guess we can't compose this function out of any primitive recursive functions.
-}
--------------------------------------------------------------------------------
-- 11.2.3 Computational complexity
-- space and time complexity
-- can have simply defined but expensive computations: e.g. ackermann function.
--------------------------------------------------------------------------------
-- 11.2.4 State
{- Suppose we have a "function" that takes in an integer and multiplies it by the
hour of the day.
Then, calling this function with the same argument at different hours can give
different results.
We can describe this as a pure computation by having State of the system be an
argument to it: f :: State -> Integer -> Integer. Now, if we call it with the
same state, it returns the same value.
Problem: If we're using state frequently, can have explicit state arguments everywhere
Also problem: We need to thread the state correctly between stateful functions, since
putStrLn "hello" followed by putStrLn "World" is different from putStrLn "world" then
putStrLn "world". (This wasn't mentioned in the book, but SPJ talks about it in Awkward Squad
paper).
Solution: Imperative languages make state implicit and take care of threading.
but can't do simple equational reasoning anymore
Solution: Haskell uses monads to enable us to describe computations and thread states.
-}
-- =============================================================================
-- 11.3 Higher Order Functions
{- DEFINITION: FIRST ORDER FUNCTION, HIGHER ORDER FUNCTION.
First order function: Takes in ordinary (non-function arguments) and result.
Higher order function: Either takes in a function argument, or produces a function
result (or both).
e.g. length is first order
e.g. map, filter, fold are higher order.
-}
--------------------------------------------------------------------------------
-- Functions that take functions as arguments:
myMap :: (a -> b) -> [a] -> [b]
myMap f = foldr ((:) . f) []
myFilter :: (a -> Bool) -> [a] -> [a]
myFilter p = foldr ifConj []
where ifConj elt acc
| p elt = elt : acc
| otherwise = acc
-- map takes in a function and applies it to a list.
-- filter takes in a predicate and uses it to remove items from a list.
--------------------------------------------------------------------------------
-- Functions that return functions as arguments.
ident, double :: Int -> Int
ident 1 = 1
ident 2 = 2
double 1 = 2
double 2 = 4
multBy :: Int -> (Int -> Int)
multBy 1 = ident
multBy 2 = double
-- here, multby is returning a function that performs the actual multiplication.
{- Evaluating multby 2 1
= (multby 2) 1 -- multby is a fn of one argument
= double 1
= 2
-}
-- less tedious way to write the same:
multBy' :: Int -> (Int -> Int)
multBy' x = (* x)
--------------------------------------------------------------------------------
-- Multiple Arguments as Tuples
{- Our functions have the signature f :: A -> B
So how to represent addition, which would require two arguments?
Answer: bundle them up into a single argument.
Instead of saying 1 + 2, we'd say (+ bundle<1,2>)
In haskell, we can bundle things together using tuples.
-}
myAdd :: Num a => (a,a) -> a
myAdd (a,b) = a + b
-- of course this is cheating because it assumes we have a magical + that can accept
-- two arguments.
-- but if we built a list that looked like [((0,1), 1), ((0,2), 2)] etc then we would
-- have the function we desired
-- Note we have to be clever in constructing the list: can't do all zeros first then ones
-- otherwise the function will never terminate.
-- same idea when we want to return multiple values.
--------------------------------------------------------------------------------
-- Multiple Arguments with Higher Order Functions
{- An alternative way to have multiple arguments would be to return a function
that consumes the remaining arguments.
i.e. 1 + 2 is actually doing (1 +) and applying 2 to the result.
1 + would be the function that adds 1 to its argument.
This method is called currying.
-}
-- =============================================================================
-- 10.4 Total and Partial Functions
{- Let f :: A -> B be a function.
If domain f == A, then the function is total.
If domain f PROPERSUBSET A, the function is partial.
e.g. sqrt :: Integer -> Integer is partial because for example, sqrt 2 is
not an integer so we sqrt would have to map 2 to undefined.
e.g. 1+ :: Natural -> Natural is total because we have a value for every
Natural Number.
-}
isTotal :: (Eq a) => Function a b -> Bool
isTotal (dom, _, maps) = all doesMap dom
where doesMap x = not $ null [y | (y,_) <- maps, y == x]
isPartial :: (Eq a) => Function a b -> Bool
isPartial src = not $ isTotal src
-- example: suppose f maps numbers to characters. source of 1 is from 1 to 5
egK3 = ([1..4], "abcd", zip [1..4] "abcd") -- note no mapping provided for 5.
egK3Total = isTotal egK3 -- expect False
-- the following is partial because it "returns bottom" for every possible value
-- in the domain
infinite_loop :: a -> a
infinite_loop x = infinite_loop x
--------------------------------------------------------------------------------
-- Discussion of the halting problem
-- Want to write a function with the following signature:
wouldHalt :: (Integer -> Integer) -> Integer -> Bool
-- It takes in a function and an argument and returns True if the function halts
-- on the argument.
wouldHalt f x = if f x == f x then True else False
-- this is a terrible idea because if f x actually goes into an infinite loop,
-- then wouldHalt never gets to return.
-- So, we can't actually execute the function. we have to analyze its definition.
-- Can this be done? No.
{- THEOREM: Halting Problem is Undecidable
i.e. there is no function would Halt such that for all f and x:
wouldHalt f x = True if f x terminates, False otherwise.
Proof: Define a function paradox :: Integer -> Integer as follows.
paradox x = if wouldHalt paradox x then paradox x else 1
Now, either wouldHalt paradox x returns True or it returns False.
Case: wouldHalt paradox x = True
Then, we run paradox x. So, we've entered an infinite loop and don't actually
halt. But wouldHalt claimed we would. So this is a contradiction.
Case: wouldHalt paradox x = False
Then, we return 1 and we've halted. But wouldHalt claimed we wouldn't halt,
so this is a paradox.
Since we get a contradiction regardless of what wouldHalt does, wouldHalt cannot exist.
(Thank you Alonzo Church and Alan Turing)
-}
-- =============================================================================
{- Exercises
Ex 1: Are the following functions partial and total?
isPartial [1,2,3] [(1, 2), (2, 3), (3, undefined)]
Partial because 3 is not mapped to a defined value.
-- TODO: my isPartial returns true because it doesn't check that the value is
something other than undefined.
Book has its isPartial take in the codomain as well.
isPartial [1,2] [(1,2), (2,3)]
False. because every element in domain is mapped to unique value.
--------------------------------------------------------------------------------
Ex 2: Are the following functions?
isFunction [(1,2), (2,2)]
yes.
isFunction [(1,2), (2,2), (3,2), (3,1)]
no. 3 is mapped to two values.
isFunction [(1,2), (2,2), (3,2)]
yes.
--------------------------------------------------------------------------------
Ex 3: what is the value of mystery x?
mystery :: Int -> Int
mystery x = if mystery x == 2 then 1 else 3
value of mystery x is bottom because it is not a terminating recursion.
--------------------------------------------------------------------------------
Ex 4: what is the value of mystery2 x?
mystery2 :: Int -> Int
mystery2 x = if x == 20 then 2 + mystery2 x else 3
mystery2 x = 22 if x is 20
3 otherwise
-}
-- =============================================================================
-- 11.5 Function Composition
{- Definition:
Suppose f :: B -> C and g :: A -> B. Then (f o g) is a function
A -> C such that (f o g) x = f (g x)
Think of composition producing a pipeline. First messages are sent to g,
then the results are piped to f.
THEOREM: composition is associative.
i.e. f o (g o h) is the same as (f o g) o h
PROOF: Direct Proof
Suppose h :: A -> B, g :: B -> C, f :: C -> D
Then, g o h :: A -> C
is the same as g (h x)
f o (g o h) :: A -> D
is the same as f (g (h x))
Similarly,
f o g :: B -> D
is the same as f (g x)
(f o g) o h :: A -> D
is the same as (f o g) (h x)
= f (g (h x))
This means we can omit all parentheses.
-}
compose :: (Eq a, Eq b, Eq c) => Function b c -> Function a b -> Function a c
compose f1@(dom1, cod1, maps1) f2@(dom2, cod2, maps2) =
(dom2, cod1, concat [apply' f1 x | x <- maps2])
where apply' rel (a,b) = case apply rel b of
Nothing -> []
Just c -> [(a,c)]
-- example:
egKFn1 = ([1..4], [1..5], [(1,2), (2,3), (3,4), (4,5)])
egKFn2 = ([1..4], [1..10], [(1,2), (2,4), (3,6), (4,8)])
composed = egKFn2 `compose` egKFn1
-- *Functions> composed
-- ([1,2,3,4],[1,2,3,4,5,6,7,8,9,10],[(1,4),(2,6),(3,8)])
--------------------------------------------------------------------------------
-- Exercises
-- Ex 5: What are the values of:
increment = (1 +)
ex5a = map (increment . increment . increment) [1,2,3]
-- we do 1+ three times i.e. do 3+
-- answer: [4,5,6]
ex5b = map ((+ 2) . (* 2) ) [1,2,3]
-- double and add 2
-- answer: 4, 6, 8
-- Exercise 6: Work out the type and graph of f . g
ex6f = ([1,2,3], ["cat", "dog", "mouse"], [(1, "cat"), (2, "dog"), (3, "mouse")])
ex6g = ("abc", [1,2,3], [('a', 1), ('b', 2), ('c', 2), ('d', 3)])
-- f :: Integer -> String
-- g :: Char -> Integer
-- f . g :: Integer -> String
-- specifically,
-- f . g = [('a', "cat"), ('b', "dog"), ('c', "dog"), ('d', "mouse")]
ex6verify = compose ex6f ex6g
-- *Functions> ex6verify
-- [('a',"cat"),('b',"dog"),('c',"dog"),('d',"mouse")]
-- Exercise 7: what does the following expression do?
ex7 xs = ((map (1+)) . (map snd)) xs
{- What is the type of ex7?
map snd :: [(a,b)] -> [b]
map 1+ :: Num a => [a] -> [a]
So, [b] and [a] must be the same.
So xs must have the type Num a => (z, a) -- z is any type
So, ex7s :: Num b => [(a,b)] -> [b]
What does the function do?
It takes in a list of tuples.
It returns a new list where 1 is added to the second item in the tuple.
*Functions> :t ex7
ex7 :: Num b => [(a, b)] -> [b]
NOTE: we can merge the two maps together using the following rule
(map f) . (map g) = map (f . g)
so, ex7 = map ((1+ ) . snd)
-}
-- Ex 8: What is the value of:
ex8 = (fst . snd . fst) ((1, (2,3)), 4)
-- (fst . snd . fst) ((1, (2,3)), 4)
-- = (fst . snd) (fst ((1, (2,3)), 4))
-- = (fst . snd) (1, (2,3))
-- = fst (snd (1, (2,3)))
-- = fst (2,3)
-- = 2
-- *Functions> ex8
-- 2
-- =============================================================================
-- 11.6 Properties of Functions
{- Definition: Surjective Function (Onto)
f :: A -> B is surjective if its codomain is the same as its image
alternatively, forall b in B, exists a in A such that (a,b) in f
-}
isSurjective :: (Eq a, Eq b) => Function a b -> Bool
isSurjective (_, codomain, maps) = codomain `setEq` (map snd maps)
subset :: (Eq a) => [a] -> [a] -> Bool
subset set1 = all ((flip elem) set1)
setEq :: (Eq a) => [a] -> [a] -> Bool
setEq s1 s2 = subset s1 s2 && subset s2 s1
egNotSurj = isSurjective ([1,2,3], "abcd", zip [1,2,3] "abcd") -- nothing maps to d
egSurj = isSurjective ([1,2,3], "abc", zip [1,2,3] "abc")
fnDouble = ([1..10], [1..10], [(x, x * 2) | x <- [1..10], x * 2 < 10])
-- Not surjective because odd numbers in 1..10 are not mapped to
--------------------------------------------------------------------------------
-- Exercise 9, 10, 11: Are the following surjective
ex9a = isSurjective ([1,2,3], [4,5], [(1,4), (2,5), (3,4)])
-- True: both 4 and 5 are mapped to
ex9b = isSurjective ([1,2,3], [4,5], [(1,4), (2,4), (3,4)])
-- False: nothing maps to 5
ex10a = isSurjective ([1,2], [2,3,4], [(1,2), (2,3)])
-- false: 4 is not mapped into
ex10b = isSurjective ([1,2,3], [1,2], [(1,1), (2,1), (3,2)])
-- true
{- 11a : map increment :: [Int] -> [Int]
LEMMA: If f :: A -> B is total and injective, then f-1 :: B -> A
defined as forall (x,y) in f, (y,x) in f-1
is a surjective function
PROOF:
Since f is total, every x is mapped to some y.
=> f-1 is surjective
Since f is injective, no distinct x are mapped to the same y.
=> f-1 is a function because no distinct y map to the same x.
THEOREM: map increment is surjective
PROOF: the inverse of the increment function is the decrement function.
The decrement function is total over the integers.
It is also injective since subtraction is unique.
The inverse of (map f) is just (map f-1).
if the g is total, then map g is total (it can produce values for any input list)
map g is also injective if g is injective
So, (map decrement) is total and injective which means (map increment) is surjective.
-}
{- 11b : take 0 :: [a] -> [a]
take 0 just produces the empty list for all inputs.
So, it is not surjective.
e.g. if we're talking about [Bool], take0 doesn't map anything to
[True] and [False].
-}
{- 11c : drop 0 :: [a] -> [a]
Returns the input list unchanged.
So, every item in codomain can be produced just by passing it as the argument
to drop0.
Hence, surjective.
-}
{- 11d : (++) xs :: [a] -> [a]
Not surjective because any list that doesn't have xs as a suffix can't be
produced.
-}
--------------------------------------------------------------------------------
{- DEFINITION: Injective Function
(which i already used above haha)
f :: A -> B is injective if:
forall x, x' in A, x != x' => f x != f x'
This means that each item in A is mapped to a distinct item in B.
-}
isInjective :: (Eq a, Eq b) => Function a b -> Bool
isInjective (_, _, []) = True
isInjective (dom, cod, ((_,b):xs)) = null [x | (x,y) <- xs, y == b] && isInjective (dom, cod, xs)
eg121 = ([1,2], [3,4,5], [(1,3), (2,5)])
eg122 = ([1,2,3], [4,5], [(1,4), (2,5), (3,5)]) -- note: 2 and 3 both map to 5
-- *Functions> isInjective eg121
-- True
-- *Functions> isInjective eg122
-- False
-- Exercise 12, 13: Are the following injective?
ex12a = isInjective ([1,2,3], [2,4], [(1,2), (2,4), (3,2)])
-- false because 1 and 3 map to 2
ex12b = isInjective ([1,2,3], [2,3,4], [(1,2), (2,4)])
-- true
ex13a = isInjective ([1,2], [1,2,3], [(1,2), (2,3)])
-- true
ex13b = isInjective ([1,2,3], [1,2], [(1,1), (2,2)])
-- true
-- Exercise 14: Suppose f :: A -> B, A has more elements than B, can f be injective?
{- Claim: If f is total, then no. If f is partial and maps at most |b| elements, then yes.
Proof: Direct proof, using the pigeon hole principle.
Let m be |B|, n be |A|. x <= n be the number of elements mapped
Case: m < x (Special case: x = n gives total function)
By pigeon hole principle, at least one item of B just be mapped to more than one
item from A.
Case : x <= m (A is a partial function)
We can map each of the x elements from A into a unique element from B without overlap.
So we can definitely have injection.
-}
-- =============================================================================
-- 11.7 Bijective Functions
{- DEFINITION: Bijection
A function is bijective if it is surjective and injective.
Since it is surjective, every item in the codomain is mapped into.
Since it is injective, every item in domain is mapped to a distinct item.
LEMMA: If f :: A -> B is total and bijective, |A| = |B|
Proof: Direct Proof
Since f is total, every element from A is mapped to something.
Since f is injective, every element is mapped to a distinct element.
So, |B| >= |A| by pigeon hole principle.
Since f is surjective, every element in B is mapped into.
So, |B| == |A|
-}
isBijective :: (Eq a, Eq b) => Function a b -> Bool
isBijective fn = isInjective fn && isSurjective fn && isTotal fn
--------------------------------------------------------------------------------
{- Definition: Permutation
A permutation is a bijective function f :: A -> A
Theorem: Identity function is a permutation.
Proof:
Since id x = x forall x :: a, id is total, injective, surjective
So, id is bijective.
Since id :: a -> a, it is a permutation
Theorem: If f and g are permutations, (f . g) is also a permutation.
Proof:
Since f :: a -> a and g :: a -> a, f . g :: a -> a
It has the required signature.
Proof strategy: we have to show that composition retains the surj, inj and total
properties that were present at the beginning.
Theorem: If f and g are bijective (and total), f . g is also bijective (and total).
Proof: Consider an arbitrary element x in domain of g.
Lemma: If f and g are total, f . g is total
Proof: Consider an arbitrary x :: a TODO: This assumes domain is nonempty
Since g is total, g x is a defined value.
So, f (g x) is itself a defined value.
So, f . g is total
Since f is surjective and g was surjective, f . g is itself surjective.
-> Since f is surjective, if we can produce every element in domain of f,
we are guaranteed to be able to produce every possible output of f
-> Since g is surjective, we can produce every element in domain of f.
-> So, f . g is surjective.
Since f and g are injective, f . g is itself injective.
-> Consider x != x'.
-> g x != g x' since g is injective.
-> Also, y != y' => f y != f y' since f is injective
-> So, f (g x) != f (g y) when x != y
-> So f . g is injective.
So, if f and g are bijective and total, the composition is a total bijection.
-}
isPermutation :: (Eq a) => Function a a -> Bool
isPermutation fn@(dom, co, maps)= dom `setEq` co && isBijective fn
ex16 = isPermutation ([1,2,3], [1,2,3], [(1,3), (2,1), (3,2)])
-- domain same as codomain
-- surjective since mappings to 1,2,3
-- injective since everything maps to distinct element
-- total since have maps from 1,2,3
-- so permutation.
ex17a = isPermutation ([1,2,3], [1,2,3], [(1,2), (2,3)])
-- 3 is not mapped to anything so not total. so not permutation
ex17b = isPermutation ([1,2,3], [1,2,3], [(1,2), (2,3), (3,1)])
-- True. Since clearly surj, inj and total.
-- Ex 18 is (1+) a permutation?
-- Domain is same as codomain
-- Total since every integer has a mapping
-- Injective since 1 + x = 1 + y => x = y
-- Surjective since for arbitrary y in domain, x = y - 1 is mapped into it
-- So is a permutation.
-- Ex 19: Show that composition of surjective functions is surjective
-- I proved a theorem for which this was a lemma above.
--------------------------------------------------------------------------------
-- Inverse Function
-- Definition: (already defined above)
inverse :: Function a b -> Function b a
inverse (dom, c, rels) = (c, dom, map swap rels)
{- Exercise 20: If f :: A -> A is a permutation. Is f-1 a permutation?
Theorem: The inverse of a permutation is also a permutation.
Proof: Have to show total, injective, surjective.
Since f is total, every x is mapped to a valid y.
=> f-1 is surjective
Since f is surjective, for all y in codomain, exists x such that f x = y
=> f-1 is total
Since f is injective, (x,y) and (x', y) in f implies x == x'
=> if (y, x) and (y,x') in f-1, x == x'
=> f-1 is an injective function
Taken together, f-1 is a total injective surjective function
aka permutation
-}
-- =============================================================================
-- 11.8 Cardinality of Sets
{- Definition: Cardinality
A set S is finite iff there is a natural number n such that there is a bijection
mapping the natural numbers {0,1, ..., n -1} to S.
The "cardinality" of S is n, and it is written |S|
-}
{- Definition: Infinite set
Set A is infinite if there exists an injective function f :: A -> B such that
B is a proper subset of A.
Note: the definition is slightly tricky. We take a proper subset of A, but
we're still able to map each element of A into a distinct element of B!!
e.g. Let N' = [2,...] i.e. naturals except 1
Then f :: N -> N', f x = 1 + x is an injective function:
if 1 + x = 1 + x', x == x'
Since we have this injection, f is infinite.
e.g. Let Bool' = [False]. Do we have an injection from Bool to Bool'?
Let's map False to False. Then don't have anything to map True to
(note: we're implicitly assuming things have to be total)
If we map True to False, then don't have anything to map False to.
So, not an injection, so Bool is not infinite.
-}
{- Definition: Same cardinality
Two sets A and B have the same cardinality if there is a bijection f :: A -> B
Example: ["cat", "dog"] has same cardinality as [True, False]
[(cat, True), (dog, False)] is a bijection
Example: Naturals has same cardinality as Integers
N = 0 1 2 3 4 5 6
Z = 0 -1 1 -2 2 -3 3
(we spiral out of Z). This is a bijection:
f :: Z -> N
f x = 2 * x if x > 0
-2 * x + 1 otherwise
-}
{- Definition: Countable
A set is countable if there is a bijection between it and the naturals.
-}
{- Exercise 21 : Why can't a finite set have an injection to its proper subset?
Proof: Suppose the set A is finite.
Then, there exists an N such that there is a bijection between
A and [0, ... , N - 1]
Let B be a proper subset of A.
Then, exists x in A such that x not in B.
So, can have a bijection between M and B, M < N
Proof: Suppose 'a' is in A but not in B.
If 'a' is mapped to k, and 'z' is mapped to N - 1
Then, map 'a' to N - 1 and 'z' to k
Now, even [0, ... , N - 2] is a bijection with B.
So, the size of B is M, M < N
By pigeon hole principle, we can't have an injection between A and B
because there are fewer elements in B. (M vs N)
-}
{- Exercise 22: Suppose your manager gave you the task of writing a program that determines
whether an arbitrary set was finite or infinite. Would you accept it? Why or why not?
DO NOT ACCEPT THE JOB!
Theorem: Halting Problem is reducible to this problem.
Proof:
Suppose you wrote cardinality :: Set -> Integer | Infinite.
Suppose it is computable.
Suppose steps f x is a function that produces a set of reduction steps while computing
f x.
In particular, if steps f x is finite, f must terminate on input x.
Then, we have an oracle for the halting problem:
willHalt f x = number (steps f x) != 'infinity'
This is a contradiction!
-}
{- Exercise 23: Suppose your manager asked you two write a program that decided whether a
function was a bijection. How would you respond?
Appropriate response: THIS CANNOT BE DONE
Suppose isBijection is computable.
Then I can ask you whether a set has a bijection with Naturals (telling me its countably
infinite), and if it isn't, i can ask you if it has a bijection with [1..N].
So, I have the cardinality function from before.
And we know how that went.
-}
--------------------------------------------------------------------------------
{- Rational Numbers are countable:
Enumerate rationals in the following manner:
(1,1)
(1,2) (2,1)
(1,3) (2,2) (3,1)
(1,4) (2,3) (3,2)
Each row in this sequence is finite, so we can print it completely before
going to the next line. So, we can reach each rational in a finite number of steps.
Hence, countable.
-}
--------------------------------------------------------------------------------
{- Real Numbers are Uncountable
We just learned the unnerving fact that cardinality can be the same even when
one set has fewer elements. e.g. Naturals and Naturals except 1 have same cardinality
So, the only way we can say that something is bigger than naturals is to show that
there is no possible bijection between it and the naturals.
Proof Sketch: Reals are strictly larger than Naturals
Actually, we'll show that there are more reals between [0,1] than all naturals.
Suppose there is an enumeration. Then we can make a table where di_j means the jth
digit of the ith real number in the iteration.
It looks like:
. d00 d01 d02 d03 ...
. d10 d11 d12 d13 ...
. d20 d21 d22 d23 ...
Where the leading dot is because we're talking out reals between 0 and 1.
Now we'll construct a new real number between 0 and 1.
The new real will be dy0 dy1 dy2 ...
To make it different from the first real in the enumeration, it is enough to make the
dy0 different from d00.
So let's say dy0 = 0 if dx0 != 0, otherwise dy0 = 1
We can keep doing this for every single digit.
We now have a number that is different from every single one in the enumeration.
We didn't need to know any details about how the enumeration was done.
(Thank you Georg Cantor)
-}
-- =============================================================================
-- Review Exercises begin here.
{- Ex 25: Program has an expression (f . g) x
1) If g goes into an infinite loop, does that mean entire expression is bottom?
No. F could produce a value without knowing its arguments:
e.g. f _ = 2.
2) If f goes into an infinite loop, does that mean entire expression is bottom?
Yes. f _ is bottom so f (g x) is itself bottom.
-}
{- Ex 26: Which of the following are true?
1) If f and g are surjective, f o g is surjective.
True: can produce every possible input for f because g is surjective.
so, can produce every possible output of f, which is the entire codomain.
SO, fog is surjective.
2) If f and g are injective, f o g is injective.
True: Proof is by contradiction.
Suppose x != x' but fog x == fog x'
Since fog x == fog x' and f is injective, we must have g x == g x'
But g is injective so x != x' => g x != g x'
Contradiction.
3) If fog if bijective, f is surjective and g is injective.
Suppose f :: B -> C, g :: A -> B
Since fog is bijective
1. fog is surjective: image of fog is C
=> Image of f is C
=> f is surjective
2. fog is injective: x != x' => fog x != fog x'
Since f is a function, f x produces exactly one value.
So, g x != g x' if fog x and fog x' are different
Since x != x' => g x != g x', g is injective.
4) If fog is bijective, gof is bijective
Proved earlier, but I assumed total as well. I think the book implicitly makes
the same assumption.
-}
--------------------------------------------------------------------------------
-- Exercise 27
ex27f = ([1,2,3], [4,5,6], [(1,4), (2,6), (3,5)])
ex27g = ([4,5,6], [1,2,3], [(4,1), (5,1), (6,2)])
ex27_a = apply (ex27g `compose` ex27f) 1
-- g (f 1) = g (4) = 1
ex27_b = apply (ex27g `compose` ex27f) 3
-- g (f 3) = g (5) = 1
ex27_c = apply (ex27f `compose` ex27g) 4
-- f (g 4) = f (1) = 4
ex27_d = apply (ex27f `compose` ex27g) 5
-- f (g 5) = f (1) = 4
--------------------------------------------------------------------------------
-- Exercise 28, 29: State properties of following functions
ex28f = ([3,4,5], [3,4,5], [(3,4), (4,5), (5,3)])
-- permutation
ex28g = ([0,1,2], [0,1,2], [(0,0), (1,1), (2,2)])
-- permutation
ex28h = ([3,4,5], [3,4,5], [(4,3), (5,4), (3,5)])
-- permutation
ex29f = ("xyz", [7,8,9,10], [('x', 8), ('y', 10), ('z', 7)])
-- total, injection, not surjection
ex29g = ([7..10], "xyz", [(7,'x'), (8, 'x'), (9, 'x'), (10, 'x')])
-- total, not injection, not surjection
ex29h = ([7..10], [7..10], [(7,10), (8, 7), (9, 8), (10, 9)])
-- permutation
--------------------------------------------------------------------------------
-- Exercise 30: Are the following functions?
ex30a = isFunction ([1..5], [1..5], [(1,2), (2,3), (3,3), (3,4), (4,4), (4,5)])
-- No because 3 and 4 are mapped into multiple objects
ex30b = isFunction ([1..5], [1..5], [(1,2), (2,1), (3,4), (4,4), (5,3)])
-- Is a function.
ex30c = isFunction ([1..5], [1..5], [(1,2), (2,3), (3,4), (4,1)])
-- 5 is not mapped to anything. So it's not a total function.
--------------------------------------------------------------------------------
-- Ex 31: Which of the following are partial functions?
-- If there was a clause f x = undefined, I just didn't add (x,undefined) to the list
-- of relations.
ex31a = ([1..3], [1..3], [(2,1), (3,2)])
-- partial because 1 is not mapped to anything
ex31b = ([1..3], [1..3], [(1,3), (2,2), (3,1)])
-- total
ex31c = ([1..3], [1..3], [])
-- partial
--------------------------------------------------------------------------------
-- Ex 32:
ex32f = ([1,2,3], [7,8,9,10], [(1,7), (2,8), (3,9)])
ex32g = ([7,8,9,10], [1,2,3], [(7,1), (8,2), (9,3), (10,1)])
ex32h = ([1,2,3], [1,2,3], [(1,3), (2,2), (3,1)])
ex32_a = isSurjective $ ex32h `compose` ex32h
-- h is a permutation so hoh is also a permutation. so it is surjective
ex32_b = isSurjective $ ex32f `compose` ex32g
-- image of g is: {1,2,3} that is domain of f. f is not surjective
-- hence fog not surjective
ex32_c = isSurjective $ ex32g `compose` ex32f
-- image of f is: {7,8,9}
-- Using that, g can produce: {1,2,3}, which is the codomain
-- Hence, surjective.
ex32_d = isSurjective $ ex32h `compose` ex32f
-- image of f is: {7,8,9}
-- h isn't even defined over this domain!
-- so not surjective
ex32_e = isSurjective $ ex32g `compose` ex32h
-- domain of g is different than image of h
-- so the function produces undefined
-- so not surjective
--------------------------------------------------------------------------------
-- Ex 33: Which are injective?
ex33f = ([1,2,3], [4,5,6], [(1,4), (2,5), (3,5)])
ex33g = ([4,5,6], [1,2,3], [(4,1), (5,2), (6,3)])
ex33h = ([4,5,6], [1,2,3], [(4,1), (5,1), (6,1)])
ex33_a = isInjective ex33f
-- 2 and 3 map to 5 so no.
ex33_b = isInjective ex33g
-- yes
ex33_c = isInjective ex33h
-- no. everything maps to 1.
--------------------------------------------------------------------------------
-- Ex 34: Which are bijections?
ex34f = ([6,7,8,9], [1,2,3], [(6,1), (7,2), (8,3), (9,3)])
ex34g = ([1,2,3], [1,2,3], [(1,3), (2,2), (3,1)])
ex34h = ([1,2,3], [6,7,8,9], [(1,6), (2,7), (3,8)])
ex34_a = isBijective $ ex34g `compose` ex34g
-- g is a permutation so gog is also a permutation.
-- so it is bijective
ex34_b = isBijective $ ex34h `compose` ex34f
-- image of f is {1,2,3}
-- using {1,2,3}, h can produce {6,7,8} but not 9
-- so not surjective
ex34_c = isBijective $ ex34f `compose` ex34h
-- image of h is {6,7,8}
-- using {6,7,8}, f can produce {1,2,3}
-- that is the codomain of (hof)
-- the resulting mapping is [(6,6), (7,7), (8,8)]
-- so injective.
-- hence bijective.
--------------------------------------------------------------------------------
-- Ex 35: Which are partial?
ex35a True = False
ex35a False = ex35a False
-- ex35a produces bottom on False so partial
ex35b True = True
ex35b False = True
-- no bottom produced. so total
--------------------------------------------------------------------------------
-- Ex 36: writing isFunction. Did this at the top of document.
--------------------------------------------------------------------------------
-- Ex 37: writing isInjection. Also done at the top
--------------------------------------------------------------------------------
-- Ex 38: Can we determine if a function is surjective without knowing the codomain?
-- No. Because you need to check that the image is equal to the codomain.
--------------------------------------------------------------------------------
-- Ex 39: How much information would you need to know about a Haskell function
-- to know that it is not the identity function.
-- the identity function is:
-- 1) function
-- 2) total
-- 3) injection
-- 4) surjection
-- 5) produces same value for any input.
-- knowing if any of these properties don't hold is sufficient.
--------------------------------------------------------------------------------
-- Ex 40: Write: a function that checks whether fog a is the same as h a for some a
comparator :: (Eq a, Eq b, Eq c) => Function b c -> Function a b -> Function a c -> a -> Bool
comparator f g h x = apply (f `compose` g) x == apply h x
--------------------------------------------------------------------------------
-- Ex 41: Is the following definition of isEven inductive?
isEven :: Int -> Bool
isEven 0 = True
isEven 1 = False
isEven n = isEven (n - 2)
{- isEven is inductively defined if i can write it as:
f 0 = k
f n = h (f (n - 1))
where h is non-recursive
If i say h (f (n - 1)) = not f (n - 1), i have a inductive definition.
So it is equivalent to an inductive definition.
-}
--------------------------------------------------------------------------------
-- Ex 42: Is the definition of isOdd inductive?
isOdd :: Int -> Bool
isOdd 0 = False
isOdd 1 = True
isOdd n = if (n < 0) then isOdd (n + 2) else isOdd (n - 2)
-- Yes. because the "h"function just does if.. then and isn't recursive.
--------------------------------------------------------------------------------
-- Ex 43: Questions about properties:
ex43f = ([1..5], [6..10], [(1,7), (2,6), (3,9), (4,7), (5,10)])
ex43g = ([6..10], "abcde", [(6,'b'), (7, 'a'), (6, 'd'), (8, 'c'), (10, 'b')])
ex43_a = isFunction ex43f
-- yes. everything in domain is mapped to a single value.
ex43_b = isInjective ex43f
-- No. 1 and 4 both map to 7.
ex43_c = isSurjective ex43f
-- No. Nothing maps to 8
ex43_d = isFunction ex43g
-- No. 6 is mapped to multiple values.
--------------------------------------------------------------------------------
{- Exercise 44: A = [1..n], f :: A -> P(A).
(1) Prove that f is not surjective.
Proof: Direct proof using pigeon hole principle.
|P(A)| = 2^n
|A| = n
Since f is a function, each item from A can be mapped to at most one item from P(A)
So, can map to at most n items.
So, at least 2^n - n items not mapped to.
Hence, not surjective.
(2) Suppose g :: X -> Y . The set (g . f) (A) is a subset of A
Relation between X and Y
X is P(A) because f produces items from P(A)
apparently the output of gof is a subset of A, so Y subsetof A
(3) Can g be injective?
Suppose f is injective.
Then, the size of the image of f is |A|
But, size of image of g is smaller than |A|
Hence, can't be injective.
If f is not injective, could have everything map into a single element
of the powerset. Easy to make this injective.
(4) Define f and g such that (f . g) is bijective
Let Y = {2,4, ..., n} i.e. all the even numbers in A
Suppose f x = {x}
Then, gof is bijective.
-}
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment