{#abstractrefinements} ======================== Abstract Refinements -------------------- Abstract Refinements ==================== Two Problems ------------
**Problem 1:** How do we specify *both* [increasing and decreasing lists](http://web.cecs.pdx.edu/~sheard/Code/QSort.html)?

**Problem 2:** How do we specify *iteration-dependence* in higher-order functions?
Problem Is Pervasive -------------------- Lets distill it to a simple example...

(First, a few aliases)
\begin{code} {-@ type Odd = {v:Int | (v mod 2) = 1} @-} {-@ type Even = {v:Int | (v mod 2) = 0} @-} \end{code}
Example: `maxInt` ----------------- Compute the larger of two `Int`s: \begin{code}
maxInt :: Int -> Int -> Int maxInt x y = if y <= x then x else y \end{code} Example: `maxInt` ----------------- Has *many incomparable* refinement types \begin{code}
maxInt :: Nat -> Nat -> Nat maxInt :: Even -> Even -> Even maxInt :: Odd -> Odd -> Odd \end{code}
Yikes. **Which** one should we use?
Refinement Polymorphism ----------------------- `maxInt` returns *one of* its two inputs `x` and `y`

--------- --- ------------------------------------------- **If** : the *inputs* satisfy a property **Then** : the *output* satisfies that property --------- --- -------------------------------------------
Above holds *for all* properties!

**Need to abstract refinements over types**
By Type Polymorphism? --------------------- \begin{code}
max :: α -> α -> α max x y = if y <= x then x else y \end{code}
Instantiate `α` at callsites \begin{code} {-@ o :: Odd @-} o = maxInt 3 7 -- α := Odd {-@ e :: Even @-} e = maxInt 2 8 -- α := Even \end{code}
By Type Polymorphism? --------------------- \begin{code}
max :: α -> α -> α max x y = if y <= x then x else y \end{code}
But there is a fly in the ointment ... Polymorphic `max` in Haskell ---------------------------- \begin{code} In Haskell the type of max is max :: (Ord α) => α -> α -> α \end{code}
\begin{code} Could *ignore* the class constraints, instantiate as before... {-@ o :: Odd @-} o = max 3 7 -- α := Odd \end{code} Polymorphic `(+)` in Haskell ---------------------------- \begin{code} ... but this is *unsound*! max :: (Ord α) => α -> α -> α (+) :: (Num α) => α -> α -> α \end{code}
*Ignoring* class constraints would let us "prove": \begin{code} {-@ no :: Odd @-} no = 3 + 7 -- α := Odd ! \end{code}
Type Polymorphism? No. ----------------------
Need to try a bit harder...
By Parametric Refinements! -------------------------- That is, enable *quantification over refinements*... Parametric Refinements ---------------------- \begin{code} {-@ maxInt :: forall

Prop>. Int

-> Int

-> Int

@-} maxInt x y = if x <= y then y else x \end{code}

Type says: **for any** `p` that is a property of `Int`,
-
`max` **takes** two `Int`s that satisfy `p`,
-
`max` **returns** an `Int` that satisfies `p`.
Parametric Refinements ---------------------- \begin{code}
{-@ maxInt :: forall

Prop>. Int

-> Int

-> Int

@-} maxInt x y = if x <= y then y else x \end{code}
[Key idea: ](http://goto.ucsd.edu/~rjhala/papers/abstract_refinement_types.html) `Int

` is `{v:Int | (p v)}`

So, Abstract Refinement is an *uninterpreted function* in SMT logic
Parametric Refinements ---------------------- \begin{code}
{-@ maxInt :: forall

Prop>. Int

-> Int

-> Int

@-} maxInt x y = if x <= y then y else x \end{code}
**Check** and **Instantiate** type using *SMT & predicate abstraction* Using Abstract Refinements -------------------------- -

**When** we call `maxInt` with args with some refinement,
-
**Then** `p` instantiated with *same* refinement,
-
**Result** of call will also have concrete refinement.
\begin{code} {-@ o' :: Odd @-} o' = maxInt 3 7 -- p := \v -> Odd v {-@ e' :: Even @-} e' = maxInt 2 8 -- p := \v -> Even v \end{code}
Using Abstract Refinements -------------------------- Or any other property
\begin{code} {-@ type RGB = {v:_ | (0 <= v && v < 256)} @-} {-@ rgb :: RGB @-} rgb = maxInt 56 8 \end{code} Recap ----- 1. **Refinements:** Types + Predicates 2. **Subtyping:** SMT Implication 3. **Measures:** Strengthened Constructors 4.
**Abstract:** Refinements over Type Signatures