lens-4.19.2: Lenses, Folds and Traversals

Copyright(C) 2012-16 Edward Kmett
LicenseBSD-style (see the file LICENSE)
MaintainerEdward Kmett <ekmett@gmail.com>
Stabilityprovisional
PortabilityRank2Types
Safe HaskellTrustworthy
LanguageHaskell2010

Control.Lens.Getter

Contents

Description

A Getter s a is just any function (s -> a), which we've flipped into continuation passing style, (a -> r) -> s -> r and decorated with Const to obtain:

type Getting r s a = (a -> Const r a) -> s -> Const r s

If we restrict access to knowledge about the type r, we could get:

type Getter s a = forall r. Getting r s a

However, for Getter (but not for Getting) we actually permit any functor f which is an instance of both Functor and Contravariant:

type Getter s a = forall f. (Contravariant f, Functor f) => (a -> f a) -> s -> f s

Everything you can do with a function, you can do with a Getter, but note that because of the continuation passing style (.) composes them in the opposite order.

Since it is only a function, every Getter obviously only retrieves a single value for a given input.

A common question is whether you can combine multiple Getters to retrieve multiple values. Recall that all Getters are Folds and that we have a Monoid m => Applicative (Const m) instance to play with. Knowing this, we can use <> to glue Folds together:

>>> (1, 2, 3, 4, 5) ^.. (_2 <> _3 <> _5)
[2,3,5]
Synopsis

Getters

type Getter s a = forall f. (Contravariant f, Functor f) => (a -> f a) -> s -> f s Source #

A Getter describes how to retrieve a single value in a way that can be composed with other LensLike constructions.

Unlike a Lens a Getter is read-only. Since a Getter cannot be used to write back there are no Lens laws that can be applied to it. In fact, it is isomorphic to an arbitrary function from (s -> a).

Moreover, a Getter can be used directly as a Fold, since it just ignores the Applicative.

type IndexedGetter i s a = forall p f. (Indexable i p, Contravariant f, Functor f) => p a (f a) -> s -> f s Source #

Every IndexedGetter is a valid IndexedFold and can be used for Getting like a Getter.

type Getting r s a = (a -> Const r a) -> s -> Const r s Source #

When you see this in a type signature it indicates that you can pass the function a Lens, Getter, Traversal, Fold, Prism, Iso, or one of the indexed variants, and it will just "do the right thing".

Most Getter combinators are able to be used with both a Getter or a Fold in limited situations, to do so, they need to be monomorphic in what we are going to extract with Const. To be compatible with Lens, Traversal and Iso we also restricted choices of the irrelevant t and b parameters.

If a function accepts a Getting r s a, then when r is a Monoid, then you can pass a Fold (or Traversal), otherwise you can only pass this a Getter or Lens.

type IndexedGetting i m s a = Indexed i a (Const m a) -> s -> Const m s Source #

Used to consume an IndexedFold.

type Accessing p m s a = p a (Const m a) -> s -> Const m s Source #

This is a convenient alias used when consuming (indexed) getters and (indexed) folds in a highly general fashion.

Building Getters

to :: (Profunctor p, Contravariant f) => (s -> a) -> Optic' p f s a Source #

Build an (index-preserving) Getter from an arbitrary Haskell function.

to f . to g ≡ to (g . f)
a ^. to f ≡ f a
>>> a ^.to f
f a
>>> ("hello","world")^.to snd
"world"
>>> 5^.to succ
6
>>> (0, -5)^._2.to abs
5
to :: (s -> a) -> IndexPreservingGetter s a

ito :: (Indexable i p, Contravariant f) => (s -> (i, a)) -> Over' p f s a Source #

ito :: (s -> (i, a)) -> IndexedGetter i s a

like :: (Profunctor p, Contravariant f, Functor f) => a -> Optic' p f s a Source #

Build an constant-valued (index-preserving) Getter from an arbitrary Haskell value.

like a . like b ≡ like b
a ^. like b ≡ b
a ^. like b ≡ a ^. to (const b)

This can be useful as a second case failing a Fold e.g. foo failing like 0

like :: a -> IndexPreservingGetter s a

ilike :: (Indexable i p, Contravariant f, Functor f) => i -> a -> Over' p f s a Source #

ilike :: i -> a -> IndexedGetter i s a

Combinators for Getters and Folds

(^.) :: s -> Getting a s a -> a infixl 8 Source #

View the value pointed to by a Getter or Lens or the result of folding over all the results of a Fold or Traversal that points at a monoidal values.

This is the same operation as view with the arguments flipped.

The fixity and semantics are such that subsequent field accesses can be performed with (.).

>>> (a,b)^._2
b
>>> ("hello","world")^._2
"world"
>>> import Data.Complex
>>> ((0, 1 :+ 2), 3)^._1._2.to magnitude
2.23606797749979
(^.) ::             s -> Getter s a     -> a
(^.) :: Monoid m => s -> Fold s m       -> m
(^.) ::             s -> Iso' s a       -> a
(^.) ::             s -> Lens' s a      -> a
(^.) :: Monoid m => s -> Traversal' s m -> m

view :: MonadReader s m => Getting a s a -> m a Source #

View the value pointed to by a Getter, Iso or Lens or the result of folding over all the results of a Fold or Traversal that points at a monoidal value.

view . toid
>>> view (to f) a
f a
>>> view _2 (1,"hello")
"hello"
>>> view (to succ) 5
6
>>> view (_2._1) ("hello",("world","!!!"))
"world"

As view is commonly used to access the target of a Getter or obtain a monoidal summary of the targets of a Fold, It may be useful to think of it as having one of these more restricted signatures:

view ::             Getter s a     -> s -> a
view :: Monoid m => Fold s m       -> s -> m
view ::             Iso' s a       -> s -> a
view ::             Lens' s a      -> s -> a
view :: Monoid m => Traversal' s m -> s -> m

In a more general setting, such as when working with a Monad transformer stack you can use:

view :: MonadReader s m             => Getter s a     -> m a
view :: (MonadReader s m, Monoid a) => Fold s a       -> m a
view :: MonadReader s m             => Iso' s a       -> m a
view :: MonadReader s m             => Lens' s a      -> m a
view :: (MonadReader s m, Monoid a) => Traversal' s a -> m a

views :: MonadReader s m => LensLike' (Const r) s a -> (a -> r) -> m r Source #

View a function of the value pointed to by a Getter or Lens or the result of folding over the result of mapping the targets of a Fold or Traversal.

views l f ≡ view (l . to f)
>>> views (to f) g a
g (f a)
>>> views _2 length (1,"hello")
5

As views is commonly used to access the target of a Getter or obtain a monoidal summary of the targets of a Fold, It may be useful to think of it as having one of these more restricted signatures:

views ::             Getter s a     -> (a -> r) -> s -> r
views :: Monoid m => Fold s a       -> (a -> m) -> s -> m
views ::             Iso' s a       -> (a -> r) -> s -> r
views ::             Lens' s a      -> (a -> r) -> s -> r
views :: Monoid m => Traversal' s a -> (a -> m) -> s -> m

In a more general setting, such as when working with a Monad transformer stack you can use:

views :: MonadReader s m             => Getter s a     -> (a -> r) -> m r
views :: (MonadReader s m, Monoid r) => Fold s a       -> (a -> r) -> m r
views :: MonadReader s m             => Iso' s a       -> (a -> r) -> m r
views :: MonadReader s m             => Lens' s a      -> (a -> r) -> m r
views :: (MonadReader s m, Monoid r) => Traversal' s a -> (a -> r) -> m r
views :: MonadReader s m => Getting r s a -> (a -> r) -> m r

use :: MonadState s m => Getting a s a -> m a Source #

Use the target of a Lens, Iso, or Getter in the current state, or use a summary of a Fold or Traversal that points to a monoidal value.

>>> evalState (use _1) (a,b)
a
>>> evalState (use _1) ("hello","world")
"hello"
use :: MonadState s m             => Getter s a     -> m a
use :: (MonadState s m, Monoid r) => Fold s r       -> m r
use :: MonadState s m             => Iso' s a       -> m a
use :: MonadState s m             => Lens' s a      -> m a
use :: (MonadState s m, Monoid r) => Traversal' s r -> m r

uses :: MonadState s m => LensLike' (Const r) s a -> (a -> r) -> m r Source #

Use the target of a Lens, Iso or Getter in the current state, or use a summary of a Fold or Traversal that points to a monoidal value.

>>> evalState (uses _1 length) ("hello","world")
5
uses :: MonadState s m             => Getter s a     -> (a -> r) -> m r
uses :: (MonadState s m, Monoid r) => Fold s a       -> (a -> r) -> m r
uses :: MonadState s m             => Lens' s a      -> (a -> r) -> m r
uses :: MonadState s m             => Iso' s a       -> (a -> r) -> m r
uses :: (MonadState s m, Monoid r) => Traversal' s a -> (a -> r) -> m r
uses :: MonadState s m => Getting r s t a b -> (a -> r) -> m r

listening :: MonadWriter w m => Getting u w u -> m a -> m (a, u) Source #

This is a generalized form of listen that only extracts the portion of the log that is focused on by a Getter. If given a Fold or a Traversal then a monoidal summary of the parts of the log that are visited will be returned.

listening :: MonadWriter w m             => Getter w u     -> m a -> m (a, u)
listening :: MonadWriter w m             => Lens' w u      -> m a -> m (a, u)
listening :: MonadWriter w m             => Iso' w u       -> m a -> m (a, u)
listening :: (MonadWriter w m, Monoid u) => Fold w u       -> m a -> m (a, u)
listening :: (MonadWriter w m, Monoid u) => Traversal' w u -> m a -> m (a, u)
listening :: (MonadWriter w m, Monoid u) => Prism' w u     -> m a -> m (a, u)

listenings :: MonadWriter w m => Getting v w u -> (u -> v) -> m a -> m (a, v) Source #

This is a generalized form of listen that only extracts the portion of the log that is focused on by a Getter. If given a Fold or a Traversal then a monoidal summary of the parts of the log that are visited will be returned.

listenings :: MonadWriter w m             => Getter w u     -> (u -> v) -> m a -> m (a, v)
listenings :: MonadWriter w m             => Lens' w u      -> (u -> v) -> m a -> m (a, v)
listenings :: MonadWriter w m             => Iso' w u       -> (u -> v) -> m a -> m (a, v)
listenings :: (MonadWriter w m, Monoid v) => Fold w u       -> (u -> v) -> m a -> m (a, v)
listenings :: (MonadWriter w m, Monoid v) => Traversal' w u -> (u -> v) -> m a -> m (a, v)
listenings :: (MonadWriter w m, Monoid v) => Prism' w u     -> (u -> v) -> m a -> m (a, v)

Indexed Getters

Indexed Getter Combinators

(^@.) :: s -> IndexedGetting i (i, a) s a -> (i, a) infixl 8 Source #

View the index and value of an IndexedGetter or IndexedLens.

This is the same operation as iview with the arguments flipped.

The fixity and semantics are such that subsequent field accesses can be performed with (.).

(^@.) :: s -> IndexedGetter i s a -> (i, a)
(^@.) :: s -> IndexedLens' i s a  -> (i, a)

The result probably doesn't have much meaning when applied to an IndexedFold.

iview :: MonadReader s m => IndexedGetting i (i, a) s a -> m (i, a) Source #

View the index and value of an IndexedGetter into the current environment as a pair.

When applied to an IndexedFold the result will most likely be a nonsensical monoidal summary of the indices tupled with a monoidal summary of the values and probably not whatever it is you wanted.

iviews :: MonadReader s m => IndexedGetting i r s a -> (i -> a -> r) -> m r Source #

View a function of the index and value of an IndexedGetter into the current environment.

When applied to an IndexedFold the result will be a monoidal summary instead of a single answer.

iviewsifoldMapOf

iuse :: MonadState s m => IndexedGetting i (i, a) s a -> m (i, a) Source #

Use the index and value of an IndexedGetter into the current state as a pair.

When applied to an IndexedFold the result will most likely be a nonsensical monoidal summary of the indices tupled with a monoidal summary of the values and probably not whatever it is you wanted.

iuses :: MonadState s m => IndexedGetting i r s a -> (i -> a -> r) -> m r Source #

Use a function of the index and value of an IndexedGetter into the current state.

When applied to an IndexedFold the result will be a monoidal summary instead of a single answer.

ilistening :: MonadWriter w m => IndexedGetting i (i, u) w u -> m a -> m (a, (i, u)) Source #

This is a generalized form of listen that only extracts the portion of the log that is focused on by a Getter. If given a Fold or a Traversal then a monoidal summary of the parts of the log that are visited will be returned.

ilistening :: MonadWriter w m             => IndexedGetter i w u     -> m a -> m (a, (i, u))
ilistening :: MonadWriter w m             => IndexedLens' i w u      -> m a -> m (a, (i, u))
ilistening :: (MonadWriter w m, Monoid u) => IndexedFold i w u       -> m a -> m (a, (i, u))
ilistening :: (MonadWriter w m, Monoid u) => IndexedTraversal' i w u -> m a -> m (a, (i, u))

ilistenings :: MonadWriter w m => IndexedGetting i v w u -> (i -> u -> v) -> m a -> m (a, v) Source #

This is a generalized form of listen that only extracts the portion of the log that is focused on by a Getter. If given a Fold or a Traversal then a monoidal summary of the parts of the log that are visited will be returned.

ilistenings :: MonadWriter w m             => IndexedGetter w u     -> (i -> u -> v) -> m a -> m (a, v)
ilistenings :: MonadWriter w m             => IndexedLens' w u      -> (i -> u -> v) -> m a -> m (a, v)
ilistenings :: (MonadWriter w m, Monoid v) => IndexedFold w u       -> (i -> u -> v) -> m a -> m (a, v)
ilistenings :: (MonadWriter w m, Monoid v) => IndexedTraversal' w u -> (i -> u -> v) -> m a -> m (a, v)

Implementation Details

class Contravariant (f :: Type -> Type) where #

The class of contravariant functors.

Whereas in Haskell, one can think of a Functor as containing or producing values, a contravariant functor is a functor that can be thought of as consuming values.

As an example, consider the type of predicate functions a -> Bool. One such predicate might be negative x = x < 0, which classifies integers as to whether they are negative. However, given this predicate, we can re-use it in other situations, providing we have a way to map values to integers. For instance, we can use the negative predicate on a person's bank balance to work out if they are currently overdrawn:

newtype Predicate a = Predicate { getPredicate :: a -> Bool }

instance Contravariant Predicate where
  contramap f (Predicate p) = Predicate (p . f)
                                         |   `- First, map the input...
                                         `----- then apply the predicate.

overdrawn :: Predicate Person
overdrawn = contramap personBankBalance negative

Any instance should be subject to the following laws:

contramap id = id
contramap f . contramap g = contramap (g . f)

Note, that the second law follows from the free theorem of the type of contramap and the first law, so you need only check that the former condition holds.

Minimal complete definition

contramap

Methods

contramap :: (a -> b) -> f b -> f a #

(>$) :: b -> f b -> f a infixl 4 #

Replace all locations in the output with the same value. The default definition is contramap . const, but this may be overridden with a more efficient version.

Instances
Contravariant Predicate

A Predicate is a Contravariant Functor, because contramap can apply its function argument to the input of the predicate.

Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> Predicate b -> Predicate a #

(>$) :: b -> Predicate b -> Predicate a #

Contravariant Comparison

A Comparison is a Contravariant Functor, because contramap can apply its function argument to each input of the comparison function.

Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> Comparison b -> Comparison a #

(>$) :: b -> Comparison b -> Comparison a #

Contravariant Equivalence

Equivalence relations are Contravariant, because you can apply the contramapped function to each input to the equivalence relation.

Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> Equivalence b -> Equivalence a #

(>$) :: b -> Equivalence b -> Equivalence a #

Contravariant (V1 :: Type -> Type) 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> V1 b -> V1 a #

(>$) :: b -> V1 b -> V1 a #

Contravariant (U1 :: Type -> Type) 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> U1 b -> U1 a #

(>$) :: b -> U1 b -> U1 a #

Contravariant (Op a) 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a0 -> b) -> Op a b -> Op a a0 #

(>$) :: b -> Op a b -> Op a a0 #

Contravariant (Proxy :: Type -> Type) 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> Proxy b -> Proxy a #

(>$) :: b -> Proxy b -> Proxy a #

Contravariant m => Contravariant (MaybeT m) 
Instance details

Defined in Control.Monad.Trans.Maybe

Methods

contramap :: (a -> b) -> MaybeT m b -> MaybeT m a #

(>$) :: b -> MaybeT m b -> MaybeT m a #

Contravariant m => Contravariant (ListT m) 
Instance details

Defined in Control.Monad.Trans.List

Methods

contramap :: (a -> b) -> ListT m b -> ListT m a #

(>$) :: b -> ListT m b -> ListT m a #

Contravariant f => Contravariant (Indexing64 f) Source # 
Instance details

Defined in Control.Lens.Internal.Indexed

Methods

contramap :: (a -> b) -> Indexing64 f b -> Indexing64 f a #

(>$) :: b -> Indexing64 f b -> Indexing64 f a #

Contravariant f => Contravariant (Indexing f) Source # 
Instance details

Defined in Control.Lens.Internal.Indexed

Methods

contramap :: (a -> b) -> Indexing f b -> Indexing f a #

(>$) :: b -> Indexing f b -> Indexing f a #

Contravariant f => Contravariant (Rec1 f) 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> Rec1 f b -> Rec1 f a #

(>$) :: b -> Rec1 f b -> Rec1 f a #

Contravariant (Const a :: Type -> Type) 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a0 -> b) -> Const a b -> Const a a0 #

(>$) :: b -> Const a b -> Const a a0 #

Contravariant f => Contravariant (Alt f) 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> Alt f b -> Alt f a #

(>$) :: b -> Alt f b -> Alt f a #

Contravariant f => Contravariant (IdentityT f) 
Instance details

Defined in Control.Monad.Trans.Identity

Methods

contramap :: (a -> b) -> IdentityT f b -> IdentityT f a #

(>$) :: b -> IdentityT f b -> IdentityT f a #

(Functor f, Contravariant g) => Contravariant (ComposeFC f g) 
Instance details

Defined in Data.Functor.Contravariant.Compose

Methods

contramap :: (a -> b) -> ComposeFC f g b -> ComposeFC f g a #

(>$) :: b -> ComposeFC f g b -> ComposeFC f g a #

(Contravariant f, Functor g) => Contravariant (ComposeCF f g) 
Instance details

Defined in Data.Functor.Contravariant.Compose

Methods

contramap :: (a -> b) -> ComposeCF f g b -> ComposeCF f g a #

(>$) :: b -> ComposeCF f g b -> ComposeCF f g a #

Contravariant m => Contravariant (ExceptT e m) 
Instance details

Defined in Control.Monad.Trans.Except

Methods

contramap :: (a -> b) -> ExceptT e m b -> ExceptT e m a #

(>$) :: b -> ExceptT e m b -> ExceptT e m a #

Contravariant m => Contravariant (ErrorT e m) 
Instance details

Defined in Control.Monad.Trans.Error

Methods

contramap :: (a -> b) -> ErrorT e m b -> ErrorT e m a #

(>$) :: b -> ErrorT e m b -> ErrorT e m a #

Contravariant m => Contravariant (StateT s m) 
Instance details

Defined in Control.Monad.Trans.State.Lazy

Methods

contramap :: (a -> b) -> StateT s m b -> StateT s m a #

(>$) :: b -> StateT s m b -> StateT s m a #

Contravariant m => Contravariant (StateT s m) 
Instance details

Defined in Control.Monad.Trans.State.Strict

Methods

contramap :: (a -> b) -> StateT s m b -> StateT s m a #

(>$) :: b -> StateT s m b -> StateT s m a #

Contravariant m => Contravariant (WriterT w m) 
Instance details

Defined in Control.Monad.Trans.Writer.Lazy

Methods

contramap :: (a -> b) -> WriterT w m b -> WriterT w m a #

(>$) :: b -> WriterT w m b -> WriterT w m a #

Contravariant m => Contravariant (WriterT w m) 
Instance details

Defined in Control.Monad.Trans.Writer.Strict

Methods

contramap :: (a -> b) -> WriterT w m b -> WriterT w m a #

(>$) :: b -> WriterT w m b -> WriterT w m a #

Contravariant f => Contravariant (Star f a) 
Instance details

Defined in Data.Profunctor.Types

Methods

contramap :: (a0 -> b) -> Star f a b -> Star f a a0 #

(>$) :: b -> Star f a b -> Star f a a0 #

Contravariant (Forget r a) 
Instance details

Defined in Data.Profunctor.Types

Methods

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

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

Contravariant f => Contravariant (Reverse f)

Derived instance.

Instance details

Defined in Data.Functor.Reverse

Methods

contramap :: (a -> b) -> Reverse f b -> Reverse f a #

(>$) :: b -> Reverse f b -> Reverse f a #

Contravariant (Constant a :: Type -> Type) 
Instance details

Defined in Data.Functor.Constant

Methods

contramap :: (a0 -> b) -> Constant a b -> Constant a a0 #

(>$) :: b -> Constant a b -> Constant a a0 #

Contravariant f => Contravariant (Backwards f)

Derived instance.

Instance details

Defined in Control.Applicative.Backwards

Methods

contramap :: (a -> b) -> Backwards f b -> Backwards f a #

(>$) :: b -> Backwards f b -> Backwards f a #

Contravariant f => Contravariant (AlongsideRight f a) Source # 
Instance details

Defined in Control.Lens.Internal.Getter

Methods

contramap :: (a0 -> b) -> AlongsideRight f a b -> AlongsideRight f a a0 #

(>$) :: b -> AlongsideRight f a b -> AlongsideRight f a a0 #

Contravariant f => Contravariant (AlongsideLeft f b) Source # 
Instance details

Defined in Control.Lens.Internal.Getter

Methods

contramap :: (a -> b0) -> AlongsideLeft f b b0 -> AlongsideLeft f b a #

(>$) :: b0 -> AlongsideLeft f b b0 -> AlongsideLeft f b a #

Contravariant (Effect m r) Source # 
Instance details

Defined in Control.Lens.Internal.Zoom

Methods

contramap :: (a -> b) -> Effect m r b -> Effect m r a #

(>$) :: b -> Effect m r b -> Effect m r a #

Contravariant (K1 i c :: Type -> Type) 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> K1 i c b -> K1 i c a #

(>$) :: b -> K1 i c b -> K1 i c a #

(Contravariant f, Contravariant g) => Contravariant (f :+: g) 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> (f :+: g) b -> (f :+: g) a #

(>$) :: b -> (f :+: g) b -> (f :+: g) a #

(Contravariant f, Contravariant g) => Contravariant (f :*: g) 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> (f :*: g) b -> (f :*: g) a #

(>$) :: b -> (f :*: g) b -> (f :*: g) a #

(Contravariant f, Contravariant g) => Contravariant (Product f g) 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> Product f g b -> Product f g a #

(>$) :: b -> Product f g b -> Product f g a #

(Contravariant f, Contravariant g) => Contravariant (Sum f g) 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> Sum f g b -> Sum f g a #

(>$) :: b -> Sum f g b -> Sum f g a #

Contravariant m => Contravariant (ReaderT r m) 
Instance details

Defined in Control.Monad.Trans.Reader

Methods

contramap :: (a -> b) -> ReaderT r m b -> ReaderT r m a #

(>$) :: b -> ReaderT r m b -> ReaderT r m a #

Contravariant f => Contravariant (M1 i c f) 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> M1 i c f b -> M1 i c f a #

(>$) :: b -> M1 i c f b -> M1 i c f a #

(Functor f, Contravariant g) => Contravariant (f :.: g) 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> (f :.: g) b -> (f :.: g) a #

(>$) :: b -> (f :.: g) b -> (f :.: g) a #

(Functor f, Contravariant g) => Contravariant (Compose f g) 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a -> b) -> Compose f g b -> Compose f g a #

(>$) :: b -> Compose f g b -> Compose f g a #

Contravariant m => Contravariant (RWST r w s m) 
Instance details

Defined in Control.Monad.Trans.RWS.Lazy

Methods

contramap :: (a -> b) -> RWST r w s m b -> RWST r w s m a #

(>$) :: b -> RWST r w s m b -> RWST r w s m a #

Contravariant m => Contravariant (RWST r w s m) 
Instance details

Defined in Control.Monad.Trans.RWS.Strict

Methods

contramap :: (a -> b) -> RWST r w s m b -> RWST r w s m a #

(>$) :: b -> RWST r w s m b -> RWST r w s m a #

(Profunctor p, Contravariant g) => Contravariant (PretextT p g a b) Source # 
Instance details

Defined in Control.Lens.Internal.Context

Methods

contramap :: (a0 -> b0) -> PretextT p g a b b0 -> PretextT p g a b a0 #

(>$) :: b0 -> PretextT p g a b b0 -> PretextT p g a b a0 #

(Profunctor p, Contravariant g) => Contravariant (BazaarT1 p g a b) Source # 
Instance details

Defined in Control.Lens.Internal.Bazaar

Methods

contramap :: (a0 -> b0) -> BazaarT1 p g a b b0 -> BazaarT1 p g a b a0 #

(>$) :: b0 -> BazaarT1 p g a b b0 -> BazaarT1 p g a b a0 #

(Profunctor p, Contravariant g) => Contravariant (BazaarT p g a b) Source # 
Instance details

Defined in Control.Lens.Internal.Bazaar

Methods

contramap :: (a0 -> b0) -> BazaarT p g a b b0 -> BazaarT p g a b a0 #

(>$) :: b0 -> BazaarT p g a b b0 -> BazaarT p g a b a0 #

Contravariant f => Contravariant (TakingWhile p f a b) Source # 
Instance details

Defined in Control.Lens.Internal.Magma

Methods

contramap :: (a0 -> b0) -> TakingWhile p f a b b0 -> TakingWhile p f a b a0 #

(>$) :: b0 -> TakingWhile p f a b b0 -> TakingWhile p f a b a0 #

Contravariant (EffectRWS w st m s) Source # 
Instance details

Defined in Control.Lens.Internal.Zoom

Methods

contramap :: (a -> b) -> EffectRWS w st m s b -> EffectRWS w st m s a #

(>$) :: b -> EffectRWS w st m s b -> EffectRWS w st m s a #

getting :: (Profunctor p, Profunctor q, Functor f, Contravariant f) => Optical p q f s t a b -> Optical' p q f s a Source #

Coerce a Getter-compatible Optical to an Optical'. This is useful when using a Traversal that is not simple as a Getter or a Fold.

getting :: Traversal s t a b          -> Fold s a
getting :: Lens s t a b               -> Getter s a
getting :: IndexedTraversal i s t a b -> IndexedFold i s a
getting :: IndexedLens i s t a b      -> IndexedGetter i s a

newtype Const a (b :: k) :: forall k. Type -> k -> Type #

The Const functor.

Constructors

Const 

Fields

Instances
Generic1 (Const a :: k -> Type) 
Instance details

Defined in Data.Functor.Const

Associated Types

type Rep1 (Const a) :: k -> Type #

Methods

from1 :: Const a a0 -> Rep1 (Const a) a0 #

to1 :: Rep1 (Const a) a0 -> Const a a0 #

TraversableWithIndex Void (Const e :: Type -> Type) Source # 
Instance details

Defined in Control.Lens.Indexed

Methods

itraverse :: Applicative f => (Void -> a -> f b) -> Const e a -> f (Const e b) Source #

itraversed :: IndexedTraversal Void (Const e a) (Const e b) a b Source #

FoldableWithIndex Void (Const e :: Type -> Type) Source # 
Instance details

Defined in Control.Lens.Indexed

Methods

ifoldMap :: Monoid m => (Void -> a -> m) -> Const e a -> m Source #

ifolded :: IndexedFold Void (Const e a) a Source #

ifoldr :: (Void -> a -> b -> b) -> b -> Const e a -> b Source #

ifoldl :: (Void -> b -> a -> b) -> b -> Const e a -> b Source #

ifoldr' :: (Void -> a -> b -> b) -> b -> Const e a -> b Source #

ifoldl' :: (Void -> b -> a -> b) -> b -> Const e a -> b Source #

FunctorWithIndex Void (Const e :: Type -> Type) Source # 
Instance details

Defined in Control.Lens.Indexed

Methods

imap :: (Void -> a -> b) -> Const e a -> Const e b Source #

imapped :: IndexedSetter Void (Const e a) (Const e b) a b Source #

Unbox a => Vector Vector (Const a b) 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) (Const a b) -> m (Vector (Const a b)) #

basicUnsafeThaw :: PrimMonad m => Vector (Const a b) -> m (Mutable Vector (PrimState m) (Const a b)) #

basicLength :: Vector (Const a b) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (Const a b) -> Vector (Const a b) #

basicUnsafeIndexM :: Monad m => Vector (Const a b) -> Int -> m (Const a b) #

basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) (Const a b) -> Vector (Const a b) -> m () #

elemseq :: Vector (Const a b) -> Const a b -> b0 -> b0 #

Unbox a => MVector MVector (Const a b) 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

basicLength :: MVector s (Const a b) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s (Const a b) -> MVector s (Const a b) #

basicOverlaps :: MVector s (Const a b) -> MVector s (Const a b) -> Bool #

basicUnsafeNew :: PrimMonad m => Int -> m (MVector (PrimState m) (Const a b)) #

basicInitialize :: PrimMonad m => MVector (PrimState m) (Const a b) -> m () #

basicUnsafeReplicate :: PrimMonad m => Int -> Const a b -> m (MVector (PrimState m) (Const a b)) #

basicUnsafeRead :: PrimMonad m => MVector (PrimState m) (Const a b) -> Int -> m (Const a b) #

basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) (Const a b) -> Int -> Const a b -> m () #

basicClear :: PrimMonad m => MVector (PrimState m) (Const a b) -> m () #

basicSet :: PrimMonad m => MVector (PrimState m) (Const a b) -> Const a b -> m () #

basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) (Const a b) -> MVector (PrimState m) (Const a b) -> m () #

basicUnsafeMove :: PrimMonad m => MVector (PrimState m) (Const a b) -> MVector (PrimState m) (Const a b) -> m () #

basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) (Const a b) -> Int -> m (MVector (PrimState m) (Const a b)) #

Bitraversable (Const :: Type -> Type -> Type)

Since: base-4.10.0.0

Instance details

Defined in Data.Bitraversable

Methods

bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> Const a b -> f (Const c d) #

Bifoldable (Const :: Type -> Type -> Type)

Since: base-4.10.0.0

Instance details

Defined in Data.Bifoldable

Methods

bifold :: Monoid m => Const m m -> m #

bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> Const a b -> m #

bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> Const a b -> c #

bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> Const a b -> c #

Bifunctor (Const :: Type -> Type -> Type)

Since: base-4.8.0.0

Instance details

Defined in Data.Bifunctor

Methods

bimap :: (a -> b) -> (c -> d) -> Const a c -> Const b d #

first :: (a -> b) -> Const a c -> Const b c #

second :: (b -> c) -> Const a b -> Const a c #

Eq2 (Const :: Type -> Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftEq2 :: (a -> b -> Bool) -> (c -> d -> Bool) -> Const a c -> Const b d -> Bool #

Ord2 (Const :: Type -> Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftCompare2 :: (a -> b -> Ordering) -> (c -> d -> Ordering) -> Const a c -> Const b d -> Ordering #

Read2 (Const :: Type -> Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftReadsPrec2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> Int -> ReadS (Const a b) #

liftReadList2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> ReadS [Const a b] #

liftReadPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec (Const a b) #

liftReadListPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec [Const a b] #

Show2 (Const :: Type -> Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftShowsPrec2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> Int -> Const a b -> ShowS #

liftShowList2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> [Const a b] -> ShowS #

Biapplicative (Const :: Type -> Type -> Type) 
Instance details

Defined in Data.Biapplicative

Methods

bipure :: a -> b -> Const a b #

(<<*>>) :: Const (a -> b) (c -> d) -> Const a c -> Const b d #

biliftA2 :: (a -> b -> c) -> (d -> e -> f) -> Const a d -> Const b e -> Const c f #

(*>>) :: Const a b -> Const c d -> Const c d #

(<<*) :: Const a b -> Const c d -> Const a b #

NFData2 (Const :: Type -> Type -> Type)

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

liftRnf2 :: (a -> ()) -> (b -> ()) -> Const a b -> () #

Hashable2 (Const :: Type -> Type -> Type) 
Instance details

Defined in Data.Hashable.Class

Methods

liftHashWithSalt2 :: (Int -> a -> Int) -> (Int -> b -> Int) -> Int -> Const a b -> Int #

Bitraversable1 (Const :: Type -> Type -> Type) 
Instance details

Defined in Data.Semigroup.Traversable.Class

Methods

bitraverse1 :: Apply f => (a -> f b) -> (c -> f d) -> Const a c -> f (Const b d) #

bisequence1 :: Apply f => Const (f a) (f b) -> f (Const a b) #

Bifoldable1 (Const :: Type -> Type -> Type) 
Instance details

Defined in Data.Semigroup.Foldable.Class

Methods

bifold1 :: Semigroup m => Const m m -> m #

bifoldMap1 :: Semigroup m => (a -> m) -> (b -> m) -> Const a b -> m #

Biapply (Const :: Type -> Type -> Type) 
Instance details

Defined in Data.Functor.Bind.Class

Methods

(<<.>>) :: Const (a -> b) (c -> d) -> Const a c -> Const b d #

(.>>) :: Const a b -> Const c d -> Const c d #

(<<.) :: Const a b -> Const c d -> Const a b #

Semigroupoid (Const :: Type -> Type -> Type) 
Instance details

Defined in Data.Semigroupoid

Methods

o :: Const j k1 -> Const i j -> Const i k1 #

Sieve (Forget r) (Const r :: Type -> Type) 
Instance details

Defined in Data.Profunctor.Sieve

Methods

sieve :: Forget r a b -> a -> Const r b #

Functor (Const m :: Type -> Type)

Since: base-2.1

Instance details

Defined in Data.Functor.Const

Methods

fmap :: (a -> b) -> Const m a -> Const m b #

(<$) :: a -> Const m b -> Const m a #

Monoid m => Applicative (Const m :: Type -> Type)

Since: base-2.0.1

Instance details

Defined in Data.Functor.Const

Methods

pure :: a -> Const m a #

(<*>) :: Const m (a -> b) -> Const m a -> Const m b #

liftA2 :: (a -> b -> c) -> Const m a -> Const m b -> Const m c #

(*>) :: Const m a -> Const m b -> Const m b #

(<*) :: Const m a -> Const m b -> Const m a #

Foldable (Const m :: Type -> Type)

Since: base-4.7.0.0

Instance details

Defined in Data.Functor.Const

Methods

fold :: Monoid m0 => Const m m0 -> m0 #

foldMap :: Monoid m0 => (a -> m0) -> Const m a -> m0 #

foldr :: (a -> b -> b) -> b -> Const m a -> b #

foldr' :: (a -> b -> b) -> b -> Const m a -> b #

foldl :: (b -> a -> b) -> b -> Const m a -> b #

foldl' :: (b -> a -> b) -> b -> Const m a -> b #

foldr1 :: (a -> a -> a) -> Const m a -> a #

foldl1 :: (a -> a -> a) -> Const m a -> a #

toList :: Const m a -> [a] #

null :: Const m a -> Bool #

length :: Const m a -> Int #

elem :: Eq a => a -> Const m a -> Bool #

maximum :: Ord a => Const m a -> a #

minimum :: Ord a => Const m a -> a #

sum :: Num a => Const m a -> a #

product :: Num a => Const m a -> a #

Traversable (Const m :: Type -> Type)

Since: base-4.7.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> Const m a -> f (Const m b) #

sequenceA :: Applicative f => Const m (f a) -> f (Const m a) #

mapM :: Monad m0 => (a -> m0 b) -> Const m a -> m0 (Const m b) #

sequence :: Monad m0 => Const m (m0 a) -> m0 (Const m a) #

Contravariant (Const a :: Type -> Type) 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a0 -> b) -> Const a b -> Const a a0 #

(>$) :: b -> Const a b -> Const a a0 #

Eq a => Eq1 (Const a :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftEq :: (a0 -> b -> Bool) -> Const a a0 -> Const a b -> Bool #

Ord a => Ord1 (Const a :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftCompare :: (a0 -> b -> Ordering) -> Const a a0 -> Const a b -> Ordering #

Read a => Read1 (Const a :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftReadsPrec :: (Int -> ReadS a0) -> ReadS [a0] -> Int -> ReadS (Const a a0) #

liftReadList :: (Int -> ReadS a0) -> ReadS [a0] -> ReadS [Const a a0] #

liftReadPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec (Const a a0) #

liftReadListPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec [Const a a0] #

Show a => Show1 (Const a :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftShowsPrec :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> Int -> Const a a0 -> ShowS #

liftShowList :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> [Const a a0] -> ShowS #

NFData a => NFData1 (Const a :: Type -> Type)

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

liftRnf :: (a0 -> ()) -> Const a a0 -> () #

Hashable a => Hashable1 (Const a :: Type -> Type) 
Instance details

Defined in Data.Hashable.Class

Methods

liftHashWithSalt :: (Int -> a0 -> Int) -> Int -> Const a a0 -> Int #

Semigroup m => Apply (Const m :: Type -> Type)

A 'Const m' is not Applicative unless its m is a Monoid, but it is an instance of Apply

Instance details

Defined in Data.Functor.Bind.Class

Methods

(<.>) :: Const m (a -> b) -> Const m a -> Const m b #

(.>) :: Const m a -> Const m b -> Const m b #

(<.) :: Const m a -> Const m b -> Const m a #

liftF2 :: (a -> b -> c) -> Const m a -> Const m b -> Const m c #

ComonadCofree (Const b :: Type -> Type) ((,) b) 
Instance details

Defined in Control.Comonad.Cofree.Class

Methods

unwrap :: (b, a) -> Const b (b, a) #

Bounded a => Bounded (Const a b)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Const

Methods

minBound :: Const a b #

maxBound :: Const a b #

Enum a => Enum (Const a b)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Const

Methods

succ :: Const a b -> Const a b #

pred :: Const a b -> Const a b #

toEnum :: Int -> Const a b #

fromEnum :: Const a b -> Int #

enumFrom :: Const a b -> [Const a b] #

enumFromThen :: Const a b -> Const a b -> [Const a b] #

enumFromTo :: Const a b -> Const a b -> [Const a b] #

enumFromThenTo :: Const a b -> Const a b -> Const a b -> [Const a b] #

Eq a => Eq (Const a b)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Const

Methods

(==) :: Const a b -> Const a b -> Bool #

(/=) :: Const a b -> Const a b -> Bool #

Floating a => Floating (Const a b)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Const

Methods

pi :: Const a b #

exp :: Const a b -> Const a b #

log :: Const a b -> Const a b #

sqrt :: Const a b -> Const a b #

(**) :: Const a b -> Const a b -> Const a b #

logBase :: Const a b -> Const a b -> Const a b #

sin :: Const a b -> Const a b #

cos :: Const a b -> Const a b #

tan :: Const a b -> Const a b #

asin :: Const a b -> Const a b #

acos :: Const a b -> Const a b #

atan :: Const a b -> Const a b #

sinh :: Const a b -> Const a b #

cosh :: Const a b -> Const a b #

tanh :: Const a b -> Const a b #

asinh :: Const a b -> Const a b #

acosh :: Const a b -> Const a b #

atanh :: Const a b -> Const a b #

log1p :: Const a b -> Const a b #

expm1 :: Const a b -> Const a b #

log1pexp :: Const a b -> Const a b #

log1mexp :: Const a b -> Const a b #

Fractional a => Fractional (Const a b)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Const

Methods

(/) :: Const a b -> Const a b -> Const a b #

recip :: Const a b -> Const a b #

fromRational :: Rational -> Const a b #

Integral a => Integral (Const a b)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Const

Methods

quot :: Const a b -> Const a b -> Const a b #

rem :: Const a b -> Const a b -> Const a b #

div :: Const a b -> Const a b -> Const a b #

mod :: Const a b -> Const a b -> Const a b #

quotRem :: Const a b -> Const a b -> (Const a b, Const a b) #

divMod :: Const a b -> Const a b -> (Const a b, Const a b) #

toInteger :: Const a b -> Integer #

(Typeable k, Data a, Typeable b) => Data (Const a b)

Since: base-4.10.0.0

Instance details

Defined in Data.Data

Methods

gfoldl :: (forall d b0. Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) -> Const a b -> c (Const a b) #

gunfold :: (forall b0 r. Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Const a b) #

toConstr :: Const a b -> Constr #

dataTypeOf :: Const a b -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Const a b)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Const a b)) #

gmapT :: (forall b0. Data b0 => b0 -> b0) -> Const a b -> Const a b #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Const a b -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Const a b -> r #

gmapQ :: (forall d. Data d => d -> u) -> Const a b -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Const a b -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Const a b -> m (Const a b) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Const a b -> m (Const a b) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Const a b -> m (Const a b) #

Num a => Num (Const a b)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Const

Methods

(+) :: Const a b -> Const a b -> Const a b #

(-) :: Const a b -> Const a b -> Const a b #

(*) :: Const a b -> Const a b -> Const a b #

negate :: Const a b -> Const a b #

abs :: Const a b -> Const a b #

signum :: Const a b -> Const a b #

fromInteger :: Integer -> Const a b #

Ord a => Ord (Const a b)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Const

Methods

compare :: Const a b -> Const a b -> Ordering #

(<) :: Const a b -> Const a b -> Bool #

(<=) :: Const a b -> Const a b -> Bool #

(>) :: Const a b -> Const a b -> Bool #

(>=) :: Const a b -> Const a b -> Bool #

max :: Const a b -> Const a b -> Const a b #

min :: Const a b -> Const a b -> Const a b #

Read a => Read (Const a b)

This instance would be equivalent to the derived instances of the Const newtype if the runConst field were removed

Since: base-4.8.0.0

Instance details

Defined in Data.Functor.Const

Real a => Real (Const a b)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Const

Methods

toRational :: Const a b -> Rational #

RealFloat a => RealFloat (Const a b)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Const

Methods

floatRadix :: Const a b -> Integer #

floatDigits :: Const a b -> Int #

floatRange :: Const a b -> (Int, Int) #

decodeFloat :: Const a b -> (Integer, Int) #

encodeFloat :: Integer -> Int -> Const a b #

exponent :: Const a b -> Int #

significand :: Const a b -> Const a b #

scaleFloat :: Int -> Const a b -> Const a b #

isNaN :: Const a b -> Bool #

isInfinite :: Const a b -> Bool #

isDenormalized :: Const a b -> Bool #

isNegativeZero :: Const a b -> Bool #

isIEEE :: Const a b -> Bool #

atan2 :: Const a b -> Const a b -> Const a b #

RealFrac a => RealFrac (Const a b)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Const

Methods

properFraction :: Integral b0 => Const a b -> (b0, Const a b) #

truncate :: Integral b0 => Const a b -> b0 #

round :: Integral b0 => Const a b -> b0 #

ceiling :: Integral b0 => Const a b -> b0 #

floor :: Integral b0 => Const a b -> b0 #

Show a => Show (Const a b)

This instance would be equivalent to the derived instances of the Const newtype if the runConst field were removed

Since: base-4.8.0.0

Instance details

Defined in Data.Functor.Const

Methods

showsPrec :: Int -> Const a b -> ShowS #

show :: Const a b -> String #

showList :: [Const a b] -> ShowS #

Ix a => Ix (Const a b)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Const

Methods

range :: (Const a b, Const a b) -> [Const a b] #

index :: (Const a b, Const a b) -> Const a b -> Int #

unsafeIndex :: (Const a b, Const a b) -> Const a b -> Int

inRange :: (Const a b, Const a b) -> Const a b -> Bool #

rangeSize :: (Const a b, Const a b) -> Int #

unsafeRangeSize :: (Const a b, Const a b) -> Int

Generic (Const a b) 
Instance details

Defined in Data.Functor.Const

Associated Types

type Rep (Const a b) :: Type -> Type #

Methods

from :: Const a b -> Rep (Const a b) x #

to :: Rep (Const a b) x -> Const a b #

Semigroup a => Semigroup (Const a b)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Const

Methods

(<>) :: Const a b -> Const a b -> Const a b #

sconcat :: NonEmpty (Const a b) -> Const a b #

stimes :: Integral b0 => b0 -> Const a b -> Const a b #

Monoid a => Monoid (Const a b)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Const

Methods

mempty :: Const a b #

mappend :: Const a b -> Const a b -> Const a b #

mconcat :: [Const a b] -> Const a b #

Storable a => Storable (Const a b)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Const

Methods

sizeOf :: Const a b -> Int #

alignment :: Const a b -> Int #

peekElemOff :: Ptr (Const a b) -> Int -> IO (Const a b) #

pokeElemOff :: Ptr (Const a b) -> Int -> Const a b -> IO () #

peekByteOff :: Ptr b0 -> Int -> IO (Const a b) #

pokeByteOff :: Ptr b0 -> Int -> Const a b -> IO () #

peek :: Ptr (Const a b) -> IO (Const a b) #

poke :: Ptr (Const a b) -> Const a b -> IO () #

Bits a => Bits (Const a b)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Const

Methods

(.&.) :: Const a b -> Const a b -> Const a b #

(.|.) :: Const a b -> Const a b -> Const a b #

xor :: Const a b -> Const a b -> Const a b #

complement :: Const a b -> Const a b #

shift :: Const a b -> Int -> Const a b #

rotate :: Const a b -> Int -> Const a b #

zeroBits :: Const a b #

bit :: Int -> Const a b #

setBit :: Const a b -> Int -> Const a b #

clearBit :: Const a b -> Int -> Const a b #

complementBit :: Const a b -> Int -> Const a b #

testBit :: Const a b -> Int -> Bool #

bitSizeMaybe :: Const a b -> Maybe Int #

bitSize :: Const a b -> Int #

isSigned :: Const a b -> Bool #

shiftL :: Const a b -> Int -> Const a b #

unsafeShiftL :: Const a b -> Int -> Const a b #

shiftR :: Const a b -> Int -> Const a b #

unsafeShiftR :: Const a b -> Int -> Const a b #

rotateL :: Const a b -> Int -> Const a b #

rotateR :: Const a b -> Int -> Const a b #

popCount :: Const a b -> Int #

FiniteBits a => FiniteBits (Const a b)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Const

NFData a => NFData (Const a b)

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Const a b -> () #

Hashable a => Hashable (Const a b) 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Const a b -> Int #

hash :: Const a b -> Int #

Prim a => Prim (Const a b)

Since: primitive-0.6.5.0

Instance details

Defined in Data.Primitive.Types

Methods

sizeOf# :: Const a b -> Int# #

alignment# :: Const a b -> Int# #

indexByteArray# :: ByteArray# -> Int# -> Const a b #

readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Const a b#) #

writeByteArray# :: MutableByteArray# s -> Int# -> Const a b -> State# s -> State# s #

setByteArray# :: MutableByteArray# s -> Int# -> Int# -> Const a b -> State# s -> State# s #

indexOffAddr# :: Addr# -> Int# -> Const a b #

readOffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Const a b#) #

writeOffAddr# :: Addr# -> Int# -> Const a b -> State# s -> State# s #

setOffAddr# :: Addr# -> Int# -> Int# -> Const a b -> State# s -> State# s #

Unbox a => Unbox (Const a b) 
Instance details

Defined in Data.Vector.Unboxed.Base

Wrapped (Const a x) Source # 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Const a x) :: Type Source #

Methods

_Wrapped' :: Iso' (Const a x) (Unwrapped (Const a x)) Source #

t ~ Const a' x' => Rewrapped (Const a x) t Source # 
Instance details

Defined in Control.Lens.Wrapped

type Rep1 (Const a :: k -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Const

type Rep1 (Const a :: k -> Type) = D1 (MetaData "Const" "Data.Functor.Const" "base" True) (C1 (MetaCons "Const" PrefixI True) (S1 (MetaSel (Just "getConst") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
newtype MVector s (Const a b) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s (Const a b) = MV_Const (MVector s a)
type Rep (Const a b)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Const

type Rep (Const a b) = D1 (MetaData "Const" "Data.Functor.Const" "base" True) (C1 (MetaCons "Const" PrefixI True) (S1 (MetaSel (Just "getConst") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
newtype Vector (Const a b) 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector (Const a b) = V_Const (Vector a)
type Unwrapped (Const a x) Source # 
Instance details

Defined in Control.Lens.Wrapped

type Unwrapped (Const a x) = a