profunctor-optics-0.0.0.2: An optics library compatible with the typeclasses in 'profunctors'.

Safe HaskellNone
LanguageHaskell2010

Data.Profunctor.Optic.Grate

Contents

Synopsis

Types

class Profunctor p => Closed (p :: Type -> Type -> Type) where #

A strong profunctor allows the monoidal structure to pass through.

A closed profunctor allows the closed structure to pass through.

Methods

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

Instances
(Distributive f, Monad f) => Closed (Kleisli f) 
Instance details

Defined in Data.Profunctor.Closed

Methods

closed :: Kleisli f a b -> Kleisli f (x -> a) (x -> b) #

Closed (Environment p) 
Instance details

Defined in Data.Profunctor.Closed

Methods

closed :: Environment p a b -> Environment p (x -> a) (x -> b) #

Closed p => Closed (Coyoneda p) 
Instance details

Defined in Data.Profunctor.Yoneda

Methods

closed :: Coyoneda p a b -> Coyoneda p (x -> a) (x -> b) #

Closed p => Closed (Yoneda p) 
Instance details

Defined in Data.Profunctor.Yoneda

Methods

closed :: Yoneda p a b -> Yoneda p (x -> a) (x -> b) #

Profunctor p => Closed (Closure p) 
Instance details

Defined in Data.Profunctor.Closed

Methods

closed :: Closure p a b -> Closure p (x -> a) (x -> b) #

Distributive f => Closed (Star f) 
Instance details

Defined in Data.Profunctor.Closed

Methods

closed :: Star f a b -> Star f (x -> a) (x -> b) #

Functor f => Closed (Costar f) 
Instance details

Defined in Data.Profunctor.Closed

Methods

closed :: Costar f a b -> Costar f (x -> a) (x -> b) #

Closed (Tagged :: Type -> Type -> Type) 
Instance details

Defined in Data.Profunctor.Closed

Methods

closed :: Tagged a b -> Tagged (x -> a) (x -> b) #

Closed ((->) :: Type -> Type -> Type) 
Instance details

Defined in Data.Profunctor.Closed

Methods

closed :: (a -> b) -> (x -> a) -> (x -> b) #

Functor f => Closed (Cokleisli f) 
Instance details

Defined in Data.Profunctor.Closed

Methods

closed :: Cokleisli f a b -> Cokleisli f (x -> a) (x -> b) #

Closed (GrateRep a b) Source # 
Instance details

Defined in Data.Profunctor.Optic.Grate

Methods

closed :: GrateRep a b a0 b0 -> GrateRep a b (x -> a0) (x -> b0) #

(Closed p, Closed q) => Closed (Product p q) 
Instance details

Defined in Data.Profunctor.Closed

Methods

closed :: Product p q a b -> Product p q (x -> a) (x -> b) #

(Functor f, Closed p) => Closed (Tannen f p) 
Instance details

Defined in Data.Profunctor.Closed

Methods

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

type Grate s t a b = forall p. Closed p => Optic p s t a b Source #

Grates access the codomain of a function.

\( \mathsf{Grate}\;S\;A = \exists I, S \cong I \to A \)

type Grate' s a = Grate s s a a Source #

type Cxgrate k s t a b = forall p. Closed p => CoindexedOptic p k s t a b Source #

type Cxgrate' k s a = Cxgrate k s s a a Source #

type AGrate s t a b = Optic (GrateRep a b) s t a b Source #

type AGrate' s a = AGrate s s a a Source #

Constructors

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

Obtain a Grate from a nested continuation.

The resulting optic is the corepresentable counterpart to Lens, and sits between Iso and Setter.

A Grate lets you lift a profunctor through any representable functor (aka Naperian container). In the special case where the indexing type is finitary (e.g. Bool) then the tabulated type is isomorphic to a fixed length vector (e.g. 'V2 a').

The identity container is representable, and representable functors are closed under composition.

See https://www.cs.ox.ac.uk/jeremy.gibbons/publications/proyo.pdf section 4.6 for more background on Grates, and compare to the lens-family version.

Caution: In order for the generated optic to be well-defined, you must ensure that the input function satisfies the following properties:

  • sabt ($ s) ≡ s
  • sabt (k -> h (k . sabt)) ≡ sabt (k -> h ($ k))

More generally, a profunctor optic must be monoidal as a natural transformation:

See Property.

cxgrate :: (((s -> a) -> k -> b) -> t) -> Cxgrate k s t a b Source #

TODO: Document

grateVl :: (forall f. Functor f => (f a -> b) -> f s -> t) -> Grate s t a b Source #

Transform a Van Laarhoven grate into a profunctor grate.

Compare vlens & cotraversalVl.

cxgrateVl :: (forall f. Functor f => (k -> f a -> b) -> f s -> t) -> Cxgrate k s t a b Source #

TODO: Document

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

Construct a Grate from a pair of inverses.

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

TODO: Document

Carriers

newtype GrateRep a b s t Source #

The GrateRep profunctor precisely characterizes Grate.

Constructors

GrateRep 

Fields

Instances
Corepresentable (GrateRep a b) Source # 
Instance details

Defined in Data.Profunctor.Optic.Grate

Associated Types

type Corep (GrateRep a b) :: Type -> Type #

Methods

cotabulate :: (Corep (GrateRep a b) d -> c) -> GrateRep a b d c #

Closed (GrateRep a b) Source # 
Instance details

Defined in Data.Profunctor.Optic.Grate

Methods

closed :: GrateRep a b a0 b0 -> GrateRep a b (x -> a0) (x -> b0) #

Costrong (GrateRep a b) Source # 
Instance details

Defined in Data.Profunctor.Optic.Grate

Methods

unfirst :: GrateRep a b (a0, d) (b0, d) -> GrateRep a b a0 b0 #

unsecond :: GrateRep a b (d, a0) (d, b0) -> GrateRep a b a0 b0 #

Profunctor (GrateRep a b) Source # 
Instance details

Defined in Data.Profunctor.Optic.Grate

Methods

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

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

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

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

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

Cosieve (GrateRep a b) (Coindex a b) Source # 
Instance details

Defined in Data.Profunctor.Optic.Grate

Methods

cosieve :: GrateRep a b a0 b0 -> Coindex a b a0 -> b0 #

type Corep (GrateRep a b) Source # 
Instance details

Defined in Data.Profunctor.Optic.Grate

type Corep (GrateRep a b) = Coindex a b

Primitive operators

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

Extract the function that characterizes a Lens.

constOf :: AGrate s t a b -> b -> t Source #

Set all fields to the given value.

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

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

Zip over a Grate with 3 arguments.

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

Zip over a Grate with 4 arguments.

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

Transform a profunctor grate into a Van Laarhoven grate.

This is a more restricted version of corepnOf

Optics

cxclosed :: Cxgrate k (c -> a) (c -> b) a b Source #

cxfirst :: Cxgrate k a b (a, c) (b, c) Source #

TODO: Document

cxsecond :: Cxgrate k a b (c, a) (c, b) Source #

TODO: Document

distributed :: Distributive f => Grate (f a) (f b) a b Source #

Access the contents of a distributive functor.

connected :: Conn s a -> Grate' s a Source #

Lift a Galois connection into a Grate.

Useful for giving precise semantics to numerical computations.

This is an example of a Grate that would not be a legal Iso, as Galois connections are not in general inverses.

>>> zipWithOf (connected i08i16) (+) 126 1
127
>>> zipWithOf (connected i08i16) (+) 126 2
127

forwarded :: Distributive m => MonadReader r m => Grate (m a) (m b) a b Source #

Lift an action into a MonadReader.

continued :: Grate a (Cont r a) r r Source #

Lift an action into a continuation.

zipWithOf continued :: (r -> r -> r) -> s -> s -> Cont r s

unlifted :: MonadUnliftIO m => Grate (m a) (m b) (IO a) (IO b) Source #

Unlift an action into an IO context.

liftIOconstOf unlifted
>>> let catchA = catch @ArithException
>>> zipWithOf unlifted (flip catchA . const) (throwIO Overflow) (print "caught")
"caught" 

Operators

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

Use a Grate to construct an Environment.

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

Use a Grate to construct a Closure.