Decouple Invariants From Data {#recursive}
==========================================
Recursive Structures
--------------------
Lets see another example of decoupling...
\begin{code}
{-# LANGUAGE NoMonomorphismRestriction #-}
module List (insertSort) where
{-@ LIQUID "--no-termination" @-}
mergeSort :: Ord a => [a] -> [a]
insertSort :: (Ord a) => [a] -> L a
slist :: L Int
slist' :: L Int
iGoUp, iGoDn, iDiff :: [Int]
infixr `C`
\end{code}
Decouple Invariants From Recursive Data
=======================================
Recall: Lists
-------------
\begin{code}
data L a = N
| C a (L a)
\end{code}
Recall: Refined Constructors
----------------------------
Define *increasing* Lists with strengthened constructors:
\begin{code}
data L a where
N :: L a
C :: hd:a -> tl: L {v:a | hd <= v} -> L a
\end{code}
Problem: Decreasing Lists?
--------------------------
What if we need *both* [increasing and decreasing lists](http://web.cecs.pdx.edu/~sheard/Code/QSort.html)?
*Separate* types are tedious...
Abstract That Refinement!
-------------------------
\begin{code}
{-@ data L a a -> Prop>
= N
| C (hd :: a) (tl :: (L
a
)) @-}
\end{code}
-
`p` is a *binary* relation between two `a` values
- Definition relates `hd` with *all* the elements of `tl`
- Recursive: `p` holds for *every pair* of elements!
Example
-------
Consider a list with *three* or more elements
\begin{code}
x1 `C` x2 `C` x3 `C` rest :: L a
\end{code}
Example: Unfold Once
--------------------
\begin{code}
x1 :: a
x2 `C` x3 `C` rest :: L
a
\end{code}
Example: Unfold Twice
---------------------
\begin{code}
x1 :: a
x2 :: a
x3 `C` rest :: L
a
\end{code}
Example: Unfold Thrice
----------------------
\begin{code}
x1 :: a
x2 :: a
x3 :: a
rest :: L
a
\end{code}
Note how `p` holds between **every pair** of elements in the list.
A Concrete Example
------------------
That was a rather *abstract*!
How can we *use* fact that `p` holds between *every pair* ?
Example: Increasing Lists
-------------------------
*Instantiate* `p` with a *concrete* refinement
\begin{code}
{-@ type IncL a = L <{\hd v -> hd <= v}> a @-}
\end{code}
- Refinement says `hd` less than each tail element `v`,
- Thus, `IncL` denotes *increaing* lists.
Example: Increasing Lists
-------------------------
LiquidHaskell verifies that `slist` is indeed increasing...
\begin{code}
{-@ slist :: IncL Int @-}
slist = 1 `C` 6 `C` 12 `C` N
\end{code}
... and protests that `slist'` is not:
\begin{code}
{-@ slist' :: IncL Int @-}
slist' = 6 `C` 1 `C` 12 `C` N
\end{code}
Insertion Sort
--------------
\begin{code}
{-@ insertSort :: (Ord a) => [a] -> IncL a @-}
insertSort = foldr insert N
insert y N = y `C` N
insert y (x `C` xs)
| y < x = y `C` (x `C` xs)
| otherwise = x `C` insert y xs
\end{code}
(*Hover* over `insert'` to see inferred type.)
Checking GHC Lists
------------------
Demo:
Above applies to GHC's List definition:
\begin{code}
data [a] a -> Prop>
= []
| (:) (h :: a) (tl :: ([a
]
))
\end{code}
Checking GHC Lists
------------------
Increasing Lists
\begin{code}
{-@ type Incs a = [a]<{\h v -> h <= v}> @-}
{-@ iGoUp :: Incs Int @-}
iGoUp = [1,2,3]
\end{code}
Checking GHC Lists
------------------
Decreasing Lists
\begin{code}
{-@ type Decs a = [a]<{\h v -> h >= v}> @-}
{-@ iGoDn :: Decs Int @-}
iGoDn = [3,2,1]
\end{code}
Checking GHC Lists
------------------
Duplicate-free Lists
\begin{code}
{-@ type Difs a = [a]<{\h v -> h /= v}> @-}
{-@ iDiff :: Difs Int @-}
iDiff = [1,3,2]
\end{code}
Checking GHC Lists
------------------
Now we can check all the usual list sorting algorithms
Example: `mergeSort` [1/2]
--------------------------
\begin{code}
{-@ mergeSort :: (Ord a) => [a] -> Incs a @-}
mergeSort [] = []
mergeSort [x] = [x]
mergeSort xs = merge xs1' xs2'
where
(xs1, xs2) = split xs
xs1' = mergeSort xs1
xs2' = mergeSort xs2
\end{code}
Example: `mergeSort` [1/2]
--------------------------
\begin{code}
split (x:y:zs) = (x:xs, y:ys)
where
(xs, ys) = split zs
split xs = (xs, [])
merge xs [] = xs
merge [] ys = ys
merge (x:xs) (y:ys)
| x <= y = x : merge xs (y:ys)
| otherwise = y : merge (x:xs) ys
\end{code}
Example: `Data.List.sort`
-------------------------
GHC's "official" list sorting routine
Juggling lists of increasing & decreasing lists
Ex: `Data.List.sort` [1/4]
--------------------------
Juggling lists of increasing & decreasing lists
\begin{code}
{-@ sort :: (Ord a) => [a] -> Incs a @-}
sort = mergeAll . sequences
sequences (a:b:xs)
| a `compare` b == GT = descending b [a] xs
| otherwise = ascending b (a:) xs
sequences [x] = [[x]]
sequences [] = [[]]
\end{code}
Ex: `Data.List.sort` [2/4]
--------------------------
Juggling lists of increasing & decreasing lists
\begin{code}
descending a as (b:bs)
| a `compare` b == GT
= descending b (a:as) bs
descending a as bs
= (a:as): sequences bs
\end{code}
Ex: `Data.List.sort` [3/4]
--------------------------
Juggling lists of increasing & decreasing lists
\begin{code}
ascending a as (b:bs)
| a `compare` b /= GT
= ascending b (\ys -> as (a:ys)) bs
ascending a as bs
= as [a]: sequences bs
\end{code}
Ex: `Data.List.sort` [4/4]
--------------------------
Juggling lists of increasing & decreasing lists
\begin{code}
mergeAll [x] = x
mergeAll xs = mergeAll (mergePairs xs)
mergePairs (a:b:xs) = merge a b: mergePairs xs
mergePairs [x] = [x]
mergePairs [] = []
\end{code}
Phew!
-----
Lets see one last example...
Example: Binary Trees
---------------------
... `Map` from keys of type `k` to values of type `a`
Implemented, in `Data.Map` as a binary tree:
\begin{code}
data Map k a = Tip
| Bin Size k a (Map k a) (Map k a)
type Size = Int
\end{code}
Two Abstract Refinements
------------------------
- `l` : relates root `key` with `left`-subtree keys
- `r` : relates root `key` with `right`-subtree keys
\begin{code}
{-@ data Map k a < l :: k -> k -> Prop
, r :: k -> k -> Prop >
= Tip
| Bin (sz :: Size) (key :: k) (val :: a)
(left :: Map (k) a)
(right :: Map (k) a) @-}
\end{code}
Ex: Binary Search Trees
-----------------------
Keys are *Binary-Search* Ordered
\begin{code}
{-@ type BST k a =
Map <{\r v -> v < r },
{\r v -> v > r }>
k a @-}
\end{code}
Ex: Minimum Heaps
-----------------
Root contains *minimum* value
\begin{code}
{-@ type MinHeap k a =
Map <{\r v -> r <= v},
{\r v -> r <= v}>
k a @-}
\end{code}
Ex: Maximum Heaps
-----------------
Root contains *maximum* value
\begin{code}
{-@ type MaxHeap k a =
Map <{\r v -> r >= v},
{\r v -> r >= v}>
k a @-}
\end{code}
Example: Data.Map
-----------------
Standard Key-Value container
- 1300+ non-comment lines
- `insert`, `split`, `merge`,...
- Rotation, Rebalance,...
SMT & inference crucial for [verification](https://github.com/ucsd-progsys/liquidhaskell/blob/master/benchmarks/esop2013-submission/Base.hs)
Recap: Abstract Refinements
---------------------------
Decouple invariants from *functions*
+ `max`
+ `loop`
+ `foldr`
Decouple invariants from *data*
+ `Vector`
+ `List`
+ `Tree`
Recap
-----
1. **Refinements:** Types + Predicates
2. **Subtyping:** SMT Implication
3. **Measures:** Strengthened Constructors
4. **Abstract Refinements:* Decouple Invariants
5. Er, what of *lazy evaluation*?