1 Functions


1.1 Readings

Discrete Mathematics using a Comptuter (O’Donnell, Hall, Page) Chapter 11

Discrete Mathematics with Applications - Metric Edition (Epp) Chapter 7

The Haskell Road to Logic, Math and Programming (Doets, van Eijck) 6

https://runestone.academy/ns/books/published/dmoi-4/sec_structures-functions.html

https://runestone.academy/ns/books/published/ads/chapter_7.html
https://runestone.academy/ns/books/published/ads/s-function-def-notation.html
https://runestone.academy/ns/books/published/ads/s-properties-of-functions.html
https://runestone.academy/ns/books/published/ads/s-function-composition.html

https://runestone.academy/ns/books/published/DiscreteMathText/chapter7.html
https://runestone.academy/ns/books/published/DiscreteMathText/functions7-1.html
https://runestone.academy/ns/books/published/DiscreteMathText/onetooneonto7-2.html

https://en.wikipedia.org/wiki/Codomain
https://en.wikipedia.org/wiki/Range_of_a_function
https://en.wikipedia.org/wiki/Image_(mathematics)
https://en.wikipedia.org/wiki/Function_(mathematics)
https://en.wikipedia.org/wiki/Function_(computer_programming)
How are these similar, and how are they different?

1.2 Overview images

MathReview/relations-functions-0.png
Relations/relations-def.png
Functions/function-types.jpg
Functions/functions-codomain-range.jpg

1.3 Code

Code-DMUC/Stdm11Functions.hs

-- # Software Tools for Discrete Mathematics
module Stdm11Functions where

import Stdm06LogicOperators
import Stdm08SetTheory
import Stdm10Relations

-- # Chapter 11.  Functions
isFun ::
  (Eq a, Eq b, Show a, Show b) =>
  Set a ->
  Set b ->
  Set (a, FunVals b) ->
  Bool
isFun f_domain f_codomain fun =
  let actual_domain = domain fun
   in normalForm actual_domain
        /\ setEq actual_domain f_domain

data FunVals a = Undefined | Value a
  deriving (Eq, Show)

isPartialFunction ::
  (Eq a, Eq b, Show a, Show b) =>
  Set a ->
  Set b ->
  Set (a, FunVals b) ->
  Bool
isPartialFunction f_domain f_codomain fun =
  isFun f_domain f_codomain fun
    /\ elem Undefined (codomain fun)

imageValues :: (Eq a, Show a) => Set (FunVals a) -> Set a
imageValues f_codomain =
  [v | (Value v) <- f_codomain]

isSurjective ::
  (Eq a, Eq b, Show a, Show b) =>
  Set a ->
  Set b ->
  Set (a, FunVals b) ->
  Bool
isSurjective f_domain f_codomain fun =
  isFun f_domain f_codomain fun
    /\ setEq f_codomain (normalizeSet (imageValues (codomain fun)))

isInjective ::
  (Eq a, Eq b, Show a, Show b) =>
  Set a ->
  Set b ->
  Set (a, FunVals b) ->
  Bool
isInjective f_domain f_codomain fun =
  let fun_image = imageValues (codomain fun)
   in isFun f_domain f_codomain fun
        /\ normalForm fun_image

functionalComposition ::
  (Eq a, Eq b, Eq c, Show a, Show b, Show c) =>
  Set (a, FunVals b) ->
  Set (b, FunVals c) ->
  Set (a, FunVals c)
functionalComposition f1 f2 =
  normalizeSet [(a, c) | (a, Value b) <- f1, (b', c) <- f2, b == b']

isBijective ::
  (Eq a, Eq b, Show a, Show b) =>
  Set a ->
  Set b ->
  Set (a, FunVals b) ->
  Bool
isBijective f_domain f_codomain fun =
  isSurjective f_domain f_codomain fun
    /\ isInjective f_domain f_codomain fun

isPermutation ::
  (Eq a, Show a) => Set a -> Set a -> Set (a, FunVals a) -> Bool
isPermutation f_domain f_codomain fun =
  isBijective f_domain f_codomain fun
    /\ setEq f_domain f_codomain

diagonal :: Int -> [(Int, Int)] -> [(Int, Int)]
diagonal stop rest =
  let interval = [1 .. stop]
   in zip interval (reverse interval) ++ rest

rationals :: [(Int, Int)]
rationals = foldr diagonal [] [1 ..]

Code-HRLMP/HL06FCT.hs

module HL06FCT where

import Data.List

f x = x ^ 2 + 1

list2fct :: (Eq a) => [(a, b)] -> a -> b
list2fct [] _ = error "function not total"
list2fct ((u, v) : uvs) x
  | x == u = v
  | otherwise = list2fct uvs x

fct2list :: (a -> b) -> [a] -> [(a, b)]
fct2list f xs = [(x, f x) | x <- xs]

ranPairs :: (Eq b) => [(a, b)] -> [b]
ranPairs f = nub [y | (_, y) <- f]

listValues :: (Enum a) => (a -> b) -> a -> [b]
listValues f i = (f i) : listValues f (succ i)

listRange :: (Bounded a, Enum a) => (a -> b) -> [b]
listRange f = [f i | i <- [minBound .. maxBound]]

curry3 :: ((a, b, c) -> d) -> a -> b -> c -> d
curry3 f x y z = f (x, y, z)

uncurry3 :: (a -> b -> c -> d) -> (a, b, c) -> d
uncurry3 f (x, y, z) = f x y z

f1 x = x ^ 2 + 2 * x + 1

g1 x = (x + 1) ^ 2

f1' = \x -> x ^ 2 + 2 * x + 1

g1' = \x -> (x + 1) ^ 2

g 0 = 0
g n = g (n - 1) + n

g' n = ((n + 1) * n) / 2

h 0 = 0
h n = h (n - 1) + (2 * n)

k 0 = 0
k n = k (n - 1) + (2 * n - 1)

fac 0 = 1
fac n = fac (n - 1) * n

fac' n = product [1 .. n]

restrict :: (Eq a) => (a -> b) -> [a] -> a -> b
restrict f xs x
  | elem x xs = f x
  | otherwise = error "argument not in domain"

restrictPairs :: (Eq a) => [(a, b)] -> [a] -> [(a, b)]
restrictPairs xys xs = [(x, y) | (x, y) <- xys, elem x xs]

image :: (Eq b) => (a -> b) -> [a] -> [b]
image f xs = nub [f x | x <- xs]

coImage :: (Eq b) => (a -> b) -> [a] -> [b] -> [a]
coImage f xs ys = [x | x <- xs, elem (f x) ys]

imagePairs :: (Eq a, Eq b) => [(a, b)] -> [a] -> [b]
imagePairs f xs = nub [y | (x, y) <- f, elem x xs]

coImagePairs :: (Eq a, Eq b) => [(a, b)] -> [b] -> [a]
coImagePairs f ys = [x | (x, y) <- f, elem y ys]

injective :: (Eq b) => (a -> b) -> [a] -> Bool
injective f [] = True
injective f (x : xs) =
  notElem (f x) (image f xs) && injective f xs

surjective :: (Eq b) => (a -> b) -> [a] -> [b] -> Bool
surjective f xs [] = True
surjective f xs (y : ys) =
  elem y (image f xs) && surjective f xs ys

c2f, f2c :: Int -> Int
c2f x = div (9 * x) 5 + 32
f2c x = div (5 * (x - 32)) 9

succ1 :: Integer -> Integer
succ1 = \x ->
  if x < 0
    then error "argument out of range"
    else x + 1

succ2 :: Integer -> [Integer]
succ2 = \x -> if x < 0 then [] else [x + 1]

pcomp :: (b -> [c]) -> (a -> [b]) -> a -> [c]
pcomp g f = \x -> concat [g y | y <- f x]

succ3 :: Integer -> Maybe Integer
succ3 = \x -> if x < 0 then Nothing else Just (x + 1)

mcomp :: (b -> Maybe c) -> (a -> Maybe b) -> a -> Maybe c
mcomp g f = (maybe Nothing g) . f

part2error :: (a -> Maybe b) -> a -> b
part2error f = (maybe (error "value undefined") id) . f

fct2equiv :: (Eq a) => (b -> a) -> b -> b -> Bool
fct2equiv f x y = (f x) == (f y)

block :: (Eq b) => (a -> b) -> a -> [a] -> [a]
block f x list = [y | y <- list, f x == f y]

Code-HRLMP/Sol06.hs

-- TODO: add all the solutions to corresponding files