-- TAG: classes -- TAG: bounds {-@ LIQUID "--no-pattern-inline" @-} module STLib where data ST s a = S {runSt :: s -> (a, s) } {-@ data ST s a
Bool, post :: a -> s -> Bool> = S { runSt :: (x:s-> ((a, s))) } @-} {-@ apply :: forall Bool, q :: a -> s -> Bool>. ST
s a -> s
-> (a, s)
@-} apply :: ST s a -> s -> (a, s) apply (S f) s = f s instance Functor (ST s) where fmap = undefined instance Applicative (ST s) where pure = undefined (<*>) = undefined instance Monad (ST s) where {-@ instance Monad (ST s) where return :: foralls -> Bool>. x:a -> ST <{v:s
| true}, p, {v:a | true}> s a ; >>= :: forall
Bool, qbind :: a -> s -> Bool, rbind :: b -> s -> Bool>. ST s a -> (xbind:a -> ST <{v:s | true}, rbind> s b) -> ST s b; >> :: forall Bool, qbind :: a -> s -> Bool, rbind :: b -> s -> Bool>. ST s a -> (ST <{v:s| true}, rbind> s b) -> ST s b @-} return x = S $ \s -> (x, s) (S m) >> k = S $ \s -> let (a, s') = m s in apply k s' (S m) >>= k = S $ \s -> let (a, s') = m s in apply (k a) s'