All and Any

Posted on 2017-05-10 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 AllAndAny
  ( all, any, _test_all_any, main_all_any
  ) where

import Testing
import Booleans
import Not
import And
import Or
import Predicates
import NaturalNumbers
import Lists
import Snoc
import Reverse
import Cat
import Map

Today we’ll define two boolean functions for lists called \(\all\) and \(\any\). Each one takes as an argument a predicate \(A \rightarrow \bool\), and then tests whether all or any of the items in a list of type \(\lists{A}\) satisfy the predicate.

Let \(A\) be a set and \(p : A \rightarrow \bool\) a predicate. Define \(\varphi : A \times \bool \rightarrow \bool\) by \[\varphi(a,q) = \band(p(a),q).\] Now define \(\all : \bool^A \rightarrow \bool^{\lists{A}}\) by \[\all(p)(x) = \foldr(\btrue)(\varphi)(x).\]

In Haskell:

Since \(\all(p)\) is defined as a \(\foldr(\ast)(\ast)\), it is the unique solution to a system of functional equations.

Let \(A\) be a set and \(p : A \rightarrow \bool\) a predicate. Then \(\all(p)\) is the unique solution \(f : \lists{A} \rightarrow \bool\) to the following equations for all \(a \in A\) and \(x \in \lists{A}\). \[\left\{\begin{array}{l} f(\nil) = \btrue \\ f(\cons(a,x)) = \band(p(a),f(x)) \end{array}\right.\]

\(\all\) interacts with \(\snoc\).

Let \(A\) be a set. For all \(p : A \rightarrow \bool\), \(a \in A\), and \(x \in \lists{A}\), we have \[\all(p,\snoc(a,x)) = \band(p(a),\all(p,x)).\]

We proceed by list induction on \(x\). For the base case \(x = \nil\), we have \[\begin{eqnarray*} & & \all(p,\snoc(a,x)) \\ & = & \all(p,\snoc(a,\nil)) \\ & \href{/posts/arithmetic-made-difficult/Snoc.html#cor-snoc-nil} = & \all(p,\cons(a,\nil)) \\ & = & \band(p(a),\all(p,\nil)) \\ & = & \band(p(a),\all(p,x)) \end{eqnarray*}\] as needed. For the inductive step, suppose the equality holds for all \(p\) and \(a\) for some \(x\) and let \(b \in A\). Using the inductive step, we have \[\begin{eqnarray*} & & \all(p,\snoc(a,\cons(b,x))) \\ & \href{/posts/arithmetic-made-difficult/Snoc.html#cor-snoc-cons} = & \all(p,\cons(b,\snoc(a,x))) \\ & = & \band(p(b),\all(p,\snoc(a,x))) \\ & = & \band(p(b),\band(p(a),\all(p,x))) \\ & = & \band(p(a),\band(p(b),\all(p,x))) \\ & = & \band(p(a),\all(p,\cons(b,x))) \end{eqnarray*}\] as needed.

\(\all\) can also be characterized as a folded map.

\[\all(p,x) = \foldr(\btrue)(\band)(\map(p)(x)).\]

We proceed by list induction on \(x\). For the base case \(x = \nil\), we have \[\begin{eqnarray*} & & \all(p,x) \\ & = & \all(p,\nil) \\ & = & \btrue \\ & \href{/posts/arithmetic-made-difficult/Lists.html#def-foldr-nil} = & \foldr(\btrue)(\band)(\nil) \\ & = & \foldr(\btrue)(\band)(\map(p)(\nil)) \\ & = & \foldr(\btrue)(\band)(\map(p)(x)) \end{eqnarray*}\] as claimed. For the inductive step, suppose the equality holds for some \(x\) and let \(a \in A\). Now \[\begin{eqnarray*} & & \all(p,\cons(a,x)) \\ & = & \band(p(a),\all(p,x)) \\ & = & \band(p(a),\foldr(\btrue)(\band)(\map(p)(x))) \\ & \href{/posts/arithmetic-made-difficult/Lists.html#def-foldr-cons} = & \foldr(\btrue)(\band)(\cons(p(a),\map(p)(x))) \\ & = & \foldr(\btrue)(\band)(\map(p)(\cons(a,x))) \end{eqnarray*}\] as needed.

Two special cases.

Let \(A\) be a set and \(p : A \rightarrow \bool\) a predicate. The following hold for all \(x \in \lists{A}\).

  1. \(\all(\ptrue)(x) = \btrue\).
  2. \(\all(\pfalse)(x) = \bfalse\) if and only if \(x \neq \nil\).
  1. We proceed by list induction on \(x\). For the base case \(x = \nil\), we have \[\begin{eqnarray*} & & \all(\ptrue,x) \\ & = & \all(\ptrue,\nil) \\ & = & \btrue \end{eqnarray*}\] as claimed. For the inductive step, suppose the equality holds for some \(x\) and let \(a \in A\). Now \[\begin{eqnarray*} & & \all(\ptrue)(\cons(a,x)) \\ & = & \band(\ptrue(a),\all(\ptrue)(x)) \\ & = & \band(\btrue,\btrue) \\ & \href{/posts/arithmetic-made-difficult/And.html#thm-and-eval-true-true} = & \btrue \end{eqnarray*}\] as claimed.
  2. We have two possibilities for \(x\). If \(x = \nil\), we have \[\begin{eqnarray*} & & \all(\pfalse)(\nil) \\ & = & \btrue, \end{eqnarray*}\] while if \(x = \cons(a,u)\), we have \[\begin{eqnarray*} & & \all(\pfalse)(\cons(a,u)) \\ & = & \band(\pfalse(a),\all(\pfalse)(u)) \\ & = & \band(\bfalse,\all(\pfalse)(u)) \\ & \href{/posts/arithmetic-made-difficult/And.html#thm-and-false-left} = & \bfalse \end{eqnarray*}\] as needed.

\(\all\) interacts with \(\cat\).

Let \(A\) be a set and \(p : A \rightarrow \bool\). For all \(x,y \in \lists{A}\) we have \[\all(p,\cat(x,y)) = \band(\all(p)(x),\all(p)(y)).\]

We proceed by list induction on \(x\). For the base case \(x = \nil\), we have \[\begin{eqnarray*} & & \all(p)(\cat(x,y)) \\ & = & \all(p)(\cat(\nil,y)) \\ & \href{/posts/arithmetic-made-difficult/Cat.html#cor-cat-nil} = & \all(p)(y) \\ & \href{/posts/arithmetic-made-difficult/And.html#thm-and-true-left} = & \band(\btrue,\all(p)(y)) \\ & = & \band(\all(p)(\nil),\all(p)(y)) \\ & = & \band(\all(p)(x),\all(p)(y)) \end{eqnarray*}\] as needed. For the inductive step, suppose the equality holds for some \(x\) and let \(a \in A\). Now \[\begin{eqnarray*} & & \all(p)(\cat(\cons(a,x),y)) \\ & \href{/posts/arithmetic-made-difficult/Cat.html#cor-cat-cons} = & \all(p)(\cons(a,\cat(x,y))) \\ & = & \band(p(a),\all(p)(\cat(x,y))) \\ & = & \band(p(a),\band(\all(p)(x),\all(p)(y))) \\ & \href{/posts/arithmetic-made-difficult/And.html#thm-and-associative} = & \band(\band(p(a),\all(p)(x)),\all(p)(y)) \\ & = & \band(\all(p)(\cons(a,x)),\all(p)(y)) \end{eqnarray*}\] as needed.

\(\all\) interacts with \(\rev\).

Let \(A\) be a set and \(p : A \rightarrow \bool\). For all \(x \in \lists{A}\) we have \[\all(p,\rev(x)) = \all(p,x).\]

We proceed by list induction on \(x\). For the base case \(x = \nil\), we have \[\begin{eqnarray*} & & \all(p,\rev(x)) \\ & = & \all(p,\rev(\nil)) \\ & \href{/posts/arithmetic-made-difficult/Reverse.html#cor-rev-nil} = & \all(p,\nil) \\ & = & \all(p,x) \end{eqnarray*}\] as claimed. For the inductive step, suppose the equality holds for some \(x\) and let \(a \in A\). Using the inductive hypothesis, we have \[\begin{eqnarray*} & & \all(p,\rev(\cons(a,x))) \\ & = & \all(p,\rev(\cat(\cons(a,\nil),x))) \\ & \href{/posts/arithmetic-made-difficult/Cat.html#thm-rev-cat-antidistribute} = & \all(p,\cat(\rev(x),\rev(\cons(a,\nil)))) \\ & = & \band(\all(p,\rev(x)),\all(p,\rev(\cons(a,\nil)))) \\ & = & \band(\all(p,x),\all(p,\cons(a,\nil))) \\ & \href{/posts/arithmetic-made-difficult/And.html#thm-and-commutative} = & \band(\all(p,\cons(a,\nil)),\all(p,x)) \\ & = & \all(p,\cat(\cons(a,\nil),x)) \\ & = & \all(p,\cons(a,x)) \end{eqnarray*}\] as claimed.

\(\all\) interacts with \(\pimpl\).

Let \(A\) be a set and \(p,q : A \rightarrow \bool\). If \(\pimpl(p,q)\), then \[\bimpl(\all(p,x),\all(q,x)).\]

We proceed by list induction on \(x\). For the base case \(x = \nil\), we have \[\begin{eqnarray*} & & \bimpl(\all(p,\nil),\all(q,\nil)) \\ & = & \bimpl(\btrue,\btrue) \\ & \href{/posts/arithmetic-made-difficult/Implies.html#thm-implies-true-hyp} = & \btrue \end{eqnarray*}\] as needed. For the inductive step, suppose the implication holds for some \(x\) and let \(a \in A\). Now \(\bimpl(p(a),q(a))\), and by the induction hypothesis \(\bimpl(\all(p,x),\all(q,x))\). Then we have \[\begin{eqnarray*} & & \bimpl(\all(p,\cons(a,x)),\all(q,\cons(a,x))) \\ & = & \bimpl(\band(p(a),\all(p,x)),\band(q(a),\all(q),x)) \\ & = & \btrue \end{eqnarray*}\] as needed.

\(\all\) interacts with \(\map\).

Let \(A\) and \(B\) be sets with \(f : A \rightarrow B\) and \(p : B \rightarrow \bool\). Then for all \(x \in \lists{A}\) we have \[\all(p)(\map(f)(x)) = \all(p \circ f)(x).\]

We proceed by list induction on \(x\). For the base case \(x = \nil\), we have \[\begin{eqnarray*} & & \all(p)(\map(f)(x)) \\ & = & \all(p)(\map(f)(\nil)) \\ & \href{/posts/arithmetic-made-difficult/Map.html#cor-map-nil} = & \all(p)(\nil) \\ & = & \btrue \\ & = & \all(p \circ f)(\nil) \\ & = & \all(p \circ f)(x) \end{eqnarray*}\] as needed. For the inductive step, suppose the equality holds for some \(x\) and let \(a \in A\). Now \[\begin{eqnarray*} & & \all(p)(\map(f)(\cons(a,x))) \\ & \href{/posts/arithmetic-made-difficult/Map.html#cor-map-cons} = & \all(p)(\cons(f(a),\map(f)(x))) \\ & = & \band(p(f(a)),\all(p)(\map(f)(x))) \\ & = & \band((p \circ f)(a),\all(p \circ f)(x)) \\ & = & \all(p \circ f)(\cons(a,x)) \end{eqnarray*}\] as needed.

\(\any\) is defined similarly.

Let \(A\) be a set and \(p : A \rightarrow \bool\) a predicate. Define \(\varphi : A \times \bool \rightarrow \bool\) by \[\varphi(a,q) = \bor(p(a),q).\] Now define \(\any : \bool^A \rightarrow \bool^{\lists{A}}\) by \[\all(p)(x) = \foldr(\bfalse)(\varphi)(x).\]

In Haskell:

Since \(\any\) is defined as a fold, it is the unique solution to a system of functional equations.

Let \(A\) be a set and \(p\) a predicate on \(A\). \(\any(p)\) is the unique map \(f : \lists{A} \rightarrow \bool\) satisfying the following equations for all \(a \in A\) and \(x \in \lists{A}\). \[\left\{\begin{array}{l} f(\nil) = \bfalse \\ f(\cons(a,x)) = \bor(p(a),f(x)) \end{array}\right.\]

\(\any\) can also be characterized as a folded map.

Let \(A\) be a set with \(p\) a predicate on \(A\). Then \[\any(p,x) = \foldr(\bfalse)(\bor)(\map(p)(x)).\]

We proceed by list induction on \(x\). For the base case \(x = \nil\), we have \[\begin{eqnarray*} & & \any(p,x) \\ & = & \any(p,\nil) \\ & = & \bfalse \\ & \href{/posts/arithmetic-made-difficult/Lists.html#def-foldr-nil} = & \foldr(\bfalse)(\bor)(\nil) \\ & = & \foldr(\bfalse)(\bor)(\map(p)(\nil)) \\ & = & \foldr(\bfalse)(\bor)(\map(p)(x)) \end{eqnarray*}\] as needed. For the inductive step, suppose the equality holds for some \(x\) and let \(a \in A\). Then we have \[\begin{eqnarray*} & & \any(p,\cons(a,x)) \\ & = & \bor(p(a),\any(x)) \\ & = & \bor(p(a),\foldr(\bfalse)(\bor)(\map(p)(x))) \\ & \href{/posts/arithmetic-made-difficult/Lists.html#def-foldr-cons} = & \foldr(\bfalse)(\bor)(\cons(p(a),\map(p)(x))) \\ & = & \foldr(\bfalse)(\bor)(\map(p)(\cons(a,x))) \end{eqnarray*}\] as needed.

A version of DeMorgan’s law holds for \(\any\) and \(\all\).

Let \(A\) be a set with \(p : A \rightarrow \bool\). Then the following hold for all \(x \in \lists{A}\).

  1. \(\any(p,x) = \bnot(\all(\bnot \circ p,x))\).
  2. \(\all(p,x) = \bnot(\any(\bnot \circ p,x))\).
  1. We proceed by list induction on \(x\). For the base case \(x = \nil\), we have \[\begin{eqnarray*} & & \bnot(\all(\bnot \circ p,x)) \\ & = & \bnot(\all(\bnot \circ p,\nil)) \\ & = & \bnot(\btrue) \\ & \href{/posts/arithmetic-made-difficult/Not.html#thm-not-true} = & \bfalse \\ & = & \foldr(\bfalse)(\varphi(p))(\nil) \\ & = & \foldr(\bfalse)(\varphi(p))(x) \end{eqnarray*}\] as needed. For the inductive step, suppose the equality holds for some \(x\) and let \(a \in A\). Then we have \[\begin{eqnarray*} & & \bnot(\all(\bnot \circ p,\cons(a,x))) \\ & = & \bnot(\band(\bnot(p(a)),\all(\bnot \circ p,x))) \\ & = & \bor(\bnot(\bnot(p(a))),\bnot(\all(\bnot \circ p,x))) \\ & = & \bor(p(a),\any(p,x)) \\ & = & \any(p,\cons(a,x)) \end{eqnarray*}\] as needed.
  2. Note that \[\begin{eqnarray*} & & \bnot(\any(\bnot \circ p,x)) \\ & = & \bnot(\bnot(\all(\bnot \circ \bnot \circ p,x))) \\ & = & \all(p,x) \end{eqnarray*}\] as claimed.

Two special cases.

Let \(A\) be a set and \(p : A \rightarrow \bool\) a predicate. The following hold for all \(x \in \lists{A}\).

  1. \(\any(\pfalse)(x) = \bfalse\).
  2. \(\any(\ptrue)(x) = \btrue\) if and only if \(x \neq \nil\).
  1. Note that \[\begin{eqnarray*} & & \any(\pfalse)(x) \\ & = & \bnot(\all(\bnot \circ \pfalse)(x)) \\ & = & \bnot(\all(\ptrue)(x)) \\ & = & \bnot(\btrue) \\ & \href{/posts/arithmetic-made-difficult/Not.html#thm-not-true} = & \bfalse \end{eqnarray*}\] as claimed.
  2. If \(x = \nil\), we have \[\begin{eqnarray*} & & \any(\pfalse)(x) \\ & = & \btrue, \end{eqnarray*}\] while if \(x = \cons(a,u)\) we have \[\begin{eqnarray*} & & \any(\ptrue)(\cons(a,u)) \\ & = & \bnot(\all(\bnot \circ \ptrue)(\cons(a,u))) \\ & = & \bnot(\all(\pfalse)(\cons(a,u))) \\ & = & \bnot(\bfalse) \\ & \href{/posts/arithmetic-made-difficult/Not.html#thm-not-false} = & \btrue \end{eqnarray*}\] as needed.

\(\any\) interacts with \(\cat\).

Let \(A\) be a set and \(p : A \rightarrow \bool\). For all \(x,y \in \lists{A}\) we have \[\any(p,\cat(x,y)) = \bor(\any(p)(x),\any(p)(y)).\]

Note that \[\begin{eqnarray*} & & \any(p,\cat(x,y)) \\ & = & \bnot(\all(\bnot \circ p,\cat(x,y))) \\ & = & \bnot(\band(\all(\bnot \circ p,x),\all(\bnot \circ p,y))) \\ & = & \bor(\bnot(\all(\bnot \circ p,x)),\bnot(\all(\bnot \circ p,y))) \\ & = & \bor(\any(p,x),\any(p,y)) \end{eqnarray*}\] as claimed.

\(\any\) interacts with \(\rev\).

Let \(A\) be a set and \(p : A \rightarrow \bool\). For all \(x,y \in \lists{A}\) we have \[\any(p,\rev(x)) = \any(p,x).\]

Note that \[\begin{eqnarray*} & & \any(p,\rev(x)) \\ & = & \bnot(\all(\bnot \circ p,\rev(x))) \\ & = & \bnot(\all(\bnot \circ p,x)) \\ & = & \any(p,x) \end{eqnarray*}\] as claimed.

\(\any\) interacts with \(\map\).

Let \(A\) and \(B\) be sets with \(f : A \rightarrow B\) and \(p : B \rightarrow \bool\). Then for all \(x \in \lists{A}\) we have \[\any(p)(\map(f)(x)) = \any(p \circ f)(x).\]

Note that \[\begin{eqnarray*} & & \any(p,\map(f)(x)) \\ & = & \bnot(\all(\bnot \circ p,\map(f)(x))) \\ & = & \bnot(\all((\bnot \circ p) \circ f,x)) \\ & = & \bnot(\all(\bnot \circ (p \circ f),x)) \\ & = & \any(p \circ f,x) \end{eqnarray*}\] as claimed.

Testing

Suite:

_test_all_any ::
  ( TypeName a, Show a, Equal a, Arbitrary a, CoArbitrary a
  , TypeName (t a), List t
  , Show (t a), Equal (t a), Arbitrary (t a)
  ) => Int -> Int -> t a -> IO ()
_test_all_any size cases t = do
  testLabel1 "all & any" t
  let args = testArgs size cases

  runTest args (_test_all_nil t)
  runTest args (_test_all_cons t)
  runTest args (_test_all_snoc t)
  runTest args (_test_all_fold_and t)
  runTest args (_test_all_const_true t)
  runTest args (_test_all_const_false t)
  runTest args (_test_all_cat t)
  runTest args (_test_all_rev t)
  runTest args (_test_all_map t)

  runTest args (_test_any_nil t)
  runTest args (_test_any_cons t)
  runTest args (_test_any_fold_or t)
  runTest args (_test_any_not_all t)
  runTest args (_test_all_not_any t)
  runTest args (_test_all_const_false t)
  runTest args (_test_all_const_true t)
  runTest args (_test_any_cat t)
  runTest args (_test_any_rev t)
  runTest args (_test_any_map t)

Main:

main_all_any :: IO ()
main_all_any = do
  _test_all_any 20 100 (nil :: ConsList Bool)
  _test_all_any 20 100 (nil :: ConsList Unary)