{-@ LIQUID "--expect-any-error" @-} -- Test for https://github.com/ucsd-progsys/liquidhaskell/issues/1907 module T1907 where {-@ foldr' :: forall b -> Bool>. (a -> b -> b) -> b -> xs:[a] -> b @-} foldr' op b = go where {-@ go :: forall b -> Bool>. xs:[a] -> b @-} go [] = b go (h:t) = op h (go t) {-@ mlength :: zs:[a] -> {v:_ | v == 42 * (len zs) } @-} mlength = foldr' (\_ n -> n + 1) 0