{-# LANGUAGE CPP #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE RankNTypes #-}
{-# OPTIONS_GHC -fno-warn-warnings-deprecations #-}
#if __GLASGOW_HASKELL__ < 708
{-# LANGUAGE Trustworthy #-}
#endif
#include "lens-common.h"
module Control.Lens.Zoom
( Magnified
, Magnify(..)
, Zoom(..)
, Zoomed
) where
import Prelude ()
import Control.Lens.Getter
import Control.Lens.Internal.Coerce
import Control.Lens.Internal.Prelude
import Control.Lens.Internal.Zoom
import Control.Lens.Type
import Control.Monad
import Control.Monad.Reader as Reader
import Control.Monad.State 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.Error
import Control.Monad.Trans.Except
import Control.Monad.Trans.List
import Control.Monad.Trans.Identity
import Control.Monad.Trans.Maybe
import Control.Monad.Trans.Free
#ifdef HLINT
{-# ANN module "HLint: ignore Use fmap" #-}
#endif
infixr 2 `zoom`, `magnify`
type family Zoomed (m :: * -> *) :: * -> * -> *
type instance Zoomed (Strict.StateT s z) = Focusing z
type instance Zoomed (Lazy.StateT s z) = Focusing z
type instance Zoomed (ReaderT e m) = Zoomed m
type instance Zoomed (IdentityT m) = Zoomed m
type instance Zoomed (Strict.RWST r w s z) = FocusingWith w z
type instance Zoomed (Lazy.RWST r w s z) = FocusingWith w z
type instance Zoomed (Strict.WriterT w m) = FocusingPlus w (Zoomed m)
type instance Zoomed (Lazy.WriterT w m) = FocusingPlus w (Zoomed m)
type instance Zoomed (ListT m) = FocusingOn [] (Zoomed m)
type instance Zoomed (MaybeT m) = FocusingMay (Zoomed m)
type instance Zoomed (ErrorT e m) = FocusingErr e (Zoomed m)
type instance Zoomed (ExceptT e m) = FocusingErr e (Zoomed m)
type instance Zoomed (FreeT f m) = FocusingFree f m (Zoomed m)
type family Magnified (m :: * -> *) :: * -> * -> *
type instance Magnified (ReaderT b m) = Effect m
type instance Magnified ((->)b) = Const
type instance Magnified (Strict.RWST a w s m) = EffectRWS w s m
type instance Magnified (Lazy.RWST a w s m) = EffectRWS w s m
type instance Magnified (IdentityT m) = Magnified m
class (MonadState s m, MonadState t n) => Zoom m n s t | m -> s, n -> t, m t -> n, n s -> m where
zoom :: LensLike' (Zoomed m c) t s -> m c -> n c
instance Monad z => Zoom (Strict.StateT s z) (Strict.StateT t z) s t where
zoom l (Strict.StateT m) = Strict.StateT $ unfocusing #. l (Focusing #. m)
{-# INLINE zoom #-}
instance Monad z => Zoom (Lazy.StateT s z) (Lazy.StateT t z) s t where
zoom l (Lazy.StateT m) = Lazy.StateT $ unfocusing #. l (Focusing #. m)
{-# INLINE zoom #-}
instance Zoom m n s t => Zoom (ReaderT e m) (ReaderT e n) s t where
zoom l (ReaderT m) = ReaderT (zoom l . m)
{-# INLINE zoom #-}
instance Zoom m n s t => Zoom (IdentityT m) (IdentityT n) s t where
zoom l (IdentityT m) = IdentityT (zoom l m)
{-# INLINE zoom #-}
instance (Monoid w, Monad z) => Zoom (Strict.RWST r w s z) (Strict.RWST r w t z) s t where
zoom l (Strict.RWST m) = Strict.RWST $ \r -> unfocusingWith #. l (FocusingWith #. m r)
{-# INLINE zoom #-}
instance (Monoid w, Monad z) => Zoom (Lazy.RWST r w s z) (Lazy.RWST r w t z) s t where
zoom l (Lazy.RWST m) = Lazy.RWST $ \r -> unfocusingWith #. l (FocusingWith #. m r)
{-# INLINE zoom #-}
instance (Monoid w, Zoom m n s t) => Zoom (Strict.WriterT w m) (Strict.WriterT w n) s t where
zoom l = Strict.WriterT . zoom (\afb -> unfocusingPlus #.. l (FocusingPlus #.. afb)) . Strict.runWriterT
{-# INLINE zoom #-}
instance (Monoid w, Zoom m n s t) => Zoom (Lazy.WriterT w m) (Lazy.WriterT w n) s t where
zoom l = Lazy.WriterT . zoom (\afb -> unfocusingPlus #.. l (FocusingPlus #.. afb)) . Lazy.runWriterT
{-# INLINE zoom #-}
instance Zoom m n s t => Zoom (ListT m) (ListT n) s t where
zoom l = ListT . zoom (\afb -> unfocusingOn . l (FocusingOn . afb)) . runListT
{-# INLINE zoom #-}
instance Zoom m n s t => Zoom (MaybeT m) (MaybeT n) s t where
zoom l = MaybeT . liftM getMay . zoom (\afb -> unfocusingMay #.. l (FocusingMay #.. afb)) . liftM May . runMaybeT
{-# INLINE zoom #-}
instance (Error e, Zoom m n s t) => Zoom (ErrorT e m) (ErrorT e n) s t where
zoom l = ErrorT . liftM getErr . zoom (\afb -> unfocusingErr #.. l (FocusingErr #.. afb)) . liftM Err . runErrorT
{-# INLINE zoom #-}
instance Zoom m n s t => Zoom (ExceptT e m) (ExceptT e n) s t where
zoom l = ExceptT . liftM getErr . zoom (\afb -> unfocusingErr #.. l (FocusingErr #.. afb)) . liftM Err . runExceptT
{-# INLINE zoom #-}
instance (Functor f, Zoom m n s t) => Zoom (FreeT f m) (FreeT f n) s t where
zoom l = FreeT . liftM (fmap (zoom l) . getFreed) . zoom (\afb -> unfocusingFree #.. l (FocusingFree #.. afb)) . liftM Freed . runFreeT
class (Magnified m ~ Magnified n, MonadReader b m, MonadReader a n) => Magnify m n b a | m -> b, n -> a, m a -> n, n b -> m where
magnify :: ((Functor (Magnified m c), Contravariant (Magnified m c))
=> LensLike' (Magnified m c) a b)
-> m c -> n c
instance Monad m => Magnify (ReaderT b m) (ReaderT a m) b a where
magnify l (ReaderT m) = ReaderT $ getEffect #. l (Effect #. m)
{-# INLINE magnify #-}
instance Magnify ((->) b) ((->) a) b a where
magnify l = views l
{-# INLINE magnify #-}
instance (Monad m, Monoid w) => Magnify (Strict.RWST b w s m) (Strict.RWST a w s m) b a where
magnify l (Strict.RWST m) = Strict.RWST $ getEffectRWS #. l (EffectRWS #. m)
{-# INLINE magnify #-}
instance (Monad m, Monoid w) => Magnify (Lazy.RWST b w s m) (Lazy.RWST a w s m) b a where
magnify l (Lazy.RWST m) = Lazy.RWST $ getEffectRWS #. l (EffectRWS #. m)
{-# INLINE magnify #-}
instance Magnify m n b a => Magnify (IdentityT m) (IdentityT n) b a where
magnify l (IdentityT m) = IdentityT (magnify l m)
{-# INLINE magnify #-}