module WhileM where {-@ LIQUID "--no-termination" @-} {-@ LIQUID "--short-names" @-} import RIO {-@ whileM :: forall < p :: World -> Prop , qc :: World -> Bool -> World -> Prop , qe :: World -> () -> World -> Prop , q :: World -> () -> World -> Prop>. {x::(), s1::World

, b::{v:Bool | Prop v}, s2::World |- World <: World

} {b::{v:Bool | Prop v}, x2::(), s1::World

, s3::World |- World <: World } {b::{v:Bool | not (Prop v)}, x2::(), s1::World

|- World <: World } RIO Bool -> RIO <{\v -> true}, qe> () -> RIO () @-} whileM :: RIO Bool -> RIO () -> RIO () whileM (RIO cond) (RIO e) = RIO $ \s1 -> case cond s1 of {(y, s2) -> if y then case e s2 of {(y2, s3) -> runState (whileM (RIO cond) (RIO e)) s3} else ((), s2) }