Abstract Refinements {#data}
============================
Recap
-----
**So far**
Abstract Refinements decouple invariants from *functions*
**Next**
Decouple invariants from *data structures*
Decouple Invariants From Data {#vector}
=======================================
Example: Vectors
----------------
\begin{code}
module LiquidArray where
import Language.Haskell.Liquid.Prelude (liquidAssume, liquidError)
{-@ LIQUID "--no-termination" @-}
initialize :: Int -> Vec Int
\end{code}
For this talk, implemented as maps from `Int` to `a`
\begin{code}
data Vec a = V (Int -> a)
\end{code}
Abstract *Domain* and *Range*
-----------------------------
Parameterize type with *two* abstract refinements:
\begin{code}
{-@ data Vec a < dom :: Int -> Prop,
rng :: Int -> a -> Prop >
= V {a :: i:Int -> a } @-}
\end{code}
- `dom`: *domain* on which `Vec` is *defined*
- `rng`: *range* and relationship with *index*
Abstract *Domain* and *Range*
-----------------------------
Diverse `Vec`tors by *instantiating* `dom` and `rng`
An alias for *segments* between `I` and `J`
\begin{code}
{-@ predicate Btwn I V J = I <= V && V < J @-}
\end{code}
Ex: Identity Vectors
--------------------
Defined between `[0..N)` mapping each key to itself:
\begin{code}
{-@ type IdVec N = Vec <{\v -> Btwn 0 v N},
{\k v -> v = k}>
Int @-}
\end{code}
Ex: Zero-Terminated Vectors
---------------------------
Defined between `[0..N)`, with *last* element equal to `0`:
\begin{code}
{-@ type ZeroTerm N =
Vec <{\v -> Btwn 0 v N},
{\k v -> k = N-1 => v = 0}>
Int @-}
\end{code}
Ex: Fibonacci Table
-------------------
A vector whose value at index `k` is either
- `0` (undefined), or,
- `k`th fibonacci number
\begin{code}
{-@ type FibV =
Vec <{\v -> true},
{\k v -> v = 0 || v = fib k}>
Int @-}
\end{code}
An API for Vectors
------------------
- `empty`
- `set`
- `get`
API: Empty Vectors
-----------------
`empty` a Vector whose domain is `false` (defined at *no* key)
\begin{code}
{-@ empty :: forall a -> Prop>.
Vec <{v:Int|false}, p> a @-}
empty = V $ \_ -> error "empty vector!"
\end{code}
Demo:
What would happen if we changed `false` to `true`?
API: `get` Key's Value
----------------------
- *Input* `key` in *domain*
- *Output* value in *range* related with `k`
\begin{code}
{-@ get :: forall a Prop,
r :: Int -> a -> Prop>.
key:Int
-> vec:Vec a
-> a @-}
get k (V f) = f k
\end{code}
API: `set` Key's Value
----------------------
- Input `key` in *domain*
- Input `val` in *range* related with `key`
- Input `vec` defined at *domain except at* `key`
- Output domain *includes* `key`
API: `set` Key's Value
----------------------
\begin{code}
{-@ set :: forall a Prop,
r :: Int -> a -> Prop>.
key: Int -> val: a
-> vec: Vec<{v:Int| v /= key},r> a
-> Vec a @-}
set key val (V f) = V $ \k -> if k == key
then val
else f k
\end{code}
Demo:
Help! Can you spot and fix the errors?
Using the Vector API
--------------------
Loop over vector, setting each key `i` equal to `i`:
\begin{code}
{-@ initialize :: n:Nat -> IdVec n @-}
initialize n = loop 0 empty
where
loop i a
| i < n = let a' = set i i a
in
loop (i+1) a'
| otherwise = a
\end{code}
Recap
-----
+ Created a `Vec` (Array) container
+ Decoupled *domain* and *range* invariants from *data*
+ Enabled analysis of *array segments*
Recap
-----
Custom *array segment* program analyses:
- Gopan-Reps-Sagiv, POPL 05
- J.-McMillan, CAV 07
- Logozzo-Cousot-Cousot, POPL 11
- Dillig-Dillig, POPL 12
Encoded in (abstract) refinement typed API.
Recap
-----
1. Refinements: Types + Predicates
2. Subtyping: SMT Implication
3. Measures: Strengthened Constructors
4. Abstract: Refinements over Type Signatures
+ Functions
+ **Data**
[[continue...]](11_Evaluation.lhs.slides.html)