| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Data.Ten.Lens
Description
Provides lenses and related functionality for the "ten" package.
Synopsis
- rep10 :: Representable10 f => Getting (Rep10 f a) (f (Rep10 f)) (Rep10 f a) -> Rep10 f a
- field10 :: Representable10 rec => Getting (Ap10 a (Rep10 rec)) (rec (Rep10 rec)) (Ap10 a (Rep10 rec)) -> Rep10 rec a
- ixRep10 :: forall k f g (a :: k) m. (Update10 f, Functor g) => Rep10 f a -> (m a -> g (m a)) -> f m -> g (f m)
- ap10 :: Iso (Ap10 s fs) (Ap10 t ft) (fs s) (ft t)
- comp :: Iso ((m :.: n) a) ((k :.: l) b) (m (n a)) (k (l b))
- _Field10 :: GEq k => k a -> Prism' (k :** m) (m a)
- _Field10' :: forall rec a m. (GEq (Rep10 rec), Representable10 rec) => (forall n. Getting (Ap10 a n) (rec n) (Ap10 a n)) -> Prism' (Rep10 rec :** m) (m a)
- (!=) :: Representable10 rec => (forall m. Getting (Ap10 a m) (rec m) (Ap10 a m)) -> f a -> Rep10 rec :** f
- (!=?) :: (Representable10 rec, Applicative f) => (forall m. Getting (Ap10 a m) (rec m) (Ap10 a m)) -> a -> Rep10 rec :** f
- fragmented :: (Functor m, Representable10 recA, Representable10 recB, f ~ OpCostar m (Rep10 recB :** m)) => ASetter (recB f) (recA f) (f b) (f a) -> Setter (Rep10 recA :** m) (Rep10 recB :** m) a b
Documentation
field10 :: Representable10 rec => Getting (Ap10 a (Rep10 rec)) (rec (Rep10 rec)) (Ap10 a (Rep10 rec)) -> Rep10 rec a Source #
Convert a lens targeting Ap10 to a Rep10.
ixRep10 :: forall k f g (a :: k) m. (Update10 f, Functor g) => Rep10 f a -> (m a -> g (m a)) -> f m -> g (f m) #
ap10 :: Iso (Ap10 s fs) (Ap10 t ft) (fs s) (ft t) Source #
An Iso between an Ap10 a m wrapper and its contained m a.
comp :: Iso ((m :.: n) a) ((k :.: l) b) (m (n a)) (k (l b)) Source #
An Iso between a (m :.: n) a wrapper and its contained m (n a).
_Field10' :: forall rec a m. (GEq (Rep10 rec), Representable10 rec) => (forall n. Getting (Ap10 a n) (rec n) (Ap10 a n)) -> Prism' (Rep10 rec :** m) (m a) Source #
(!=) :: Representable10 rec => (forall m. Getting (Ap10 a m) (rec m) (Ap10 a m)) -> f a -> Rep10 rec :** f infixr 5 Source #
Shortcut to construct a (:**) from a Getter.
Note that this assumes the fields are ultimately wrapped in Ap10.  If a
 particular field doesn't have Ap10 (which can only arise from a
 manually-written Representable10 instance), just pretend it does by adding
 from ap10 to the lens.
(!=?) :: (Representable10 rec, Applicative f) => (forall m. Getting (Ap10 a m) (rec m) (Ap10 a m)) -> a -> Rep10 rec :** f infixr 5 Source #
fragmented :: (Functor m, Representable10 recA, Representable10 recB, f ~ OpCostar m (Rep10 recB :** m)) => ASetter (recB f) (recA f) (f b) (f a) -> Setter (Rep10 recA :** m) (Rep10 recB :** m) a b Source #
Lifts a Setter to work underneath (:**).
This means if you know how to change the type of a whole record, you can use
 this to change the type of a (:**).
Example usage:
data MyRecord a m = MyRecord { _mrA :: Ap10 a m, _mrInt :: Ap10 Int m } mrA :: Lens' (MyRecord a m) (MyRecord b m) (Ap10 m a) (Ap10 m b)
example :: Rep10 (MyRecord Int) :** Identity -> Rep10 (MyRecord String) :** Identity example = fragmented (mrA.ap10) %~ show