\( \usepackage{bussproofs} \)
Post Archive

Correct By Construction First Order Logic

Table of Contents

\usepackage{bussproofs}

1. Introduction

I’ve been reviewing some axiomatic set theory, and every time I do, it makes me want to work on a first order logic, set theory based proof assistant, since so much axiomatic set theory can be pretty easily formalized in a competent first order logic proof assistant. I started working on it in Haskell, but then I had an idea: if I do this in Idris, or some dependently typed programming language, I can make it so that it is only possible to construct well-formed formulas and correct proofs. Then I don’t even need to check the proofs, as they will necessarily be correct by construction!

Here’s the idea. With types, we can restrict our own options, eliminating incorrect options. For example, I might write the following function in python to add two integers together.

def add(x, y):
    return x + y  

But there’s nothing stopping me from incorrectly calling add("hello, ", "world!"). With the C equivalent of this function, it is impossible to incorrectly supply strings as arguments. The compiler will notice this issue at compile time and complain.

int add(int x, int y) {
    return x + y;
}  

The idea, then, is to have some functions (really type constructors), to build objects representing proofs, but the types are engineered in such a way that it is impossible to construct an incorrect proof. If you attempt to construct an incorrect proof, you will get a type error at compile time.

2. Prerequisites

You should be able to understand this blog post if you have:

  1. Strong familiarity with a strongly typed functional programming language. Haskell would be ideal, but experience with OCaml, SML, or something like that would also suffice.
  2. Familiarity with mathematical proofs, both reading and writing them.
  3. Comfort with basic logic, so knowing how to read and manipulate logical formulas.

3. Dependent Types

In order to pull off this scheme, we need some very fancy types. In particular, we need dependent types.

A dependent type is a type that depends on a value. It’s easiest to explain this kind of dependency by analogy. The simplest kind of dependency is a function. A function is a value that depends on another value. So, for example, in the Haskell function below, the value of foo depends on the value of x.

foo :: Integer -> Integer
foo x = x * x + 4

But, in some programming languages like Haskell, we can have more complex dependencies. For example, a generic function is a value depending on a type. You can even make this dependency explicit with the forall keyword, though that is usually not necessary.

id :: forall a. a -> a
id x = x

Additionally, in Haskell, you can have a higher-kinded type, that is a type depending on another type, with the canonical example being the Maybe type.

data Maybe a = Nothing | Just a

With dependent types, we just allow types to depend on values (imagine if a in the previous example were an Integer for example).

With all of these options available, we reach the top of the lambda cube and nearly completely eliminate the distinction between types and values.

3.1. Idris

Idris is basically just Haskell with dependent types, so if you are familiar with Haskell, you should be able to follow along. We’ll just quickly go over some examples to get you familiar with Idris. The biggest, or at least most common, syntactic difference between Haskell and Idris is that Haskell uses :: for type annotations and (:) for the cons operator, while Idris does it the correct way.

Regular Functions

The first example above is almost completely unchanged in Idris.

foo : Integer -> Integer
foo x = x * x + 4

The Identity Function

For the identity function, things get a little different. The most obvious way to do the identity function is as follows:

id : (A : Type) -> A -> A
id A x = x

There are a couple things to note here. First, the (A : Type) -> A -> A, means that the first argument is of type Type, i.e. is a type1, and is named A. We need to give it a name because the rest of the type depends on it. This is just like a appearing in the body of the type in the identity function example in Haskell, we just only needed the name, because such a dependency is only allowed to be a type in Haskell2.

Then if we want to use this function, we have to supply the type as well.

id Nat 3

This should feel really silly though, since A can always be inferred from x. Idris allows implicit arguments which are arguments to a function that can always be inferred from the other arguments. To indicate implicit arguments, you can use {A : Type} rather than (A : Type). So then the identity function will be the following.

id : {A : Type} -> A -> A
id x = x

Since A occurs as the type of something, Idris can also tell that A is going to be type Type, so we don’t need to specify that either.

id : {A : _} -> A -> A
id x = x

We can do even better though, using a very handy shorthand. If an identifier beginning with a lower case letter occurs in a type definition, it is assumed to be an implicit parameter. So we can actually define the identity function in the same way as Haskell.

id : a -> a
id x = x

But this syntax is much more general than it is in Haskell. These implicit parameters don’t need to just be types, and we will see more examples of that later.

Higher Kinded Types

Idris of course allows higher kinded types. The Maybe example works unmodified.

data Maybe a = Nothing | Just a

However, it is much more common to use GADT syntax.

data Maybe : Type -> Type where
  Nothing : Maybe a
  Just    : a -> Maybe a

There are a couple things to note here. First, note that we have to give the type of Maybe. In Haskell, this isn’t necessary, since types can only depend on other types, but here the type of the dependency matters. Furthermore, recall that this is shorthand for the following.

data Maybe : Type -> Type where
  Nothing : {a : Type} -> Maybe a
  Just    : {a : Type} -> a -> Maybe a

Dependent Types

Now let’s get to some examples that don’t work in Haskell! A very important type in Idris is that of the natural numbers.

data Nat : Type where
  Z : Nat
  S : Nat -> Nat

Here Z represents 0, and S represents the successor function taking \(x\) to \(x + 1\). Of course Idris allows us to use regular numerals. Let’s say we want to make a predecessor function. We could do it like so.

pred : Nat -> Maybe Nat
pred 0     = Nothing
pred (S k) = Just k

And this would be a perfectly fine way to implement this. But we can do “better.” Check this out.

NatOrInt : Nat -> Type
NatOrInt 0     = Integer
NatOrInt (S k) = Nat

pred : (x : Nat) -> NatOrInt x
pred 0     = -1
pred (S k) = k

Notice that NatOrInt is a dependent type. It’s just like Maybe, except rather than depending on a type it depends on a value. Then pred’s type is also dependent, as the return type depends on the value of the argument. This is a fairly contrived example. We will see a more sensible example soon.

4. Vectors

The canonical example of something that requires dependent types is the type Vect.

4.1. Lists

First, let’s look at lists.

data List : Type -> Type where
  Nil  : List a
  (::) : a -> List a -> List a

This is the GADT way to define this type, but this is just a more explicit version of the usual definition3.

data List a = Nil | (::) a (List a)

Lists are great, but there is a fundamental problem with them that happens when we try to write a function to index into a list.

index : List a -> Nat -> a
index []        i     = ?uh_oh
index (x :: xs) 0     = x
index (x :: xs) (S i) = index xs i

We can write most of the function without issue, but, since we can’t guarantee that the index is in range, we have to decide what to do if the index is out of bounds. There are generally two approaches:

  1. Crash. This is the approach taken by head and tail in Haskell’s standard library, though it is generally disfavored in Haskell now, since it is very easy to ignore the possibility of an error.
  2. Rather than return an a, return a Maybe a. This forces the caller to handle the possibility of an error, which is a both a pro since it means that the potential error will be handled, but is also a con because it’s annoying and there can be situations where you have already verified that an error is impossible, but still have to deal with an impossible error anyway.

Dependent types allow for a third approach, namely require the caller to prove ahead of time that errors are impossible. This is not strictly better than the other approaches, but can sometimes be a life-saver. Let’s see how we can use dependent types to fix this problem.

4.2. Definition

Here’s our definition of Vect.

data Vect : Nat -> Type -> Type
  Nil  : Vect 0 a
  (::) : a -> Vect n a -> Vect (S n) a

There’s a lot to digest here. Let’s go line by line. First, the type of Vect is Nat -> Type -> Type. This means it is a type depending on a natural number and another type. The natural number represents the length of the vector, and the type is the type of the contents of the vector.

Then, we have Nil : Vect 0 a. Remember that this is shorthand for Nil : {a : Type} -> Vect 0 a. So whenever you use Nil, Idris will try to figure out what a is from the context. Furthermore, note that we need GADTs here, since the type of Nil involves specializing the Nat argument.

Finally, we have (::) : a -> Vect n a -> Vect (S n) a. This introduces a constructor (::), which is an infix operator. It takes on its left an argument of type a, where a is again inferred from context. On its right, it takes an argument of type Vect n a. Note that n is a lower case identifier, so it is also an implicit argument, even though n is a Nat, not a type4. Then the resulting Vect is length S n and still holds values of type a.

Let’s type check the term [1, 2, 3], which desugars to 1 :: 2 :: 3 :: Nil as an example3. We begin with Nil, which is type Vect 0 a. Idris can’t figure out what a is quite yet. Then we get to 3 :: Nil. The relevant types are:

  • 3 : Nat
  • (::) : a -> Vect n a -> Vect (S n) a
  • Nil : Vect 0 a.

By matching these up, Idris is able to see that a must be Nat. Idris can also see that n must be 0, even though n is a value of type Nat, rather than a type. With n = 0 and a = Nat, we then have 3 :: Nil : Vect (S 0) Nat, and S 0 = 1, so 3 :: Nil : Vect 1 Nat. Then we have

  • 2 : Nat
  • (::) : a -> Vect n a -> Vect (S n) a
  • Nil : Vect 1 a=.

Idris is again able to match these types and conclude that a = Nat and n = 1. This means that 2 :: 3 :: Nil must be type Vect (S 1) Nat = Vect 2 Nat.

Finally, Idris can do this one more time to conclude that 1 :: 2 :: 3 :: Nil : Vect 3 Nat.

4.3. Map

We can write normal functions on vectors without much issue. One easy one is map : (a -> b) -> Vect n a -> Vect n b.

map : (a -> b) -> Vect n a -> Vect n b
map f []        = []
map f (x :: xs) = f x :: map f xs

Note that we are casually proving that mapping a function over a list doesn’t change its length. By the way, implementing this interactively is quite the experience. Since this function is actually the only possible function with this type signature5, Idris is able to write almost the entire function by itself.

Incidentally, better tooling is another good argument for stronger types, since stronger types means the compiler understands your program better and can help you out more.

4.4. Append

One standard function that works, but is much more complicated than it first appears is append.

(++) : Vect n a -> Vect m a -> Vect (n + m) a
[]        ++ ys = ys
(x :: xs) ++ ys = x :: (xs ++ ys)

The standard definition seems to work just fine. However, this is incredibly fragile, and we are really quite lucky that this works out. You might rightly wonder how Idris can tell that the output is length n + m. It turns out that this works because we exactly follow the definition of addition. One major downside to dependent types is that, since values can appear in types, implementation can become part of the interface. Here is how addition is defined.

(+) : Nat -> Nat -> Nat
0     + y = y
(S x) + y = S (x + y)

If addition had been defined as follows instead, then the previous definition of append would no longer type check.

(+) : Nat -> Nat -> Nat
x + 0     = x
x + (S y) = S (x + y)

Let’s look closely at the lengths of the vectors in the implementation of append. In the first clause we have [] ++ ys = ys. [] is just shorthand for Nil, which we know is type Vect 0 a. All we know about ys is that it is type Vect m a. The return value in this situation is ys, which again is type Vect m a. What Idris does to type check in this situation is it attempts to unify the actual return type, Vect m a, with the declared return type, Vect (n + m) a. But since n = 0, we have Vect (0 + m) a. It can immediately see from the first clause of the definition of addition that 0 + m = m, so Vect m a unifies with Vect (n + m) a.

The second clause is more complicated. Here are the relevant types:

  • x : a
  • xs : Vect k a
  • x :​: xs : Vect (S k) a
  • ys : Vect m a
  • xs ++ ys : Vect (k + m) a (since xs : Vect k a and ys : Vect m a, inductively assuming append to be well-typed yields Vect (k + m) a for the type of xs ++ ys)
  • x :​: (xs ++ ys) : Vect (S (k + m)) a

In this situation, n = S k. Our final return value was type Vect (S (k + m)) a. The declared return value is Vect (n + m) a = Vect (S k + m) a. Looking at the second clause in the definition of addition, we see S k + m = S (k + m), so these two types do in fact unify.

The specific implementation of addition ends up impacting whether or not append type checks. This is what I mean when I say that, with dependent types, the implementation is part of the interface6. This is so tricky, in fact, that in Idris there are three levels of exporting something:

  1. private. The default. This means that the function/type/interface/etc. is not exported at all.
  2. export. This means that the type of the definition is exported, but only the type, not the implementation.
  3. public export. This means that both the type and implementation are exported. This is longer and more cumbersome to type on purpose, and should only be reserved for definitions that are intended to occur in types.

4.5. Reverse

That was tricky, but things get even trickier with reverse.

reverse : Vect n a -> Vect n a
reverse []        = []
reverse (x :: xs) = reverse xs ++ [x]

This standard definition seems like it would be fine, but doesn’t actually type check. Instead we get the error message

While processing right hand side of reverse. Can’t solve constraint between: plus n 1 and S n.

with reverse xs ++ [x] highlighted. The problem here is that reverse xs ++ [x] is type Vect (n + 1) a, while the return type should be Vect (S n) a. While S n is obviously equal to n + 1, Idris can’t see that. Recall that, in the definition of addition, we recurred on the first argument. In n + 1, we can’t further simplify, since we can’t tell whether n = 0 or n = S k for some k. We would have to somehow convince Idris that these two types are the same. It is possible to do this, but it’s a pretty significant diversion, and doesn’t really come up later. Look here for a brief overview of how to solve this, and here for a lot more detail.

4.6. Index

reverse and append were tricky, but let’s finally look at indexing into a vector. We know that a vector of type Vect k a has k elements, but how can we restrict the index to be less than k?

Fin

The solution, as with all problems in Idris, is more types. We will have a type Fin : Nat -> Type such that Fin n has precisely n elements. This will serve as our index into a vector. Then index will have type index : Fin n -> Vect n a -> a. Since there are precisely n elements of Fin n, and Vect n a has n elements, it is impossible to go out of bounds.

Here’s how we implement Fin.

data Fin : Nat -> Type where
  FZ : Fin (S n)
  FS : Fin n -> Fin (S n)

This definition is a little tricky; it took me a while to figure out why this works when learning this stuff. First, note that there are no elements of type Fin 0, since the output of any constructor is always Fin (S n) and no successor is equal to zero. There’s only one way to make an element of type Fin 1, namely FZ, since FS would require an argument of type Fin 0 to yield something of type Fin 1 which is impossible.

Then there are two ways to make an element of type Fin 2. First, FZ when n = 1 is type Fin (S 1) = Fin 2, but, additionally, we know that FZ : Fin 1 when n = 0, so we get FS FZ : Fin 2.

Type Elements
Fin 0  
Fin 1 FZ
Fin 2 FZ, FS FZ
Fin 3 FZ, FS FZ, FS (FS FZ)
\(\vdots\) \(\vdots\)

Fortunately, Idris deals with much of this complexity for us, and is capable of automatically coercing any number literal less than n to the appropriate Fin n.

index

Now we can finally implement index.

index : Fin n -> Vect n a -> a

Note that the return type is a, not Maybe a, not Either String a, just a genuine a. I think the experience of implementing this interactively is very enlightening. I put my cursor on index and press a key combination to add a clause to this definition. This results in the following setup, but with the variables renamed to be more sensible.

index : Fin n -> Vect n a -> a
index i xs = ?rhs_index

The ?rhs_index is a typed hole. It is an missing portion of the program. Idris can infer its type and help guide you into filling it. I can then put my cursor on i and press a key combination that splits i along all possible constructors, yielding the following, again with variables renamed.

index : Fin n -> Vect n a -> a
index FZ      xs = ?rhs_index_0
index (FS i') xs = ?rhs_index_1

Placing my cursor on the first xs and pressing the same key combination again yields the following.

index : Fin n -> Vect n a -> a
index FZ      (x :: xs) = ?rhs_index_0
index (FS i') xs        = ?rhs_index_1

Note that it did not generate a case for []! This is because that would mean n = 0, meaning the first argument would be of type Fin 0, which is impossible! In fact, you can explicitly write the following if you want.

index : Fin n -> Vect n a -> a
index FZ      []        impossible
index FZ      (x :: xs) = ?rhs_index_0
index (FS i') xs        = ?rhs_index_1

In the FZ and x :: xs case, the index is zero, so we can safely just return x.

index : Fin n -> Vect n a -> a
index FZ      (x :: xs) = x
index (FS i') xs        = ?rhs_index_1

In the FS i' case, we can again split xs, yielding the following, since again the n = 0 case is impossible.

index : Fin n -> Vect n a -> a
index FZ      (x :: xs) = x
index (FS i') (x :: xs) = ?rhs_index_1

This time, i' is an index less than n - 1 and xs is a vector of length n - 1, so we can just recursively call index on i' and xs.

index : Fin n -> Vect n a -> a
index FZ      (x :: xs) = x
index (FS i') (x :: xs) = index i' xs

Isn’t that cool! We don’t need to handle the empty vector case at all because it’s provably impossible!

And here’s what happens if you case split on xs first.

5. First Order Logic

The whole goal of this project was to create a correct by construction implementation of first order logic. Since I’m expecting a more computer science oriented audience, I figured I’d very quickly go over some FOL basics. A first order language is a kind of formal mathematical language. This formal mathematical language has a syntax and a semantics, though we won’t need semantics in this example.

5.1. Syntax

A first order language \(\mathcal{L}\) has some specified function and relation symbols, with specified arities. For example, the language \(\mathcal{L}_{\mathrm{NT}}\) of number theory might have binary function symbols \(+\) and \(\cdot\), a unary function symbol \(S\), a nullary function symbol (constant symbol) \(0\), and a binary relation symbol \(\leq\). Some example terms in this language might include \(S S S 0 + S S 0\), or \(S(S(0 + S 0 \cdot S 0) \cdot S S S 0)\), or \(x + S y\) (since we have variables for free). Importantly, terms like \(+(0(S(x, y)), 0)\) are not correct, since the arities are incorrect; the function symbols are not given the correct number of arguments.

We can relate terms via the relation symbols, as well as equality, which we always assume to have for free. So some example simple formulas of \(\mathcal{L}_{\mathrm{NT}}\) are \(x + y = y + x\), \(S x \leq x \cdot 2\), \(x \cdot y = S(0 + S S y)\) (these formulas don’t need to be true). We can also combine formulas together with the standard connectives \(\wedge\) (and), \(\vee\) (or), \(\to\) (implies), and \(\neg\) (not). We can also use the quantifiers \(\forall\) and \(\exists\), meaning “for all” and “there exists” respectively. So \[ \forall x\, \forall y\, [x \leq y \wedge \neg (x = y) \to y \leq x] \] states that for every \(x\) and \(y\), if \(x \leq y\) but \(x \neq y\), then \(y \leq x\).

We might also have the language of group theory \(\mathcal{L}_{\mathrm{G}} = \{\cdot,\,e\}\). We can then state the group axioms as:

  1. \(\forall x\, [x \cdot e = x \wedge e \cdot x = x]\)
  2. \(\forall x\, \forall y\, \forall z\,[x \cdot (y \cdot z) = (x \cdot y) \cdot z]\)
  3. \(\forall x\,\exists y [x \cdot y = e \wedge y \cdot x = e]\).

It’s also occasionally convenient to add the symbol \(\bot\) meaning false. You can treat it as an abbreviation for \(\neg \forall x\, [x = x]\) or some similar such formula.

5.2. Proof

We can also formalize what proofs look like. There are a million ways to do this, and the details don’t particularly matter, but we will discuss one simple proof system similar to what we will formalize in Idris later. Proofs will be relative to a context of local assumptions, often denoted \(\Gamma\). The notation \(\Gamma \vdash \phi\) means that you can prove \(\phi\) in the context \(\Gamma\). The proof system consists of several rules indicating what you can prove in what contexts. Here are some example rules for manipulating conjunctions.

\(\wedge I\)
if \(\Gamma \vdash \phi\) and \(\Gamma \vdash \psi\), then \(\Gamma \vdash \phi \wedge \psi\).
\(\wedge E_\ell\)
if \(\Gamma \vdash \phi \wedge \psi\), then \(\Gamma \vdash \phi\).
\(\wedge E_r\)
if \(\Gamma \vdash \phi \wedge \psi\), then \(\Gamma \vdash \psi\).

The whole point of the context is to include assumptions or hypotheses. So we will have a rule \(\mathrm{hyp}\), short for hypothesis, that says that we can prove, from our assumptions, any of our assumptions.

\(\mathrm{hyp}\)
if \(\phi \in \Gamma\), then \(\Gamma \vdash \phi\).

There is a particular format that we often write these rules in. We will place the hypotheses, draw a horizontal line, and put the conclusion below the line. We usually will also put the rule in parentheses to the right of the line. So the rule \(\wedge I\) looks like this:

\begin{prooftree} \AxiomC{\(\Gamma \vdash \phi\)} \AxiomC{\(\Gamma \vdash \psi\)} \RightLabel{\((\wedge I)\)} \BinaryInfC{\(\Gamma \vdash \phi \wedge \psi\)} \end{prooftree}

If a rule has no hypotheses, like \(\mathrm{hyp}\), we put a blank line.

\begin{prooftree} \AxiomC{} \RightLabel{(hyp)}\UnaryInfC{\(\Gamma \vdash \phi\)} \end{prooftree}

Then we can make a proof by stacking these deductions one after the other, making a big tree.

Here’s a proof that \(\phi \wedge \psi \vdash \psi \wedge \phi\).

\begin{prooftree} \AxiomC{} \RightLabel{(hyp)}\UnaryInfC{\(\phi \wedge \psi \vdash \phi \wedge \psi\)} \RightLabel{(\(\wedge E_r\))} \UnaryInfC{\(\phi \wedge \psi \vdash \psi\)} \AxiomC{} \RightLabel{(hyp)}\UnaryInfC{\(\phi \wedge \psi \vdash \phi \wedge \psi\)} \RightLabel{(\(\wedge E_\ell\))} \UnaryInfC{\(\phi \wedge \psi \vdash \phi\)} \RightLabel{\((\wedge I)\)} \BinaryInfC{\(\phi \wedge \psi \vdash \psi \wedge \phi\)} \end{prooftree}

Don’t worry too much about the details. We will see a lot more of this later. Let’s get on with actually implementing this in Idris!

6. Signatures

We want to be able to support arbitrary signatures, so we need some way of representing signatures.

6.1. Definitions

Our signatures will need function and relation symbols. First, here’s a representation of function and relation symbols.

record FuncSym where
  constructor MkFuncSym
  name  : String
  arity : Nat

record RelSym where
  constructor MkRelSym
  name  : String
  arity : Nat

Function and relation symbols each have a name and arity. I haven’t introduced records, but this is approximately equivalent to the following definition.

data FuncSym = MkFuncSym String Nat

name : FuncSym -> String
name (MkFuncSym name _) = name

arity : FuncSym -> Nat
arity (MkFuncSym _ arity) = arity

While record projections are just in the regular function namespace, Idris is a lot less picky about stuff like this than Haskell. It is abundantly clear from the types which projection function is intended.

Then a signature just consists of some relation and function symbols.

record Signature (n, m : Nat) where
  constructor MkSignature
  funcs : Vect n FuncSym
  rels  : Vect m RelSym

We are using a vector here because, rather than indicate function and relation symbols by name, we will indicate them by index into this vector, so our representation of a function symbol in a term will be a Fin n. That way it is impossible to give a string that doesn’t refer to any function symbol.

Getting the arity of a function or relation symbol just from the index will come in handy.

funcArity : Signature n _ -> Fin n -> Nat
funcArity (MkSignature funcs rels) i = (index i funcs).arity

relArity : Signature _ m -> Fin m -> Nat
relArity (MkSignature funcs rels) i = (index i rels).arity

6.2. Example

And that’s about it for Signature. Things get much more interesting when we move on to Term’s. Before we do that though, let’s build up an implementation of \(\mathcal{L}_{\mathrm{NT}}\) as an example.

Zero is a nullary function symbol.

zero : FuncSym
zero = MkFuncSym "0" 0

\(S\) is a unary function symbol.

suc : FuncSym
suc = MkFuncSym "S" 1

We also have \(+\) and \(\cdot\) as binary function symbols.

plus : FuncSym
plus = MkFuncSym "+" 2

times : FuncSym
times = MkFuncSym "*" 2

And, finally, \(\leq\) is a binary relation symbol.

leq : RelSym
leq = MkRelSym "<=" 2

Then we can package these together into a signature.

NT : Signature 4 1
NT = MkSignature
  [ zero, suc, plus, times ]
  [ leq ]

7. Term

7.1. Definitions

Here’s the definition of a Term.

data Term : Signature nFuncs nRels -> Nat -> Type where
  Var  : Fin n -> Term sig n
  Func : (i : Fin nFuncs) -> Vect (funcArity sig i) (Term sig n) -> Term sig n

This is a lot to unpack. Term is a Type, depending on a Signature with nFuncs function symbols and nRels relation symbols, as well as a Nat. The meaning of the Signature is clear, but the Nat less so. The Nat indicates an upper bound on the number of variables that can occur, which will be very handy later. So in the term \(1 + 1\), there aren’t any variables, meaning n can be anything. But in the term \(x + y\), there are two variables, so n needs to be at least 2.

There will implicitly be a list of variables available, more on this once we get to formulas, so Var takes an index into this list. We can imagine having a list of variables, say \(x,\, y,\, z\). Then Var 0 corresponds to \(x\), Var 1 to \(y\), and Var 2 to \(z\). This is why we need an upper bound on the number of variables occurring in the term.

Then the Func constructor is what made me switch from Haskell to Idris and get very excited. Func takes an i : Fin nFuncs, an index into the list of function symbols of the signature, and a Vect (funcArity sig i) (Term sig n). This is the argument list. It has length funcArity sig i, the arity of the function symbol with index i in the signature sig, and its elements are type Term sig n, that is terms from signature sig with the same upper bound on the number of variables as the main term.

7.2. Examples

This is confusing, so let’s create some terms in the language \(\mathcal{L}_\mathrm{NT}\) to get a feel for it. Let’s start with the term \(1 + 1\), or rather \(S 0 + S 0\). First the type signature. It is a term in the language \(\mathcal{L}_{\mathrm{NT}}\) with no variables, so that would make it a Term NT 0.

s0ps0 : Term NT 0
s0ps0 = Func 2
  [ Func 1 [ Func 0 [] ]
  , Func 1 [ Func 0 [] ]
  ]

The second element in our list of functions was plus, so the outermost Func is index 2. Likewise, suc is index 1 and zero is index 0.

If we had made a mistake and left off the second argument to plus, for example, we would get the following.

s0ps0' : Term NT 0
s0ps0' = Func 2
  [ Func 1 [ Func 0 [] ] ]

Then Idris would get very upset and give the following error message:

- + Errors (1)
 `-- src/Test.idr line 35 col 2:
     While processing right hand side of s0ps0'. When unifying:
         1
     and:
         2
     Mismatch between: 0 and 1.

     Test:35:3--35:25
      32 | 
      33 | s0ps0' : Term NT 0
      34 | s0ps0' = Func 2
      35 |   [ Func 1 [ Func 0 [] ] ]
             ^^^^^^^^^^^^^^^^^^^^^^

It’s not the most helpful error message in the world, but the 1 and 2 it’s unifying are from the length of the vector given as the argument list to Func 1 and evaluating funcArity NT 1, the expected argument length.

But if we take a step back for a moment, this is absolutely incredible. Giving the wrong number of arguments to a function symbol is a type error! When doing further analysis of terms later, we never need to deal with wrong numbers of arguments, since the type system guarantees, statically, that everything is correct. All the errors are taken care of at compile time7!

Working with the Func constructors directly is a bit of a pain, so let’s make some handy abbreviations.

A bit of a nasty trick I learned from Rocq is to use O (a capital ’o’) to represent zero if zero is already taken and 0 doesn’t work as an identifier. It works surprisingly well.

O : Term NT d
O = Func 0 []

Then we can make a function S : Term NT d -> Term NT d, such that for any term t, S t is the term \(S t\).

S : Term NT d -> Term NT d
S t = Func 1 [ t ]

Likewise, we can get a little fancy and implement \(+\) and \(\cdot\) as infix operators.

(+) : Term NT d -> Term NT d -> Term NT d
s + t = Func 2 [ s, t ]

(*) : Term NT d -> Term NT d -> Term NT d
s * t = Func 3 [ s, t ]

Now we can write the same term as before as S O + S O, which is significantly easier to read. We even get the precedence right, so we can do things like S O + S O * S (S O) and have it parse correctly as \(S 0 + S 0 * S S 0\).

Let’s start making logical formulas!

8. Formula

8.1. Definitions

The definition of Formula is similar to Term.

data Formula : Signature nFuncs nRels -> Nat -> Type where
  Equal  : Term sig n -> Term sig n -> Formula sig n
  Rel    : (i : Fin nRels) -> Vect (relArity sig i) (Term sig n) -> Formula sig n
  Imp    : Formula sig n -> Formula sig n -> Formula sig n
  Bot    : Formula sig n
  Forall : Formula sig (S n) -> Formula sig n

Formula is again indexed by a signature and a Nat, and we have some constructors for making various formulas. It might seem like we don’t have enough, but it turns out this is actually enough to define anything (\(\neg \phi = \phi \to \bot\), then \(\phi \wedge \psi = \neg (\phi \to \neg \psi)\), \(\phi \vee \psi = \neg (\neg \phi \wedge \neg \psi)\), \(\exists x\, \phi = \neg \exists x \,\neg \phi\), etc.). Rel is very similar to Func from Term, in that it takes an index into the list of relation symbols and a vector of arguments of the appropriate length.

We can now start to go into how variables work in a bit more detail. The Nat, rather than just being an upper bound on the number of variables, is, more precisely, an upper bound on the number of free variables that occur in a formula. This was the same as the number of variables in Term, since Term doesn’t have any binders, but Formula does.

What Forall does, is it takes a formula with \(n + 1\) free variables, and binds a variable, leaving only \(n\) free variables. For example, suppose \(\phi\) is a formula with \(n + 1\) free variables, say \(x_1, x_2, \dots, x_n, x_{n+1}\). Then we can write \(\phi(x_1, \dots, x_n, x_{n+1})\). Then the formula \(\forall y\, [\phi(x_1, \dots, x_n, y)]\) only has \(n\) free variables, since \(y\) is now bound.

This begs the question, how does Forall actually bind variables? What associates a variable with a particular quantifier? I’m using De Bruijn indices. So variables are numbers, and the number indicates the number of binders between the variable and its binder. Let’s work through an example. Take the formula \(\forall x\, [(\forall y\, [x \leq y]) \to x = 0]\). This has no free variables, so it is type Formula NT n for any n. If we look at \(x \leq y\), there is one binder between \(x\) and where it is bound, so this occurrence of \(x\) has a De Bruijn index of \(1\). On the other hand, there aren’t any binders between \(y\) and its binder, so this occurrence of \(y\) has a De Bruijn index of \(0\). However, notice that the second occurrence of \(x\) is out of scope of \(y\), so there aren’t any binders between it and its binder, meaning this occurrence of \(x\) has a De Bruijn index of \(0\). So we can translate this formula into \(\forall \, [(\forall \, [1' \leq 0']) \to 0' = 0\), where the primes indicate indices.

You can also think of the Nat index as being the smallest number of quantifiers you would need to add in order to bind every variable.

8.2. Examples

Let’s continue our NT example. Before we do, though, let’s make some abbreviations. First we will abbreviate equality and \(\leq\).

infix 1 .=
(.=) : Term sig n -> Term sig n -> Formula sig n
(.=) = Equal

(<=) : Term NT n -> Term NT n -> Formula NT n
t1 <= t2 = Rel 0 [ t1, t2 ]

We can also make an infix version of Imp.

infixr 2 ==>
(==>) : Formula sig n -> Formula sig n -> Formula sig n
(==>) = Imp

We can also define negation in terms of Imp and Bot.

Not : Formula sig n -> Formula sig n
Not phi = phi ==> Bot

Then we can define conjunction in terms of Imp and Not.

(&&) : Formula sig n -> Formula sig n -> Formula sig n
phi && psi = Not (phi ==> Not psi)

Then we can also define disjunction.

(||) : Formula sig n -> Formula sig n -> Formula sig n
phi || psi = Not (Not phi && Not psi)

With these abbreviations established, let’s state some interesting facts about number theory.

Let’s state that addition is commutative. This would be \(\forall x\, \forall y\, [x + y = y + x]\). Our translation into Idris is as follows. First, we need to find all the De Bruijn indices. There aren’t any binders between \(y\) and its binder, and there is one between \(x\) and its binder, so we have \(\forall \, \forall\, [1' + 0' = 0' + 1']\). From here, it’s pretty straightforward to translate this to Idris.

addComm : Formula NT n
addComm = Forall (Forall (Var 1 + Var 0 .= Var 0 + Var 1))

We can even translate that complicated example from before into Idris no problem.

harderFormula : Formula NT n
harderFormula = Forall (Forall (Var 1 <= Var 0) -> Var 0 .= O)

Let’s translate all the Peano Axioms into Idris here. These are the axioms used as a foundation for number theory.

First, we have that \(0\) is not a successor, formally stated as \(\forall x\,[\neg 0 = S x]\). We can translate this easily enough.

zeroNotSuc : Formula NT d
zeroNotSuc = Forall (Not (O .= S (Var 0)))

Next we have that the successor function is injective, stated as \(\forall x\, \forall y\, [S x = S y \to x = y]\). This isn’t too difficult to translate to Idris.

sucInj : Formula NT d
sucInj = Forall (Forall (S (Var 0) .= S (Var 1) ==> Var 0 .= Var 1))

We also want \(x + 0 = x\), which we can state as below.

addZeroR : Formula NT d
addZeroR = Forall (Var 0 + O .= Var 0)

For convenience, and now that we’re more comfortable with De Bruijn indices, let’s establish the convention that \(y\) is the most recently bound variable, and \(x\) bound before that. Then we can make the abbreviations shown below.

Y : Term sig (S d)
Y = Var 0

X : Term sig (S (S d))
X = Var 1

This makes the formulas a little more natural looking.

We want \(\forall x\, \forall y\,[x + Sy = S(x + y)]\), which intuitively is true, since \(x + (y + 1) = (x + y) + 1\).

addSR : Formula NT d
addSR = Forall (Forall (X + S Y .= S (X + Y)))

Anything times zero is zero, so we should have \(\forall y\,[y \cdot 0 = 0]\). Note that we use \(y\) here, since it’s the most recently bound variable.

mulZeroR : Formula NT d
mulZeroR = Forall (Y * O .= O)

We want \(x \cdot (y + 1) = x \cdot y + x\), or \(\forall x\, \forall y\, [x \cdot S y = x \cdot y + x]\).

mulSucR : Formula NT d
mulSucR = Forall (Forall (X * S Y .= X * Y + X))

The final axiom is the most difficult. This is the axiom schema of induction. It says that for every formula \(\phi\) with at least one free variable \(x\), the following formula is an axiom: \[ \phi(0) \to (\forall x\, [\phi(x) \to \phi(S x)]) \to \forall x\, [\phi(x)] \] In English, if \(\phi(0)\) holds, and whenever \(\phi(x)\) holds, \(\phi(S x)\) holds, then \(\phi\) holds for every \(x\).

The way we are going to implement this is by making a function of type Formula NT (S d) -> Formula NT d. It will take a formula \(\phi\) with at least one free variable (i.e. a argument phi : Formula NT (S d)) and output the previously mentioned formula.

In order to do this, we do need the notion of substitution. The details are technical and very annoying, so I will be skipping them here. All the code is available here if you want to see the details. Here’s the implementation of induction8.

induction : {d : _} -> Formula NT (S d) -> Formula NT d
induction phi =
  elimBinder O phi ==>                            -- phi(0) ->
  (Forall (phi ==> (sub 0 (S Y) phi))) ==>        -- (forall x, [phi(x) -> phi(S x)]) ->
  Forall phi                                      -- forall x, [phi(x)]

I know I’m itching to prove something using these axioms, so let’s get into proofs!

9. Proof

9.1. Definitions

I mentioned before that proofs are relative to a context, so we need some notion of a context. I implemented a type Context : Signature n m -> Nat -> Type that you can think of as a Vect k (Formula sig n), but the n’s on each formula are allowed to vary. The actual details of how this works don’t particularly matter, but the details are all available here.

With this out of the way, we can finally get to Proof! Here is the definition of Proof:

data Proof : Context sig g -> Formula sig n -> Type where
  Hyp     : {c : Context sig g} -> (i : Fin g) -> Proof c (snd (index i c))
  Weaken  : Proof c1 phi -> Subset c1 c2 -> Proof c2 phi
  ImpI    : Proof (phi :: c) psi -> Proof c (Imp phi psi)
  ImpE    : Proof c (Imp phi psi) -> Proof c phi -> Proof c psi
  ForallI : Proof c phi -> Proof c (Forall phi)
  ForallE : Proof c (Forall phi) -> Proof c (elimBinder t phi)
  BotE    : Proof c Bot -> Proof c phi
  Contra  : Proof (Not phi :: c) Bot -> Proof c phi  
  EqI     : Proof c (Equal t t)
  EqE     : {phi : Formula sig (S n)} -> Proof c (Equal s t) -> Proof c (elimBinder s phi) -> Proof c (elimBinder t phi)

An object of type Proof Gamma phi represents a proof of \(\phi\) in context \(\Gamma\), i.e. a witness that \(\Gamma \vdash \phi\). Each constructor in this type corresponds to a rule you can use to create a proof. Let’s go over each of these rules.

Hyp

First we have the constructor Hyp, short for hypothesis. This says that, in context c, Hyp i, where i is an index into the context, is a proof from c of the i-th entry of c. In other words, this is a representation of the following rule:

\begin{prooftree} \AxiomC{\(\phi \in \Gamma\)} \UnaryInfC{\(\Gamma \vdash \phi\)} \end{prooftree}

This intuitively makes sense. If you are assuming \(\phi\) to be true, then you can prove \(\phi\) from your list of assumptions.

Weaken

This is an annoying technical rule. It says that

\begin{prooftree} \AxiomC{\(\Delta \subseteq \Gamma\)} \AxiomC{\(\Delta \vdash \phi\)} \BinaryInfC{\(\Gamma \vdash \phi\)} \end{prooftree}

or that if you can prove \(\phi\) from a list of assumptions \(\Delta\), then you will still be able to prove \(\phi\) if you add some additional unused assumptions. The way that this works in code is that Weaken takes a proof of phi from context c1, and an object Subset c1 c2 that you can only create if c1 is a subset of c2 (in the same way that you can only create an object of type Fin n if n is greater than zero), and then returns a proof of phi from c2. It seems like you should be able to prove this rule as a theorem, and you probably can, but it ends up being an absolute nightmare, since you need to keep track of the indices of all the hypotheses. There’s probably a better formulation of Hyp making Weaken unnecessary, but it is still a useful rule regardless.

ImpI

This is the introduction rule for implication, i.e. allows you to prove an implication. The idea is that if you can prove \(\phi \to \psi\) by assuming \(\phi\) and deducing \(\psi\). More formally, we can say the following.

\begin{prooftree} \AxiomC{\(\Gamma,\,\phi \vdash \psi\)} \UnaryInfC{\(\Gamma \vdash \phi \to \psi\)} \end{prooftree}

In code, ImpI takes an argument of type Proof (phi :: c) psi and produces a Proof c (Imp phi psi).

ImpE

This is the elimination rule for implication, i.e. lets you use an implication. This is the famous modus ponens logical rule, saying that if you’ve proved \(\phi \to \psi\), and you’ve proved \(\phi\), then you can conclude that \(\psi\) holds. More formally,

\begin{prooftree} \AxiomC{\(\Gamma \vdash \phi \to \psi\)} \AxiomC{\(\Gamma \vdash \phi\)} \BinaryInfC{\(\Gamma \vdash \psi\)} \end{prooftree}

And in code, ImpE takes a Proof c (Imp phi psi) and produces a Proof c phi.

ForallI

This is the introduction rule for \(\forall\). The way you normally prove a \(\forall\) statement, for example \(\forall x\, \phi(x)\), is by beginning with “Let \(x\) …”, and eventually concluding \(\phi(x)\). Then, since \(x\) was arbitrary, you conclude that \(\forall x\, \phi(x)\) must hold. This is normally formalized by saying that if \(\phi\) has a free variable \(x\) that doesn’t occur in any assumptions \(\Gamma\), so that \(x\) is truly arbitrary, then from \(\Gamma \vdash \phi\), you can conclude \(\Gamma \vdash \forall x\, \phi\). However, since we are using De Bruijn indices, no variable in \(\phi\) can be the same as a variable in \(\Gamma\), we don’t need this proviso. Hence our rule will simply be

\begin{prooftree} \AxiomC{\(\Gamma \vdash \phi\)} \UnaryInfC{\(\Gamma \vdash \forall \phi\)} \end{prooftree}

or in code, ForallI : Proof c phi -> Proof c (Forall phi).

ForallE

This is the elimination rule for \(\forall\). If you have proved that \(\forall x\,\phi(x)\), then for any term \(t\) you should have \(\phi(t)\). So our rule will be

\begin{prooftree} \AxiomC{\(\Gamma \vdash \forall x\,\phi(x)\)} \UnaryInfC{\(\Gamma \vdash \phi(t)\)} \end{prooftree}

In symbols, we have ForallE : Proof c (Forall phi) -> Proof c (elimBinder t phi) (see 8 for more details on elimBinder).

BotE

This is the elimination rule for \(\bot\). If you have proven a contradiction, then you can prove anything, so

\begin{prooftree} \AxiomC{\(\Gamma \vdash \bot\)} \UnaryInfC{\(\Gamma \vdash \phi\)} \end{prooftree}

or BotE : Proof c Bot -> Proof c phi. Recall that \(\neg \phi\) is defined to be an abbreviation for \(\phi \to \bot\). So if we have proven \(\phi\) and \(\phi \to \bot\), we can use ImpE to get a proof of \(\bot\), which makes sense, since \(\phi\) and \(\neg \phi\) should be contradictory.

Contra

This rule formalizes proof by contradiction9. One tactic for proving \(\phi\) is to assume \(\neg \phi\) and derive a contradiction. We can formalize this as follows.

\begin{prooftree} \AxiomC{\(\Gamma,\, \neg \phi \vdash \bot\)} \UnaryInfC{\(\Gamma \vdash \phi\)} \end{prooftree}

Then in code, Contra : Proof (Not phi :: c) Bot -> Proof c phi.

This is similar to proving \(\neg \phi\) by assuming \(\phi\) and deriving a contradiction, but it is quite distinct. If you assume \(\neg \phi\) and derive a contradiction, you’ve proved \(\neg \phi \to \bot\), or \(\neg\neg\phi\), which isn’t immediately the same thing as \(\phi\). An equivalent rule would be to allow you to conclude \(\phi\) from \(\neg\neg\phi\), or that for every \(\phi\), we have \(\phi \vee \neg\phi\).

EqI

This is straightforward. The safest way to introduce an equality is with \(t = t\). From any set of assumptions, we can conclude that \(t = t\) for any term \(t\).

\begin{prooftree} \AxiomC{} \UnaryInfC{\(\Gamma \vdash t = t\)} \end{prooftree}

Or in code, just EqRefl : Proof c (Equal t t).

EqE

Using equality is more complicated. The idea is that if we’ve proved that \(t = s\), and also proved \(\phi(t)\), we should be able to substitute \(s\) for \(t\) and conclude \(\phi(s)\).

\begin{prooftree} \AxiomC{\(\Gamma \vdash t = s\)} \AxiomC{\(\Gamma \vdash \phi(t)\)} \BinaryInfC{\(\Gamma \vdash \phi(s)\)} \end{prooftree}

The way this works in code is a little trickier. We have EqE : Proof c (Equal t s) -> Proof c (elimBinder t phi) -> Proof c (elimBinder s phi). Idris will almost never be able to figure out phi on its own, meaning we will have to supply it. It is possible to be given two terms and two formulas and find such a \(\phi\) if it exists, but that requires implementing a kind of unification, which isn’t really necessary for a relatively simple proof system like this.

And this is all the rules we need! It doesn’t seem like much, but it is more than enough to get us going.

9.2. Examples

Let’s start by proving some very basic facts.

Double Negatives

I mentioned that Contra is equivalent to \(\neg \neg \phi \to \phi\), so let’s prove that. To be clear, our goal is to prove that if \(\Gamma \vdash \neg \neg \phi\), then \(\Gamma \vdash \phi\) using Contra. Here’s the idea behind our proof.

Suppose by way of contradiction that \(\neg \phi\). But this is already a contradiction, since we, by assumption, have \(\neg\neg\phi\). Therefore we must have \(\phi\).

More formally, we can write our proof as follows.

\begin{prooftree} \AxiomC{\(\Gamma \vdash \neg\neg \phi\)} \RightLabel{weaken}\UnaryInfC{\(\Gamma,\,\neg \phi \vdash \neg\neg\phi\)} \AxiomC{} \RightLabel{hyp}\UnaryInfC{\(\Gamma,\,\neg \phi \vdash \neg \phi\)} \RightLabel{ImpE}\BinaryInfC{\(\Gamma,\,\neg\phi \vdash \bot\)} \RightLabel{contra}\UnaryInfC{\(\Gamma \vdash \phi\)} \end{prooftree}

Now let’s implement this in Idris. Let’s do it interactively again. We begin with the statement of our theorem and a hole.

doubleNeg : Proof c (Not (Not phi)) -> Proof c phi
doubleNeg pf = ?rhs

Investigating the type of the tells us our current goal. Idris says that the hole is type Proof c phi, so that is our current goal. We know our strategy is contradiction, so let’s start with Contra.

doubleNeg : Proof c (Not (Not phi)) -> Proof c phi
doubleNeg pf =
  Contra $
  ?rhs  

Checking the hole now, it says that our goal has transformed into Proof (Not phi :: c) Bot. We also have available pf : Proof c (Not (Not phi)). But we know that Not (Not phi) and Not phi are a contradiction! Since Not (Not phi) is really Not phi ==> Bot, we want to use ImpE. ImpE takes two arguments, so let’s update the holes.

doubleNeg : Proof c (Not (Not phi)) -> Proof c phi
doubleNeg pf =
  Contra $
  ImpE ?implication $
  ?hypothesis  

The type of the hole ?implication is Proof (Not phi :: c) (Imp ?phi Bot), and the type of ?hypothesis is Proof (Not phi :: c) ?phi. What this means is that Idris can tell that we are trying to make something of type Proof (Not phi :: c) Bot, and we are using ImpE to do so. In order to use ImpE, we want a proof of ?phi ==> ?psi and a proof of ?phi, to yield a proof of ?psi. We’re trying to produce a proof of Bot, so that must be what ?psi is, but Idris can’t tell what ?phi should be.

Fortunately, we know that we have (Not phi) ==> Bot and Not phi, so ?phi, confusingly, is Not phi. Our proof of (Not phi) ==> Bot is just pf. Annoyingly, we need the Weaken rule here, since pf : Proof c (Not (Not phi)) and we need a proof of Not (Not phi) from (Not phi) :: c.

doubleNeg : Proof c (Not (Not phi)) -> Proof c phi
doubleNeg pf =
  Contra $
  ImpE (Weaken pf (Missing Same)) $
  ?hypothesis

Ignore the Missing Same part. That’s the proof that c is a subset of Not phi :: c.

Now we gave a proof of Not phi ==> Bot, so Idris knows that ?phi = Not phi, and know says that the type of the ?hypothesis hole is Proof (Not phi :: c) (Not phi). But we have an easy proof of this, since Not phi is one of our hypotheses. In fact, it is the hypothesis in index 0, so we can prove this with Hyp 0.

doubleNeg : Proof c (Not (Not phi)) -> Proof c phi
doubleNeg pf =
  Contra $
  ImpE (Weaken pf (Missing Same)) $
  Hyp 0

And this type checks! Since it type checks, it must be a correct proof, since the only way to build proof objects is by following the deduction rules!

AndI

We defined \(\phi \wedge \psi\) to be \(\neg (\phi \to \neg \psi)\), but how do we know this is correct? We would like it if \(\Gamma \vdash \phi\) and \(\Gamma \vdash \psi\) means \(\Gamma \vdash \phi \wedge \psi\) and vice versa. Let’s start with the forward direction.

Suppose \(\Gamma \vdash \phi\) and \(\Gamma \vdash \psi\), then \(\Gamma \vdash \phi \wedge \psi\), that is \(\Gamma \vdash \neg (\phi \to \neg \psi)\).

Suppose \(\phi \to \neg \psi\). We want a contradiction. Since \(\Gamma \vdash \phi\), we have \(\Gamma,\,\phi \to \neg\psi \vdash \neg \psi\) by ImpE (and Weaken and Hyp). But \(\neg \psi\) is just shorthand for \(\psi \to \bot\), and we have \(\Gamma \vdash \psi\), so we must have \(\Gamma,\,\phi\to\neg\psi \vdash \bot\). But then by ImpI we must have \(\Gamma \vdash (\phi \to \neg \psi) \to \bot\), which is just shorthand for \(\Gamma \vdash \neg (\phi \to \neg \psi)\) as desired.

Now let’s formalize this!

\begin{prooftree} \AxiomC{\(\Gamma \vdash \phi\)} \UnaryInfC{\(\Gamma,\,\phi \to \neg \psi \vdash \phi\)} \AxiomC{} \UnaryInfC{\(\Gamma,\,\phi \to \neg \psi \vdash \phi \to \neg\psi\)} \BinaryInfC{\(\Gamma,\,\phi \to \neg \psi \vdash \neg \psi\)} \AxiomC{\(\Gamma \vdash \psi\)} \UnaryInfC{\(\Gamma,\,\phi \to \neg \psi \vdash \psi\)} \BinaryInfC{\(\Gamma,\,\phi \to \neg\psi \vdash \bot\)} \UnaryInfC{\(\Gamma \vdash \neg(\phi \to \neg \psi)\)} \end{prooftree}

Working through this proof tree backwards, we have the following term.

AndI : {d : _} -> {c : _} -> {phi, psi : Formula sig d} ->
  Proof c phi -> Proof c psi ->
  Proof c (phi && psi)
AndI pfPhi pfPsi =
  ImpI $
  ImpE
    (ImpE (Hyp 0) $
     Weaken pfPhi $ Missing Same)
    (Weaken pfPsi $ Missing Same)

It may be a little anticlimactic, but I’m going to stop here. Once we’ve got the ability to prove things like this, we can just go all day proving things.

10. Further Reading

This post isn’t based off any particular individual sources, but there are some good books and resources I would recommend if you want to learn more in no particular order.

  • Types and Programming Languages by Benjamin Pierce. I haven’t personally read it, but it is the bible of type theory, and I’ve heard it is very good. It has a very CS perspective, and views type theory from the lens of how it can improve programming, rather than how it can be used to do math. As a result, it also looks at practical concerns like implementation.
  • Type Driven Development with Idris by Edwin Brady. A fantastic introduction to Idris and dependent types. It mostly focuses on how using dependent types, and advanced type systems more broadly, is extremely productive for programmers. Be warned, the book is written for Idris 1, rather than Idris 2, and as such some sections are outdated. Consult here if you encounter issues.
  • Type Theory and Formal Proof by Nederpelt and Geuvers. Slowly, thoroughly, and accessibly builds up a type theory based formal proof system. One of the best introductions to the lambda cube and using type theory as a basis for logic.
  • Mathematical Logic by Chiswell and Hodges. This was the book I learned first order logic from. There are a million books that cover this topic, and do so well, but I enjoyed this book.

Footnotes:

1

So Type is the type of types, represented as * in Haskell. In Idris, currently, though there are plans to change this, Type is also itself type Type. This can cause problems if you are trying to use Idris directly to prove things, but it isn’t an issue for Idris as a programming language.

2

This isn’t super relevant, but there are some nasty things you can do with this. Types are ordinary values like any other, meaning you can pattern match on them!

id : (A : Type) -> A -> A
id Nat  x = x + 1
id Bool b = not b
id A    x = x

More sensible languages, like Agda, disallow this, but it is pretty cool.

3

Note that, in Idris, any type with constructors Nil and (::) can be written using list notation, with [1, 2, 3] being translated into 1 :: 2 :: 3 :: Nil for example.

4

There’s something even cooler going on here, too. Idris has a multiplicity type system, which is a generalization of linear types. The details don’t matter too much, but there are three possible multiplicities a type can have.

  1. 0, meaning the value is erased,
  2. 1, meaning the value is linear,
  3. or unlimited, meaning the value can be used an unlimited number of times.

These lowercase identifier implicit arguments are by default multiplicity 0. That means the length of the vector is erased at runtime! It doesn’t even end up existing at all, just being used for type checking.

5

You can only pattern match on unerased values, so shenanigans like from footnote 2 above aren’t possible here.

6

For those who are performance minded, you can give two implementations of a function and indicate that one should be used in type checking and the other at runtime. So, for instance, addition is defined in terms of this horrendously slow and inefficient unary representation for ease of proving things, but gets replaced with normal binary arithmetic at runtime.

7

Things get significantly more complicated if you want to parse a term and yield a result of type Term. It’s clearly possible to write down a malformed term that you then have to parse. When parsing, you will have to check that the term is valid and handle errors. If you have a function, say parseTerm : (d : Nat) -> (sig : Signature n m) -> String -> Maybe (Term sig d), or something like that, the return type being Term sig d, means you must have at least correctly rejected all the incorrect terms, a fairly strong guarantee of correctness.

8

Here are a couple more details for the curious. elimBinder takes a Formula sig (S d) and a Term sig d, and returns a Formula sig d. The intuition here is that we are completely getting rid of that variable and binder. We imagine the formula as sitting under a bunch of universal quantifiers and we’re plugging something into the outermost \(\forall\). sub on the other hand just substitutes a term for a variable without eliminating one of the outer implied quantifiers. More concretely, we can think of \(\phi(x)\) as sitting under a \(\forall\) somewhere, like \(\forall x\, [ \dots \phi(x)]\). Then elimBinder O phi is the formula \(\phi(0)\), while sub 0 O phi is \(\forall x [ \dots \phi(0) ]\) with the outer imaginary quantifier still being there. In the case of \(\forall x\, [\phi(x) \to \phi(S x)]\), we still have an outer quantifier, so we want to use sub, while in the case of \(\phi(0)\), we don’t have an outer quantifier, so we use elimBinder.

We need the {d : _} -> ... in the type signature for annoying multiplicity reasons (see 4). Automatic, lowercase implicit arguments are by default erased at runtime. In order to go from Formula sig (S d) to Formula sig d, we do need to know what d is, meaning it cannot be erased. Explicitly adding d into the type signature makes it have unlimited multiplicity, meaning it exists at runtime.

9

This rule makes the logic system described here classical rather than constructive. Classical logic is normal everyday mathematical reasoning. But it can have some weird side effects. Here’s a classic example.

There exist irrational numbers \(a\) and \(b\) such that \(a^{b}\) is rational.

Consider \(\sqrt 2^{\sqrt 2}\). It is either rational or irrational. If \(\sqrt 2^{\sqrt 2}\) is rational, then it is an example of the proposition, with \(a = b = \sqrt 2\). On the other hand, if \(\sqrt 2^{\sqrt 2}\) is irrational, then \(a = \sqrt 2^{\sqrt 2}\) and \(b = \sqrt 2\) works, because then \(a^{b} = \left(\sqrt 2^{\sqrt 2}\right)^{\sqrt 2} = \sqrt 2^{2} = 2\) is rational.

What’s weird about this is that we proved the existence of two numbers with some properties without actually giving an example.

In constructive logic, this kind of reasoning is not allowed. Limiting reasoning to just constructive logic makes it much easier to work computationally. For example, proofs are able to be turned into programs that find (counter)examples. It turns out that there isn’t much of a difference either way. If you are able to prove \(\phi\) using classical logic, then you are always able to prove either \(\phi\) or \(\neg \neg \phi\) using just constructive logic.

Date: 2025-08-07 Thu 00:00

Author: William Ball

Created: 2025-11-21 Fri 23:55

Validate