{-# OPTIONS -fglasgow-exts -fno-warn-orphans #-} {-# LANGUAGE ScopedTypeVariables, UndecidableInstances #-} ----------------------------------------------------------------------------- -- | -- Module : Control.Monad.StateX -- Copyright : (c) Mark Snyder 2008. -- License : BSD-style -- Maintainer : Mark Snyder, marks@ittc.ku.edu -- Portability : non-portable (multi-param classes, functional dependencies) -- -- State monads. -- -- This module is inspired by the paper -- /Functional Programming with Overloading and -- Higher-Order Polymorphism/, -- Mark P Jones () -- Advanced School of Functional Programming, 1995. ----------------------------------------------------------------------------- module Control.Monad.StateX ( module Control.Monad.StateX.Lazy, module Control.Monad.Index ) where import Control.Monad.StateX.Lazy import Control.Monad.Index import Control.Monad.Error import Control.Monad.State import Control.Monad.Reader import Control.Monad.Writer instance (Error e, MonadStateX ix s m) => MonadStateX ix s (ErrorT e m) where getx (ixv::ix) = lift $ getx ixv putx (ixv::ix) = lift . putx ixv instance (MonadStateX ix s1 m, Index ix) => MonadStateX ix s1 (StateT s2 m) where getx (ixv::ix) = StateT $ \s -> do n <- getx ixv return (n,s) putx (ixv::ix) (v::s1) = StateT $ \s -> do putx ixv v return ((),s) instance (Index ix, MonadStateX ix s m) => MonadStateX ix s (ReaderT r m) where getx (ixv::ix) = lift $ getx ixv putx (ixv::ix) v = lift $ putx ixv v instance (Index ix, MonadStateX ix s m, Monoid w) => MonadStateX ix s (WriterT w m) where getx (ixv::ix) = lift $ getx ixv putx (ixv::ix) s = lift $ putx ixv s