\begin{code}
module Loop (
listSum
, sumNats
) where
import Prelude
{-@ LIQUID "--no-termination"@-}
sumNats :: [Int] -> Int
add :: Int -> Int -> Int
\end{code}
Higher-Order Specifications
---------------------------
Types scale to *Higher-Order* Specifications
+ map
+ fold
+ visitors
+ callbacks
+ ...
Very difficult with *first-order program logics*
Higher Order Specifications
===========================
Example: Higher Order Loop
--------------------------
\begin{code}
loop :: Int -> Int -> α -> (Int -> α -> α) -> α
loop lo hi base f = go lo base
where
go i acc
| i < hi = go (i+1) (f i acc)
| otherwise = acc
\end{code}
By subtyping, we infer `f` called with values `(Btwn lo hi)`
Example: Summing Lists
----------------------
\begin{code}
listSum :: [Int] -> Int
listSum xs = loop 0 n 0 body
where
body = \i acc -> acc + (xs !! i)
n = length xs
\end{code}
**Function Subtyping**
+ `body` called with `i :: Btwn 0 (llen xs)`
+ Hence, indexing with `!!` is safe.
**Step 2. Horn-Constraints**
By type checking the templates
**Step 3. Fixpoint**
Abstract interpretatn. to get solution for $\kvar{}$
Iteration Dependence
--------------------
**Problem:** Cannot use parametric polymorphism to verify
\begin{code}
{-@ add :: n:Nat -> m:Nat -> {v:Nat|v=m+n} @-}
add n m = loop 0 m n (\_ i -> i + 1)
\end{code}
As property only holds after **last iteration** ...
... cannot instantiate $\alpha \defeq \reft{v}{\Int}{v = n + m}$