microlens-mtl-0.1.11.1: microlens support for Reader/Writer/State from mtl

Copyright(C) 2013-2016 Edward Kmett 2015-2016 Artyom
LicenseBSD-style (see the file LICENSE)
Safe HaskellTrustworthy
LanguageHaskell2010

Lens.Micro.Mtl

Contents

Description

 

Synopsis

Getting

view :: MonadReader s m => Getting a s a -> m a Source #

view is a synonym for (^.), generalised for MonadReader (we are able to use it instead of (^.) since functions are instances of the MonadReader class):

>>> view _1 (1, 2)
1

When you're using Reader for config and your config type has lenses generated for it, most of the time you'll be using view instead of asks:

doSomething :: (MonadReader Config m) => m Int
doSomething = do
  thingy        <- view setting1  -- same as “asks (^. setting1)”
  anotherThingy <- view setting2
  ...

preview :: MonadReader s m => Getting (First a) s a -> m (Maybe a) Source #

preview is a synonym for (^?), generalised for MonadReader (just like view, which is a synonym for (^.)).

>>> preview each [1..5]
Just 1

use :: MonadState s m => Getting a s a -> m a Source #

use is (^.) (or view) which implicitly operates on the state; for instance, if your state is a record containing a field foo, you can write

x <- use foo

to extract foo from the state. In other words, use is the same as gets, but for getters instead of functions.

The implementation of use is straightforward:

use l = gets (view l)

If you need to extract something with a fold or traversal, you need preuse.

preuse :: MonadState s m => Getting (First a) s a -> m (Maybe a) Source #

preuse is (^?) (or preview) which implicitly operates on the state – it takes the state and applies a traversal (or fold) to it to extract the 1st element the traversal points at.

preuse l = gets (preview l)

Setting

(%=) :: MonadState s m => ASetter s s a b -> (a -> b) -> m () infix 4 Source #

Modify state by applying a function to a part of the state. An example:

>>> execState (do _1 %= (+1); _2 %= reverse) (1,"hello")
(2,"olleh")

Implementation:

l %= f = modify (l %~ f)

If you also want to get the value before/after the modification, use (<<%=)/(<%=).

There are a few specialised versions of (%=) which mimic C operators:

  • (+=) for addition
  • (-=) for substraction
  • (*=) for multiplication
  • (//=) for division

modifying :: MonadState s m => ASetter s s a b -> (a -> b) -> m () Source #

A synonym for (%=).

(.=) :: MonadState s m => ASetter s s a b -> b -> m () infix 4 Source #

Modify state by “assigning” a value to a part of the state.

This is merely (.~) which works in MonadState:

l .= x = modify (l .~ x)

If you also want to know the value that was replaced by (.=), use (<<.=).

assign :: MonadState s m => ASetter s s a b -> b -> m () Source #

A synonym for (.=).

(?=) :: MonadState s m => ASetter s s a (Maybe b) -> b -> m () infix 4 Source #

(?=) is a version of (.=) that wraps the value into Just before setting.

l ?= b = l .= Just b

It can be useful in combination with at.

(<~) :: MonadState s m => ASetter s s a b -> m b -> m () infixr 2 Source #

(<~) is a version of (.=) that takes a monadic value (and then executes it and assigns the result to the lens).

l <~ mb = do
  b <- mb
  l .= b

Convenience

(&~) :: s -> State s a -> s infixl 1 Source #

This can be used to chain lens operations using op= syntax rather than op~ syntax for simple non-type-changing cases. >>> (10,20) & _1 .~ 30 & _2 .~ 40 (30,40)

>>> (10,20) &~ do _1 .= 30; _2 .= 40
(30,40)

This does not support type-changing assignment, e.g.

>>> (10,20) & _1 .~ "hello"
("hello",20)

Specialised modifying operators

The following operators mimic well-known C operators (+=, -=, etc). (//=) stands for division.

They're implemented like this:

l += x = l %= (+x)
l -= x = l %= (subtract x)
...

(+=) :: (MonadState s m, Num a) => ASetter s s a a -> a -> m () infix 4 Source #

(-=) :: (MonadState s m, Num a) => ASetter s s a a -> a -> m () infix 4 Source #

(*=) :: (MonadState s m, Num a) => ASetter s s a a -> a -> m () infix 4 Source #

(//=) :: (MonadState s m, Fractional a) => ASetter s s a a -> a -> m () infix 4 Source #

Setting with passthrough

(<%=) :: MonadState s m => LensLike ((,) b) s s a b -> (a -> b) -> m b infix 4 Source #

Modify state and return the modified (new) value.

l <%= f = do
  l %= f
  use l

(<.=) :: MonadState s m => LensLike ((,) b) s s a b -> b -> m b infix 4 Source #

Set state and return new value.

l <.= b = do
  l .= b
  return b

(<?=) :: MonadState s m => LensLike ((,) b) s s a (Maybe b) -> b -> m b infix 4 Source #

(<?=) is a version of (<.=) that wraps the value into Just before setting.

l <?= b = do
  l .= Just b
  return b

It can be useful in combination with at.

(<<%=) :: MonadState s m => LensLike ((,) a) s s a b -> (a -> b) -> m a infix 4 Source #

Modify state and return the old value (i.e. as it was before the modificaton).

l <<%= f = do
  old <- use l
  l %= f
  return old

(<<.=) :: MonadState s m => LensLike ((,) a) s s a b -> b -> m a infix 4 Source #

Set state and return the old value.

l <<.= b = do
  old <- use l
  l .= b
  return old

Zooming

zoom :: Zoom m n s t => 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 = do
  zoom (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 = do
  zoom (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 newtyped transformers in your monad stack. This can be done as follows:

import Lens.Micro.Mtl.Internal

type instance Zoomed (MyStateT s m) = Zoomed (StateT s m)

instance Monad m => Zoom (MyStateT s m) (MyStateT t m) s t where
    zoom l (MyStateT m) = MyStateT (zoom l m)

magnify :: Magnify m n b a => 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 a
magnify :: 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 instance Magnified (MyReaderT r m) = Magnified (ReaderT r m)

instance Monad m => Magnify (MyReaderT r m) (MyReaderT t m) r t where
    magnify l (MyReaderT m) = MyReaderT (magnify l m)