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

Description

 
Synopsis

Bifocal

type Bifocal s t a b = forall p f. (Alternator p, Filtrator p, Alternative f, Filterable f) => p a (f b) -> p s (f t) Source #

Bifocals are bidirectional parser optics.

Every one of the following is a Bifocal.

Bifocals are isomorphic to Binoculars.

type ABifocal s t a b = Binocular a b a (Maybe b) -> Binocular a b s (Maybe t) Source #

If you see ABifocal in a signature for a function, the function is expecting a Bifocal.

Combinators

bifocal :: Binocular a b s t -> Bifocal s t a b Source #

Build a Bifocal from a concrete Binocular.

mapBifocal :: (Alternator p, Filtrator p) => ABifocal s t a b -> p a b -> p s t Source #

Action of ABifocal on partial Distributors.

cloneBifocal :: ABifocal s t a b -> Bifocal s t a b Source #

Clone ABifocal so that you can reuse the same monomorphically typed Bifocal for different purposes.

withBifocal :: (Alternative f, Filterable f) => ABifocal s t a b -> ((s -> Maybe a) -> f b) -> f t Source #

chainedl1 :: APartialIso a b (a, a) (b, b) -> Bifocal a b a b Source #

Left associate a binary constructor pattern to sequence one or more times.

chainedr1 :: APartialIso a b (a, a) (b, b) -> Bifocal a b a b Source #

Right associate a binary constructor pattern to sequence one or more times.

chainedl :: APartialIso a b (a, a) (b, b) -> APartialIso a b () () -> Bifocal a b a b Source #

Left associate a binary constructor pattern to sequence one or more times, or use a nilary constructor pattern to sequence zero times.

chainedr :: APartialIso a b (a, a) (b, b) -> APartialIso a b () () -> Bifocal a b a b Source #

Right associate a binary constructor pattern to sequence one or more times, or use a nilary constructor pattern to sequence zero times.

Binocular

newtype Binocular a b s t Source #

Binocular provides an efficient concrete representation of Bifocals.

Constructors

Binocular 

Fields

Instances

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

Defined in Control.Lens.Bifocal

Methods

anyToken :: Binocular a b a b Source #

Alternator (Binocular a b) Source # 
Instance details

Defined in Control.Lens.Bifocal

Methods

alternate :: Either (Binocular a b a0 b0) (Binocular a b c d) -> Binocular a b (Either a0 c) (Either b0 d) Source #

someP :: Binocular a b a0 b0 -> Binocular a b [a0] [b0] Source #

Distributor (Binocular a b) Source # 
Instance details

Defined in Control.Lens.Bifocal

Methods

zeroP :: Binocular a b Void Void Source #

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

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

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

Filtrator (Binocular a b) Source # 
Instance details

Defined in Control.Lens.Bifocal

Methods

filtrate :: Binocular a b (Either a0 c) (Either b0 d) -> (Binocular a b a0 b0, Binocular a b c d) Source #

Choice (Binocular a b) Source # 
Instance details

Defined in Control.Lens.Bifocal

Methods

left' :: Binocular a b a0 b0 -> Binocular a b (Either a0 c) (Either b0 c) #

right' :: Binocular a b a0 b0 -> Binocular a b (Either c a0) (Either c b0) #

Cochoice (Binocular a b) Source # 
Instance details

Defined in Control.Lens.Bifocal

Methods

unleft :: Binocular a b (Either a0 d) (Either b0 d) -> Binocular a b a0 b0 #

unright :: Binocular a b (Either d a0) (Either d b0) -> Binocular a b a0 b0 #

Profunctor (Binocular a b) Source # 
Instance details

Defined in Control.Lens.Bifocal

Methods

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

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

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

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

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

Alternative (Binocular a b s) Source # 
Instance details

Defined in Control.Lens.Bifocal

Methods

empty :: Binocular a b s a0 #

(<|>) :: Binocular a b s a0 -> Binocular a b s a0 -> Binocular a b s a0 #

some :: Binocular a b s a0 -> Binocular a b s [a0] #

many :: Binocular a b s a0 -> Binocular a b s [a0] #

Applicative (Binocular a b s) Source # 
Instance details

Defined in Control.Lens.Bifocal

Methods

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

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

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

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

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

Functor (Binocular a b s) Source # 
Instance details

Defined in Control.Lens.Bifocal

Methods

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

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

Filterable (Binocular a b s) Source # 
Instance details

Defined in Control.Lens.Bifocal

Methods

mapMaybe :: (a0 -> Maybe b0) -> Binocular a b s a0 -> Binocular a b s b0 #

catMaybes :: Binocular a b s (Maybe a0) -> Binocular a b s a0 #

filter :: (a0 -> Bool) -> Binocular a b s a0 -> Binocular a b s a0 #

drain :: Binocular a b s a0 -> Binocular a b s b0 #

runBinocular :: (Alternator p, Filtrator p) => Binocular a b s t -> p a b -> p s t Source #

Run a Binocular on a partial Distributor.

Prismoid

type Prismoid s t a b = forall p f. (Alternator p, Alternative f) => p a (f b) -> p s (f t) Source #

Prismoids generalize Bifocals, combining Prisms and Diopters.

somed :: Prismoid [a] [b] a b Source #

One or more.

lefted :: Prismoid (Either a c) (Either b d) a b Source #

lefted is like _Left, except with heterogeneous Right parameters.

righted :: Prismoid (Either c a) (Either d b) a b Source #

righted is like _Right, except with heterogeneous Left parameters.

Filtroid

type Filtroid s t a b = forall p f. (Filtrator p, Filterable f) => p a (f b) -> p s (f t) Source #

An optic for Filtrators, Filtroids generalize Bifocals.

unlefted :: Filtroid a b (Either a c) (Either b d) Source #

Dual to lefted.

unrighted :: Filtroid a b (Either c a) (Either d b) Source #

Dual to righted.