Copyright | (C) 2025 - Eitan Chatav |
---|---|
License | BSD-style (see the file LICENSE) |
Maintainer | Eitan Chatav <eitan.chatav@gmail.com> |
Stability | provisional |
Portability | non-portable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Control.Lens.Diopter
Contents
Description
Synopsis
- type Diopter s t a b = forall p f. (Distributor p, Applicative f) => p a (f b) -> p s (f t)
- type ADiopter s t a b = Dioptrice a b a (Identity b) -> Dioptrice a b s (Identity t)
- diopter :: Homogeneous h => (s -> h a) -> (h b -> t) -> Diopter s t a b
- withDiopter :: ADiopter s t a b -> (forall h. Homogeneous h => (s -> h a) -> (h b -> t) -> r) -> r
- cloneDiopter :: ADiopter s t a b -> Diopter s t a b
- mapDiopter :: Distributor p => ADiopter s t a b -> p a b -> p s t
- optioned :: Diopter (Maybe a) (Maybe b) a b
- manied :: Diopter [a] [b] a b
- homogenized :: Homogeneous t => Diopter (t a) (t b) a b
- data Dioptrice a b s t where
- Dioptrice :: Homogeneous h => (s -> h a) -> (h b -> t) -> Dioptrice a b s t
- runDioptrice :: Distributor p => Dioptrice a b s t -> p a b -> p s t
Diopter
type Diopter s t a b = forall p f. (Distributor p, Applicative f) => p a (f b) -> p s (f t) Source #
Combinators
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 #
mapDiopter :: Distributor p => ADiopter s t a b -> p a b -> p s t Source #
Action of ADiopter
on Distributor
s.
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 #
Constructors
Dioptrice :: Homogeneous h => (s -> h a) -> (h b -> t) -> Dioptrice a b s t |
Instances
Tokenized a b (Dioptrice a b) Source # | |
Defined in Control.Lens.Diopter | |
Distributor (Dioptrice a b) Source # | |
Defined in Control.Lens.Diopter | |
Profunctor (Dioptrice a b) Source # | |
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 # | |
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 # | |
runDioptrice :: Distributor p => Dioptrice a b s t -> p a b -> p s t Source #
Run a Dioptrice
on a Distributor
.