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.Diopter

Description

 
Synopsis

Diopter

type Diopter s t a b = forall p f. (Distributor p, Applicative f) => p a (f b) -> p s (f t) Source #

Diopters are an optic that generalizes Bifocals and Traversals.

Every Iso and Monocle is a Diopter.

Diopters are isomorphic to Dioptrices.

type ADiopter s t a b = Dioptrice a b a (Identity b) -> Dioptrice a b s (Identity t) Source #

If you see ADiopter in a signature for a function, the function is expecting a Diopter.

Combinators

diopter :: Homogeneous h => (s -> h a) -> (h b -> t) -> Diopter s t a b Source #

Build a Diopter.

withDiopter :: ADiopter s t a b -> (forall h. Homogeneous h => (s -> h a) -> (h b -> t) -> r) -> r Source #

Convert ADiopter to the pair of functions that characterize it.

cloneDiopter :: ADiopter s t a b -> Diopter s t a b Source #

Clone ADiopter so that you can reuse the same monomorphically typed Diopter for different purposes.

mapDiopter :: Distributor p => ADiopter s t a b -> p a b -> p s t Source #

Action of ADiopter on Distributors.

optioned :: Diopter (Maybe a) (Maybe b) a b Source #

One or none.

manied :: Diopter [a] [b] a b Source #

Zero or more.

homogenized :: Homogeneous t => Diopter (t a) (t b) a b Source #

Build a Diopter from a Homogeneous countable sum of countable products.

traverse = homogenized
homogenized = ditraversed

Dioptrice

data Dioptrice a b s t where Source #

A Dioptrice provides efficient access to some pair of functions that make up a Diopter.

Constructors

Dioptrice :: Homogeneous h => (s -> h a) -> (h b -> t) -> Dioptrice a b s t 

Instances

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

Defined in Control.Lens.Diopter

Methods

anyToken :: Dioptrice a b a b Source #

Distributor (Dioptrice a b) Source # 
Instance details

Defined in Control.Lens.Diopter

Methods

zeroP :: Dioptrice a b Void Void Source #

(>+<) :: Dioptrice a b a0 b0 -> Dioptrice a b c d -> Dioptrice a b (Either a0 c) (Either b0 d) Source #

optionalP :: Dioptrice a b a0 b0 -> Dioptrice a b (Maybe a0) (Maybe b0) Source #

manyP :: Dioptrice a b a0 b0 -> Dioptrice a b [a0] [b0] Source #

Profunctor (Dioptrice a b) Source # 
Instance details

Defined in Control.Lens.Diopter

Methods

dimap :: (a0 -> b0) -> (c -> d) -> Dioptrice a b b0 c -> Dioptrice a b a0 d #

lmap :: (a0 -> b0) -> Dioptrice a b b0 c -> Dioptrice a b a0 c #

rmap :: (b0 -> c) -> Dioptrice a b a0 b0 -> Dioptrice a b a0 c #

(#.) :: forall a0 b0 c q. Coercible c b0 => q b0 c -> Dioptrice a b a0 b0 -> Dioptrice a b a0 c #

(.#) :: forall a0 b0 c q. Coercible b0 a0 => Dioptrice a b b0 c -> q a0 b0 -> Dioptrice a b a0 c #

Applicative (Dioptrice a b s) Source # 
Instance details

Defined in Control.Lens.Diopter

Methods

pure :: a0 -> Dioptrice a b s a0 #

(<*>) :: Dioptrice a b s (a0 -> b0) -> Dioptrice a b s a0 -> Dioptrice a b s b0 #

liftA2 :: (a0 -> b0 -> c) -> Dioptrice a b s a0 -> Dioptrice a b s b0 -> Dioptrice a b s c #

(*>) :: Dioptrice a b s a0 -> Dioptrice a b s b0 -> Dioptrice a b s b0 #

(<*) :: Dioptrice a b s a0 -> Dioptrice a b s b0 -> Dioptrice a b s a0 #

Functor (Dioptrice a b s) Source # 
Instance details

Defined in Control.Lens.Diopter

Methods

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

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

runDioptrice :: Distributor p => Dioptrice a b s t -> p a b -> p s t Source #

Run a Dioptrice on a Distributor.