| Copyright | (C) 2013-2016 Edward Kmett 2015-2016 Artyom | 
|---|---|
| License | BSD-style (see the file LICENSE) | 
| Safe Haskell | Unsafe | 
| Language | Haskell2010 | 
Lens.Micro.Internal
Contents
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:
- traversedis here because otherwise there'd be a dependency cycle
- setsis here because it's used in RULEs
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.
- traversed :: Traversable f => Traversal (f a) (f b) a b
- folded :: Foldable f => SimpleFold (f a) a
- foldring :: Monoid r => ((a -> Const r a -> Const r a) -> Const r a -> s -> Const r a) -> (a -> Const r b) -> s -> Const r t
- foldrOf :: Getting (Endo r) s a -> (a -> r -> r) -> r -> s -> r
- foldMapOf :: Getting r s a -> (a -> r) -> s -> r
- sets :: ((a -> b) -> s -> t) -> ASetter s t a b
- (#.) :: Coercible c b => (b -> c) -> (a -> b) -> a -> c
- (.#) :: Coercible b a => (b -> c) -> (a -> b) -> a -> c
- phantom :: Const r a -> Const r b
- class Each s t a b | s -> a, t -> b, s b -> t, t a -> s where
- type family Index (s :: *) :: *
- type family IxValue (m :: *) :: *
- class Ixed m where
- class Ixed m => At m where
- ixAt :: At m => Index m -> Traversal' m (IxValue m)
- class Field1 s t a b | s -> a, t -> b, s b -> t, t a -> s where
- class Field2 s t a b | s -> a, t -> b, s b -> t, t a -> s where
- class Field3 s t a b | s -> a, t -> b, s b -> t, t a -> s where
- class Field4 s t a b | s -> a, t -> b, s b -> t, t a -> s where
- class Field5 s t a b | s -> a, t -> b, s b -> t, t a -> s where
- class Cons s t a b | s -> a, t -> b, s b -> t, t a -> s where
- class Snoc s t a b | s -> a, t -> b, s b -> t, t a -> s where
- class Strict lazy strict | lazy -> strict, strict -> lazy where
- type HasCallStack = ?callStack :: CallStack
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 => SimpleFold (f a) a Source #
foldring :: Monoid r => ((a -> Const r a -> Const r a) -> Const r a -> s -> Const r a) -> (a -> Const r b) -> s -> Const r t Source #
class Each s t a b | s -> a, t -> b, s b -> t, t a -> s where Source #
Minimal complete definition
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 beach::Traversal(Maybea) (Maybeb) a beach::Traversal(a,a) (b,b) a beach::Traversal(a,a,a) (b,b,b) a beach::Traversal(a,a,a,a) (b,b,b,b) a beach::Traversal(a,a,a,a,a) (b,b,b,b,b) a beach:: (RealFloata,RealFloatb) =>Traversal(Complexa) (Complexb) a b
You can also use each with types from array, bytestring, and containers by using microlens-ghc, or additionally with types from vector, text, and unordered-containers by using microlens-platform.
Instances
| Each [a] [b] a b Source # | |
| Each (Maybe a) (Maybe b) a b Source # | |
| Each (NonEmpty a) (NonEmpty b) a b Source # | |
| Each (Complex a) (Complex b) a b Source # | |
| ((~) * a b, (~) * q r) => Each (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 # | |
| ((~) * a b, (~) * a c, (~) * a d, (~) * q r, (~) * q s, (~) * q t) => Each (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 # | |
Minimal complete definition
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 3Just 3
Of course, the element may not be present (which means that you can use ix as a safe variant of (!!)):
>>>[0..5] ^? ix 10Nothing
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] aix:: (Eqe) => e ->Traversal'(e -> a) a
You can also use ix with types from array, bytestring, and containers by using microlens-ghc, or additionally with types from vector, text, and unordered-containers by using microlens-platform.
class Ixed m => At m where Source #
Minimal complete definition
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 valueNothing:
Data.Map.insert k a m = m&at k.~Just a Data.Map.delete k m = m&at k.~Nothing
Or you could use (?~) instead of (.~):
Data.Map.insert k a m = m&at k?~a
Note that at doesn't work for arrays or lists. You can't delete an arbitrary element from an array (what would be left in its place?), and you can't set an arbitrary element in a list because if the index is out of list's bounds, you'd have to somehow fill the stretch between the last element and the element you just inserted (i.e. [1,2,3] & at 10 .~ 5 is undefined). If you want to modify an already existing value in an array or list, you should use ix instead.
at is often used with non. See the documentation of non for examples.
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
Gives access to the 1st field of a tuple (up to 5-tuples).
Getting the 1st component:
>>>(1,2,3,4,5) ^. _11
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:
_1f t = (,)<$>f (fstt)<*>pure(sndt)
or, alternatively,
_1f ~(a,b) = (\a' -> (a',b))<$>f a
(where ~ means a lazy pattern).
class Strict lazy strict | lazy -> strict, strict -> lazy where Source #
Methods
strict :: Lens' lazy strict Source #
strict lets you convert between strict and lazy versions of a datatype:
>>>let someText = "hello" :: Lazy.Text>>>someText ^. strict"hello" :: Strict.Text
It can also be useful if you have a function that works on a strict type but your type is lazy:
stripDiacritics :: Strict.Text -> Strict.Text stripDiacritics = ...
>>>let someText = "Paul Erdős" :: Lazy.Text>>>someText & strict %~ stripDiacritics"Paul Erdos" :: Lazy.Text
strict works on ByteString and StateT/WriterT/RWST if you use microlens-ghc, and additionally on Text if you use microlens-platform.
CallStack
type HasCallStack = ?callStack :: CallStack #
Request a CallStack.
NOTE: The implicit parameter ?callStack :: CallStack is an
 implementation detail and should not be considered part of the
 CallStack API, we may decide to change the implementation in the
 future.
Since: 4.9.0.0