-- | -- Module: Control.ContStuff.Instances -- Copyright: (c) 2010 Ertugrul Soeylemez -- License: BSD3 -- Maintainer: Ertugrul Soeylemez -- Stability: experimental -- -- This module implements some miscellaneous type class instances. {-# LANGUAGE TypeFamilies #-} module Control.ContStuff.Instances () where import qualified Control.Exception as E import Control.ContStuff.Classes import Control.ContStuff.Trans import Control.Monad.Trans.Class ---------------- -- Exceptions -- ---------------- instance HasExceptions (Either e) where type Exception (Either e) = e raise = Left try = Right instance HasExceptions Maybe where type Exception Maybe = () raise = const Nothing try = Just . maybe (Left ()) Right instance HasExceptions IO where type Exception IO = E.SomeException raise = E.throwIO try = E.try -------------- -- Readable -- -------------- instance (Monad m, Readable m) => Readable (ChoiceT r i m) where type StateOf (ChoiceT r i m) = StateOf m get = lift get instance (Monad m, Readable m) => Readable (ContT r m) where type StateOf (ContT r m) = StateOf m get = lift get instance (Monad m, Readable m) => Readable (EitherT r e m) where type StateOf (EitherT r e m) = StateOf m get = lift get instance (Monad m, Readable m) => Readable (IdentityT m) where type StateOf (IdentityT m) = StateOf m get = lift get instance (Monad m, Readable m) => Readable (MaybeT r m) where type StateOf (MaybeT r m) = StateOf m get = lift get -------------- -- Stateful -- -------------- instance (Monad m, Stateful m) => Stateful (ChoiceT r i m) where put = lift . put putLazy = lift . putLazy instance (Monad m, Stateful m) => Stateful (ContT r m) where put = lift . put putLazy = lift . putLazy instance (Monad m, Stateful m) => Stateful (EitherT r e m) where put = lift . put putLazy = lift . putLazy instance (Monad m, Stateful m) => Stateful (IdentityT m) where put = lift . put putLazy = lift . putLazy instance (Monad m, Stateful m) => Stateful (MaybeT r m) where put = lift . put putLazy = lift . putLazy