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

Data.Profunctor.Distributor

Description

 
Synopsis

Monoidal

type Monoidal p = (Profunctor p, forall x. Applicative (p x)) Source #

A lax Monoidal product Profunctor has unit oneP and product >*< lax monoidal structure morphisms. This is equivalent to the Profunctor also being Applicative.

Laws:

>>> let (f >< g) (a,c) = (f a, g c)
>>> let lunit = dimap (\((),a) -> a) (\a -> ((),a))
>>> let runit = dimap (\(a,()) -> a) (\a -> (a,()))
>>> let assoc = dimap (\(a,(b,c)) -> ((a,b),c)) (\((a,b),c) -> (a,(b,c)))
prop> dimap (f >< g) (h >< i) (p >*< q) = dimap f h p >*< dimap g i q
prop> oneP >*< p = lunit p
prop> p >*< oneP = runit p
prop> p >*< q >*< r = assoc ((p >*< q) >*< r)

oneP :: Monoidal p => p () () Source #

oneP is the unit of a Monoidal Profunctor.

(>*<) :: Monoidal p => p a b -> p c d -> p (a, c) (b, d) infixr 6 Source #

>*< is the product of a Monoidal Profunctor.

(>*) :: Monoidal p => p () c -> p a b -> p a b infixl 5 Source #

>* sequences actions, discarding the value of the first argument; analagous to *>, extending it to Monoidal.

oneP >* p = p

(*<) :: Monoidal p => p a b -> p () c -> p a b infixl 5 Source #

*< sequences actions, discarding the value of the first argument; analagous to <*, extending it to Monoidal.

p *< oneP = p

dimap2 :: Monoidal p => (s -> a) -> (s -> c) -> (b -> d -> t) -> p a b -> p c d -> p s t Source #

dimap2 is a curried, functionalized form of >*<, analagous to liftA2.

foreverP :: Monoidal p => p () c -> p a b Source #

foreverP repeats an action indefinitely; analagous to forever, extending it to Monoidal.

replicateP :: (Traversable t, Distributive t, Monoidal p) => p a b -> p (t a) (t b) Source #

Thanks to Fy on Monoidal Café Discord.

replicateP is roughly analagous to replicateM, repeating an action a number of times. However, instead of an Int term, it expects a Traversable & Distributive type. Such a type is a homogeneous countable product.

meander :: (Monoidal p, Choice p) => ATraversal s t a b -> p a b -> p s t Source #

meander gives a default implementation for the wander method of Traversing for any Monoidal, Choice & Strong Profunctor.

It is invertible when p is Strong, though it's not needed for its definition.

See Pickering, Gibbons & Wu, Profunctor Optics - Modular Data Accessors

(>:<) :: (Monoidal p, Choice p, Cons s t a b) => p a b -> p s t -> p s t infixr 5 Source #

A Monoidal Cons operator.

Distributor

class Monoidal p => Distributor p where Source #

A Distributor, or lax distributive profunctor, respects distributive category structure, that is nilary and binary products and coproducts, (), (,), Void and Either. It has zero zeroP and sum >+< lax monoidal structure morphisms.

In addition to the product laws for Monoidal, we have sum laws for Distributor.

Laws:

>>> :{
let f |+| g = either (Left . f) (Right . g)
    lunit = dimap (either absurd id) Right
    runit = dimap (either id absurd) Left
    assoc = dimap
      (either (Left . Left) (either (Left . Right) Right))
      (either (either Left (Right . Left)) (Right . Right))
:}
prop> dimap (f |+| g) (h |+| i) (p >+< q) = dimap f h p >+< dimap g i q
prop> zeroP >+< p = lunit p
prop> p >+< zeroP = runit p
prop> p >+< q >+< r = assoc ((p >+< q) >+< r)

Minimal complete definition

Nothing

Methods

zeroP :: p Void Void Source #

The zero structure morphism of a Distributor.

default zeroP :: Alternator p => p Void Void Source #

(>+<) :: p a b -> p c d -> p (Either a c) (Either b d) infixr 3 Source #

The sum structure morphism of a Distributor.

default (>+<) :: Alternator p => p a b -> p c d -> p (Either a c) (Either b d) Source #

optionalP :: p a b -> p (Maybe a) (Maybe b) Source #

One or none.

manyP :: p a b -> p [a] [b] Source #

Zero or more.

Instances

Instances details
(ArrowZero p, ArrowChoice p) => Distributor (WrappedArrow p) Source # 
Instance details

Defined in Data.Profunctor.Distributor

Monad m => Distributor (Kleisli m) Source # 
Instance details

Defined in Data.Profunctor.Distributor

Methods

zeroP :: Kleisli m Void Void Source #

(>+<) :: Kleisli m a b -> Kleisli m c d -> Kleisli m (Either a c) (Either b d) Source #

optionalP :: Kleisli m a b -> Kleisli m (Maybe a) (Maybe b) Source #

manyP :: Kleisli m a b -> Kleisli m [a] [b] Source #

Distributor p => Distributor (Coyoneda p) Source # 
Instance details

Defined in Data.Profunctor.Distributor

Methods

zeroP :: Coyoneda p Void Void Source #

(>+<) :: Coyoneda p a b -> Coyoneda p c d -> Coyoneda p (Either a c) (Either b d) Source #

optionalP :: Coyoneda p a b -> Coyoneda p (Maybe a) (Maybe b) Source #

manyP :: Coyoneda p a b -> Coyoneda p [a] [b] Source #

Distributor p => Distributor (Yoneda p) Source # 
Instance details

Defined in Data.Profunctor.Distributor

Methods

zeroP :: Yoneda p Void Void Source #

(>+<) :: Yoneda p a b -> Yoneda p c d -> Yoneda p (Either a c) (Either b d) Source #

optionalP :: Yoneda p a b -> Yoneda p (Maybe a) (Maybe b) Source #

manyP :: Yoneda p a b -> Yoneda p [a] [b] 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 #

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 #

(Monad f, Alternative f) => Distributor (Parsor s f) Source # 
Instance details

Defined in Data.Profunctor.Distributor

Methods

zeroP :: Parsor s f Void Void Source #

(>+<) :: Parsor s f a b -> Parsor s f c d -> Parsor s f (Either a c) (Either b d) Source #

optionalP :: Parsor s f a b -> Parsor s f (Maybe a) (Maybe b) Source #

manyP :: Parsor s f a b -> Parsor s f [a] [b] Source #

Applicative f => Distributor (Printor s f) Source # 
Instance details

Defined in Data.Profunctor.Distributor

Methods

zeroP :: Printor s f Void Void Source #

(>+<) :: Printor s f a b -> Printor s f c d -> Printor s f (Either a c) (Either b d) Source #

optionalP :: Printor s f a b -> Printor s f (Maybe a) (Maybe b) Source #

manyP :: Printor s f a b -> Printor s f [a] [b] Source #

(Distributor p, Applicative f) => Distributor (WrappedPafb f p) Source # 
Instance details

Defined in Data.Profunctor.Distributor

Methods

zeroP :: WrappedPafb f p Void Void Source #

(>+<) :: WrappedPafb f p a b -> WrappedPafb f p c d -> WrappedPafb f p (Either a c) (Either b d) Source #

optionalP :: WrappedPafb f p a b -> WrappedPafb f p (Maybe a) (Maybe b) Source #

manyP :: WrappedPafb f p a b -> WrappedPafb f p [a] [b] Source #

Adjunction f u => Distributor (Costar f) Source # 
Instance details

Defined in Data.Profunctor.Distributor

Methods

zeroP :: Costar f Void Void Source #

(>+<) :: Costar f a b -> Costar f c d -> Costar f (Either a c) (Either b d) Source #

optionalP :: Costar f a b -> Costar f (Maybe a) (Maybe b) Source #

manyP :: Costar f a b -> Costar f [a] [b] Source #

Monoid s => Distributor (Forget s :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.Profunctor.Distributor

Methods

zeroP :: Forget s Void Void Source #

(>+<) :: Forget s a b -> Forget s c d -> Forget s (Either a c) (Either b d) Source #

optionalP :: Forget s a b -> Forget s (Maybe a) (Maybe b) Source #

manyP :: Forget s a b -> Forget s [a] [b] Source #

Applicative f => Distributor (Star f) Source # 
Instance details

Defined in Data.Profunctor.Distributor

Methods

zeroP :: Star f Void Void Source #

(>+<) :: Star f a b -> Star f c d -> Star f (Either a c) (Either b d) Source #

optionalP :: Star f a b -> Star f (Maybe a) (Maybe b) Source #

manyP :: Star f a b -> Star f [a] [b] Source #

Distributor (->) Source # 
Instance details

Defined in Data.Profunctor.Distributor

Methods

zeroP :: Void -> Void Source #

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

optionalP :: (a -> b) -> Maybe a -> Maybe b Source #

manyP :: (a -> b) -> [a] -> [b] Source #

Decidable f => Distributor (Clown f :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.Profunctor.Distributor

Methods

zeroP :: Clown f Void Void Source #

(>+<) :: Clown f a b -> Clown f c d -> Clown f (Either a c) (Either b d) Source #

optionalP :: Clown f a b -> Clown f (Maybe a) (Maybe b) Source #

manyP :: Clown f a b -> Clown f [a] [b] Source #

Alternative f => Distributor (Joker f :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.Profunctor.Distributor

Methods

zeroP :: Joker f Void Void Source #

(>+<) :: Joker f a b -> Joker f c d -> Joker f (Either a c) (Either b d) Source #

optionalP :: Joker f a b -> Joker f (Maybe a) (Maybe b) Source #

manyP :: Joker f a b -> Joker f [a] [b] Source #

(ArrowZero p, ArrowChoice p) => Distributor (WrappedArrow p) Source # 
Instance details

Defined in Data.Profunctor.Distributor

(Distributor p, Distributor q) => Distributor (Product p q) Source # 
Instance details

Defined in Data.Profunctor.Distributor

Methods

zeroP :: Product p q Void Void Source #

(>+<) :: Product p q a b -> Product p q c d -> Product p q (Either a c) (Either b d) Source #

optionalP :: Product p q a b -> Product p q (Maybe a) (Maybe b) Source #

manyP :: Product p q a b -> Product p q [a] [b] Source #

(Applicative f, Distributor p) => Distributor (Cayley f p) Source # 
Instance details

Defined in Data.Profunctor.Distributor

Methods

zeroP :: Cayley f p Void Void Source #

(>+<) :: Cayley f p a b -> Cayley f p c d -> Cayley f p (Either a c) (Either b d) Source #

optionalP :: Cayley f p a b -> Cayley f p (Maybe a) (Maybe b) Source #

manyP :: Cayley f p a b -> Cayley f p [a] [b] Source #

(Distributor p, Distributor q) => Distributor (Procompose p q) Source # 
Instance details

Defined in Data.Profunctor.Distributor

Methods

zeroP :: Procompose p q Void Void Source #

(>+<) :: Procompose p q a b -> Procompose p q c d -> Procompose p q (Either a c) (Either b d) Source #

optionalP :: Procompose p q a b -> Procompose p q (Maybe a) (Maybe b) Source #

manyP :: Procompose p q a b -> Procompose p q [a] [b] Source #

dialt :: Distributor p => (s -> Either a c) -> (b -> t) -> (d -> t) -> p a b -> p c d -> p s t Source #

dialt is a functionalized form of >+<.

class Traversable t => Homogeneous t where Source #

A class of Homogeneous countable sums of countable products.

Minimal complete definition

Nothing

Methods

homogeneously :: Distributor p => p a b -> p (t a) (t b) Source #

Sequences actions homogeneously.

homogeneously @Maybe = optionalP
homogeneously @[] = manyP

Any Traversable & Distributive countable product can be given a default implementation for the homogeneously method.

homogeneously = replicateP

And any user-defined homogeneous algebraic datatype has a default instance for Homogeneous, by deriving Generic1.

default homogeneously :: (Generic1 t, Homogeneous (Rep1 t), Distributor p) => p a b -> p (t a) (t b) Source #

Instances

Instances details
Homogeneous Identity Source # 
Instance details

Defined in Data.Profunctor.Distributor

Methods

homogeneously :: Distributor p => p a b -> p (Identity a) (Identity b) Source #

Homogeneous Par1 Source # 
Instance details

Defined in Data.Profunctor.Distributor

Methods

homogeneously :: Distributor p => p a b -> p (Par1 a) (Par1 b) Source #

Homogeneous Maybe Source # 
Instance details

Defined in Data.Profunctor.Distributor

Methods

homogeneously :: Distributor p => p a b -> p (Maybe a) (Maybe b) Source #

Homogeneous List Source # 
Instance details

Defined in Data.Profunctor.Distributor

Methods

homogeneously :: Distributor p => p a b -> p [a] [b] Source #

Homogeneous (U1 :: Type -> Type) Source # 
Instance details

Defined in Data.Profunctor.Distributor

Methods

homogeneously :: Distributor p => p a b -> p (U1 a) (U1 b) Source #

Homogeneous (V1 :: Type -> Type) Source # 
Instance details

Defined in Data.Profunctor.Distributor

Methods

homogeneously :: Distributor p => p a b -> p (V1 a) (V1 b) Source #

Homogeneous (Const () :: Type -> Type) Source # 
Instance details

Defined in Data.Profunctor.Distributor

Methods

homogeneously :: Distributor p => p a b -> p (Const () a) (Const () b) Source #

(Homogeneous s, Homogeneous t) => Homogeneous (Product s t) Source # 
Instance details

Defined in Data.Profunctor.Distributor

Methods

homogeneously :: Distributor p => p a b -> p (Product s t a) (Product s t b) Source #

(Homogeneous s, Homogeneous t) => Homogeneous (Sum s t) Source # 
Instance details

Defined in Data.Profunctor.Distributor

Methods

homogeneously :: Distributor p => p a b -> p (Sum s t a) (Sum s t b) Source #

(Homogeneous s, Homogeneous t) => Homogeneous (s :*: t) Source # 
Instance details

Defined in Data.Profunctor.Distributor

Methods

homogeneously :: Distributor p => p a b -> p ((s :*: t) a) ((s :*: t) b) Source #

(Homogeneous s, Homogeneous t) => Homogeneous (s :+: t) Source # 
Instance details

Defined in Data.Profunctor.Distributor

Methods

homogeneously :: Distributor p => p a b -> p ((s :+: t) a) ((s :+: t) b) Source #

Homogeneous (K1 i () :: Type -> Type) Source # 
Instance details

Defined in Data.Profunctor.Distributor

Methods

homogeneously :: Distributor p => p a b -> p (K1 i () a) (K1 i () b) Source #

(Homogeneous s, Homogeneous t) => Homogeneous (Compose s t) Source # 
Instance details

Defined in Data.Profunctor.Distributor

Methods

homogeneously :: Distributor p => p a b -> p (Compose s t a) (Compose s t b) Source #

(Homogeneous s, Homogeneous t) => Homogeneous (s :.: t) Source # 
Instance details

Defined in Data.Profunctor.Distributor

Methods

homogeneously :: Distributor p => p a b -> p ((s :.: t) a) ((s :.: t) b) Source #

Homogeneous t => Homogeneous (M1 i c t) Source # 
Instance details

Defined in Data.Profunctor.Distributor

Methods

homogeneously :: Distributor p => p a b -> p (M1 i c t a) (M1 i c t b) Source #

Alternator/Filtrator

class (Choice p, Distributor p, forall x. Alternative (p x)) => Alternator p where Source #

The Alternator class co-extends Choice and Distributor, as well as Alternative, adding the alternate method, which is a lax monoidal structure morphism on sums.

For the case of Functors the analog of alternate can be defined without any other constraint, but the case of Profunctors turns out to be slighly more complex.

Minimal complete definition

Nothing

Methods

alternate :: Either (p a b) (p c d) -> p (Either a c) (Either b d) Source #

left' = alternate . Left
right' = alternate . Right
zeroP = empty
x >+< y = alternate (Left x) <|> alternate (Right y)

alternate has a default when Cochoice.

default alternate :: Cochoice p => Either (p a b) (p c d) -> p (Either a c) (Either b d) Source #

someP :: p a b -> p [a] [b] Source #

One or more.

Instances

Instances details
Alternator p => Alternator (Coyoneda p) Source # 
Instance details

Defined in Data.Profunctor.Distributor

Methods

alternate :: Either (Coyoneda p a b) (Coyoneda p c d) -> Coyoneda p (Either a c) (Either b d) Source #

someP :: Coyoneda p a b -> Coyoneda p [a] [b] Source #

Alternator p => Alternator (Yoneda p) Source # 
Instance details

Defined in Data.Profunctor.Distributor

Methods

alternate :: Either (Yoneda p a b) (Yoneda p c d) -> Yoneda p (Either a c) (Either b d) Source #

someP :: Yoneda p a b -> Yoneda p [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 #

(Monad f, Alternative f) => Alternator (Parsor s f) Source # 
Instance details

Defined in Data.Profunctor.Distributor

Methods

alternate :: Either (Parsor s f a b) (Parsor s f c d) -> Parsor s f (Either a c) (Either b d) Source #

someP :: Parsor s f a b -> Parsor s f [a] [b] Source #

Alternative f => Alternator (Printor s f) Source # 
Instance details

Defined in Data.Profunctor.Distributor

Methods

alternate :: Either (Printor s f a b) (Printor s f c d) -> Printor s f (Either a c) (Either b d) Source #

someP :: Printor s f a b -> Printor s f [a] [b] Source #

(Alternator p, Alternative f) => Alternator (WrappedPafb f p) Source # 
Instance details

Defined in Data.Profunctor.Distributor

Methods

alternate :: Either (WrappedPafb f p a b) (WrappedPafb f p c d) -> WrappedPafb f p (Either a c) (Either b d) Source #

someP :: WrappedPafb f p a b -> WrappedPafb f p [a] [b] Source #

class (Cochoice p, forall x. Filterable (p x)) => Filtrator p where Source #

The Filtrator class extends Cochoice, as well as Filterable, adding the filtrate method, which is an oplax monoidal structure morphism dual to >+<.

Minimal complete definition

Nothing

Methods

filtrate :: p (Either a c) (Either b d) -> (p a b, p c d) Source #

unleft = fst . filtrate
unright = snd . filtrate

filtrate is a distant relative to partitionEithers.

filtrate has a default when Choice.

default filtrate :: Choice p => p (Either a c) (Either b d) -> (p a b, p c d) Source #

Instances

Instances details
Filtrator p => Filtrator (Coyoneda p) Source # 
Instance details

Defined in Data.Profunctor.Distributor

Methods

filtrate :: Coyoneda p (Either a c) (Either b d) -> (Coyoneda p a b, Coyoneda p c d) Source #

Filtrator p => Filtrator (Yoneda p) Source # 
Instance details

Defined in Data.Profunctor.Distributor

Methods

filtrate :: Yoneda p (Either a c) (Either b d) -> (Yoneda p a b, Yoneda p c d) 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 #

Filtrator (PartialExchange a b) Source # 
Instance details

Defined in Data.Profunctor.Distributor

Methods

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

Filterable f => Filtrator (Parsor s f) Source # 
Instance details

Defined in Data.Profunctor.Distributor

Methods

filtrate :: Parsor s f (Either a c) (Either b d) -> (Parsor s f a b, Parsor s f c d) Source #

Filtrator (Printor s f) Source # 
Instance details

Defined in Data.Profunctor.Distributor

Methods

filtrate :: Printor s f (Either a c) (Either b d) -> (Printor s f a b, Printor s f c d) Source #

(Filtrator p, Filterable f) => Filtrator (WrappedPafb f p) Source # 
Instance details

Defined in Data.Profunctor.Distributor

Methods

filtrate :: WrappedPafb f p (Either a c) (Either b d) -> (WrappedPafb f p a b, WrappedPafb f p c d) Source #

Filtrator (Forget r :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.Profunctor.Distributor

Methods

filtrate :: Forget r (Either a c) (Either b d) -> (Forget r a b, Forget r c d) Source #

(Filterable f, Traversable f) => Filtrator (Star f) Source # 
Instance details

Defined in Data.Profunctor.Distributor

Methods

filtrate :: Star f (Either a c) (Either b d) -> (Star f a b, Star f c d) Source #

SepBy

data SepBy p Source #

Used to sequence multiple times, separated by a separateBy, begun by a beginBy, and ended by an endBy.

Constructors

SepBy 

Fields

sepBy :: Monoidal p => p () () -> SepBy p Source #

A default SepBy constructor which can be modified by updating beginBy, or endBy fields

noSep :: Monoidal p => SepBy p Source #

No separator, beginning or ending delimiters.

zeroOrMore :: Distributor p => SepBy p -> p a b -> p [a] [b] Source #

zeroOrMore (sepBy noSep) = manyP

oneOrMore :: Alternator p => SepBy p -> p a b -> p [a] [b] Source #

oneOrMore (sepBy noSep) = someP

chainl1 Source #

Arguments

:: (Choice p, Cochoice p, Distributor p) 
=> APartialIso a b (a, a) (b, b)

binary constructor pattern

-> SepBy p 
-> p a b 
-> p a b 

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

chainr1 Source #

Arguments

:: (Choice p, Cochoice p, Distributor p) 
=> APartialIso a b (a, a) (b, b)

binary constructor pattern

-> SepBy p 
-> p a b 
-> p a b 

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

chainl Source #

Arguments

:: (Alternator p, Filtrator p) 
=> APartialIso a b (a, a) (b, b)

binary constructor pattern

-> APartialIso a b () ()

nilary constructor pattern

-> SepBy p 
-> p a b 
-> p a b 

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

chainr Source #

Arguments

:: (Alternator p, Filtrator p) 
=> APartialIso a b (a, a) (b, b)

binary constructor pattern

-> APartialIso a b () ()

nilary constructor pattern

-> SepBy p 
-> p a b 
-> p a b 

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

Tokenized

class Tokenized a b p | p -> a, p -> b where Source #

Tokenized serves two different purposes. The anyToken method is used

  • by token-stream printer/parsers, to sequence a single token;
  • and for concrete optics, as an identity morphism.

In the former case the associated input and output token types are same. In the latter case, observe that Identical is a free Tokenized.

Methods

anyToken :: p a b Source #

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 #

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

Defined in Control.Lens.Diopter

Methods

anyToken :: Dioptrice a b a b Source #

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

Defined in Control.Lens.Grate

Methods

anyToken :: Grating a b a b Source #

Tokenized a b (Monocular a b) Source # 
Instance details

Defined in Control.Lens.Monocle

Methods

anyToken :: Monocular a b a b Source #

Tokenized a b (PartialExchange a b) Source # 
Instance details

Defined in Data.Profunctor.Distributor

Methods

anyToken :: PartialExchange a b a b Source #

Tokenized a b (Exchange a b) Source # 
Instance details

Defined in Data.Profunctor.Distributor

Methods

anyToken :: Exchange a b a b Source #

Tokenized a b (Market a b) Source # 
Instance details

Defined in Data.Profunctor.Distributor

Methods

anyToken :: Market a b a b Source #

(Alternative f, Cons s s c c) => Tokenized c c (Parsor s f) Source # 
Instance details

Defined in Data.Profunctor.Distributor

Methods

anyToken :: Parsor s f c c Source #

(Applicative f, Cons s s c c) => Tokenized c c (Printor s f) Source # 
Instance details

Defined in Data.Profunctor.Distributor

Methods

anyToken :: Printor s f c c Source #

Tokenized a b (Identical a b) Source # 
Instance details

Defined in Data.Profunctor.Distributor

Methods

anyToken :: Identical a b a b Source #

satisfy :: (Choice p, Cochoice p, Tokenized c c p) => (c -> Bool) -> p c c Source #

Sequences a single token that satisfies a predicate.

token :: (Cochoice p, Eq c, Tokenized c c p) => c -> p () () Source #

Sequences a single specified token.

tokens :: (Cochoice p, Monoidal p, Eq c, Tokenized c c p) => [c] -> p () () Source #

Sequences a specified stream of tokens. It can be used as a default definition for the fromString method of IsString when Tokenized Char Char.

Printor/Parsor

newtype Printor s f a b Source #

A function from things to containers of functions of strings to strings. Printor is a degenerate Profunctor which is constant in its covariant argument.

Constructors

Printor 

Fields

Instances

Instances details
(Applicative f, Cons s s c c) => Tokenized c c (Printor s f) Source # 
Instance details

Defined in Data.Profunctor.Distributor

Methods

anyToken :: Printor s f c c Source #

Alternative f => Alternator (Printor s f) Source # 
Instance details

Defined in Data.Profunctor.Distributor

Methods

alternate :: Either (Printor s f a b) (Printor s f c d) -> Printor s f (Either a c) (Either b d) Source #

someP :: Printor s f a b -> Printor s f [a] [b] Source #

Applicative f => Distributor (Printor s f) Source # 
Instance details

Defined in Data.Profunctor.Distributor

Methods

zeroP :: Printor s f Void Void Source #

(>+<) :: Printor s f a b -> Printor s f c d -> Printor s f (Either a c) (Either b d) Source #

optionalP :: Printor s f a b -> Printor s f (Maybe a) (Maybe b) Source #

manyP :: Printor s f a b -> Printor s f [a] [b] Source #

Filtrator (Printor s f) Source # 
Instance details

Defined in Data.Profunctor.Distributor

Methods

filtrate :: Printor s f (Either a c) (Either b d) -> (Printor s f a b, Printor s f c d) Source #

(Alternative f, Cons s s Char Char) => Grammatical (Printor s f) Source # 
Instance details

Defined in Text.Grammar.Distributor

Alternative f => Choice (Printor s f) Source # 
Instance details

Defined in Data.Profunctor.Distributor

Methods

left' :: Printor s f a b -> Printor s f (Either a c) (Either b c) #

right' :: Printor s f a b -> Printor s f (Either c a) (Either c b) #

Cochoice (Printor s f) Source # 
Instance details

Defined in Data.Profunctor.Distributor

Methods

unleft :: Printor s f (Either a d) (Either b d) -> Printor s f a b #

unright :: Printor s f (Either d a) (Either d b) -> Printor s f a b #

Profunctor (Printor s f) Source # 
Instance details

Defined in Data.Profunctor.Distributor

Methods

dimap :: (a -> b) -> (c -> d) -> Printor s f b c -> Printor s f a d #

lmap :: (a -> b) -> Printor s f b c -> Printor s f a c #

rmap :: (b -> c) -> Printor s f a b -> Printor s f a c #

(#.) :: forall a b c q. Coercible c b => q b c -> Printor s f a b -> Printor s f a c #

(.#) :: forall a b c q. Coercible b a => Printor s f b c -> q a b -> Printor s f a c #

Contravariant (Printor s f a) Source # 
Instance details

Defined in Data.Profunctor.Distributor

Methods

contramap :: (a' -> a0) -> Printor s f a a0 -> Printor s f a a' #

(>$) :: b -> Printor s f a b -> Printor s f a a0 #

Alternative f => Alternative (Printor s f a) Source # 
Instance details

Defined in Data.Profunctor.Distributor

Methods

empty :: Printor s f a a0 #

(<|>) :: Printor s f a a0 -> Printor s f a a0 -> Printor s f a a0 #

some :: Printor s f a a0 -> Printor s f a [a0] #

many :: Printor s f a a0 -> Printor s f a [a0] #

Applicative f => Applicative (Printor s f a) Source # 
Instance details

Defined in Data.Profunctor.Distributor

Methods

pure :: a0 -> Printor s f a a0 #

(<*>) :: Printor s f a (a0 -> b) -> Printor s f a a0 -> Printor s f a b #

liftA2 :: (a0 -> b -> c) -> Printor s f a a0 -> Printor s f a b -> Printor s f a c #

(*>) :: Printor s f a a0 -> Printor s f a b -> Printor s f a b #

(<*) :: Printor s f a a0 -> Printor s f a b -> Printor s f a a0 #

Functor (Printor s f a) Source # 
Instance details

Defined in Data.Profunctor.Distributor

Methods

fmap :: (a0 -> b) -> Printor s f a a0 -> Printor s f a b #

(<$) :: a0 -> Printor s f a b -> Printor s f a a0 #

Filterable (Printor s f a) Source # 
Instance details

Defined in Data.Profunctor.Distributor

Methods

mapMaybe :: (a0 -> Maybe b) -> Printor s f a a0 -> Printor s f a b #

catMaybes :: Printor s f a (Maybe a0) -> Printor s f a a0 #

filter :: (a0 -> Bool) -> Printor s f a a0 -> Printor s f a a0 #

drain :: Printor s f a a0 -> Printor s f a b #

(Applicative f, Cons s s Char Char) => IsString (Printor s f () ()) Source # 
Instance details

Defined in Data.Profunctor.Distributor

Methods

fromString :: String -> Printor s f () () #

newtype Parsor s f a b Source #

A function from strings to containers of pairs of things and strings. Parsor is a degenerate Profunctor which is constant in its contravariant argument.

Constructors

Parsor 

Fields

Instances

Instances details
(Alternative f, Cons s s c c) => Tokenized c c (Parsor s f) Source # 
Instance details

Defined in Data.Profunctor.Distributor

Methods

anyToken :: Parsor s f c c Source #

Functor f => Bifunctor (Parsor s f) Source # 
Instance details

Defined in Data.Profunctor.Distributor

Methods

bimap :: (a -> b) -> (c -> d) -> Parsor s f a c -> Parsor s f b d #

first :: (a -> b) -> Parsor s f a c -> Parsor s f b c #

second :: (b -> c) -> Parsor s f a b -> Parsor s f a c #

(Monad f, Alternative f) => Alternator (Parsor s f) Source # 
Instance details

Defined in Data.Profunctor.Distributor

Methods

alternate :: Either (Parsor s f a b) (Parsor s f c d) -> Parsor s f (Either a c) (Either b d) Source #

someP :: Parsor s f a b -> Parsor s f [a] [b] Source #

(Monad f, Alternative f) => Distributor (Parsor s f) Source # 
Instance details

Defined in Data.Profunctor.Distributor

Methods

zeroP :: Parsor s f Void Void Source #

(>+<) :: Parsor s f a b -> Parsor s f c d -> Parsor s f (Either a c) (Either b d) Source #

optionalP :: Parsor s f a b -> Parsor s f (Maybe a) (Maybe b) Source #

manyP :: Parsor s f a b -> Parsor s f [a] [b] Source #

Filterable f => Filtrator (Parsor s f) Source # 
Instance details

Defined in Data.Profunctor.Distributor

Methods

filtrate :: Parsor s f (Either a c) (Either b d) -> (Parsor s f a b, Parsor s f c d) Source #

(Monad f, Alternative f, Filterable f, Cons s s Char Char) => Grammatical (Parsor s f) Source # 
Instance details

Defined in Text.Grammar.Distributor

(Monad f, Alternative f) => Choice (Parsor s f) Source # 
Instance details

Defined in Data.Profunctor.Distributor

Methods

left' :: Parsor s f a b -> Parsor s f (Either a c) (Either b c) #

right' :: Parsor s f a b -> Parsor s f (Either c a) (Either c b) #

Filterable f => Cochoice (Parsor s f) Source # 
Instance details

Defined in Data.Profunctor.Distributor

Methods

unleft :: Parsor s f (Either a d) (Either b d) -> Parsor s f a b #

unright :: Parsor s f (Either d a) (Either d b) -> Parsor s f a b #

Functor f => Profunctor (Parsor s f) Source # 
Instance details

Defined in Data.Profunctor.Distributor

Methods

dimap :: (a -> b) -> (c -> d) -> Parsor s f b c -> Parsor s f a d #

lmap :: (a -> b) -> Parsor s f b c -> Parsor s f a c #

rmap :: (b -> c) -> Parsor s f a b -> Parsor s f a c #

(#.) :: forall a b c q. Coercible c b => q b c -> Parsor s f a b -> Parsor s f a c #

(.#) :: forall a b c q. Coercible b a => Parsor s f b c -> q a b -> Parsor s f a c #

(Alternative f, Monad f) => Alternative (Parsor s f a) Source # 
Instance details

Defined in Data.Profunctor.Distributor

Methods

empty :: Parsor s f a a0 #

(<|>) :: Parsor s f a a0 -> Parsor s f a a0 -> Parsor s f a a0 #

some :: Parsor s f a a0 -> Parsor s f a [a0] #

many :: Parsor s f a a0 -> Parsor s f a [a0] #

Monad f => Applicative (Parsor s f a) Source # 
Instance details

Defined in Data.Profunctor.Distributor

Methods

pure :: a0 -> Parsor s f a a0 #

(<*>) :: Parsor s f a (a0 -> b) -> Parsor s f a a0 -> Parsor s f a b #

liftA2 :: (a0 -> b -> c) -> Parsor s f a a0 -> Parsor s f a b -> Parsor s f a c #

(*>) :: Parsor s f a a0 -> Parsor s f a b -> Parsor s f a b #

(<*) :: Parsor s f a a0 -> Parsor s f a b -> Parsor s f a a0 #

Functor f => Functor (Parsor s f a) Source # 
Instance details

Defined in Data.Profunctor.Distributor

Methods

fmap :: (a0 -> b) -> Parsor s f a a0 -> Parsor s f a b #

(<$) :: a0 -> Parsor s f a b -> Parsor s f a a0 #

Filterable f => Filterable (Parsor s f a) Source # 
Instance details

Defined in Data.Profunctor.Distributor

Methods

mapMaybe :: (a0 -> Maybe b) -> Parsor s f a a0 -> Parsor s f a b #

catMaybes :: Parsor s f a (Maybe a0) -> Parsor s f a a0 #

filter :: (a0 -> Bool) -> Parsor s f a a0 -> Parsor s f a a0 #

drain :: Parsor s f a a0 -> Parsor s f a b #

(Alternative f, Filterable f, Monad f, Cons s s Char Char) => IsString (Parsor s f () ()) Source # 
Instance details

Defined in Data.Profunctor.Distributor

Methods

fromString :: String -> Parsor s f () () #

Orphan instances

Arrow p => Profunctor (WrappedArrow p) Source # 
Instance details

Methods

dimap :: (a -> b) -> (c -> d) -> WrappedArrow p b c -> WrappedArrow p a d #

lmap :: (a -> b) -> WrappedArrow p b c -> WrappedArrow p a c #

rmap :: (b -> c) -> WrappedArrow p a b -> WrappedArrow p a c #

(#.) :: forall a b c q. Coercible c b => q b c -> WrappedArrow p a b -> WrappedArrow p a c #

(.#) :: forall a b c q. Coercible b a => WrappedArrow p b c -> q a b -> WrappedArrow p a c #

(Profunctor p, Alternative (p a)) => Alternative (Coyoneda p a) Source # 
Instance details

Methods

empty :: Coyoneda p a a0 #

(<|>) :: Coyoneda p a a0 -> Coyoneda p a a0 -> Coyoneda p a a0 #

some :: Coyoneda p a a0 -> Coyoneda p a [a0] #

many :: Coyoneda p a a0 -> Coyoneda p a [a0] #

(Profunctor p, Alternative (p a)) => Alternative (Yoneda p a) Source # 
Instance details

Methods

empty :: Yoneda p a a0 #

(<|>) :: Yoneda p a a0 -> Yoneda p a a0 -> Yoneda p a a0 #

some :: Yoneda p a a0 -> Yoneda p a [a0] #

many :: Yoneda p a a0 -> Yoneda p a [a0] #

(Profunctor p, Applicative (p a)) => Applicative (Coyoneda p a) Source # 
Instance details

Methods

pure :: a0 -> Coyoneda p a a0 #

(<*>) :: Coyoneda p a (a0 -> b) -> Coyoneda p a a0 -> Coyoneda p a b #

liftA2 :: (a0 -> b -> c) -> Coyoneda p a a0 -> Coyoneda p a b -> Coyoneda p a c #

(*>) :: Coyoneda p a a0 -> Coyoneda p a b -> Coyoneda p a b #

(<*) :: Coyoneda p a a0 -> Coyoneda p a b -> Coyoneda p a a0 #

(Profunctor p, Applicative (p a)) => Applicative (Yoneda p a) Source # 
Instance details

Methods

pure :: a0 -> Yoneda p a a0 #

(<*>) :: Yoneda p a (a0 -> b) -> Yoneda p a a0 -> Yoneda p a b #

liftA2 :: (a0 -> b -> c) -> Yoneda p a a0 -> Yoneda p a b -> Yoneda p a c #

(*>) :: Yoneda p a a0 -> Yoneda p a b -> Yoneda p a b #

(<*) :: Yoneda p a a0 -> Yoneda p a b -> Yoneda p a a0 #

(Closed p, Distributive f) => Closed (WrappedPafb f p) Source # 
Instance details

Methods

closed :: WrappedPafb f p a b -> WrappedPafb f p (x -> a) (x -> b) #

(Profunctor p, Alternative (p a), Applicative f) => Alternative (WrappedPafb f p a) Source # 
Instance details

Methods

empty :: WrappedPafb f p a a0 #

(<|>) :: WrappedPafb f p a a0 -> WrappedPafb f p a a0 -> WrappedPafb f p a a0 #

some :: WrappedPafb f p a a0 -> WrappedPafb f p a [a0] #

many :: WrappedPafb f p a a0 -> WrappedPafb f p a [a0] #

(Profunctor p, Applicative (p a), Applicative f) => Applicative (WrappedPafb f p a) Source # 
Instance details

Methods

pure :: a0 -> WrappedPafb f p a a0 #

(<*>) :: WrappedPafb f p a (a0 -> b) -> WrappedPafb f p a a0 -> WrappedPafb f p a b #

liftA2 :: (a0 -> b -> c) -> WrappedPafb f p a a0 -> WrappedPafb f p a b -> WrappedPafb f p a c #

(*>) :: WrappedPafb f p a a0 -> WrappedPafb f p a b -> WrappedPafb f p a b #

(<*) :: WrappedPafb f p a a0 -> WrappedPafb f p a b -> WrappedPafb f p a a0 #

Monoid r => Applicative (Forget r a :: Type -> Type) Source # 
Instance details

Methods

pure :: a0 -> Forget r a a0 #

(<*>) :: Forget r a (a0 -> b) -> Forget r a a0 -> Forget r a b #

liftA2 :: (a0 -> b -> c) -> Forget r a a0 -> Forget r a b -> Forget r a c #

(*>) :: Forget r a a0 -> Forget r a b -> Forget r a b #

(<*) :: Forget r a a0 -> Forget r a b -> Forget r a a0 #

Decidable f => Applicative (Clown f a :: Type -> Type) Source # 
Instance details

Methods

pure :: a0 -> Clown f a a0 #

(<*>) :: Clown f a (a0 -> b) -> Clown f a a0 -> Clown f a b #

liftA2 :: (a0 -> b -> c) -> Clown f a a0 -> Clown f a b -> Clown f a c #

(*>) :: Clown f a a0 -> Clown f a b -> Clown f a b #

(<*) :: Clown f a a0 -> Clown f a b -> Clown f a a0 #

Applicative f => Applicative (Joker f a) Source # 
Instance details

Methods

pure :: a0 -> Joker f a a0 #

(<*>) :: Joker f a (a0 -> b) -> Joker f a a0 -> Joker f a b #

liftA2 :: (a0 -> b -> c) -> Joker f a a0 -> Joker f a b -> Joker f a c #

(*>) :: Joker f a a0 -> Joker f a b -> Joker f a b #

(<*) :: Joker f a a0 -> Joker f a b -> Joker f a a0 #

Arrow p => Applicative (WrappedArrow p a) Source # 
Instance details

Methods

pure :: a0 -> WrappedArrow p a a0 #

(<*>) :: WrappedArrow p a (a0 -> b) -> WrappedArrow p a a0 -> WrappedArrow p a b #

liftA2 :: (a0 -> b -> c) -> WrappedArrow p a a0 -> WrappedArrow p a b -> WrappedArrow p a c #

(*>) :: WrappedArrow p a a0 -> WrappedArrow p a b -> WrappedArrow p a b #

(<*) :: WrappedArrow p a a0 -> WrappedArrow p a b -> WrappedArrow p a a0 #

Arrow p => Functor (WrappedArrow p a) Source # 
Instance details

Methods

fmap :: (a0 -> b) -> WrappedArrow p a a0 -> WrappedArrow p a b #

(<$) :: a0 -> WrappedArrow p a b -> WrappedArrow p a a0 #

(Monoidal p, Monoidal q) => Applicative (Product p q a) Source # 
Instance details

Methods

pure :: a0 -> Product p q a a0 #

(<*>) :: Product p q a (a0 -> b) -> Product p q a a0 -> Product p q a b #

liftA2 :: (a0 -> b -> c) -> Product p q a a0 -> Product p q a b -> Product p q a c #

(*>) :: Product p q a a0 -> Product p q a b -> Product p q a b #

(<*) :: Product p q a a0 -> Product p q a b -> Product p q a a0 #

(Applicative f, Applicative (p a)) => Applicative (Cayley f p a) Source # 
Instance details

Methods

pure :: a0 -> Cayley f p a a0 #

(<*>) :: Cayley f p a (a0 -> b) -> Cayley f p a a0 -> Cayley f p a b #

liftA2 :: (a0 -> b -> c) -> Cayley f p a a0 -> Cayley f p a b -> Cayley f p a c #

(*>) :: Cayley f p a a0 -> Cayley f p a b -> Cayley f p a b #

(<*) :: Cayley f p a a0 -> Cayley f p a b -> Cayley f p a a0 #

(Monoidal p, Applicative (q a)) => Applicative (Procompose p q a) Source # 
Instance details

Methods

pure :: a0 -> Procompose p q a a0 #

(<*>) :: Procompose p q a (a0 -> b) -> Procompose p q a a0 -> Procompose p q a b #

liftA2 :: (a0 -> b -> c) -> Procompose p q a a0 -> Procompose p q a b -> Procompose p q a c #

(*>) :: Procompose p q a a0 -> Procompose p q a b -> Procompose p q a b #

(<*) :: Procompose p q a a0 -> Procompose p q a b -> Procompose p q a a0 #

(Functor f, Functor (p a)) => Functor (Cayley f p a) Source # 
Instance details

Methods

fmap :: (a0 -> b) -> Cayley f p a a0 -> Cayley f p a b #

(<$) :: a0 -> Cayley f p a b -> Cayley f p a a0 #