Reputation: 787
I am following the Liquid Haskell tutorial:
http://ucsd-progsys.github.io/liquidhaskell-tutorial/04-poly.html
and this example fails:
module Test2 where
import Data.Vector
import Prelude hiding (length)
vectorSum :: Vector Int -> Int
vectorSum vec = go 0 0
where
go acc i
| i < length vec = go (acc + (vec ! i)) (i + 1)
| otherwise = acc
with the following error:
Error: Liquid Type Mismatch
10 | | i < length vec = go (acc + (vec ! i)) (i + 1)
^^^^^^^^^^^^^^^^^
Inferred type
VV : {v : GHC.Types.Int | v == acc + ?b}
not a subtype of Required type
VV : {VV : GHC.Types.Int | VV < acc
&& VV >= 0}
In Context
?b : GHC.Types.Int
acc : GHC.Types.Int
The question is why? The guard (i < length vec) should ensure that (vec ! i) is safe.
Upvotes: 1
Views: 140
Reputation: 26
This looks like a termination error. Liquid Haskell here seems to assume that acc
is the termination metric of go
(probably because it's the first Int
argument). As such it should always be non-negative and decreasing in each iteration (hence the error message you get).
The way to fix this is providing a correct termination metric, which fulfills the above criteria. Here this would be length vec - i
and the corresponding signature for go
is:
{-@ go :: _ -> i:_ -> _ /[length vec - i] @-}
or something along those lines.
Upvotes: 1
Reputation: 809
First of all, I don't know which version of LH you were using but I just had the exact same problem. The tutorial states that
LiquidHaskell verifies vectorSum – or, to be precise, the safety of the vector accesses vec ! i. The verification works out because LiquidHaskell is able to automatically infer
go :: Int -> {v:Int | 0 <= v && v <= sz} -> Int
which states that the second parameter i is between 0 and the length of vec (inclusive). LiquidHaskell uses this and the test that i < sz to establish that i is between 0 and (vlen vec) to prove safety.
They also state that the tutorial is not in accordance with the current version of LiquidHaskell.
It seems that the (refinement-)type inference of LH has changed a bit since the tutorial was written, probably generalizing types more than before, which results in this problem.
The problem is NOT that LH doesn't figure out the guard properly. The problem is that it fails to verify the property 0 <= v
.
The following checks fine with version 0.8.6.2 of LH:
{-@ LIQUID "--short-names" @-}
{-@ LIQUID "--no-termination" @-}
{-@ LIQUID "--reflection" @-}
import Prelude hiding (length)
import Data.Vector
{-@ go' :: v:Vector Int -> Int -> {i:Int | i>=0 } ->Int @-}
go' :: Vector Int -> Int -> Int -> Int
go' vec acc i
| i < sz = go' vec (acc + (vec ! i)) (i + 1)
| otherwise = acc
where sz = length vec
vecSum :: Vector Int -> Int
vecSum vec = go' vec 0 0
It seems that LH infers thas go is a function in its own right and might be called with an integer smaller than 0 (which it obviously isn't).
I am still playing with that example to convince LH of this fact. If anybody had more success on this please leave a comment.
EDIT:
I found the following paragraph in the same tutorial; It seems that this might have changed:
At the call
loop 0 n 0 body
the parameterslo
andhi
are instantiated with0
andn
respectively, which, by the way is where the inference engine deduces non-negativity.
Upvotes: 1