microlens-0.3.5.1: A tiny part of the lens library with no dependencies

Safe HaskellUnsafe
LanguageHaskell2010

Lens.Micro.Internal

Description

This module is needed to give other packages from the microlens family (like microlens-ghc) access to functions and classes that don't need to be exported from Lens.Micro (because they just clutter the namespace). Also, okay, uh, e.g. traversed is here because otherwise there'd be a dependency cycle.

Classes like Each, Ixed, etc are provided for convenience – you're not supposed to export functions that work on all members of Ixed, for instance. Only microlens can do that. You mustn't declare instances of those classes for other types, either; these classes are incompatible with lens's classes, and by doing so you would divide the ecosystem.

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

Documentation

traversed :: Traversable f => Traversal (f a) (f b) a b Source #

traversed traverses any Traversable container (list, vector, Map, Maybe, you name it):

>>> Just 1 ^.. traversed
[1]

traversed is the same as traverse, but can be faster thanks to magic rewrite rules.

folded :: (Foldable f, Applicative (Const r)) => Getting r (f a) a Source #

folded is a fold for anything Foldable. In a way, it's an opposite of mapped – the most powerful getter, but can't be used as a setter.

foldring :: Applicative (Const r) => ((a -> Const r a -> Const r a) -> Const r a -> s -> Const r a) -> (a -> Const r b) -> s -> Const r t Source #

foldrOf :: Getting (Endo r) s a -> (a -> r -> r) -> r -> s -> r Source #

foldMapOf :: Getting r s a -> (a -> r) -> s -> r Source #

sets :: ((a -> b) -> s -> t) -> ASetter s t a b Source #

sets creates an ASetter from an ordinary function. (The only thing it does is wrapping and unwrapping Identity.)

(#.) :: Coercible c b => (b -> c) -> (a -> b) -> a -> c Source #

(.#) :: Coercible b a => (b -> c) -> (a -> b) -> a -> c Source #

phantom :: Const r a -> Const r b Source #

class Each s t a b | s -> a, t -> b, s b -> t, t a -> s where Source #

Methods

each :: Traversal s t a b Source #

each tries to be a universal Traversal – it behaves like traversed in most situations, but also adds support for e.g. tuples with same-typed values:

>>> (1,2) & each %~ succ
(2,3)
>>> ["x", "y", "z"] ^. each
"xyz"

However, note that each doesn't work on every instance of Traversable. If you have a Traversable which isn't supported by each, you can use traversed instead. Personally, I like using each instead of traversed whenever possible – it's shorter and more descriptive.

You can use each with these things:

each :: Traversal [a] [b] a b

each :: Traversal (Maybe a) (Maybe b) a b

each :: Traversal (a,a) (b,b) a b
each :: Traversal (a,a,a) (b,b,b) a b
each :: Traversal (a,a,a,a) (b,b,b,b) a b
each :: Traversal (a,a,a,a,a) (b,b,b,b,b) a b

each :: (RealFloat a, RealFloat b) => Traversal (Complex a) (Complex b) a b

Additionally, you can use each with types from array, bytestring, and containers by using Lens.Micro.GHC from microlens-ghc, or with types from vector, text, and unordered-containers by using Lens.Micro.Platform from microlens-platform.

each :: (Traversable g, s ~ g a, t ~ g b) => Traversal s t a b Source #

each tries to be a universal Traversal – it behaves like traversed in most situations, but also adds support for e.g. tuples with same-typed values:

>>> (1,2) & each %~ succ
(2,3)
>>> ["x", "y", "z"] ^. each
"xyz"

However, note that each doesn't work on every instance of Traversable. If you have a Traversable which isn't supported by each, you can use traversed instead. Personally, I like using each instead of traversed whenever possible – it's shorter and more descriptive.

You can use each with these things:

each :: Traversal [a] [b] a b

each :: Traversal (Maybe a) (Maybe b) a b

each :: Traversal (a,a) (b,b) a b
each :: Traversal (a,a,a) (b,b,b) a b
each :: Traversal (a,a,a,a) (b,b,b,b) a b
each :: Traversal (a,a,a,a,a) (b,b,b,b,b) a b

each :: (RealFloat a, RealFloat b) => Traversal (Complex a) (Complex b) a b

Additionally, you can use each with types from array, bytestring, and containers by using Lens.Micro.GHC from microlens-ghc, or with types from vector, text, and unordered-containers by using Lens.Micro.Platform from microlens-platform.

Instances

Each [a] [b] a b Source # 

Methods

each :: Traversal [a] [b] a b Source #

Each (Maybe a) (Maybe b) a b Source # 

Methods

each :: Traversal (Maybe a) (Maybe b) a b Source #

Each (Complex a) (Complex b) a b Source # 

Methods

each :: Traversal (Complex a) (Complex b) a b Source #

((~) * a b, (~) * q r) => Each (a, b) (q, r) a q Source # 

Methods

each :: Traversal (a, b) (q, r) a q Source #

((~) * a b, (~) * a c, (~) * q r, (~) * q s) => Each (a, b, c) (q, r, s) a q Source # 

Methods

each :: Traversal (a, b, c) (q, r, s) a q Source #

((~) * a b, (~) * a c, (~) * a d, (~) * q r, (~) * q s, (~) * q t) => Each (a, b, c, d) (q, r, s, t) a q Source # 

Methods

each :: Traversal (a, b, c, d) (q, r, s, t) a q Source #

((~) * a b, (~) * a c, (~) * a d, (~) * a e, (~) * q r, (~) * q s, (~) * q t, (~) * q u) => Each (a, b, c, d, e) (q, r, s, t, u) a q Source # 

Methods

each :: Traversal (a, b, c, d, e) (q, r, s, t, u) a q Source #

type family Index (s :: *) :: * Source #

Instances

type Index [a] Source # 
type Index [a] = Int
type Index (e -> a) Source # 
type Index (e -> a) = e

type family IxValue (m :: *) :: * Source #

Instances

type IxValue [a] Source # 
type IxValue [a] = a
type IxValue (e -> a) Source # 
type IxValue (e -> a) = a

class Ixed m where Source #

Methods

ix :: Index m -> Traversal' m (IxValue m) Source #

This traversal lets you access (and update) an arbitrary element in a list, array, Map, etc. (If you want to insert or delete elements as well, look at at.)

An example for lists:

>>> [0..5] & ix 3 .~ 10
[0,1,2,10,4,5]

You can use it for getting, too:

>>> [0..5] ^? ix 3
Just 3

Of course, the element may not be present (which means that you can use ix as a safe variant of (!!)):

>>> [0..5] ^? ix 10
Nothing

Another useful instance is the one for functions – it lets you modify their outputs for specific inputs. For instance, here's maximum that returns 0 when the list is empty (instead of throwing an exception):

maximum0 = maximum & ix [] .~ 0

The following instances are provided in this package:

ix :: Int -> Traversal' [a] a

ix :: (Eq e) => e -> Traversal' (e -> a) a

Additionally, you can use ix with types from array, bytestring, and containers by using Lens.Micro.GHC from microlens-ghc, or with types from vector, text, and unordered-containers by using Lens.Micro.Platform from microlens-platform.

ix :: At m => Index m -> Traversal' m (IxValue m) Source #

This traversal lets you access (and update) an arbitrary element in a list, array, Map, etc. (If you want to insert or delete elements as well, look at at.)

An example for lists:

>>> [0..5] & ix 3 .~ 10
[0,1,2,10,4,5]

You can use it for getting, too:

>>> [0..5] ^? ix 3
Just 3

Of course, the element may not be present (which means that you can use ix as a safe variant of (!!)):

>>> [0..5] ^? ix 10
Nothing

Another useful instance is the one for functions – it lets you modify their outputs for specific inputs. For instance, here's maximum that returns 0 when the list is empty (instead of throwing an exception):

maximum0 = maximum & ix [] .~ 0

The following instances are provided in this package:

ix :: Int -> Traversal' [a] a

ix :: (Eq e) => e -> Traversal' (e -> a) a

Additionally, you can use ix with types from array, bytestring, and containers by using Lens.Micro.GHC from microlens-ghc, or with types from vector, text, and unordered-containers by using Lens.Micro.Platform from microlens-platform.

Instances

Ixed [a] Source # 

Methods

ix :: Index [a] -> Traversal' [a] (IxValue [a]) Source #

Eq e => Ixed (e -> a) Source # 

Methods

ix :: Index (e -> a) -> Traversal' (e -> a) (IxValue (e -> a)) Source #

class Ixed m => At m where Source #

Minimal complete definition

at

Methods

at :: Index m -> Lens' m (Maybe (IxValue m)) Source #

This lens lets you read, write, or delete elements in Map-like structures. It returns Nothing when the value isn't found, just like lookup:

Data.Map.lookup k m = m ^. at k

However, it also lets you insert and delete values by setting the value to Just value or Nothing:

Data.Map.insert k a m = m & at k .~ Just a

Data.Map.delete k m = m & at k .~ Nothing

at doesn't work for arrays, because you can't delete an arbitrary element from an array.

If you want to modify an already existing value, you should use ix instead because then you won't have to deal with Maybe (ix is available for all types that have at).

at is often used with non.

Note that at isn't strict for Map, even if you're using Data.Map.Strict:

>>> Data.Map.Strict.size (Data.Map.Strict.empty & at 1 .~ Just undefined)
1

The reason for such behavior is that there's actually no “strict Map” type; Data.Map.Strict just provides some strict functions for ordinary Maps.

This package doesn't actually provide any instances for at, but there are instances for Map and IntMap in microlens-ghc and an instance for HashMap in microlens-platform.

class Field1 s t a b | s -> a, t -> b, s b -> t, t a -> s where Source #

Methods

_1 :: Lens s t a b Source #

Gives access to the 1st field of a tuple (up to 5-tuples).

Getting the 1st component:

>>> (1,2,3,4,5) ^. _1
1

Setting the 1st component:

>>> (1,2,3) & _1 .~ 10
(10,2,3)

Note that this lens is lazy, and can set fields even of undefined:

>>> set _1 10 undefined :: (Int, Int)
(10,*** Exception: Prelude.undefined

This is done to avoid violating a lens law stating that you can get back what you put:

>>> view _1 . set _1 10 $ (undefined :: (Int, Int))
10

The implementation (for 2-tuples) is:

_1 f t = (,) <$> f    (fst t)
             <*> pure (snd t)

or, alternatively,

_1 f ~(a,b) = (\a' -> (a',b)) <$> f a

(where ~ means a lazy pattern).

_2, _3, _4, and _5 are also available (see below).

Instances

Field1 (a, b) (a', b) a a' Source # 

Methods

_1 :: Lens (a, b) (a', b) a a' Source #

Field1 (a, b, c) (a', b, c) a a' Source # 

Methods

_1 :: Lens (a, b, c) (a', b, c) a a' Source #

Field1 (a, b, c, d) (a', b, c, d) a a' Source # 

Methods

_1 :: Lens (a, b, c, d) (a', b, c, d) a a' Source #

Field1 (a, b, c, d, e) (a', b, c, d, e) a a' Source # 

Methods

_1 :: Lens (a, b, c, d, e) (a', b, c, d, e) a a' Source #

class Field2 s t a b | s -> a, t -> b, s b -> t, t a -> s where Source #

Methods

_2 :: Lens s t a b Source #

Instances

Field2 (a, b) (a, b') b b' Source # 

Methods

_2 :: Lens (a, b) (a, b') b b' Source #

Field2 (a, b, c) (a, b', c) b b' Source # 

Methods

_2 :: Lens (a, b, c) (a, b', c) b b' Source #

Field2 (a, b, c, d) (a, b', c, d) b b' Source # 

Methods

_2 :: Lens (a, b, c, d) (a, b', c, d) b b' Source #

Field2 (a, b, c, d, e) (a, b', c, d, e) b b' Source # 

Methods

_2 :: Lens (a, b, c, d, e) (a, b', c, d, e) b b' Source #

class Field3 s t a b | s -> a, t -> b, s b -> t, t a -> s where Source #

Methods

_3 :: Lens s t a b Source #

Instances

Field3 (a, b, c) (a, b, c') c c' Source # 

Methods

_3 :: Lens (a, b, c) (a, b, c') c c' Source #

Field3 (a, b, c, d) (a, b, c', d) c c' Source # 

Methods

_3 :: Lens (a, b, c, d) (a, b, c', d) c c' Source #

Field3 (a, b, c, d, e) (a, b, c', d, e) c c' Source # 

Methods

_3 :: Lens (a, b, c, d, e) (a, b, c', d, e) c c' Source #

class Field4 s t a b | s -> a, t -> b, s b -> t, t a -> s where Source #

Methods

_4 :: Lens s t a b Source #

Instances

Field4 (a, b, c, d) (a, b, c, d') d d' Source # 

Methods

_4 :: Lens (a, b, c, d) (a, b, c, d') d d' Source #

Field4 (a, b, c, d, e) (a, b, c, d', e) d d' Source # 

Methods

_4 :: Lens (a, b, c, d, e) (a, b, c, d', e) d d' Source #

class Field5 s t a b | s -> a, t -> b, s b -> t, t a -> s where Source #

Methods

_5 :: Lens s t a b Source #

Instances

Field5 (a, b, c, d, e) (a, b, c, d, e') e e' Source # 

Methods

_5 :: Lens (a, b, c, d, e) (a, b, c, d, e') e e' Source #

class Cons s t a b | s -> a, t -> b, s b -> t, t a -> s where Source #

Methods

_Cons :: Traversal s t (a, s) (b, t) Source #

Instances

Cons [a] [b] a b Source # 

Methods

_Cons :: Traversal [a] [b] (a, [a]) (b, [b]) Source #

class Snoc s t a b | s -> a, t -> b, s b -> t, t a -> s where Source #

Methods

_Snoc :: Traversal s t (s, a) (t, b) Source #

Instances

Snoc [a] [b] a b Source # 

Methods

_Snoc :: Traversal [a] [b] ([a], a) ([b], b) Source #