A few years ago, Martín Escardó wrote an article about a seemingly-impossible program that can exhaustively search the uncountably infinite "Cantor space" (infinite streams of bits). He then showed that spaces that can be thus searched form a monad (which I threw onto hackage), and wrote a paper about the mathematical foundations which is seemingly impossible to understand.
Anyway, I thought I would give a different perspective on what is going on here. This is a more operational account, however some of the underlying topology might peek out for a few seconds. I’m no topologist, so it will be brief and possibly incorrect.
Let’s start with a simpler infinite space to search. The lazy naturals, or the one-point compactification of the naturals:
data Nat = Zero | Succ Nat
deriving (Eq,Ord,Show)
infinity = Succ infinity
Let’s partially instantiate Num
just so we have something to play with.
instance Num Nat where
Zero + y = y
Succ x + y = Succ (x + y)
Zero * y = Zero
Succ x * y = y + (x * y)
fromInteger 0 = Zero
fromInteger n = Succ (fromInteger (n-1))
We wish to construct this function:
search :: (Nat -> Bool) -> Maybe Nat
Which returns a Nat
satisfying the criterion if there is one, otherwise Nothing
. We assume that the given criterion is total, that is, it always returns, even if it is given infinity
. We’re not trying to solve the halting problem. :-)
Let’s try to write this in direct style:
search f | f Zero = Just Zero
| otherwise = Succ <$> search (f . Succ)
That is, if the predicate worked for Zero
, then Zero
is our guy. Otherwise, see if there is an x
such that f (Succ x)
matches the predicate, and if so, return Succ x
. Make sense?
And it seems to work.
ghci> search (\x -> x + 1 == 2)
Just (Succ Zero)
ghci> search (\x -> x*x == 16)
Just (Succ (Succ (Succ (Succ Zero))))
Er, almost.
ghci> search (\x -> x*x == 15)
(infinite loop)
We want it to return Nothing
in this last case. It’s no surprise that it didn’t — there is no condition under which search
is capable of returning Nothing
, that definition would pass if Maybe
were defined data Maybe a = Just a
.
It is not at all clear that it is even possible to get what we want. But one of Escardó’s insights showed that it is: make a variant of search
that is allowed to lie.
-- lyingSearch f returns a Nat n such that f n, but if there is none, then
-- it returns a Nat anyway.
lyingSearch :: (Nat -> Bool) -> Nat
lyingSearch f | f Zero = Zero
| otherwise = Succ (lyingSearch (f . Succ))
And then we can define our regular search
in terms of it:
search' f | f possibleMatch = Just possibleMatch
| otherwise = Nothing
where
possibleMatch = lyingSearch f
Let’s try.
ghci> search' (\x -> x*x == 16) -- as before
Just (Succ (Succ (Succ (Succ Zero))))
ghci> search' (\x -> x*x == 15)
Nothing
Woah! How the heck did it know that? Let’s see what happened.
let f = \x -> x*x == 15
lyingSearch f
0*0 /= 15
Succ (lyingSearch (f . Succ))
1*1 /= 15
Succ (Succ (lyingSearch (f . Succ . Succ)))
2*2 /= 15
...
That condition is never going to pass, so lyingSearch
going to keep taking the Succ
branch forever, thus returning infinity
. Inspection of the definition of *
reveals that infinity * infinity = infinity
, and infinity
differs from 15
once you peel off 15 Succ
s, thus f infinity = False
.
With this example in mind, the correctness of search'
is fairly apparent. Exercise for the readers who are smarter than me: prove it formally.
Since a proper Maybe
-returning search is trivial to construct given one of these lying functions, the question becomes: for which data types can we implement a lying search function? It is a challenging but approachable exercise to show that it can be done for every recursive polynomial type, and I recommend it to anyone interested in the subject.
Hint: begin with a Search
data type:
newtype Search a = S ((a -> Bool) -> a)
Implement its Functor instance, and then implement the following combinators:
searchUnit :: Search ()
searchEither :: Search a -> Search b -> Search (Either a b)
searchPair :: Search a -> Search b -> Search (a,b)
newtype Nu f = Roll { unroll :: f (Nu f) }
searchNu :: (forall a. Search a -> Search (f a)) -> Search (Nu f)
More Hint: is searchPair
giving you trouble? To construct (a,b)
, first find a
such that there exists a y
that makes (a,y)
match the predicate. Then construct b
using your newly found a
.
The aforementioned Cantor space is a recursive polynomial type, so we already have it’s search function.
type Cantor = Nu ((,) Bool)
searchCantor = searchNu (searchPair searchBool)
ghci> take 30 . show $ searchCantor (not . fst . unroll . snd . unroll)
"(True,(False,(True,(True,(True"
We can’t expect to construct a reasonable Search Integer
. We could encode in the bits of an Integer
the execution trace of a Turing machine, as in the proof of the undecidability of the Post correspondence problem. We could write a total function validTrace :: Integer -> Bool
that returns True
if and only if the given integer represents a valid trace that ends in a halting state. And we could also write a function initialState :: Integer -> MachineState
that extracts the first state of the machine. Then the function \machine -> searchInteger (\x -> initialState x == machine && validTrace x)
would solve the halting problem.
The reason this argument doesn’t work for Nat
is because the validTrace
function would loop on infinity
, thus violating the precondition that our predicates must be total.
I hear the following question begging to be explored next: are there any searchable types that are not recursive polynomials?
