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.Bifocal
Description
Synopsis
- 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)
- type ABifocal s t a b = Binocular a b a (Maybe b) -> Binocular a b s (Maybe t)
- bifocal :: Binocular a b s t -> Bifocal s t a b
- mapBifocal :: (Alternator p, Filtrator p) => ABifocal s t a b -> p a b -> p s t
- cloneBifocal :: ABifocal s t a b -> Bifocal s t a b
- withBifocal :: (Alternative f, Filterable f) => ABifocal s t a b -> ((s -> Maybe a) -> f b) -> f t
- chainedl1 :: APartialIso a b (a, a) (b, b) -> Bifocal a b a b
- chainedr1 :: APartialIso a b (a, a) (b, b) -> Bifocal a b a b
- chainedl :: APartialIso a b (a, a) (b, b) -> APartialIso a b () () -> Bifocal a b a b
- chainedr :: APartialIso a b (a, a) (b, b) -> APartialIso a b () () -> Bifocal a b a b
- newtype Binocular a b s t = Binocular {
- unBinocular :: forall f. (Alternative f, Filterable f) => ((s -> Maybe a) -> f b) -> f t
- runBinocular :: (Alternator p, Filtrator p) => Binocular a b s t -> p a b -> p s t
- type Prismoid s t a b = forall p f. (Alternator p, Alternative f) => p a (f b) -> p s (f t)
- somed :: Prismoid [a] [b] a b
- lefted :: Prismoid (Either a c) (Either b d) a b
- righted :: Prismoid (Either c a) (Either d b) a b
- type Filtroid s t a b = forall p f. (Filtrator p, Filterable f) => p a (f b) -> p s (f t)
- unlefted :: Filtroid a b (Either a c) (Either b d)
- unrighted :: Filtroid a b (Either c a) (Either d b)
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 #
Combinators
mapBifocal :: (Alternator p, Filtrator p) => ABifocal s t a b -> p a b -> p s t Source #
Action of ABifocal
on partial Distributor
s.
cloneBifocal :: ABifocal s t a b -> Bifocal s t a b Source #
withBifocal :: (Alternative f, Filterable f) => ABifocal s t a b -> ((s -> Maybe a) -> f b) -> f t Source #
Run ABifocal
over an Alternative
& Filterable
.
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 #
Constructors
Binocular | |
Fields
|
Instances
Tokenized a b (Binocular a b) Source # | |
Defined in Control.Lens.Bifocal | |
Alternator (Binocular a b) Source # | |
Distributor (Binocular a b) Source # | |
Defined in Control.Lens.Bifocal | |
Filtrator (Binocular a b) Source # | |
Choice (Binocular a b) Source # | |
Cochoice (Binocular a b) Source # | |
Profunctor (Binocular a b) Source # | |
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 # | |
Applicative (Binocular a b s) Source # | |
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 # | |
Filterable (Binocular a b s) Source # | |
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 #
Filtroid
type Filtroid s t a b = forall p f. (Filtrator p, Filterable f) => p a (f b) -> p s (f t) Source #