Copyright | (C) 2013-2016 Edward Kmett 2015-2016 Artyom Kazak 2018 Monadfix |
---|---|
License | BSD-style (see the file LICENSE) |
Safe Haskell | Trustworthy |
Language | Haskell2010 |
This module lets you define your own instances of Zoom
and Magnify
.
The warning from Lens.Micro.Internal applies to this module as well. Don't export functions that have Zoom
or Magnify
in their type signatures. If you absolutely need to define an instance (e.g. for internal use), only do it for your own types, because otherwise I might add an instance to one of the microlens packages later and if our instances are different it might lead to subtle bugs.
Synopsis
- type family Zoomed (m :: * -> *) :: * -> * -> *
- class (MonadState s m, MonadState t n) => Zoom m n s t | m -> s, n -> t, m t -> n, n s -> m where
- type family Magnified (m :: * -> *) :: * -> * -> *
- class (MonadReader b m, MonadReader a n) => Magnify m n b a | m -> b, n -> a, m a -> n, n b -> m where
- newtype Focusing m s a = Focusing {
- unfocusing :: m (s, a)
- newtype FocusingWith w m s a = FocusingWith {
- unfocusingWith :: m (s, a, w)
- newtype FocusingPlus w k s a = FocusingPlus {
- unfocusingPlus :: k (s, w) a
- newtype FocusingOn f k s a = FocusingOn {
- unfocusingOn :: k (f s) a
- newtype FocusingMay k s a = FocusingMay {
- unfocusingMay :: k (May s) a
- newtype FocusingErr e k s a = FocusingErr {
- unfocusingErr :: k (Err e s) a
- newtype Effect m r a = Effect {
- getEffect :: m r
- newtype EffectRWS w st m s a = EffectRWS {
- getEffectRWS :: st -> m (s, st, w)
- newtype May a = May {}
- newtype Err e a = Err {}
Classes
type family Zoomed (m :: * -> *) :: * -> * -> * Source #
This type family is used by Zoom
to describe the common effect type.
Instances
type Zoomed (ListT m) Source # | |
Defined in Lens.Micro.Mtl.Internal | |
type Zoomed (MaybeT m) Source # | |
Defined in Lens.Micro.Mtl.Internal | |
type Zoomed (IdentityT m) Source # | |
Defined in Lens.Micro.Mtl.Internal | |
type Zoomed (ErrorT e m) Source # | |
Defined in Lens.Micro.Mtl.Internal | |
type Zoomed (ExceptT e m) Source # | |
Defined in Lens.Micro.Mtl.Internal | |
type Zoomed (StateT s z) Source # | |
Defined in Lens.Micro.Mtl.Internal | |
type Zoomed (StateT s z) Source # | |
Defined in Lens.Micro.Mtl.Internal | |
type Zoomed (WriterT w m) Source # | |
Defined in Lens.Micro.Mtl.Internal | |
type Zoomed (WriterT w m) Source # | |
Defined in Lens.Micro.Mtl.Internal | |
type Zoomed (ReaderT e m) Source # | |
Defined in Lens.Micro.Mtl.Internal | |
type Zoomed (RWST r w s z) Source # | |
Defined in Lens.Micro.Mtl.Internal | |
type Zoomed (RWST r w s z) Source # | |
Defined in Lens.Micro.Mtl.Internal |
class (MonadState s m, MonadState t n) => Zoom m n s t | m -> s, n -> t, m t -> n, n s -> m where Source #
zoom :: LensLike' (Zoomed m c) t s -> m c -> n c infixr 2 Source #
When you're in a state monad, this function lets you operate on a part of your state. For instance, if your state was a record containing a position
field, after zooming position
would become your whole state (and when you modify it, the bigger structure would be modified as well).
(Your State
/ StateT
or RWS
/ RWST
can be anywhere in the stack, but you can't use zoom
with arbitrary MonadState
because it doesn't provide any methods to change the type of the state. See this issue for details.)
For the sake of the example, let's define some types first:
data Position = Position { _x, _y :: Int } data Player = Player { _position :: Position, ... } data Game = Game { _player :: Player, _obstacles :: [Position], ... } concat <$> mapM makeLenses [''Position, ''Player, ''Game]
Now, here's an action that moves the player north-east:
moveNE ::State
Game () moveNE = do player.position.x+=
1 player.position.y+=
1
With zoom
, you can use player.position
to focus just on a part of the state:
moveNE ::State
Game () moveNE = dozoom
(player.position) $ do x+=
1 y+=
1
You can just as well use it for retrieving things out of the state:
getCoords ::State
Game (Int, Int) getCoords =zoom
(player.position) ((,)<$>
use
x<*>
use
y)
Or more explicitly:
getCoords =zoom
(player.position) $ do x' <-use
x y' <-use
y return (x', y')
When you pass a traversal to zoom
, it'll work as a loop. For instance, here we move all obstacles:
moveObstaclesNE ::State
Game () moveObstaclesNE = dozoom
(obstacles.each
) $ do x+=
1 y+=
1
If the action returns a result, all results would be combined with <>
– the same way they're combined when ^.
is passed a traversal. In this example, moveObstaclesNE
returns a list of old coordinates of obstacles in addition to moving them:
moveObstaclesNE = do xys <-zoom
(obstacles.each
) $ do -- Get old coordinates. x' <-use
x y' <-use
y -- Update them. x.=
x' + 1 y.=
y' + 1 -- Return a single-element list with old coordinates. return [(x', y')] ...
Finally, you might need to write your own instances of Zoom
if you use newtype
d transformers in your monad stack. This can be done as follows:
import Lens.Micro.Mtl.Internal type instanceZoomed
(MyStateT s m) =Zoomed
(StateT s m) instance Monad m =>Zoom
(MyStateT s m) (MyStateT t m) s t wherezoom
l (MyStateT m) = MyStateT (zoom
l m)
Instances
Zoom m n s t => Zoom (ListT m) (ListT n) s t Source # | |
Zoom m n s t => Zoom (MaybeT m) (MaybeT n) s t Source # | |
Zoom m n s t => Zoom (IdentityT m) (IdentityT n) s t Source # | |
(Error e, Zoom m n s t) => Zoom (ErrorT e m) (ErrorT e n) s t Source # | |
Zoom m n s t => Zoom (ExceptT e m) (ExceptT e n) s t Source # | |
Monad z => Zoom (StateT s z) (StateT t z) s t Source # | |
Monad z => Zoom (StateT s z) (StateT t z) s t Source # | |
(Monoid w, Zoom m n s t) => Zoom (WriterT w m) (WriterT w n) s t Source # | |
(Monoid w, Zoom m n s t) => Zoom (WriterT w m) (WriterT w n) s t Source # | |
Zoom m n s t => Zoom (ReaderT e m) (ReaderT e n) s t Source # | |
(Monoid w, Monad z) => Zoom (RWST r w s z) (RWST r w t z) s t Source # | |
(Monoid w, Monad z) => Zoom (RWST r w s z) (RWST r w t z) s t Source # | |
type family Magnified (m :: * -> *) :: * -> * -> * Source #
This type family is used by Magnify
to describe the common effect type.
Instances
type Magnified (IdentityT m) Source # | |
Defined in Lens.Micro.Mtl.Internal | |
type Magnified ((->) b :: Type -> Type) Source # | |
type Magnified (ReaderT b m) Source # | |
Defined in Lens.Micro.Mtl.Internal | |
type Magnified (RWST a w s m) Source # | |
Defined in Lens.Micro.Mtl.Internal | |
type Magnified (RWST a w s m) Source # | |
Defined in Lens.Micro.Mtl.Internal |
class (MonadReader b m, MonadReader a n) => Magnify m n b a | m -> b, n -> a, m a -> n, n b -> m where Source #
magnify :: LensLike' (Magnified m c) a b -> m c -> n c infixr 2 Source #
This is an equivalent of local
which lets you apply a getter to your environment instead of merely applying a function (and it also lets you change the type of the environment).
local
:: (r -> r) ->Reader
r a ->Reader
r amagnify
:: Getter r x ->Reader
x a ->Reader
r a
magnify
works with Reader
/ ReaderT
, RWS
/ RWST
, and (->)
.
Here's an example of magnify
being used to work with a part of a bigger config. First, the types:
data URL = URL { _protocol :: Maybe String, _path :: String } data Config = Config { _base :: URL, ... } makeLenses ''URL makeLenses ''Config
Now, let's define a function which returns the base url:
getBase ::Reader
Config String getBase = do protocol <-fromMaybe
"https"<$>
view
(base.protocol) path <-view
(base.path) return (protocol ++ path)
With magnify
, we can factor out base
:
getBase =magnify
base $ do protocol <-fromMaybe
"https"<$>
view
protocol path <-view
path return (protocol ++ path)
This concludes the example.
Finally, you should know writing instances of Magnify
for your own types can be done as follows:
import Lens.Micro.Mtl.Internal type instanceMagnified
(MyReaderT r m) =Magnified
(ReaderT r m) instance Monad m =>Magnify
(MyReaderT r m) (MyReaderT t m) r t wheremagnify
l (MyReaderT m) = MyReaderT (magnify
l m)
Instances
Magnify m n b a => Magnify (IdentityT m) (IdentityT n) b a Source # | |
Magnify ((->) b :: Type -> Type) ((->) a :: Type -> Type) b a Source # | |
Monad m => Magnify (ReaderT b m) (ReaderT a m) b a Source # | |
(Monad m, Monoid w) => Magnify (RWST b w s m) (RWST a w s m) b a Source # | |
(Monad m, Monoid w) => Magnify (RWST b w s m) (RWST a w s m) b a Source # | |
Focusing (used for Zoom
)
newtype Focusing m s a Source #
Focusing | |
|
newtype FocusingWith w m s a Source #
FocusingWith | |
|
Instances
Monad m => Functor (FocusingWith w m s) Source # | |
Defined in Lens.Micro.Mtl.Internal fmap :: (a -> b) -> FocusingWith w m s a -> FocusingWith w m s b # (<$) :: a -> FocusingWith w m s b -> FocusingWith w m s a # | |
(Monad m, Monoid s, Monoid w) => Applicative (FocusingWith w m s) Source # | |
Defined in Lens.Micro.Mtl.Internal pure :: a -> FocusingWith w m s a # (<*>) :: FocusingWith w m s (a -> b) -> FocusingWith w m s a -> FocusingWith w m s b # liftA2 :: (a -> b -> c) -> FocusingWith w m s a -> FocusingWith w m s b -> FocusingWith w m s c # (*>) :: FocusingWith w m s a -> FocusingWith w m s b -> FocusingWith w m s b # (<*) :: FocusingWith w m s a -> FocusingWith w m s b -> FocusingWith w m s a # |
newtype FocusingPlus w k s a Source #
FocusingPlus | |
|
Instances
Functor (k (s, w)) => Functor (FocusingPlus w k s) Source # | |
Defined in Lens.Micro.Mtl.Internal fmap :: (a -> b) -> FocusingPlus w k s a -> FocusingPlus w k s b # (<$) :: a -> FocusingPlus w k s b -> FocusingPlus w k s a # | |
Applicative (k (s, w)) => Applicative (FocusingPlus w k s) Source # | |
Defined in Lens.Micro.Mtl.Internal pure :: a -> FocusingPlus w k s a # (<*>) :: FocusingPlus w k s (a -> b) -> FocusingPlus w k s a -> FocusingPlus w k s b # liftA2 :: (a -> b -> c) -> FocusingPlus w k s a -> FocusingPlus w k s b -> FocusingPlus w k s c # (*>) :: FocusingPlus w k s a -> FocusingPlus w k s b -> FocusingPlus w k s b # (<*) :: FocusingPlus w k s a -> FocusingPlus w k s b -> FocusingPlus w k s a # |
newtype FocusingOn f k s a Source #
FocusingOn | |
|
Instances
Functor (k (f s)) => Functor (FocusingOn f k s) Source # | |
Defined in Lens.Micro.Mtl.Internal fmap :: (a -> b) -> FocusingOn f k s a -> FocusingOn f k s b # (<$) :: a -> FocusingOn f k s b -> FocusingOn f k s a # | |
Applicative (k (f s)) => Applicative (FocusingOn f k s) Source # | |
Defined in Lens.Micro.Mtl.Internal pure :: a -> FocusingOn f k s a # (<*>) :: FocusingOn f k s (a -> b) -> FocusingOn f k s a -> FocusingOn f k s b # liftA2 :: (a -> b -> c) -> FocusingOn f k s a -> FocusingOn f k s b -> FocusingOn f k s c # (*>) :: FocusingOn f k s a -> FocusingOn f k s b -> FocusingOn f k s b # (<*) :: FocusingOn f k s a -> FocusingOn f k s b -> FocusingOn f k s a # |
newtype FocusingMay k s a Source #
FocusingMay | |
|
Instances
Functor (k (May s)) => Functor (FocusingMay k s) Source # | |
Defined in Lens.Micro.Mtl.Internal fmap :: (a -> b) -> FocusingMay k s a -> FocusingMay k s b # (<$) :: a -> FocusingMay k s b -> FocusingMay k s a # | |
Applicative (k (May s)) => Applicative (FocusingMay k s) Source # | |
Defined in Lens.Micro.Mtl.Internal pure :: a -> FocusingMay k s a # (<*>) :: FocusingMay k s (a -> b) -> FocusingMay k s a -> FocusingMay k s b # liftA2 :: (a -> b -> c) -> FocusingMay k s a -> FocusingMay k s b -> FocusingMay k s c # (*>) :: FocusingMay k s a -> FocusingMay k s b -> FocusingMay k s b # (<*) :: FocusingMay k s a -> FocusingMay k s b -> FocusingMay k s a # |
newtype FocusingErr e k s a Source #
FocusingErr | |
|
Instances
Functor (k (Err e s)) => Functor (FocusingErr e k s) Source # | |
Defined in Lens.Micro.Mtl.Internal fmap :: (a -> b) -> FocusingErr e k s a -> FocusingErr e k s b # (<$) :: a -> FocusingErr e k s b -> FocusingErr e k s a # | |
Applicative (k (Err e s)) => Applicative (FocusingErr e k s) Source # | |
Defined in Lens.Micro.Mtl.Internal pure :: a -> FocusingErr e k s a # (<*>) :: FocusingErr e k s (a -> b) -> FocusingErr e k s a -> FocusingErr e k s b # liftA2 :: (a -> b -> c) -> FocusingErr e k s a -> FocusingErr e k s b -> FocusingErr e k s c # (*>) :: FocusingErr e k s a -> FocusingErr e k s b -> FocusingErr e k s b # (<*) :: FocusingErr e k s a -> FocusingErr e k s b -> FocusingErr e k s a # |
Effect (used for Magnify
)
Wrap a monadic effect with a phantom type argument.
newtype EffectRWS w st m s a Source #
Wrap a monadic effect with a phantom type argument. Used when magnifying RWST
.
EffectRWS | |
|
Instances
Functor (EffectRWS w st m s) Source # | |
(Monoid s, Monoid w, Monad m) => Applicative (EffectRWS w st m s) Source # | |
Defined in Lens.Micro.Mtl.Internal pure :: a -> EffectRWS w st m s a # (<*>) :: EffectRWS w st m s (a -> b) -> EffectRWS w st m s a -> EffectRWS w st m s b # liftA2 :: (a -> b -> c) -> EffectRWS w st m s a -> EffectRWS w st m s b -> EffectRWS w st m s c # (*>) :: EffectRWS w st m s a -> EffectRWS w st m s b -> EffectRWS w st m s b # (<*) :: EffectRWS w st m s a -> EffectRWS w st m s b -> EffectRWS w st m s a # |