Copyright | (C) 2025 - Eitan Chatav |
---|---|
License | BSD-style (see the file LICENSE) |
Maintainer | Eitan Chatav <eitan.chatav@gmail.com> |
Stability | provisional |
Portability | non-portable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Control.Lens.Grate
Contents
Description
See O'Connor, Grate: A new kind of Optic
Synopsis
- type Grate s t a b = forall p f. (Closed p, Monoidal p, Distributive f, Applicative f) => p a (f b) -> p s (f t)
- type AGrate s t a b = Grating a b a (Identity b) -> Grating a b s (Identity t)
- grate :: (((s -> a) -> b) -> t) -> Grate s t a b
- withGrate :: AGrate s t a b -> ((s -> a) -> b) -> t
- cloneGrate :: AGrate s t a b -> Grate s t a b
- mapGrate :: Closed p => AGrate s t a b -> p a b -> p s t
- cotraversed :: Distributive g => Grate (g a) (g b) a b
- represented :: Representable g => Grate (g a) (g b) a b
- cotraverseOf :: Functor f => AGrate s t a b -> (f a -> b) -> f s -> t
- distributeOf :: Functor f => AGrate s t b (f b) -> f s -> t
- collectOf :: Functor f => AGrate s t b (f b) -> (a -> s) -> f a -> t
- distributing :: (Closed p, forall x. Functor (p x), Distributive g) => AGrate s t a b -> p a (g b) -> g (p s t)
- newtype Grating a b s t = Grating {
- runGrating :: ((s -> a) -> b) -> t
Grate
type Grate s t a b = forall p f. (Closed p, Monoidal p, Distributive f, Applicative f) => p a (f b) -> p s (f t) Source #
Grate
s are an optic that are dual to
Traversal
s, as Distributive
is Traversable
.
Combinators
cloneGrate :: AGrate s t a b -> Grate s t a b Source #
mapGrate :: Closed p => AGrate s t a b -> p a b -> p s t Source #
Action of AGrate
on Closed
Profunctor
s.
cotraversed :: Distributive g => Grate (g a) (g b) a b Source #
Build a Grate
from a Distributive
.
represented :: Representable g => Grate (g a) (g b) a b Source #
Build a Grate
from a Representable
.
cotraverseOf :: Functor f => AGrate s t a b -> (f a -> b) -> f s -> t Source #
Dual to traverseOf
.
distributeOf :: Functor f => AGrate s t b (f b) -> f s -> t Source #
Dual to sequenceAOf
.
distributing :: (Closed p, forall x. Functor (p x), Distributive g) => AGrate s t a b -> p a (g b) -> g (p s t) Source #
Distribute over a Closed
Profunctor
.
Grating
newtype Grating a b s t Source #
Constructors
Grating | |
Fields
|
Instances
Tokenized a b (Grating a b) Source # | |
Defined in Control.Lens.Grate | |
Representable (Grating a b s) Source # | |
Applicative (Grating a b s) Source # | |
Defined in Control.Lens.Grate Methods pure :: a0 -> Grating a b s a0 # (<*>) :: Grating a b s (a0 -> b0) -> Grating a b s a0 -> Grating a b s b0 # liftA2 :: (a0 -> b0 -> c) -> Grating a b s a0 -> Grating a b s b0 -> Grating a b s c # (*>) :: Grating a b s a0 -> Grating a b s b0 -> Grating a b s b0 # (<*) :: Grating a b s a0 -> Grating a b s b0 -> Grating a b s a0 # | |
Functor (Grating a b s) Source # | |
Distributive (Grating a b s) Source # | |
Defined in Control.Lens.Grate Methods distribute :: Functor f => f (Grating a b s a0) -> Grating a b s (f a0) # collect :: Functor f => (a0 -> Grating a b s b0) -> f a0 -> Grating a b s (f b0) # distributeM :: Monad m => m (Grating a b s a0) -> Grating a b s (m a0) # collectM :: Monad m => (a0 -> Grating a b s b0) -> m a0 -> Grating a b s (m b0) # | |
type Rep (Grating a b s) Source # | |
Defined in Control.Lens.Grate |