Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- type Lens s t a b = forall (f :: * -> *). Functor f => (a -> f b) -> s -> f t
- type Lens' s a = Lens s s a a
- lens :: (s -> a) -> (s -> b -> t) -> Lens s t a b
- class HasAny (sel :: k) s t a b | s sel k -> a where
- class Subtype sup sub where
- class Ixed m => At m where
- sans :: At m => Index m -> m -> m
- type family Index s :: *
- type family IxValue m :: *
- class Contains m where
Lens
type Lens s t a b = forall (f :: * -> *). Functor f => (a -> f b) -> s -> f t #
A Lens
is actually a lens family as described in
http://comonad.com/reader/2012/mirrored-lenses/.
With great power comes great responsibility and a Lens
is subject to the
three common sense Lens
laws:
1) You get back what you put in:
view
l (set
l v s) ≡ v
2) Putting back what you got doesn't change anything:
set
l (view
l s) s ≡ s
3) Setting twice is the same as setting once:
set
l v' (set
l v s) ≡set
l v' s
These laws are strong enough that the 4 type parameters of a Lens
cannot
vary fully independently. For more on how they interact, read the "Why is
it a Lens Family?" section of
http://comonad.com/reader/2012/mirrored-lenses/.
There are some emergent properties of these laws:
1)
must be injective for every set
l ss
This is a consequence of law #1
2)
must be surjective, because of law #2, which indicates that it is possible to obtain any set
lv
from some s
such that set
s v = s
3) Given just the first two laws you can prove a weaker form of law #3 where the values v
that you are setting match:
set
l v (set
l v s) ≡set
l v s
Every Lens
can be used directly as a Setter
or Traversal
.
You can also use a Lens
for Getting
as if it were a
Fold
or Getter
.
Since every Lens
is a valid Traversal
, the
Traversal
laws are required of any Lens
you create:
lpure
≡pure
fmap
(l f).
l g ≡getCompose
.
l (Compose
.
fmap
f.
g)
typeLens
s t a b = forall f.Functor
f =>LensLike
f s t a b
HasAny
class HasAny (sel :: k) s t a b | s sel k -> a where #
A lens that focuses on a part of a product as identified by some
selector. Currently supported selectors are field names, positions and
unique types. Compatible with the lens package's Lens
type.
>>>
human ^. the @Int
50
>>>
human ^. the @"name"
"Tunyasz"
>>>
human ^. the @3
"London"
Instances
HasPosition i s t a b => HasAny (i :: Nat) s t a b | |
Defined in Data.Generics.Product.Any | |
HasField field s t a b => HasAny (field :: Symbol) s t a b | |
Defined in Data.Generics.Product.Any | |
(HasType a s, t ~ s, a ~ b) => HasAny (a :: *) s t a b | |
Defined in Data.Generics.Product.Any |
Subtype
Structural subtype relationship
sub
is a (structural) subtype
of sup
, if its fields are a subset of
those of sup
.
super :: Lens sub sub sup sup #
Structural subtype lens. Given a subtype relationship sub :< sup
,
we can focus on the sub
structure of sup
.
>>>
human ^. super @Animal
Animal {name = "Tunyasz", age = 50}
>>>
set (super @Animal) (Animal "dog" 10) human
Human {name = "dog", age = 10, address = "London"}
Cast the more specific subtype to the more general supertype
>>>
upcast human :: Animal
Animal {name = "Tunyasz", age = 50}
>>>
upcast (upcast human :: Animal) :: Human
... ... The type 'Animal' is not a subtype of 'Human'. ... The following fields are missing from 'Animal': ... address ...
Plug a smaller structure into a larger one
>>>
smash (Animal "dog" 10) human
Human {name = "dog", age = 10, address = "London"}
At
At
provides a Lens
that can be used to read,
write or delete the value associated with a key in a Map
-like
container on an ad hoc basis.
An instance of At
should satisfy:
ix
k ≡at
k.
traverse
Instances
At IntSet | |
At (Maybe a) | |
At (IntMap a) | |
Ord k => At (Set k) | |
(Eq k, Hashable k) => At (HashSet k) | |
(Eq k, Hashable k) => At (HashMap k a) | |
Ord k => At (Map k a) | |
(Eq k, Hashable k) => At (InsOrdHashMap k a) | |
Defined in Data.HashMap.Strict.InsOrd at :: Index (InsOrdHashMap k a) -> Lens' (InsOrdHashMap k a) (Maybe (IxValue (InsOrdHashMap k a))) # |
Instances
type Index ByteString | |
Defined in Control.Lens.At | |
type Index ByteString | |
Defined in Control.Lens.At | |
type Index Text | |
Defined in Control.Lens.At | |
type Index Value | |
Defined in Data.Aeson.Lens | |
type Index Text | |
Defined in Control.Lens.At | |
type Index IntSet | |
Defined in Control.Lens.At | |
type Index [a] | |
Defined in Control.Lens.At | |
type Index (Maybe a) | |
Defined in Control.Lens.At | |
type Index (Complex a) | |
Defined in Control.Lens.At | |
type Index (Identity a) | |
Defined in Control.Lens.At | |
type Index (NonEmpty a) | |
Defined in Control.Lens.At | |
type Index (IntMap a) | |
Defined in Control.Lens.At | |
type Index (Tree a) | |
Defined in Control.Lens.At | |
type Index (Seq a) | |
Defined in Control.Lens.At | |
type Index (Set a) | |
Defined in Control.Lens.At | |
type Index (Vector a) | |
Defined in Control.Lens.At | |
type Index (Vector a) | |
Defined in Control.Lens.At | |
type Index (Vector a) | |
Defined in Control.Lens.At | |
type Index (HashSet a) | |
Defined in Control.Lens.At | |
type Index (Vector a) | |
Defined in Control.Lens.At | |
type Index (e -> a) | |
Defined in Control.Lens.At type Index (e -> a) = e | |
type Index (a, b) | |
Defined in Control.Lens.At | |
type Index (HashMap k a) | |
Defined in Control.Lens.At | |
type Index (Map k a) | |
Defined in Control.Lens.At | |
type Index (UArray i e) | |
Defined in Control.Lens.At | |
type Index (Array i e) | |
Defined in Control.Lens.At | |
type Index (InsOrdHashMap k v) | |
Defined in Data.HashMap.Strict.InsOrd | |
type Index (a, b, c) | |
Defined in Control.Lens.At | |
type Index (a, b, c, d) | |
Defined in Control.Lens.At | |
type Index (a, b, c, d, e) | |
Defined in Control.Lens.At | |
type Index (a, b, c, d, e, f) | |
Defined in Control.Lens.At | |
type Index (a, b, c, d, e, f, g) | |
Defined in Control.Lens.At | |
type Index (a, b, c, d, e, f, g, h) | |
Defined in Control.Lens.At | |
type Index (a, b, c, d, e, f, g, h, i) | |
Defined in Control.Lens.At |
Instances
type IxValue ByteString | |
Defined in Control.Lens.At | |
type IxValue ByteString | |
Defined in Control.Lens.At | |
type IxValue Text | |
Defined in Control.Lens.At | |
type IxValue Value | |
Defined in Data.Aeson.Lens | |
type IxValue Text | |
Defined in Control.Lens.At | |
type IxValue IntSet | |
Defined in Control.Lens.At | |
type IxValue [a] | |
Defined in Control.Lens.At type IxValue [a] = a | |
type IxValue (Maybe a) | |
Defined in Control.Lens.At | |
type IxValue (Identity a) | |
Defined in Control.Lens.At | |
type IxValue (NonEmpty a) | |
Defined in Control.Lens.At | |
type IxValue (IntMap a) | |
Defined in Control.Lens.At | |
type IxValue (Tree a) | |
Defined in Control.Lens.At | |
type IxValue (Seq a) | |
Defined in Control.Lens.At | |
type IxValue (Set k) | |
Defined in Control.Lens.At | |
type IxValue (Vector a) | |
Defined in Control.Lens.At | |
type IxValue (Vector a) | |
Defined in Control.Lens.At | |
type IxValue (Vector a) | |
Defined in Control.Lens.At | |
type IxValue (HashSet k) | |
Defined in Control.Lens.At | |
type IxValue (Vector a) | |
Defined in Control.Lens.At | |
type IxValue (e -> a) | |
Defined in Control.Lens.At type IxValue (e -> a) = a | |
type IxValue (a, a2) | |
Defined in Control.Lens.At type IxValue (a, a2) = a | |
type IxValue (HashMap k a) | |
Defined in Control.Lens.At | |
type IxValue (Map k a) | |
Defined in Control.Lens.At | |
type IxValue (UArray i e) | |
Defined in Control.Lens.At | |
type IxValue (Array i e) | |
Defined in Control.Lens.At | |
type IxValue (InsOrdHashMap k v) | |
Defined in Data.HashMap.Strict.InsOrd | |
type IxValue (a, a2, a3) | |
Defined in Control.Lens.At type IxValue (a, a2, a3) = a | |
type IxValue (a, a2, a3, a4) | |
Defined in Control.Lens.At type IxValue (a, a2, a3, a4) = a | |
type IxValue (a, a2, a3, a4, a5) | |
Defined in Control.Lens.At type IxValue (a, a2, a3, a4, a5) = a | |
type IxValue (a, a2, a3, a4, a5, a6) | |
Defined in Control.Lens.At type IxValue (a, a2, a3, a4, a5, a6) = a | |
type IxValue (a, a2, a3, a4, a5, a6, a7) | |
Defined in Control.Lens.At type IxValue (a, a2, a3, a4, a5, a6, a7) = a | |
type IxValue (a, a2, a3, a4, a5, a6, a7, a8) | |
Defined in Control.Lens.At type IxValue (a, a2, a3, a4, a5, a6, a7, a8) = a | |
type IxValue (a, a2, a3, a4, a5, a6, a7, a8, a9) | |
Defined in Control.Lens.At type IxValue (a, a2, a3, a4, a5, a6, a7, a8, a9) = a |
Contains
This class provides a simple Lens
that lets you view (and modify)
information about whether or not a container contains a given Index
.
contains :: Index m -> Lens' m Bool #
>>>
IntSet.fromList [1,2,3,4] ^. contains 3
True
>>>
IntSet.fromList [1,2,3,4] ^. contains 5
False
>>>
IntSet.fromList [1,2,3,4] & contains 3 .~ False
fromList [1,2,4]