Copyright | (c) Mario Román 2020 |
---|---|
License | GPL-3 |
Maintainer | mromang08@gmail.com |
Stability | experimental |
Portability | POSIX |
Safe Haskell | Safe |
Language | Haskell2010 |
Provides combinators for the library of optics in terms of Tambara modules.
Synopsis
- newtype Viewing a b s t = Viewing {
- getView :: s -> a
- newtype Previewing a b s t = Previewing {
- getPreview :: s -> Maybe a
- newtype Setting a b s t = Setting {
- getSet :: (a -> b) -> s -> t
- newtype Classifying m a b s t = Classifying {
- getClassify :: Monad m => m s -> b -> t
- newtype Aggregating a b s t = Aggregate {
- getAggregate :: [s] -> ([a] -> b) -> t
- newtype Updating m a b s t = Update {}
- newtype Replacing a b s t = Replace {
- getReplace :: (a -> b) -> s -> t
- (^.) :: s -> (Viewing a b a b -> Viewing a b s t) -> a
- (?.) :: s -> (Previewing a b a b -> Previewing a b s t) -> Maybe a
- (.~) :: (Setting a b a b -> Setting a b s t) -> b -> s -> t
- (%~) :: (Replacing a b a b -> Replacing a b s t) -> (a -> b) -> s -> t
- (.?) :: Monad m => (Classifying m a b a b -> Classifying m a b s t) -> b -> m s -> t
- (>-) :: (Aggregating a b a b -> Aggregating a b s t) -> ([a] -> b) -> [s] -> t
- mupdate :: Monad m => (Updating m a b a b -> Updating m a b s t) -> b -> s -> m t
Documentation
newtype Viewing a b s t Source #
Viewing is a profunctor that can be used to implement a view
operation. Viewing is a Tambara module for all the optics that
admit the view
operator.
Instances
Monad m => Tambara (Any :: Type -> Constraint) ((->) :: Type -> Type -> Type) (Any :: Type -> Constraint) ((->) :: Type -> Type -> Type) (Algebra m :: Type -> Constraint) ((->) :: Type -> Type -> Type) (,) () (,) (,) (Viewing a b :: Type -> Type -> Type) Source # | |
Tambara (Any :: Type -> Constraint) ((->) :: Type -> Type -> Type) (Any :: Type -> Constraint) ((->) :: Type -> Type -> Type) (Any :: Type -> Constraint) ((->) :: Type -> Type -> Type) (,) () (,) (,) (Viewing a b :: Type -> Type -> Type) Source # | |
Profunctor (Any :: Type -> Constraint) ((->) :: Type -> Type -> Type) (Any :: Type -> Constraint) ((->) :: Type -> Type -> Type) (Viewing a b :: Type -> Type -> Type) Source # | |
newtype Previewing a b s t Source #
Previewing is a profunctor that can be used to implement a
preview
operation. Previewing is a Tambara module for all the
optics that admit the preview
operator.
Previewing | |
|
Instances
newtype Setting a b s t Source #
Setting is a Tambara module for all the optics that admit the
set
operator.
Instances
Tambara (Any :: Type -> Constraint) ((->) :: Type -> Type -> Type) (Any :: Type -> Constraint) ((->) :: Type -> Type -> Type) (Any :: Type -> Constraint) ((->) :: Type -> Type -> Type) Either Void Either Either (Setting a b :: Type -> Type -> Type) Source # | |
Tambara (Any :: Type -> Constraint) ((->) :: Type -> Type -> Type) (Any :: Type -> Constraint) ((->) :: Type -> Type -> Type) (Any :: Type -> Constraint) ((->) :: Type -> Type -> Type) (,) () (,) (,) (Setting a b :: Type -> Type -> Type) Source # | |
Profunctor (Any :: Type -> Constraint) ((->) :: Type -> Type -> Type) (Any :: Type -> Constraint) ((->) :: Type -> Type -> Type) (Setting a b :: Type -> Type -> Type) Source # | |
newtype Classifying m a b s t Source #
Classifying is a Tambara module for all the optics that admit the
classify
operator.
Classifying | |
|
Instances
Monad m => Tambara (Any :: Type -> Constraint) ((->) :: Type -> Type -> Type) (Any :: Type -> Constraint) ((->) :: Type -> Type -> Type) (Algebra m :: Type -> Constraint) ((->) :: Type -> Type -> Type) (,) () (,) (,) (Classifying m a b :: Type -> Type -> Type) Source # | |
Defined in Combinators tambara :: (Any x, Any y, Algebra m w) => Classifying m a b x y -> Classifying m a b (w, x) (w, y) Source # | |
Monad m => Profunctor (Any :: Type -> Constraint) ((->) :: Type -> Type -> Type) (Any :: Type -> Constraint) ((->) :: Type -> Type -> Type) (Classifying m a b :: Type -> Type -> Type) Source # | |
Defined in Combinators dimap :: (Any x1, Any x2, Any y1, Any y2) => (x2 -> x1) -> (y1 -> y2) -> Classifying m a b x1 y1 -> Classifying m a b x2 y2 Source # |
newtype Aggregating a b s t Source #
Aggregating is a Tambara module for the optics that admit an aggregate
operator.
Aggregate | |
|
Instances
newtype Updating m a b s t Source #
Updating is a Tambara module for the optics admitting an update
operator.
Instances
Monad m => Tambara (Any :: Type -> Constraint) ((->) :: Type -> Type -> Type) (Any :: Type -> Constraint) (Kleisli m :: Type -> Type -> Type) (Any :: Type -> Constraint) ((->) :: Type -> Type -> Type) (,) () (,) (,) (Updating m a b :: Type -> Type -> Type) Source # | |
Monad m => Profunctor (Any :: Type -> Constraint) ((->) :: Type -> Type -> Type) (Any :: Type -> Constraint) ((->) :: Type -> Type -> Type) (Updating m a b :: Type -> Type -> Type) Source # | |
Monad m => Profunctor (Any :: Type -> Constraint) ((->) :: Type -> Type -> Type) (Any :: Type -> Constraint) (Kleisli m :: Type -> Type -> Type) (Updating m a b :: Type -> Type -> Type) Source # | |
newtype Replacing a b s t Source #
Replacing is a Tambara module for the optics admitting an over
operator.
Replace | |
|
Instances
(^.) :: s -> (Viewing a b a b -> Viewing a b s t) -> a infixl 8 Source #
Inspired by the "view" operator of Kmett et al's lens library. The
fixity and semantics are such that subsequent field accesses can be
performed with .
.
(?.) :: s -> (Previewing a b a b -> Previewing a b s t) -> Maybe a infixl 8 Source #
Inspired by the "preview" operator of Kmett et al's lens library. The
fixity and semantics are such that subsequent field accesses can be
performed with .
.
(.~) :: (Setting a b a b -> Setting a b s t) -> b -> s -> t infixl 8 Source #
Inspired by the "set" operator of Kmett et al's lens library. The
fixity and semantics are such that subsequent field accesses can be
performed with .
.
(%~) :: (Replacing a b a b -> Replacing a b s t) -> (a -> b) -> s -> t infixl 8 Source #
Inspired by the "over" operator of Kmett et al's lens library. The
fixity and semantics are such that subsequent field accesses can be
performed with .
.
(.?) :: Monad m => (Classifying m a b a b -> Classifying m a b s t) -> b -> m s -> t infixl 8 Source #
A "classify" operator. The fixity and semantics are such that
subsequent field accesses can be performed with .
.
(>-) :: (Aggregating a b a b -> Aggregating a b s t) -> ([a] -> b) -> [s] -> t infixl 8 Source #
An "aggregate" operator. The fixity and semantics are such that
subsequent field accesses can be performed with .
.