{-# LANGUAGE TupleSections #-}
{-@ LIQUID "--no-warnings" @-}
{-@ LIQUID "--short-names" @-}
{-@ LIQUID "--diff" @-}
module Termination where
import Prelude hiding (reverse, sum, repeat)
ack :: Int -> Int -> Int
range :: Int -> Int -> [Int]
fastSum :: Int -> Int -> Int
{-@ split :: xs:[a] -> Halves a xs @-}
split :: [a] -> ([a], [a])
split (x:(y:zs)) = (x:xs, y:ys) where (xs, ys) = split zs
split xs = (xs, [])
{-@ type Halves a Xs = {v: (Half a Xs, Half a Xs) | len (fst v) + len (snd v) == len Xs} @-}
{-@ type Half a Xs = {v:[a] | (len v > 1) => (len v < len Xs)} @-}
Avoiding Infinite Loops
Example: Proving Termination of sum
sum :: Int -> Int
sum 0 = 0
sum n = n + sum (n - 1)
Q: (Why) does this terminate?
Proving Termination
Proving Termination
Termination: A well founded metric decreases at each recursive call
Proving Termination
Termination: A well founded metric decreases at each recursive call
Metric gets strictly smaller and has a lower-bound
Proving Termination
Termination: A well founded metric decreases at each recursive call
Metric gets strictly smaller and has a lower-bound
e.g. 99 bottles, 98 bottles, ...
Example: Proving Termination of sum
sum' :: Int -> Int
sum' 0 = 0
sum' n = n + sum (n - 1)
Default Metric
FirstInt parameter
Always gets smaller, but what's the lower bound?
User Specified Termination Metrics
The first Int need not always be decreasing!
User Specified Termination Metrics
The first Int need not always be decreasing!
{-@ fastSum :: Int -> Int -> Int @-}
fastSum total 0 = total
fastSum total n = fastSum (total + n) (n - 1)
Specify metric as an expression over the inputs
User Specified Termination Metrics
Specify metric as an expression over the inputs
{-@ range :: lo:Int -> hi:Int -> [Int] @-}
range lo hi
| lo < hi = lo : range (lo + 1) hi
| otherwise = []
Q: What metric proves range terminates?
Proving Termination
Liquid Haskell Checks
A well founded metric decreases at each recursive call.