Maximum and Minimum

Posted on 2017-04-07 by nbloomf
Tags: arithmetic-made-difficult, literate-haskell

This page is part of a series on Arithmetic Made Difficult.

This post is literate Haskell; you can load the source into GHCi and play along.


{-# LANGUAGE NoImplicitPrelude #-}
module MaxAndMin
  ( max, min, _test_max_min, main_max_min
  ) where

import Testing
import Booleans
import And
import NaturalNumbers
import Plus
import Times
import LessThanOrEqualTo

With \(\nleq\) in hand we can also define max and min functions. These are less interesting since they do not have to be defined recursively.

We define \(\nmax : \nats \times \nats \rightarrow \nats\) by \[\nmax(a,b) = \bif{\nleq(a,b)}{b}{a}\] and \(\nmin : \nats \times \nats \rightarrow \nats\) by \[\nmin(a,b) = \bif{\nleq(a,b)}{a}{b}.\]

In Haskell:

Special cases.

Let \(a \in \nats\). Then we have the following.

  1. \(\nmax(\zero,a) = a\).
  2. \(\nmax(a,a) = a\).
  3. \(\nmin(\zero,a) = \zero\).
  4. \(\nmin(a,a) = a\).
  1. We have \[\begin{eqnarray*} & & \nmax(\zero,a) \\ & \href{/posts/arithmetic-made-difficult/MaxAndMin.html#def-max} = & \bif{\nleq(\zero,a)}{a}{\zero} \\ & \href{/posts/arithmetic-made-difficult/LessThanOrEqualTo.html#thm-leq-zero} = & \bif{\btrue}{a}{\zero} \\ & \href{/posts/arithmetic-made-difficult/Booleans.html#cor-if-true} = & a \end{eqnarray*}\] as claimed.
  2. We have \[\begin{eqnarray*} & & \nmax(a,a) \\ & \href{/posts/arithmetic-made-difficult/MaxAndMin.html#def-max} = & \bif{\nleq(a,a)}{a}{a} \\ & \href{/posts/arithmetic-made-difficult/LessThanOrEqualTo.html#thm-leq-reflexive} = & \bif{\btrue}{a}{a} \\ & \href{/posts/arithmetic-made-difficult/Booleans.html#cor-if-true} = & a \end{eqnarray*}\] as claimed.
  3. We have \[\begin{eqnarray*} & & \nmin(\zero,a) \\ & \href{/posts/arithmetic-made-difficult/MaxAndMin.html#def-min} = & \bif{\nleq(\zero,a)}{\zero}{a} \\ & \href{/posts/arithmetic-made-difficult/LessThanOrEqualTo.html#thm-leq-zero} = & \bif{\btrue}{\zero}{a} \\ & \href{/posts/arithmetic-made-difficult/Booleans.html#cor-if-true} = & \zero \end{eqnarray*}\] as claimed.
  4. We have \[\begin{eqnarray*} & & \nmin(a,a) \\ & \href{/posts/arithmetic-made-difficult/MaxAndMin.html#def-min} = & \bif{\nleq(a,a)}{a}{a} \\ & \href{/posts/arithmetic-made-difficult/LessThanOrEqualTo.html#thm-leq-reflexive} = & \bif{\btrue}{a}{a} \\ & \href{/posts/arithmetic-made-difficult/Booleans.html#cor-if-true} = & a \end{eqnarray*}\] as claimed.

\(\nmax\) and \(\nmin\) are commutative.

Let \(a,b \in \nats\). Then we have the following.

  1. \(\nmax(a,b) = \nmax(b,a)\).
  2. \(\nmin(a,b) = \nmin(b,a)\).
  1. If $(a,b) = , we have \[\begin{eqnarray*} & & \nmax(a,b) \\ & \href{/posts/arithmetic-made-difficult/MaxAndMin.html#def-max} = & \bif{\nleq(a,b)}{b}{a} \\ & \href{/posts/arithmetic-made-difficult/Not.html#thm-not-involution} = & \bif{\bnot(\bnot(\nleq(a,b)))}{b}{a} \\ & \href{/posts/arithmetic-made-difficult/Not.html#thm-ifnot} = & \bif{\bnot(\nleq(a,b))}{a}{b} \\ & = & \bif{\nleq(b,a)}{a}{b} \\ & \href{/posts/arithmetic-made-difficult/MaxAndMin.html#def-max} = & \nmax(b,a) \end{eqnarray*}\] as claimed; similarly, if \(\nleq(b,a) = \bfalse\) then \(\nmax(a,b) = \nmax(b,a)\). Suppose then that \(\nleq(a,b) = \nleq(b,a) = \btrue\). By antisymmetry we have \(a = b\), and thus \(\nmax(a,b) = \nmax(b,a)\).
  2. If $(a,b) = , we have \[\begin{eqnarray*} & & \nmin(a,b) \\ & \href{/posts/arithmetic-made-difficult/MaxAndMin.html#def-min} = & \bif{\nleq(a,b)}{a}{b} \\ & \href{/posts/arithmetic-made-difficult/Not.html#thm-not-involution} = & \bif{\bnot(\bnot(\nleq(a,b)))}{a}{b} \\ & \href{/posts/arithmetic-made-difficult/Not.html#thm-ifnot} = & \bif{\bnot(\nleq(a,b))}{b}{a} \\ & = & \bif{\nleq(b,a)}{b}{a} \\ & \href{/posts/arithmetic-made-difficult/MaxAndMin.html#def-min} = & \nmin(b,a) \end{eqnarray*}\] as claimed; similarly, if \(\nleq(b,a) = \bfalse\) then \(\nmin(a,b) = \nmin(b,a)\). Suppose then that \(\nleq(a,b) = \nleq(b,a) = \btrue\). By antisymmetry we have \(a = b\), and thus \(\nmin(a,b) = \nmin(b,a)\).

\(\nplus\) and \(\next\) distribute over \(\nmax\) and \(\nmin\).

Let \(a,b,c \in \nats\). Then we have the following.

  1. \(\nmax(\next(a),\next(b)) = \next(\nmax(a,b))\).
  2. \(\nmax(\nplus(c,a),\nplus(c,b)) = \nplus(c,\nmax(a,b))\).
  3. \(\nmin(\next(a),\next(b)) = \next(\nmin(a,b))\).
  4. \(\nmin(\nplus(c,a),\nplus(c,b)) = \nplus(c,\nmin(a,b))\).
  1. We have \[\begin{eqnarray*} & & \nmax(\next(a),\next(b)) \\ & \href{/posts/arithmetic-made-difficult/MaxAndMin.html#def-max} = & \bif{\nleq(\next(a),\next(b))}{\next(b)}{\next(a)} \\ & \href{/posts/arithmetic-made-difficult/LessThanOrEqualTo.html#thm-leq-next-cancel} = & \bif{\nleq(a,b)}{\next(b)}{\next(a)} \\ & \href{/posts/arithmetic-made-difficult/Booleans.html#thm-iffunc} = & \next(\bif{\nleq(a,b)}{b}{a}) \\ & \href{/posts/arithmetic-made-difficult/MaxAndMin.html#def-max} = & \next(\nmax(a,b)) \end{eqnarray*}\] as claimed.
  2. We have \[\begin{eqnarray*} & & \nmax(\nplus(c,a),\nplus(c,b)) \\ & \href{/posts/arithmetic-made-difficult/MaxAndMin.html#def-max} = & \bif{\nleq(\nplus(c,a),\nplus(c,b))}{\nplus(c,b)}{\nplus(c,a)} \\ & \href{/posts/arithmetic-made-difficult/LessThanOrEqualTo.html#thm-leq-plus-compatible-left} = & \bif{\nleq(a,b)}{\nplus(c,b)}{\nplus(c,a)} \\ & \href{/posts/arithmetic-made-difficult/Booleans.html#thm-iffunc} = & \nplus(c,\bif{\nleq(a,b)}{b}{a}) \\ & \href{/posts/arithmetic-made-difficult/MaxAndMin.html#def-max} = & \nplus(c,\nmax(a,b)) \end{eqnarray*}\] as claimed.
  3. We have \[\begin{eqnarray*} & & \nmin(\next(a),\next(b)) \\ & \href{/posts/arithmetic-made-difficult/MaxAndMin.html#def-min} = & \bif{\nleq(\next(a),\next(b))}{\next(a)}{\next(b)} \\ & \href{/posts/arithmetic-made-difficult/LessThanOrEqualTo.html#thm-leq-next-cancel} = & \bif{\nleq(a,b)}{\next(a)}{\next(b)} \\ & \href{/posts/arithmetic-made-difficult/Booleans.html#thm-iffunc} = & \next(\bif{\nleq(a,b)}{a}{b}) \\ & \href{/posts/arithmetic-made-difficult/MaxAndMin.html#def-min} = & \next(\nmin(a,b)) \end{eqnarray*}\] as claimed.
  4. We have \[\begin{eqnarray*} & & \nmin(\nplus(c,a),\nplus(c,b)) \\ & \href{/posts/arithmetic-made-difficult/MaxAndMin.html#def-min} = & \bif{\nleq(\nplus(c,a),\nplus(c,b))}{\nplus(c,a)}{\nplus(c,b)} \\ & \href{/posts/arithmetic-made-difficult/LessThanOrEqualTo.html#thm-leq-plus-compatible-left} = & \bif{\nleq(a,b)}{\nplus(c,a)}{\nplus(c,b)} \\ & \href{/posts/arithmetic-made-difficult/Booleans.html#thm-iffunc} = & \nplus(c,\bif{\nleq(a,b)}{a}{b}) \\ & \href{/posts/arithmetic-made-difficult/MaxAndMin.html#def-min} = & \nplus(c,\nmin(a,b)) \end{eqnarray*}\] as claimed.

\(\ntimes\) distributes over \(\nmax\) and \(\nmin\).

Let \(a,b,c \in \nats\). Then we have the following.

  1. \(\nmax(\ntimes(c,a),\ntimes(c,b)) = \ntimes(c,\nmax(a,b))\).
  2. \(\nmin(\ntimes(c,a),\ntimes(c,b)) = \ntimes(c,\nmin(a,b))\).
  1. We consider two possibilities. If \(c = \zero\), we have \[\begin{eqnarray*} & & \nmax(\ntimes(c,a),\ntimes(c,b)) \\ & \let{c = \zero} = & \nmax(\ntimes(\zero,a),\ntimes(\zero,b)) \\ & = & \nmax(\zero,\ntimes(\zero,b)) \\ & \href{/posts/arithmetic-made-difficult/Times.html#cor-times-up-zero} = & \nmax(\zero,\zero) \\ & \href{/posts/arithmetic-made-difficult/MaxAndMin.html#thm-max-zero-left} = & \zero \\ & \href{/posts/arithmetic-made-difficult/Times.html#cor-times-up-zero} = & \ntimes(\zero,\nmax(a,b)) \\ & \let{c = \zero} = & \ntimes(c,\nmax(a,b)) \end{eqnarray*}\] as claimed. If \(c = \next(d)\), we have \[\begin{eqnarray*} & & \nmax(\ntimes(c,a),\ntimes(c,b)) \\ & \href{/posts/arithmetic-made-difficult/MaxAndMin.html#def-max} = & \bif{\nleq(\ntimes(c,a),\ntimes(c,b))}{\ntimes(c,b)}{\ntimes(c,a)} \\ & = & \bif{\nleq(\ntimes(\next(d),a),\ntimes(\next(d),b))}{\ntimes(c,b)}{\ntimes(c,a)} \\ & = & \bif{\nleq(a,b)}{\ntimes(c,b)}{\ntimes(c,a)} \\ & \href{/posts/arithmetic-made-difficult/Booleans.html#thm-iffunc} = & \ntimes(c,\bif{\nleq(a,b)}{b}{a}) \\ & \href{/posts/arithmetic-made-difficult/MaxAndMin.html#def-max} = & \ntimes(c,\nmax(a,b)) \end{eqnarray*}\] as claimed.
  2. We consider two possibilities. If \(c = \zero\), we have \[\begin{eqnarray*} & & \nmin(\ntimes(c,a),\ntimes(c,b)) \\ & \let{c = \zero} = & \nmin(\ntimes(\zero,a),\ntimes(\zero,b)) \\ & = & \nmin(\zero,\ntimes(\zero,b)) \\ & \href{/posts/arithmetic-made-difficult/Times.html#cor-times-up-zero} = & \nmin(\zero,\zero) \\ & \href{/posts/arithmetic-made-difficult/MaxAndMin.html#thm-min-zero-left} = & \zero \\ & \href{/posts/arithmetic-made-difficult/Times.html#cor-times-up-zero} = & \ntimes(\zero,\nmin(a,b)) \\ & \let{c = \zero} = & \ntimes(c,\nmin(a,b)) \end{eqnarray*}\] as claimed. If \(c = \next(d)\), we have \[\begin{eqnarray*} & & \nmin(\ntimes(c,a),\ntimes(c,b)) \\ & \href{/posts/arithmetic-made-difficult/MaxAndMin.html#def-min} = & \bif{\nleq(\ntimes(c,a),\ntimes(c,b))}{\ntimes(c,a)}{\ntimes(c,b)} \\ & = & \bif{\nleq(\ntimes(\next(d),a),\ntimes(\next(d),b))}{\ntimes(c,a)}{\ntimes(c,b)} \\ & = & \bif{\nleq(a,b)}{\ntimes(c,a)}{\ntimes(c,b)} \\ & \href{/posts/arithmetic-made-difficult/Booleans.html#thm-iffunc} = & \ntimes(c,\bif{\nleq(a,b)}{a}{b}) \\ & \href{/posts/arithmetic-made-difficult/MaxAndMin.html#def-min} = & \ntimes(c,\nmin(a,b)) \end{eqnarray*}\] as claimed.

\(\nmax\) and \(\nmin\) are associative.

Let \(a,b,c \in \nats\). Then we have the following.

  1. \(\nmax(a,\nmax(b,c)) = \nmax(\nmax(a,b),c)\).
  2. \(\nmin(a,\nmin(b,c)) = \nmin(\nmin(a,b),c)\).
  1. Set \[\begin{eqnarray*} & & \nmax(a,\nmax(b,c)) \\ & \href{/posts/arithmetic-made-difficult/MaxAndMin.html#def-max} = & \bif{\nleq(a,\nmax(b,c))}{\nmax(b,c)}{a} \\ & \href{/posts/arithmetic-made-difficult/MaxAndMin.html#def-max} = & \bif{\nleq(a,\bif{\nleq(b,c)}{c}{b})}{\nmax(b,c)}{a} \\ & \href{/posts/arithmetic-made-difficult/Booleans.html#thm-iffunc} = & \bif{\bif{\nleq(b,c)}{\nleq(a,c)}{\nleq(a,b)}}{\nmax(b,c)}{a} \\ & \href{/posts/arithmetic-made-difficult/MaxAndMin.html#def-max} = & \bif{\bif{\nleq(b,c)}{\nleq(a,c)}{\nleq(a,b)}}{\bif{\nleq(b,c)}{c}{b}}{a} \\ & = & Q \end{eqnarray*}\] and \[\begin{eqnarray*} & & \nmax(\nmax(a,b),c) \\ & \href{/posts/arithmetic-made-difficult/MaxAndMin.html#def-max} = & \bif{\nleq(\nmax(a,b),c)}{c}{\nmax(a,b)} \\ & \href{/posts/arithmetic-made-difficult/MaxAndMin.html#def-max} = & \bif{\nleq(\bif{\nleq(a,b)}{b}{a},c)}{c}{\nmax(a,b)} \\ & = & \bif{\bif{\nleq(a,b)}{\nleq(b,c)}{\nleq(a,c)}}{c}{\nmax(a,b)} \\ & \href{/posts/arithmetic-made-difficult/MaxAndMin.html#def-max} = & \bif{\bif{\nleq(a,b)}{\nleq(b,c)}{\nleq(a,c)}}{c}{\bif{\nleq(a,b)}{b}{a}} \\ & = & R. \end{eqnarray*}\] as claimed. If \(\nleq(a,b) = \btrue\) and \(\nleq(b,c) = \btrue\), by transitivity we have \(\nleq(a,c) = \btrue\) and \[Q = \bif{\nleq(a,c)}{c}{a} = c = \bif{\nleq(b,c)}{c}{b} = R.\] If \(\nleq(a,b) = \btrue\) and \(\nleq(b,c) = \bfalse\), we have \[Q = \bif{\nleq(a,b)}{b}{a} = b = \bif{\nleq(b,c)}{c}{b} = R.\] Suppose \(\nleq(a,b) = \bfalse\); then \(\nleq(b,a) = \btrue\). If \(\nleq(a,c) = \btrue\), we have \(\nleq(b,c) = \btrue\) and \[Q = \bif{\nleq(a,c)}{c}{a} = R,\] and if \(\nleq(a,c) = \bfalse\), then \(\nleq(c,a) = \btrue\) and \[Q = \bif{\bfalse}{\bif{\nleq(b,c)}{c}{b}}{a} = a = \bif{\nleq(a,c)}{c}{a} = R.\]
  2. Analogous to (1).

\(\nmax\) and \(\nmin\) satisfy a “least upper bound” and “greatest lower bound” property, respectively, with respect to \(\nleq\).

Let \(a,b,c \in \nats\). Then we have the following.

  1. If \(\nleq(a,c)\) and \(\nleq(b,c)\), then \(\nleq(\nmax(a,b),c)\).
  2. If \(\nleq(c,a)\) and \(\nleq(c,b)\), then \(\nleq(c,\nmin(a,b))\).
  3. \(\nleq(\nmin(a,b),\nmax(a,b)) = \btrue\).
  1. If \(\nleq(a,b) = \btrue\), then \(\nmax(a,b) = b\), and if \(\nleq(a,b) = \bfalse\), then \(\nleq(b,a) = \btrue\), so that \(\nmax(a,b) = a\). In either case we have \(\nleq(\nmax(a,b),c)\).
  2. If \(\nleq(a,b) = \btrue\), then \(\nmin(a,b) = a\), and if \(\nleq(a,b) = \bfalse\), then \(\nleq(b,a) = \btrue\), so that \(\nmin(a,b) = b\). In either case we have \(\nleq(c,\nmin(a,b))\).
  3. Suppose \(\nleq(a,b)\). Now \(\nmin(a,b) = a\) and \(\nmax(a,b) = b\), so that \[\nleq(\nmin(a,b),\nmax(a,b)) = \nleq(a,b) = \btrue\] as claimed. Now if \(\nleq(a,b) = \bfalse\), then \(\nleq(b,a) = \btrue\), and we instead have \(\nmin(a,b) = b\) and \(\nmax(a,b) = a\).

\(\nmax\) and \(\nmin\) interact with \(\nplus\) and \(\ntimes\).

Let \(a,b,c \in \nats\). Then we have the following.

  1. \(\nplus(\nmin(a,b),\nmax(a,b)) = \nplus(a,b)\).
  2. \(\ntimes(\nmin(a,b),\nmax(a,b)) = \ntimes(a,b)\).

We’ll prove both of these at once. Suppose \(\nleq(a,b)\). Now \(\nmin(a,b) = a\) and \(\nmax(a,b) = b\), so that \[\nplus(\nmin(a,b),\nmax(a,b)) = \nplus(a,b)\] and \[\ntimes(\nmin(a,b),\nmax(a,b)) = \ntimes(a,b)\] as claimed. Now if \(\nleq(a,b) = \bfalse\), then \(\nleq(b,a) = \btrue\), and we instead have \(\nmin(a,b) = b\) and \(\nmax(a,b) = a\). Then \[\nplus(\nmin(a,b),\nmax(a,b)) = \nplus(b,a) = \nplus(a,b)\] and \[\ntimes(\nmin(a,b),\nmax(a,b)) = \ntimes(b,a) = \ntimes(a,b)\] as claimed.

And \(\nmax\) and \(\nmin\) distribute over each other.

Let \(a,b,c \in \nats\). Then we have the following.

  1. \(\nmin(a,\nmax(b,c)) = \nmax(\nmin(a,b),\nmin(a,c))\).
  2. \(\nmax(a,\nmin(b,c)) = \nmin(\nmax(a,b),\nmax(a,c))\).
  3. \(\nmin(\nmax(b,c),a) = \nmax(\nmin(b,a),\nmin(c,a))\).
  4. \(\nmax(\nmin(b,c),a) = \nmin(\nmax(b,a),\nmax(c,a))\).
  1. Brute force time! Suppose \(\nleq(a,b) = \btrue\). If \(\nleq(a,c) = \btrue\), then \(\nleq(a,\nmin(b,c))\), so that \(\nleq(a,\nmax(b,c))\). Now we have \[\begin{eqnarray*} & & \nmax(\nmin(a,b),\nmin(a,c)) \\ & = & \nmax(a,a) \\ & \href{/posts/arithmetic-made-difficult/MaxAndMin.html#thm-max-idempotent} = & a \\ & = & \nmin(a,\nmax(b,c)). \end{eqnarray*}\] Suppose \(\nleq(a,c) = \bfalse\); then \(\nleq(c,a) = \btrue\), and by transitivity \(\nleq(c,b) = \btrue\) so that \(\nmax(b,c) = b\). Now \[\begin{eqnarray*} & & \nmax(\nmin(a,b),\nmin(a,c)) \\ & = & \nmax(a,c) \\ & = & a \\ & = & \nmin(a,b) \\ & = & \nmin(a,\nmax(b,c)). \end{eqnarray*}\] Now suppose \(\nleq(a,b) = \bfalse\), so that \(\nleq(b,a) = \btrue\). If \(\nleq(a,c)\), then \(\nleq(b,c)\) by transitivity. So we have \[\begin{eqnarray*} & & \nmax(\nmin(a,b),\nmin(a,c)) \\ & = & \nmax(b,a) \\ & = & a \\ & = & \nmin(a,c) \\ & = & \nmin(a,\nmax(b,c)). \end{eqnarray*}\] If \(\nleq(a,c) = \bfalse\), then \(\nleq(c,a) = \btrue\). In this case we have \(\nleq(\nmax(b,c),a)\), so that \[\begin{eqnarray*} & & \nmax(\nmin(a,b),\nmin(a,c)) \\ & = & \nmax(b,c) \\ & = & \nmin(a,\nmax(b,c)). \end{eqnarray*}\]
  2. Similar to (4), which we can agree was super tedious.
  3. Follows from (4) and commutativity.
  4. Follows from (5) and commutativity.

woo!

Testing

Suite:

_test_max_min ::
  ( TypeName n, Natural n, Equal n, Arbitrary n, Show n
  ) => Int -> Int -> n -> IO ()
_test_max_min size cases n = do
  testLabel1 "min & max" n
  let args = testArgs size cases

  runTest args (_test_max_zero n)
  runTest args (_test_max_idempotent n)
  runTest args (_test_min_zero n)
  runTest args (_test_min_idempotent n)
  runTest args (_test_max_commutative n)
  runTest args (_test_min_commutative n)
  runTest args (_test_max_next n)
  runTest args (_test_max_plus n)
  runTest args (_test_min_next n)
  runTest args (_test_min_plus n)
  runTest args (_test_max_times n)
  runTest args (_test_min_times n)
  runTest args (_test_max_associative n)
  runTest args (_test_min_associative n)
  runTest args (_test_max_lub n)
  runTest args (_test_min_glb n)
  runTest args (_test_max_min_leq n)
  runTest args (_test_max_min_plus n)
  runTest args (_test_max_min_times n)
  runTest args (_test_max_min_distributive_left n)
  runTest args (_test_max_min_distributive_right n)
  runTest args (_test_min_max_distributive_left n)
  runTest args (_test_min_max_distributive_right n)

Main:

main_max_min :: IO ()
main_max_min = do
  _test_max_min 100 100 (zero :: Unary)