#if defined(__GLASGOW_HASKELL__) && __GLASGOW_HASKELL__ >= 704
#endif
module Control.Lens.Zoom
  ( Magnify(..)
  , Zoom(..)
  ) where
import Control.Lens.Getter
import Control.Lens.Internal
import Control.Lens.Internal.Combinators
import Control.Lens.Type
import Control.Monad
import Control.Monad.Reader.Class       as Reader
import Control.Monad.State.Class        as State
import Control.Monad.Trans.State.Lazy   as Lazy
import Control.Monad.Trans.State.Strict as Strict
import Control.Monad.Trans.Writer.Lazy   as Lazy
import Control.Monad.Trans.Writer.Strict as Strict
import Control.Monad.Trans.RWS.Lazy   as Lazy
import Control.Monad.Trans.RWS.Strict as Strict
import Control.Monad.Trans.Reader
import Control.Monad.Trans.Error
import Control.Monad.Trans.List
import Control.Monad.Trans.Identity
import Control.Monad.Trans.Maybe
import Data.Monoid
class (MonadState s m, MonadState t n) => Zoom m n k s t | m -> s k, n -> t k, m t -> n, n s -> m where
  
  
  
  
  
  
  
  
  
  
  
  
  
  
  
  
  
  
  
  
  
  zoom :: Monad m => SimpleLensLike (k c) t s -> m c -> n c
instance Monad z => Zoom (Strict.StateT s z) (Strict.StateT t z) (Focusing z) s t where
  zoom l (Strict.StateT m) = Strict.StateT $ unfocusing# (l (focusing# m))
  
instance Monad z => Zoom (Lazy.StateT s z) (Lazy.StateT t z) (Focusing z) s t where
  zoom l (Lazy.StateT m) = Lazy.StateT $ unfocusing# (l (focusing# m))
  
instance Zoom m n k s t => Zoom (ReaderT e m) (ReaderT e n) k s t where
  zoom l (ReaderT m) = ReaderT (zoom l . m)
  
instance Zoom m n k s t => Zoom (IdentityT m) (IdentityT n) k s t where
  zoom l (IdentityT m) = IdentityT (zoom l m)
  
instance (Monoid w, Monad z) => Zoom (Strict.RWST r w s z) (Strict.RWST r w t z) (FocusingWith w z) s t where
  zoom l (Strict.RWST m) = Strict.RWST $ \r -> unfocusingWith# (l (focusingWith# (m r)))
  
instance (Monoid w, Monad z) => Zoom (Lazy.RWST r w s z) (Lazy.RWST r w t z) (FocusingWith w z) s t where
  zoom l (Lazy.RWST m) = Lazy.RWST $ \r -> unfocusingWith# (l (focusingWith# (m r)))
  
instance (Monoid w, Zoom m n k s t) => Zoom (Strict.WriterT w m) (Strict.WriterT w n) (FocusingPlus w k) s t where
  zoom l = Strict.WriterT . zoom (\afb -> unfocusingPlus# (l (focusingPlus# afb))) . Strict.runWriterT
  
instance (Monoid w, Zoom m n k s t) => Zoom (Lazy.WriterT w m) (Lazy.WriterT w n) (FocusingPlus w k) s t where
  zoom l = Lazy.WriterT . zoom (\afb -> unfocusingPlus# (l (focusingPlus# afb))) . Lazy.runWriterT
  
instance Zoom m n k s t => Zoom (ListT m) (ListT n) (FocusingOn [] k) s t where
  zoom l = ListT . zoom (\afb -> unfocusingOn . l (FocusingOn . afb)) . runListT
  
instance Zoom m n k s t => Zoom (MaybeT m) (MaybeT n) (FocusingMay k) s t where
  zoom l = MaybeT . liftM getMay . zoom (\afb -> unfocusingMay# (l (focusingMay# afb))) . liftM May . runMaybeT
  
instance (Error e, Zoom m n k s t) => Zoom (ErrorT e m) (ErrorT e n) (FocusingErr e k) s t where
  zoom l = ErrorT . liftM getErr . zoom (\afb -> unfocusingErr# (l (focusingErr# afb))) . liftM Err . runErrorT
  
class (MonadReader b m, MonadReader a n) => Magnify m n k b a | m -> b, n -> a, m a -> n, n b -> m where
  
  
  
  
  
  
  
  
  
  
  
  
  
  
  
  magnify :: ((b -> k c b) -> a -> k c a) -> m c -> n c
instance Monad m => Magnify (ReaderT b m) (ReaderT a m) (Effect m) b a where
  magnify l (ReaderT m) = ReaderT $ getEffect# (l (effect# m))
  
instance Magnify ((->) b) ((->) a) Accessor b a where
  magnify = views
  
instance (Monad m, Monoid w) => Magnify (Strict.RWST b w s m) (Strict.RWST a w s m) (EffectRWS w s m) b a where
  magnify l (Strict.RWST m) = Strict.RWST $ getEffectRWS# (l (effectRWS# m))
  
instance (Monad m, Monoid w) => Magnify (Lazy.RWST b w s m) (Lazy.RWST a w s m) (EffectRWS w s m) b a where
  magnify l (Lazy.RWST m) = Lazy.RWST $ getEffectRWS# (l (effectRWS# m))
  
instance Magnify m n k b a => Magnify (IdentityT m) (IdentityT n) k b a where
  magnify l (IdentityT m) = IdentityT (magnify l m)