Zeno

From HaskellWiki
Revision as of 14:43, 20 April 2011 by Will (talk | contribs) (Created the wiki page for Zeno.)
(diff) ← Older revision | Latest revision (diff) | Newer revision → (diff)
Jump to navigation Jump to search
The printable version is no longer supported and may have rendering errors. Please update your browser bookmarks and please use the default browser print function instead.

DRAFT. THE VERSION OF ZENO DESCRIBED HEREIN HAS NOT YET BEEN RELEASED.

Introduction

Zeno is an automated proof system for Haskell program properties; developed at Imperial College London by William Sonnex, Sophia Drossopoulou and Susan Eisenbach. It aims to solve the general problem of equality between two Haskell terms, for any input value.

Many program verification tools available today are of the model checking variety; able to traverse a very large but finite search space very quickly. These are well suited to problems with a large description, but no recursive datatypes. Zeno on the other hand is designed to inductively prove properties over an infinite search space, but only those with a small and simple specification.

One can try Zeno online at TryZeno, or cabal install zeno to use it from home. Find the latest paper on Zeno here, though please note that Zeno no longer uses the described proof output syntax but instead outputs proofs as Isabelle theories.


Features

  • Outputs proofs and translated Haskell programs to an Isabelle/HOL theory file and will automatically invoke Isabelle to check it (requires isabelle to be visible on the command line).
  • Works with full Haskell98 along with any GHC extensions not related to the type system. Unfortunately not all Haskell code is then convertable to Isabelle/HOL, see Zeno#Caveats Caveats for details.
  • Its property language is a Haskell DSL, so should be relatively intuitive.


Example Usage

The first thing you need is the Zeno.hs file, this should be in Zeno's installation directory, or you can grab it [here]. This contains the definitions for Haskell's property DSL so now we can start writing our code:

module Test where

import Prelude ()
import Zeno

data Nat = Zero | Succ Nat

length :: [a] -> Nat
length [] = Zero
length (x:xs) = Succ (length xs)

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

class Num a where
  (+) :: a -> a -> a

instance Num Nat where
  Zero + y = y
  Succ x + y = Succ (x + y)

Notice we have stopped any Prelude functions from being imported, this is important as we have no source code available for them; Zeno can only work with functions for which it can see the definition. The only built in GHC types we have are lists, which are automatically available, and Bool, which Zeno.hs will import for you.

Now that we have some code we can define a property about this code. Properties are built through equality between terms, using the (:=:) constructor defined in Zeno.hs. We then pass this to the prove function to turn an equality into a property (Prop). We recommended looking at the Zeno.hs file to see how properties are constructed (it's very short).

The following code will express that the length of two appended lists is the sum of their individual lengths:

prop_length xs ys
  = prove (length (xs ++ ys) :=: length xs + length ys)

Add this to the above code and save it to Test.hs. We can now check prop_length by running zeno Test.hs. As a bug/feature this will also check Zeno.proveBool, a helper function in Zeno.hs, as this looks like a property. To restrict this to just prop_length we can run zeno -m prop Test.hs, which will only check properties whose name contains the text prop.

Say we want to express arbitrary propositions, we can do an equality check with True. Take the following code (appended to the code above):

class Eq a where
  (==) :: a -> a -> Bool
  
instance Eq Nat where
  Zero == Zero = True
  Succ x == Succ y = x == y
  _ == _ = False
  
prop_eq_ref :: Nat -> Prop
prop_eq_ref x = prove (x == x :=: True)

We have also provided the helper function proveBool to make this more succinct; an equivalent definition of prop_eq_ref would be:

prop_eq_ref x = proveBool (x == x)

We can also add conditions/antecedents to our properties, using the given and givenBool functions:

elem :: Eq a => a -> [a] -> Bool
elem _ [] = False
elem n (x:xs) 
  | n == x = True
  | otherwise = elem n xs
  
prop_elem :: Nat -> [Nat] -> [Nat] -> Prop
prop_elem n xs ys
  = givenBool (n `elem` ys)
  $ proveBool (n `elem` (xs ++ ys))

Here prop_elem expresses that if n is an element of ys then n is an element of xs ++ ys. Notice that we had to explicitly type everything to be Nat, as this proof does not exist for every type (consider the () type).


Caveats

Isabelle/HOL output

While Zeno is able to reason about any valid Haskell definition, not all of these can be converted to Isabelle for checking. There are two main restrictions:

  1. No internal recursive definitions; don't put recursive functions inside your functions.
  2. No non-terminating definitions. This also means you cannot use default type-class methods, as GHC transforms these internally to a co-recursive value.

While the above restrictions are founded in Isabelle's input language, there are a few which are laziness on part of Zeno's developers, and are on our to-do list:

  1. No partial definitions; only use total pattern matches.
  2. No mututally recursive datatypes.
  3. No tuple types beyond quadruples.

If you are wondering why a certain bit of code cannot be converted to Isabelle try running Zeno with the --print-core flag, to output Zeno's internal representation for your code.


Primitive Types

Zeno can only reason about inductive datatypes, meaning the only built-in types it can use are lists, tuples and Bools. No Integers, Ints, Chars, etc.; Zeno will replace them all with undefined.


Infinite and undefined values

Everything you have just read about Zeno is a huge lie. Zeno doesn't actually prove properties of Haskell programs, but only those in which every value is finite and well-defined. For example, Zeno can prove reverse (reverse xs) = xs, which is not true for infinite lists, as xs could still be pattern matched upon, whereas evaluating reverse (reverse xs) starts an infinite loop (undefined).

Another example (courtesy of Tillmann Rendel) is takeWhile p xs ++ dropWhile p xs = xs, which is not true when p = const undefined and xs /= [], as the left hand side of the equality would hence become undefined.

You might ask why this is a Haskell theorem prover, rather than an ML one, if it cannot deal with infinite values, which would be a very valid question. As it stands however Zeno is more a base-line for us to start more advanced research into lazy functional program verification, which will include attempting to tackle this issue.