Curry-Howard-Lambek correspondence

From HaskellWiki
Revision as of 05:46, 5 November 2006 by DonStewart (talk | contribs) (more fmt)
Jump to navigation Jump to search

The Curry-Howard isomorphism is an isomorphism between types (in programming languages) and propositions (in logic). Interestingly, the isomorphism maps programs (functions in Haskell) to (constructive) proofs (and vice versa). (Note there is also a third part to this correspondance, sometimes called the Curry-Howard-Lambek correspondance, that shows an equivalance to Cartesian closed categories)

The Answer

As is well established by now,

theAnswer :: Integer
theAnswer = 42

The logical interpretation of the program is that the type Integer is inhibited (by the value 42), so the existence of this program proves the proposition Integer (a type without any value is the "bottom" type, a proposition with no proof).

Inference

A (non-trivial) Haskell function maps a value (of type a, say) to another value (of type b), therefore, given a value of type a (a proof of a), it constructs a value of type b (so the proof is transformed into a proof of b)! So b is inhibited if a is, and a proof of a -> b is established (hence the notation, in case you were wondering).

representation :: Bool -> Integer
representation False = 0
representation True = 1

says, for example, if Boolean is inhibited, so is Integer (well, the point here is demonstration, not discovery).

Connectives

Of course, atomic propositions contribute little towards knowledge, and the Haskell type system incorporates the logical connectives and , though heavily disguised. Haskell handles conjuction in the manner described by Intuitionistic Logic. When a program has type , the value returned itself indicates which one. The algebraic data types in Haskell has a tag on each alternative, the constructor, to indicate the injections:

data Message a = OK a | Warning a | Error a

p2pShare :: Integer -> Message String
p2pShare n | n == 0 = Warning "Share! Freeloading hurts your peers."
           | n < 0 = Error "You cannot possibly share a negative number of files!"
           | n > 0 = OK ("You are sharing " ++ show n ++ " files."

So any one of OK String, Warning String or Error String proves the proposition Message String, leaving out any two constructors would not invalidate the program. At the same time, a proof of Message String can be pattern matched against the constructors to see which one it proves. On the other hand, to prove String is inhibited from the proposition Message String, it has to be proven that you can prove String from any of the alternatives...

show :: Message String -> String
show (OK s) = s
show (Warning s) = "Warning: " ++ s
show (Error s) = "ERROR! " ++ s

The conjuction is handled via an isomorphism in Closed Cartesian Categories in general (Haskell types belong to this category): . That is, instead of a function from to , we can have a function that takes an argument of type and returns another function of type , that is, a function that takes to give (finally) a result of type : this technique is (known as currying) logically means .

(insert quasi-funny example here)

So in Haskell, currying takes care of the connective. Logically, a proof of is a pair of proofs of the propositions. In Haskell, to have the final value, values of both and have to be supplied (in turn) to the (curried) function.

Theorems for free!

Things get interesting when polymorphism comes in. The composition operator in Haskell proves a very simple theorem.

(.) :: (a -> b) -> (b -> c) -> (a -> c)
(.) f g x = f (g x)

The type is, actually, forall a b c. (a -> b) -> (b -> c) -> (a -> c), to be a bit verbose, which says, logically speaking, for all propositions a, b and c, if from a, b can be proven, and if from b, c can be proven, then from a, c can be proven (the program says how to go about proving: just compose the given proofs!)

Type Classes

A type class in Haskell is a proposition about a type.

class Eq a where
    (==) :: a -> a -> Bool
    (/=) :: a -> a -> Bool

means, logically, there is a type a for which the type a -> a -> Bool is inhibited, or, from a it can be proved that a -> a -> Bool (the class promises two different proofs for this, having names == and /=). This proposition is of existential nature (not to be confused with existential type). A proof for this proposition (that there is a type that conforms to the specification) is (obviously) a set of proofs of the advertized proposition (an implementation), by an instance declaration:

instance Eq Bool where
    True  == True  = True
    False == False = True
    _     == _     = False

(/=) a b = not (a == b)

Indexed Types

(please someone complete this, should be quite interesting, I have no idea what it should look like logically)