distributors-0.1.0.2: Unifying Parsers, Printers & Grammars
Copyright(C) 2025 - Eitan Chatav
LicenseBSD-style (see the file LICENSE)
MaintainerEitan Chatav <eitan.chatav@gmail.com>
Stabilityprovisional
Portabilitynon-portable
Safe HaskellSafe-Inferred
LanguageHaskell2010

Control.Lens.Grate

Description

Synopsis

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 #

Grates are an optic that are dual to Traversals, as Distributive is Traversable.

Every Monocle is a Grate.

Grates are isomorphic to Gratings.

type AGrate s t a b = Grating a b a (Identity b) -> Grating a b s (Identity t) Source #

If you see AGrate in a signature for a function, the function is expecting a Grate.

Combinators

grate :: (((s -> a) -> b) -> t) -> Grate s t a b Source #

Build a Grate.

withGrate :: AGrate s t a b -> ((s -> a) -> b) -> t Source #

Run AGrate.

cloneGrate :: AGrate s t a b -> Grate s t a b Source #

Clone AGrate so that you can reuse the same monomorphically typed Grate for different purposes.

mapGrate :: Closed p => AGrate s t a b -> p a b -> p s t Source #

Action of AGrate on Closed Profunctors.

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.

collectOf :: Functor f => AGrate s t b (f b) -> (a -> s) -> f a -> t Source #

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 #

Grating provides an efficient concrete representation of Grates.

Constructors

Grating 

Fields

Instances

Instances details
Tokenized a b (Grating a b) Source # 
Instance details

Defined in Control.Lens.Grate

Methods

anyToken :: Grating a b a b Source #

Representable (Grating a b s) Source # 
Instance details

Defined in Control.Lens.Grate

Associated Types

type Rep (Grating a b s) #

Methods

tabulate :: (Rep (Grating a b s) -> a0) -> Grating a b s a0 #

index :: Grating a b s a0 -> Rep (Grating a b s) -> a0 #

Applicative (Grating a b s) Source # 
Instance details

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 # 
Instance details

Defined in Control.Lens.Grate

Methods

fmap :: (a0 -> b0) -> Grating a b s a0 -> Grating a b s b0 #

(<$) :: a0 -> Grating a b s b0 -> Grating a b s a0 #

Distributive (Grating a b s) Source # 
Instance details

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 # 
Instance details

Defined in Control.Lens.Grate

type Rep (Grating a b s) = (s -> a) -> b