Protected.hs

module Protected where
import MemMonads
import Monad(liftM)

-- Environment+exception monad transformer
newtype EnvEx m e a = E (e->m (Maybe a))
unE (E m) = m
ex = E

instance Monad m => Monad (EnvEx m e) where
  return x = ex $ \e->return (Just x)
  m1>>=xm2 = ex $ \e->unE m1 e>>=maybe (return Nothing) (\a->unE (xm2 a) e)

type Protect m a = EnvEx m (a->Bool)

protect a m = ex $ \valid->if valid a then liftM Just m else return Nothing

instance MemMonad m a w => MemMonad (Protect m a) a w where
  rd a = protect a (rd a)
  wr a w = protect a (wr a w)

runProtected b valid m = liftM (maybe b id) (unE m valid)

Plain-text version of Protected.hs | Valid HTML?