Copyright | (C) 2013-16 Edward Kmett |
---|---|
License | BSD-style (see the file LICENSE) |
Maintainer | Edward Kmett <ekmett@gmail.com> |
Stability | experimental |
Portability | non-portable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
This lets the subset of users who vociferously disagree about the full scope and set of operators that should be exported from lens to not have to look at any operator with which they disagree.
import Control.Lens.Combinators
Synopsis
- class (Functor t, Foldable t) => Traversable (t :: Type -> Type) where
- traverse :: Applicative f => (a -> f b) -> t a -> f (t b)
- class Contravariant (f :: Type -> Type) where
- class Bifunctor (p :: Type -> Type -> Type) where
- bimap :: (a -> b) -> (c -> d) -> p a c -> p b d
- newtype Identity a = Identity {
- runIdentity :: a
- newtype Const a (b :: k) = Const {
- getConst :: a
- data (a :: k) :~: (b :: k) where
- itoList :: FoldableWithIndex i f => f a -> [(i, a)]
- ifoldlM :: (FoldableWithIndex i f, Monad m) => (i -> b -> a -> m b) -> b -> f a -> m b
- ifoldrM :: (FoldableWithIndex i f, Monad m) => (i -> a -> b -> m b) -> b -> f a -> m b
- ifind :: FoldableWithIndex i f => (i -> a -> Bool) -> f a -> Maybe (i, a)
- iconcatMap :: FoldableWithIndex i f => (i -> a -> [b]) -> f a -> [b]
- iforM_ :: (FoldableWithIndex i t, Monad m) => t a -> (i -> a -> m b) -> m ()
- imapM_ :: (FoldableWithIndex i t, Monad m) => (i -> a -> m b) -> t a -> m ()
- ifor_ :: (FoldableWithIndex i t, Applicative f) => t a -> (i -> a -> f b) -> f ()
- itraverse_ :: (FoldableWithIndex i t, Applicative f) => (i -> a -> f b) -> t a -> f ()
- none :: Foldable f => (a -> Bool) -> f a -> Bool
- inone :: FoldableWithIndex i f => (i -> a -> Bool) -> f a -> Bool
- iall :: FoldableWithIndex i f => (i -> a -> Bool) -> f a -> Bool
- iany :: FoldableWithIndex i f => (i -> a -> Bool) -> f a -> Bool
- imapAccumL :: TraversableWithIndex i t => (i -> s -> a -> (s, b)) -> s -> t a -> (s, t b)
- imapAccumR :: TraversableWithIndex i t => (i -> s -> a -> (s, b)) -> s -> t a -> (s, t b)
- iforM :: (TraversableWithIndex i t, Monad m) => t a -> (i -> a -> m b) -> m (t b)
- imapM :: (TraversableWithIndex i t, Monad m) => (i -> a -> m b) -> t a -> m (t b)
- ifor :: (TraversableWithIndex i t, Applicative f) => t a -> (i -> a -> f b) -> f (t b)
- class Functor f => FunctorWithIndex i (f :: Type -> Type) | f -> i where
- imap :: (i -> a -> b) -> f a -> f b
- class Foldable f => FoldableWithIndex i (f :: Type -> Type) | f -> i where
- class (FunctorWithIndex i t, FoldableWithIndex i t, Traversable t) => TraversableWithIndex i (t :: Type -> Type) | t -> i where
- itraverse :: Applicative f => (i -> a -> f b) -> t a -> f (t b)
- class Profunctor (p :: Type -> Type -> Type) where
- class Profunctor p => Choice (p :: Type -> Type -> Type) where
- sequenceBy :: Traversable t => (forall x. x -> f x) -> (forall x y. f (x -> y) -> f x -> f y) -> t (f a) -> f (t a)
- traverseBy :: Traversable t => (forall x. x -> f x) -> (forall x y. f (x -> y) -> f x -> f y) -> (a -> f b) -> t a -> f (t b)
- foldMapBy :: Foldable t => (r -> r -> r) -> r -> (a -> r) -> t a -> r
- foldBy :: Foldable t => (a -> a -> a) -> a -> t a -> a
- class (Foldable1 t, Traversable t) => Traversable1 (t :: Type -> Type) where
- class Reversing t where
- reversing :: t -> t
- data Level i a
- newtype Indexed i a b = Indexed {
- runIndexed :: i -> a -> b
- class Conjoined p => Indexable i p where
- indexed :: p a b -> i -> a -> b
- class (Choice p, Corepresentable p, Comonad (Corep p), Traversable (Corep p), Strong p, Representable p, Monad (Rep p), MonadFix (Rep p), Distributive (Rep p), Costrong p, ArrowLoop p, ArrowApply p, ArrowChoice p, Closed p) => Conjoined p where
- indexing :: Indexable Int p => ((a -> Indexing f b) -> s -> Indexing f t) -> p a (f b) -> s -> f t
- indexing64 :: Indexable Int64 p => ((a -> Indexing64 f b) -> s -> Indexing64 f t) -> p a (f b) -> s -> f t
- withIndex :: (Indexable i p, Functor f) => p (i, s) (f (j, t)) -> Indexed i s (f t)
- asIndex :: (Indexable i p, Contravariant f, Functor f) => p i (f i) -> Indexed i s (f s)
- data Rightmost a
- data Leftmost a
- data Sequenced a m
- data Traversed a f
- type Context' a = Context a a
- data Context a b t = Context (b -> t) a
- type Bazaar1' p a = Bazaar1 p a a
- newtype Bazaar1 p a b t = Bazaar1 {
- runBazaar1 :: forall f. Apply f => p a (f b) -> f t
- type Bazaar' p a = Bazaar p a a
- newtype Bazaar p a b t = Bazaar {
- runBazaar :: forall f. Applicative f => p a (f b) -> f t
- data Magma i t b a
- class (Profunctor p, Bifunctor p) => Reviewable p
- retagged :: (Profunctor p, Bifunctor p) => p a b -> p s b
- class (Applicative f, Distributive f, Traversable f) => Settable f
- type Over' p f s a = Over p f s s a a
- type Over p f s t a b = p a (f b) -> s -> f t
- type IndexedLensLike' i f s a = IndexedLensLike i f s s a a
- type IndexedLensLike i f s t a b = forall p. Indexable i p => p a (f b) -> s -> f t
- type LensLike' f s a = LensLike f s s a a
- type LensLike f s t a b = (a -> f b) -> s -> f t
- type Optical' p q f s a = Optical p q f s s a a
- type Optical p q f s t a b = p a (f b) -> q s (f t)
- type Optic' p f s a = Optic p f s s a a
- type Optic p f s t a b = p a (f b) -> p s (f t)
- type Simple f s a = f s s a a
- type IndexPreservingFold1 s a = forall p f. (Conjoined p, Contravariant f, Apply f) => p a (f a) -> p s (f s)
- type IndexedFold1 i s a = forall p f. (Indexable i p, Contravariant f, Apply f) => p a (f a) -> s -> f s
- type Fold1 s a = forall f. (Contravariant f, Apply f) => (a -> f a) -> s -> f s
- type IndexPreservingFold s a = forall p f. (Conjoined p, Contravariant f, Applicative f) => p a (f a) -> p s (f s)
- type IndexedFold i s a = forall p f. (Indexable i p, Contravariant f, Applicative f) => p a (f a) -> s -> f s
- type Fold s a = forall f. (Contravariant f, Applicative f) => (a -> f a) -> s -> f s
- type IndexPreservingGetter s a = forall p f. (Conjoined p, Contravariant f, Functor f) => p a (f a) -> p s (f s)
- type IndexedGetter i s a = forall p f. (Indexable i p, Contravariant f, Functor f) => p a (f a) -> s -> f s
- type Getter s a = forall f. (Contravariant f, Functor f) => (a -> f a) -> s -> f s
- type As a = Equality' a a
- type Equality' s a = Equality s s a a
- type Equality (s :: k1) (t :: k2) (a :: k1) (b :: k2) = forall k3 (p :: k1 -> k3 -> Type) (f :: k2 -> k3). p a (f b) -> p s (f t)
- type Prism' s a = Prism s s a a
- type Prism s t a b = forall p f. (Choice p, Applicative f) => p a (f b) -> p s (f t)
- type AReview t b = Optic' Tagged Identity t b
- type Review t b = forall p f. (Choice p, Bifunctor p, Settable f) => Optic' p f t b
- type Iso' s a = Iso s s a a
- type Iso s t a b = forall p f. (Profunctor p, Functor f) => p a (f b) -> p s (f t)
- type IndexPreservingSetter' s a = IndexPreservingSetter s s a a
- type IndexPreservingSetter s t a b = forall p f. (Conjoined p, Settable f) => p a (f b) -> p s (f t)
- type IndexedSetter' i s a = IndexedSetter i s s a a
- type IndexedSetter i s t a b = forall f p. (Indexable i p, Settable f) => p a (f b) -> s -> f t
- type Setter' s a = Setter s s a a
- type Setter s t a b = forall f. Settable f => (a -> f b) -> s -> f t
- type IndexPreservingTraversal1' s a = IndexPreservingTraversal1 s s a a
- type IndexPreservingTraversal1 s t a b = forall p f. (Conjoined p, Apply f) => p a (f b) -> p s (f t)
- type IndexPreservingTraversal' s a = IndexPreservingTraversal s s a a
- type IndexPreservingTraversal s t a b = forall p f. (Conjoined p, Applicative f) => p a (f b) -> p s (f t)
- type IndexedTraversal1' i s a = IndexedTraversal1 i s s a a
- type IndexedTraversal1 i s t a b = forall p f. (Indexable i p, Apply f) => p a (f b) -> s -> f t
- type IndexedTraversal' i s a = IndexedTraversal i s s a a
- type IndexedTraversal i s t a b = forall p f. (Indexable i p, Applicative f) => p a (f b) -> s -> f t
- type Traversal1' s a = Traversal1 s s a a
- type Traversal1 s t a b = forall f. Apply f => (a -> f b) -> s -> f t
- type Traversal' s a = Traversal s s a a
- type Traversal s t a b = forall f. Applicative f => (a -> f b) -> s -> f t
- type IndexPreservingLens' s a = IndexPreservingLens s s a a
- type IndexPreservingLens s t a b = forall p f. (Conjoined p, Functor f) => p a (f b) -> p s (f t)
- type IndexedLens' i s a = IndexedLens i s s a a
- type IndexedLens i s t a b = forall f p. (Indexable i p, Functor f) => p a (f b) -> s -> f t
- type Lens' s a = Lens s s a a
- type Lens s t a b = forall f. Functor f => (a -> f b) -> s -> f t
- type Setting' p s a = Setting p s s a a
- type Setting p s t a b = p a (Identity b) -> s -> Identity t
- type AnIndexedSetter' i s a = AnIndexedSetter i s s a a
- type AnIndexedSetter i s t a b = Indexed i a (Identity b) -> s -> Identity t
- type ASetter' s a = ASetter s s a a
- type ASetter s t a b = (a -> Identity b) -> s -> Identity t
- mapped :: Functor f => Setter (f a) (f b) a b
- lifted :: Monad m => Setter (m a) (m b) a b
- contramapped :: Contravariant f => Setter (f b) (f a) a b
- argument :: Profunctor p => Setter (p b r) (p a r) a b
- setting :: ((a -> b) -> s -> t) -> IndexPreservingSetter s t a b
- sets :: (Profunctor p, Profunctor q, Settable f) => (p a b -> q s t) -> Optical p q f s t a b
- cloneSetter :: ASetter s t a b -> Setter s t a b
- cloneIndexPreservingSetter :: ASetter s t a b -> IndexPreservingSetter s t a b
- cloneIndexedSetter :: AnIndexedSetter i s t a b -> IndexedSetter i s t a b
- over :: ASetter s t a b -> (a -> b) -> s -> t
- set :: ASetter s t a b -> b -> s -> t
- set' :: ASetter' s a -> a -> s -> s
- assign :: MonadState s m => ASetter s s a b -> b -> m ()
- modifying :: MonadState s m => ASetter s s a b -> (a -> b) -> m ()
- scribe :: (MonadWriter t m, Monoid s) => ASetter s t a b -> b -> m ()
- passing :: MonadWriter w m => Setter w w u v -> m (a, u -> v) -> m a
- ipassing :: MonadWriter w m => IndexedSetter i w w u v -> m (a, i -> u -> v) -> m a
- censoring :: MonadWriter w m => Setter w w u v -> (u -> v) -> m a -> m a
- icensoring :: MonadWriter w m => IndexedSetter i w w u v -> (i -> u -> v) -> m a -> m a
- locally :: MonadReader s m => ASetter s s a b -> (a -> b) -> m r -> m r
- ilocally :: MonadReader s m => AnIndexedSetter i s s a b -> (i -> a -> b) -> m r -> m r
- iover :: AnIndexedSetter i s t a b -> (i -> a -> b) -> s -> t
- iset :: AnIndexedSetter i s t a b -> (i -> b) -> s -> t
- isets :: ((i -> a -> b) -> s -> t) -> IndexedSetter i s t a b
- imodifying :: MonadState s m => AnIndexedSetter i s s a b -> (i -> a -> b) -> m ()
- assignA :: Arrow p => ASetter s t a b -> p s b -> p s t
- mapOf :: ASetter s t a b -> (a -> b) -> s -> t
- imapOf :: AnIndexedSetter i s t a b -> (i -> a -> b) -> s -> t
- type AnIndexedLens' i s a = AnIndexedLens i s s a a
- type AnIndexedLens i s t a b = Optical (Indexed i) (->) (Pretext (Indexed i) a b) s t a b
- type ALens' s a = ALens s s a a
- type ALens s t a b = LensLike (Pretext (->) a b) s t a b
- lens :: (s -> a) -> (s -> b -> t) -> Lens s t a b
- withLens :: forall s t a b rep (r :: TYPE rep). ALens s t a b -> ((s -> a) -> (s -> b -> t) -> r) -> r
- iplens :: (s -> a) -> (s -> b -> t) -> IndexPreservingLens s t a b
- ilens :: (s -> (i, a)) -> (s -> b -> t) -> IndexedLens i s t a b
- inside :: Corepresentable p => ALens s t a b -> Lens (p e s) (p e t) (p e a) (p e b)
- choosing :: Functor f => LensLike f s t a b -> LensLike f s' t' a b -> LensLike f (Either s s') (Either t t') a b
- chosen :: IndexPreservingLens (Either a a) (Either b b) a b
- alongside :: LensLike (AlongsideLeft f b') s t a b -> LensLike (AlongsideRight f t) s' t' a' b' -> LensLike f (s, s') (t, t') (a, a') (b, b')
- locus :: IndexedComonadStore p => Lens (p a c s) (p b c s) a b
- cloneLens :: ALens s t a b -> Lens s t a b
- cloneIndexPreservingLens :: ALens s t a b -> IndexPreservingLens s t a b
- cloneIndexedLens :: AnIndexedLens i s t a b -> IndexedLens i s t a b
- overA :: Arrow ar => LensLike (Context a b) s t a b -> ar a b -> ar s t
- storing :: ALens s t a b -> b -> s -> t
- devoid :: Over p f Void Void a b
- united :: Lens' a ()
- head1 :: Traversable1 t => Lens' (t a) a
- last1 :: Traversable1 t => Lens' (t a) a
- fusing :: Functor f => LensLike (Yoneda f) s t a b -> LensLike f s t a b
- class Field19 s t a b | s -> a, t -> b, s b -> t, t a -> s where
- class Field18 s t a b | s -> a, t -> b, s b -> t, t a -> s where
- class Field17 s t a b | s -> a, t -> b, s b -> t, t a -> s where
- class Field16 s t a b | s -> a, t -> b, s b -> t, t a -> s where
- class Field15 s t a b | s -> a, t -> b, s b -> t, t a -> s where
- class Field14 s t a b | s -> a, t -> b, s b -> t, t a -> s where
- class Field13 s t a b | s -> a, t -> b, s b -> t, t a -> s where
- class Field12 s t a b | s -> a, t -> b, s b -> t, t a -> s where
- class Field11 s t a b | s -> a, t -> b, s b -> t, t a -> s where
- class Field10 s t a b | s -> a, t -> b, s b -> t, t a -> s where
- class Field9 s t a b | s -> a, t -> b, s b -> t, t a -> s where
- class Field8 s t a b | s -> a, t -> b, s b -> t, t a -> s where
- class Field7 s t a b | s -> a, t -> b, s b -> t, t a -> s where
- class Field6 s t a b | s -> a, t -> b, s b -> t, t a -> s where
- class Field5 s t a b | s -> a, t -> b, s b -> t, t a -> s where
- class Field4 s t a b | s -> a, t -> b, s b -> t, t a -> s where
- class Field3 s t a b | s -> a, t -> b, s b -> t, t a -> s where
- class Field2 s t a b | s -> a, t -> b, s b -> t, t a -> s where
- class Field1 s t a b | s -> a, t -> b, s b -> t, t a -> s where
- _1' :: Field1 s t a b => Lens s t a b
- _2' :: Field2 s t a b => Lens s t a b
- _3' :: Field3 s t a b => Lens s t a b
- _4' :: Field4 s t a b => Lens s t a b
- _5' :: Field5 s t a b => Lens s t a b
- _6' :: Field6 s t a b => Lens s t a b
- _7' :: Field7 s t a b => Lens s t a b
- _8' :: Field8 s t a b => Lens s t a b
- _9' :: Field9 s t a b => Lens s t a b
- _10' :: Field10 s t a b => Lens s t a b
- _11' :: Field11 s t a b => Lens s t a b
- _12' :: Field12 s t a b => Lens s t a b
- _13' :: Field13 s t a b => Lens s t a b
- _14' :: Field14 s t a b => Lens s t a b
- _15' :: Field15 s t a b => Lens s t a b
- _16' :: Field16 s t a b => Lens s t a b
- _17' :: Field17 s t a b => Lens s t a b
- _18' :: Field18 s t a b => Lens s t a b
- _19' :: Field19 s t a b => Lens s t a b
- type Accessing p m s a = p a (Const m a) -> s -> Const m s
- type IndexedGetting i m s a = Indexed i a (Const m a) -> s -> Const m s
- type Getting r s a = (a -> Const r a) -> s -> Const r s
- to :: (Profunctor p, Contravariant f) => (s -> a) -> Optic' p f s a
- ito :: (Indexable i p, Contravariant f) => (s -> (i, a)) -> Over' p f s a
- like :: (Profunctor p, Contravariant f, Functor f) => a -> Optic' p f s a
- ilike :: (Indexable i p, Contravariant f, Functor f) => i -> a -> Over' p f s a
- view :: MonadReader s m => Getting a s a -> m a
- views :: MonadReader s m => LensLike' (Const r) s a -> (a -> r) -> m r
- use :: MonadState s m => Getting a s a -> m a
- uses :: MonadState s m => LensLike' (Const r) s a -> (a -> r) -> m r
- listening :: MonadWriter w m => Getting u w u -> m a -> m (a, u)
- ilistening :: MonadWriter w m => IndexedGetting i (i, u) w u -> m a -> m (a, (i, u))
- listenings :: MonadWriter w m => Getting v w u -> (u -> v) -> m a -> m (a, v)
- ilistenings :: MonadWriter w m => IndexedGetting i v w u -> (i -> u -> v) -> m a -> m (a, v)
- iview :: MonadReader s m => IndexedGetting i (i, a) s a -> m (i, a)
- iviews :: MonadReader s m => IndexedGetting i r s a -> (i -> a -> r) -> m r
- iuse :: MonadState s m => IndexedGetting i (i, a) s a -> m (i, a)
- iuses :: MonadState s m => IndexedGetting i r s a -> (i -> a -> r) -> m r
- getting :: (Profunctor p, Profunctor q, Functor f, Contravariant f) => Optical p q f s t a b -> Optical' p q f s a
- unto :: (Profunctor p, Bifunctor p, Functor f) => (b -> t) -> Optic p f s t a b
- un :: (Profunctor p, Bifunctor p, Functor f) => Getting a s a -> Optic' p f a s
- re :: AReview t b -> Getter b t
- review :: MonadReader b m => AReview t b -> m t
- reviews :: MonadReader b m => AReview t b -> (t -> r) -> m r
- reuse :: MonadState b m => AReview t b -> m t
- reuses :: MonadState b m => AReview t b -> (t -> r) -> m r
- reviewing :: (Bifunctor p, Functor f) => Optic Tagged Identity s t a b -> Optic' p f t b
- class Suffixed t where
- class Prefixed t where
- type APrism' s a = APrism s s a a
- type APrism s t a b = Market a b a (Identity b) -> Market a b s (Identity t)
- withPrism :: APrism s t a b -> ((b -> t) -> (s -> Either t a) -> r) -> r
- clonePrism :: APrism s t a b -> Prism s t a b
- prism :: (b -> t) -> (s -> Either t a) -> Prism s t a b
- prism' :: (b -> s) -> (s -> Maybe a) -> Prism s s a b
- outside :: Representable p => APrism s t a b -> Lens (p t r) (p s r) (p b r) (p a r)
- without :: APrism s t a b -> APrism u v c d -> Prism (Either s u) (Either t v) (Either a c) (Either b d)
- aside :: APrism s t a b -> Prism (e, s) (e, t) (e, a) (e, b)
- below :: Traversable f => APrism' s a -> Prism' (f s) (f a)
- isn't :: APrism s t a b -> s -> Bool
- matching :: APrism s t a b -> s -> Either t a
- matching' :: LensLike (Either a) s t a b -> s -> Either t a
- _Left :: Prism (Either a c) (Either b c) a b
- _Right :: Prism (Either c a) (Either c b) a b
- _Just :: Prism (Maybe a) (Maybe b) a b
- _Nothing :: Prism' (Maybe a) ()
- _Void :: Prism s s a Void
- only :: Eq a => a -> Prism' a ()
- nearly :: a -> (a -> Bool) -> Prism' a ()
- _Show :: (Read a, Show a) => Prism' String a
- folding :: Foldable f => (s -> f a) -> Fold s a
- ifolding :: (Foldable f, Indexable i p, Contravariant g, Applicative g) => (s -> f (i, a)) -> Over p g s t a b
- foldring :: (Contravariant f, Applicative f) => ((a -> f a -> f a) -> f a -> s -> f a) -> LensLike f s t a b
- ifoldring :: (Indexable i p, Contravariant f, Applicative f) => ((i -> a -> f a -> f a) -> f a -> s -> f a) -> Over p f s t a b
- folded :: Foldable f => IndexedFold Int (f a) a
- folded64 :: Foldable f => IndexedFold Int64 (f a) a
- repeated :: Apply f => LensLike' f a a
- replicated :: Int -> Fold a a
- cycled :: Apply f => LensLike f s t a b -> LensLike f s t a b
- unfolded :: (b -> Maybe (a, b)) -> Fold b a
- iterated :: Apply f => (a -> a) -> LensLike' f a a
- filtered :: (Choice p, Applicative f) => (a -> Bool) -> Optic' p f a a
- filteredBy :: (Indexable i p, Applicative f) => Getting (First i) a i -> p a (f a) -> a -> f a
- takingWhile :: (Conjoined p, Applicative f) => (a -> Bool) -> Over p (TakingWhile p f a a) s t a a -> Over p f s t a a
- droppingWhile :: (Conjoined p, Profunctor q, Applicative f) => (a -> Bool) -> Optical p q (Compose (State Bool) f) s t a a -> Optical p q f s t a a
- worded :: Applicative f => IndexedLensLike' Int f String String
- lined :: Applicative f => IndexedLensLike' Int f String String
- foldMapOf :: Getting r s a -> (a -> r) -> s -> r
- foldOf :: Getting a s a -> s -> a
- foldrOf :: Getting (Endo r) s a -> (a -> r -> r) -> r -> s -> r
- foldlOf :: Getting (Dual (Endo r)) s a -> (r -> a -> r) -> r -> s -> r
- toListOf :: Getting (Endo [a]) s a -> s -> [a]
- toNonEmptyOf :: Getting (NonEmptyDList a) s a -> s -> NonEmpty a
- andOf :: Getting All s Bool -> s -> Bool
- orOf :: Getting Any s Bool -> s -> Bool
- anyOf :: Getting Any s a -> (a -> Bool) -> s -> Bool
- allOf :: Getting All s a -> (a -> Bool) -> s -> Bool
- noneOf :: Getting Any s a -> (a -> Bool) -> s -> Bool
- productOf :: Num a => Getting (Endo (Endo a)) s a -> s -> a
- sumOf :: Num a => Getting (Endo (Endo a)) s a -> s -> a
- traverseOf_ :: Functor f => Getting (Traversed r f) s a -> (a -> f r) -> s -> f ()
- forOf_ :: Functor f => Getting (Traversed r f) s a -> s -> (a -> f r) -> f ()
- sequenceAOf_ :: Functor f => Getting (Traversed a f) s (f a) -> s -> f ()
- traverse1Of_ :: Functor f => Getting (TraversedF r f) s a -> (a -> f r) -> s -> f ()
- for1Of_ :: Functor f => Getting (TraversedF r f) s a -> s -> (a -> f r) -> f ()
- sequence1Of_ :: Functor f => Getting (TraversedF a f) s (f a) -> s -> f ()
- mapMOf_ :: Monad m => Getting (Sequenced r m) s a -> (a -> m r) -> s -> m ()
- forMOf_ :: Monad m => Getting (Sequenced r m) s a -> s -> (a -> m r) -> m ()
- sequenceOf_ :: Monad m => Getting (Sequenced a m) s (m a) -> s -> m ()
- asumOf :: Alternative f => Getting (Endo (f a)) s (f a) -> s -> f a
- msumOf :: MonadPlus m => Getting (Endo (m a)) s (m a) -> s -> m a
- elemOf :: Eq a => Getting Any s a -> a -> s -> Bool
- notElemOf :: Eq a => Getting All s a -> a -> s -> Bool
- concatMapOf :: Getting [r] s a -> (a -> [r]) -> s -> [r]
- concatOf :: Getting [r] s [r] -> s -> [r]
- lengthOf :: Getting (Endo (Endo Int)) s a -> s -> Int
- firstOf :: Getting (Leftmost a) s a -> s -> Maybe a
- first1Of :: Getting (First a) s a -> s -> a
- lastOf :: Getting (Rightmost a) s a -> s -> Maybe a
- last1Of :: Getting (Last a) s a -> s -> a
- nullOf :: Getting All s a -> s -> Bool
- notNullOf :: Getting Any s a -> s -> Bool
- maximumOf :: Ord a => Getting (Endo (Endo (Maybe a))) s a -> s -> Maybe a
- maximum1Of :: Ord a => Getting (Max a) s a -> s -> a
- minimumOf :: Ord a => Getting (Endo (Endo (Maybe a))) s a -> s -> Maybe a
- minimum1Of :: Ord a => Getting (Min a) s a -> s -> a
- maximumByOf :: Getting (Endo (Endo (Maybe a))) s a -> (a -> a -> Ordering) -> s -> Maybe a
- minimumByOf :: Getting (Endo (Endo (Maybe a))) s a -> (a -> a -> Ordering) -> s -> Maybe a
- findOf :: Getting (Endo (Maybe a)) s a -> (a -> Bool) -> s -> Maybe a
- findMOf :: Monad m => Getting (Endo (m (Maybe a))) s a -> (a -> m Bool) -> s -> m (Maybe a)
- lookupOf :: Eq k => Getting (Endo (Maybe v)) s (k, v) -> k -> s -> Maybe v
- foldr1Of :: HasCallStack => Getting (Endo (Maybe a)) s a -> (a -> a -> a) -> s -> a
- foldl1Of :: HasCallStack => Getting (Dual (Endo (Maybe a))) s a -> (a -> a -> a) -> s -> a
- foldrOf' :: Getting (Dual (Endo (Endo r))) s a -> (a -> r -> r) -> r -> s -> r
- foldlOf' :: Getting (Endo (Endo r)) s a -> (r -> a -> r) -> r -> s -> r
- foldr1Of' :: HasCallStack => Getting (Dual (Endo (Endo (Maybe a)))) s a -> (a -> a -> a) -> s -> a
- foldl1Of' :: HasCallStack => Getting (Endo (Endo (Maybe a))) s a -> (a -> a -> a) -> s -> a
- foldrMOf :: Monad m => Getting (Dual (Endo (r -> m r))) s a -> (a -> r -> m r) -> r -> s -> m r
- foldlMOf :: Monad m => Getting (Endo (r -> m r)) s a -> (r -> a -> m r) -> r -> s -> m r
- has :: Getting Any s a -> s -> Bool
- hasn't :: Getting All s a -> s -> Bool
- pre :: Getting (First a) s a -> IndexPreservingGetter s (Maybe a)
- ipre :: IndexedGetting i (First (i, a)) s a -> IndexPreservingGetter s (Maybe (i, a))
- preview :: MonadReader s m => Getting (First a) s a -> m (Maybe a)
- ipreview :: MonadReader s m => IndexedGetting i (First (i, a)) s a -> m (Maybe (i, a))
- previews :: MonadReader s m => Getting (First r) s a -> (a -> r) -> m (Maybe r)
- ipreviews :: MonadReader s m => IndexedGetting i (First r) s a -> (i -> a -> r) -> m (Maybe r)
- preuse :: MonadState s m => Getting (First a) s a -> m (Maybe a)
- ipreuse :: MonadState s m => IndexedGetting i (First (i, a)) s a -> m (Maybe (i, a))
- preuses :: MonadState s m => Getting (First r) s a -> (a -> r) -> m (Maybe r)
- ipreuses :: MonadState s m => IndexedGetting i (First r) s a -> (i -> a -> r) -> m (Maybe r)
- backwards :: (Profunctor p, Profunctor q) => Optical p q (Backwards f) s t a b -> Optical p q f s t a b
- ifoldMapOf :: IndexedGetting i m s a -> (i -> a -> m) -> s -> m
- ifoldrOf :: IndexedGetting i (Endo r) s a -> (i -> a -> r -> r) -> r -> s -> r
- ifoldlOf :: IndexedGetting i (Dual (Endo r)) s a -> (i -> r -> a -> r) -> r -> s -> r
- ianyOf :: IndexedGetting i Any s a -> (i -> a -> Bool) -> s -> Bool
- iallOf :: IndexedGetting i All s a -> (i -> a -> Bool) -> s -> Bool
- inoneOf :: IndexedGetting i Any s a -> (i -> a -> Bool) -> s -> Bool
- itraverseOf_ :: Functor f => IndexedGetting i (Traversed r f) s a -> (i -> a -> f r) -> s -> f ()
- iforOf_ :: Functor f => IndexedGetting i (Traversed r f) s a -> s -> (i -> a -> f r) -> f ()
- imapMOf_ :: Monad m => IndexedGetting i (Sequenced r m) s a -> (i -> a -> m r) -> s -> m ()
- iforMOf_ :: Monad m => IndexedGetting i (Sequenced r m) s a -> s -> (i -> a -> m r) -> m ()
- iconcatMapOf :: IndexedGetting i [r] s a -> (i -> a -> [r]) -> s -> [r]
- ifindOf :: IndexedGetting i (Endo (Maybe a)) s a -> (i -> a -> Bool) -> s -> Maybe a
- ifindMOf :: Monad m => IndexedGetting i (Endo (m (Maybe a))) s a -> (i -> a -> m Bool) -> s -> m (Maybe a)
- ifoldrOf' :: IndexedGetting i (Dual (Endo (r -> r))) s a -> (i -> a -> r -> r) -> r -> s -> r
- ifoldlOf' :: IndexedGetting i (Endo (r -> r)) s a -> (i -> r -> a -> r) -> r -> s -> r
- ifoldrMOf :: Monad m => IndexedGetting i (Dual (Endo (r -> m r))) s a -> (i -> a -> r -> m r) -> r -> s -> m r
- ifoldlMOf :: Monad m => IndexedGetting i (Endo (r -> m r)) s a -> (i -> r -> a -> m r) -> r -> s -> m r
- itoListOf :: IndexedGetting i (Endo [(i, a)]) s a -> s -> [(i, a)]
- elemIndexOf :: Eq a => IndexedGetting i (First i) s a -> a -> s -> Maybe i
- elemIndicesOf :: Eq a => IndexedGetting i (Endo [i]) s a -> a -> s -> [i]
- findIndexOf :: IndexedGetting i (First i) s a -> (a -> Bool) -> s -> Maybe i
- findIndicesOf :: IndexedGetting i (Endo [i]) s a -> (a -> Bool) -> s -> [i]
- ifiltered :: (Indexable i p, Applicative f) => (i -> a -> Bool) -> Optical' p (Indexed i) f a a
- itakingWhile :: (Indexable i p, Profunctor q, Contravariant f, Applicative f) => (i -> a -> Bool) -> Optical' (Indexed i) q (Const (Endo (f s))) s a -> Optical' p q f s a
- idroppingWhile :: (Indexable i p, Profunctor q, Applicative f) => (i -> a -> Bool) -> Optical (Indexed i) q (Compose (State Bool) f) s t a a -> Optical p q f s t a a
- foldByOf :: Fold s a -> (a -> a -> a) -> a -> s -> a
- foldMapByOf :: Fold s a -> (r -> r -> r) -> r -> (a -> r) -> s -> r
- class Ord k => TraverseMax k m | m -> k where
- traverseMax :: IndexedTraversal' k (m v) v
- class Ord k => TraverseMin k m | m -> k where
- traverseMin :: IndexedTraversal' k (m v) v
- type Traversing1' p f s a = Traversing1 p f s s a a
- type Traversing' p f s a = Traversing p f s s a a
- type Traversing1 p f s t a b = Over p (BazaarT1 p f a b) s t a b
- type Traversing p f s t a b = Over p (BazaarT p f a b) s t a b
- type AnIndexedTraversal1' i s a = AnIndexedTraversal1 i s s a a
- type AnIndexedTraversal' i s a = AnIndexedTraversal i s s a a
- type AnIndexedTraversal1 i s t a b = Over (Indexed i) (Bazaar1 (Indexed i) a b) s t a b
- type AnIndexedTraversal i s t a b = Over (Indexed i) (Bazaar (Indexed i) a b) s t a b
- type ATraversal1' s a = ATraversal1 s s a a
- type ATraversal1 s t a b = LensLike (Bazaar1 (->) a b) s t a b
- type ATraversal' s a = ATraversal s s a a
- type ATraversal s t a b = LensLike (Bazaar (->) a b) s t a b
- traversal :: ((a -> f b) -> s -> f t) -> LensLike f s t a b
- traverseOf :: LensLike f s t a b -> (a -> f b) -> s -> f t
- forOf :: LensLike f s t a b -> s -> (a -> f b) -> f t
- sequenceAOf :: LensLike f s t (f b) b -> s -> f t
- mapMOf :: LensLike (WrappedMonad m) s t a b -> (a -> m b) -> s -> m t
- forMOf :: LensLike (WrappedMonad m) s t a b -> s -> (a -> m b) -> m t
- sequenceOf :: LensLike (WrappedMonad m) s t (m b) b -> s -> m t
- transposeOf :: LensLike ZipList s t [a] a -> s -> [t]
- mapAccumROf :: LensLike (Backwards (State acc)) s t a b -> (acc -> a -> (acc, b)) -> acc -> s -> (acc, t)
- mapAccumLOf :: LensLike (State acc) s t a b -> (acc -> a -> (acc, b)) -> acc -> s -> (acc, t)
- scanr1Of :: LensLike (Backwards (State (Maybe a))) s t a a -> (a -> a -> a) -> s -> t
- scanl1Of :: LensLike (State (Maybe a)) s t a a -> (a -> a -> a) -> s -> t
- loci :: Traversal (Bazaar (->) a c s) (Bazaar (->) b c s) a b
- iloci :: IndexedTraversal i (Bazaar (Indexed i) a c s) (Bazaar (Indexed i) b c s) a b
- partsOf :: Functor f => Traversing (->) f s t a a -> LensLike f s t [a] [a]
- ipartsOf :: forall i p f s t a. (Indexable [i] p, Functor f) => Traversing (Indexed i) f s t a a -> Over p f s t [a] [a]
- partsOf' :: ATraversal s t a a -> Lens s t [a] [a]
- ipartsOf' :: forall i p f s t a. (Indexable [i] p, Functor f) => Over (Indexed i) (Bazaar' (Indexed i) a) s t a a -> Over p f s t [a] [a]
- unsafePartsOf :: Functor f => Traversing (->) f s t a b -> LensLike f s t [a] [b]
- iunsafePartsOf :: forall i p f s t a b. (Indexable [i] p, Functor f) => Traversing (Indexed i) f s t a b -> Over p f s t [a] [b]
- unsafePartsOf' :: ATraversal s t a b -> Lens s t [a] [b]
- iunsafePartsOf' :: forall i s t a b. Over (Indexed i) (Bazaar (Indexed i) a b) s t a b -> IndexedLens [i] s t [a] [b]
- singular :: (HasCallStack, Conjoined p, Functor f) => Traversing p f s t a a -> Over p f s t a a
- unsafeSingular :: (HasCallStack, Conjoined p, Functor f) => Traversing p f s t a b -> Over p f s t a b
- holesOf :: Conjoined p => Over p (Bazaar p a a) s t a a -> s -> [Pretext p a a t]
- holes1Of :: Conjoined p => Over p (Bazaar1 p a a) s t a a -> s -> NonEmpty (Pretext p a a t)
- both :: Bitraversable r => Traversal (r a a) (r b b) a b
- both1 :: Bitraversable1 r => Traversal1 (r a a) (r b b) a b
- beside :: (Representable q, Applicative (Rep q), Applicative f, Bitraversable r) => Optical p q f s t a b -> Optical p q f s' t' a b -> Optical p q f (r s s') (r t t') a b
- taking :: (Conjoined p, Applicative f) => Int -> Traversing p f s t a a -> Over p f s t a a
- dropping :: (Conjoined p, Applicative f) => Int -> Over p (Indexing f) s t a a -> Over p f s t a a
- cloneTraversal :: ATraversal s t a b -> Traversal s t a b
- cloneIndexPreservingTraversal :: ATraversal s t a b -> IndexPreservingTraversal s t a b
- cloneIndexedTraversal :: AnIndexedTraversal i s t a b -> IndexedTraversal i s t a b
- cloneTraversal1 :: ATraversal1 s t a b -> Traversal1 s t a b
- cloneIndexPreservingTraversal1 :: ATraversal1 s t a b -> IndexPreservingTraversal1 s t a b
- cloneIndexedTraversal1 :: AnIndexedTraversal1 i s t a b -> IndexedTraversal1 i s t a b
- itraverseOf :: (Indexed i a (f b) -> s -> f t) -> (i -> a -> f b) -> s -> f t
- iforOf :: (Indexed i a (f b) -> s -> f t) -> s -> (i -> a -> f b) -> f t
- imapMOf :: Over (Indexed i) (WrappedMonad m) s t a b -> (i -> a -> m b) -> s -> m t
- iforMOf :: (Indexed i a (WrappedMonad m b) -> s -> WrappedMonad m t) -> s -> (i -> a -> m b) -> m t
- imapAccumROf :: Over (Indexed i) (Backwards (State acc)) s t a b -> (i -> acc -> a -> (acc, b)) -> acc -> s -> (acc, t)
- imapAccumLOf :: Over (Indexed i) (State acc) s t a b -> (i -> acc -> a -> (acc, b)) -> acc -> s -> (acc, t)
- traversed :: Traversable f => IndexedTraversal Int (f a) (f b) a b
- traversed1 :: Traversable1 f => IndexedTraversal1 Int (f a) (f b) a b
- traversed64 :: Traversable f => IndexedTraversal Int64 (f a) (f b) a b
- ignored :: Applicative f => pafb -> s -> f s
- elementOf :: Applicative f => LensLike (Indexing f) s t a a -> Int -> IndexedLensLike Int f s t a a
- element :: Traversable t => Int -> IndexedTraversal' Int (t a) a
- elementsOf :: Applicative f => LensLike (Indexing f) s t a a -> (Int -> Bool) -> IndexedLensLike Int f s t a a
- elements :: Traversable t => (Int -> Bool) -> IndexedTraversal' Int (t a) a
- failover :: Alternative m => LensLike ((,) Any) s t a b -> (a -> b) -> s -> m t
- ifailover :: Alternative m => Over (Indexed i) ((,) Any) s t a b -> (i -> a -> b) -> s -> m t
- failing :: (Conjoined p, Applicative f) => Traversing p f s t a b -> Over p f s t a b -> Over p f s t a b
- deepOf :: (Conjoined p, Applicative f) => LensLike f s t s t -> Traversing p f s t a b -> Over p f s t a b
- confusing :: Applicative f => LensLike (Curried (Yoneda f) (Yoneda f)) s t a b -> LensLike f s t a b
- traverseByOf :: Traversal s t a b -> (forall x. x -> f x) -> (forall x y. f (x -> y) -> f x -> f y) -> (a -> f b) -> s -> f t
- sequenceByOf :: Traversal s t (f b) b -> (forall x. x -> f x) -> (forall x y. f (x -> y) -> f x -> f y) -> s -> f t
- levels :: Applicative f => Traversing (->) f s t a b -> IndexedLensLike Int f s t (Level () a) (Level () b)
- ilevels :: Applicative f => Traversing (Indexed i) f s t a b -> IndexedLensLike Int f s t (Level i a) (Level j b)
- type ReifiedPrism' s a = ReifiedPrism s s a a
- newtype ReifiedPrism s t a b = Prism {}
- type ReifiedIso' s a = ReifiedIso s s a a
- newtype ReifiedIso s t a b = Iso {}
- type ReifiedIndexedSetter' i s a = ReifiedIndexedSetter i s s a a
- newtype ReifiedIndexedSetter i s t a b = IndexedSetter {
- runIndexedSetter :: IndexedSetter i s t a b
- type ReifiedSetter' s a = ReifiedSetter s s a a
- newtype ReifiedSetter s t a b = Setter {}
- newtype ReifiedIndexedFold i s a = IndexedFold {
- runIndexedFold :: IndexedFold i s a
- newtype ReifiedFold s a = Fold {}
- newtype ReifiedIndexedGetter i s a = IndexedGetter {
- runIndexedGetter :: IndexedGetter i s a
- newtype ReifiedGetter s a = Getter {}
- type ReifiedTraversal' s a = ReifiedTraversal s s a a
- newtype ReifiedTraversal s t a b = Traversal {
- runTraversal :: Traversal s t a b
- type ReifiedIndexedTraversal' i s a = ReifiedIndexedTraversal i s s a a
- newtype ReifiedIndexedTraversal i s t a b = IndexedTraversal {
- runIndexedTraversal :: IndexedTraversal i s t a b
- type ReifiedIndexedLens' i s a = ReifiedIndexedLens i s s a a
- newtype ReifiedIndexedLens i s t a b = IndexedLens {
- runIndexedLens :: IndexedLens i s t a b
- type ReifiedLens' s a = ReifiedLens s s a a
- newtype ReifiedLens s t a b = Lens {}
- selfIndex :: Indexable a p => p a fb -> a -> fb
- reindexed :: Indexable j p => (i -> j) -> (Indexed i a b -> r) -> p a b -> r
- icompose :: Indexable p c => (i -> j -> p) -> (Indexed i s t -> r) -> (Indexed j a b -> s -> t) -> c a b -> r
- indices :: (Indexable i p, Applicative f) => (i -> Bool) -> Optical' p (Indexed i) f a a
- index :: (Indexable i p, Eq i, Applicative f) => i -> Optical' p (Indexed i) f a a
- imapped :: FunctorWithIndex i f => IndexedSetter i (f a) (f b) a b
- ifolded :: FoldableWithIndex i f => IndexedFold i (f a) a
- itraversed :: TraversableWithIndex i t => IndexedTraversal i (t a) (t b) a b
- ifoldMapBy :: FoldableWithIndex i t => (r -> r -> r) -> r -> (i -> a -> r) -> t a -> r
- ifoldMapByOf :: IndexedFold i t a -> (r -> r -> r) -> r -> (i -> a -> r) -> t -> r
- itraverseBy :: TraversableWithIndex i t => (forall x. x -> f x) -> (forall x y. f (x -> y) -> f x -> f y) -> (i -> a -> f b) -> t a -> f (t b)
- itraverseByOf :: IndexedTraversal i s t a b -> (forall x. x -> f x) -> (forall x y. f (x -> y) -> f x -> f y) -> (i -> a -> f b) -> s -> f t
- type AnEquality' s a = AnEquality s s a a
- type AnEquality s t a b = Identical a (Proxy b) a (Proxy b) -> Identical a (Proxy b) s (Proxy t)
- data Identical a b s t where
- runEq :: AnEquality s t a b -> Identical s t a b
- substEq :: forall s t a b rep (r :: TYPE rep). AnEquality s t a b -> ((s ~ a, t ~ b) => r) -> r
- mapEq :: forall k1 k2 (s :: k1) (t :: k2) (a :: k1) (b :: k2) (f :: k1 -> Type). AnEquality s t a b -> f s -> f a
- fromEq :: AnEquality s t a b -> Equality b a t s
- simply :: forall p f s a rep (r :: TYPE rep). (Optic' p f s a -> r) -> Optic' p f s a -> r
- simple :: Equality' a a
- cloneEquality :: AnEquality s t a b -> Equality s t a b
- equality :: (s :~: a) -> (b :~: t) -> Equality s t a b
- equality' :: (a :~: b) -> Equality' a b
- overEquality :: AnEquality s t a b -> p a b -> p s t
- underEquality :: AnEquality s t a b -> p t s -> p b a
- fromLeibniz :: (Identical a b a b -> Identical a b s t) -> Equality s t a b
- fromLeibniz' :: ((s :~: s) -> s :~: a) -> Equality' s a
- withEquality :: forall s t a b rep (r :: TYPE rep). AnEquality s t a b -> ((s :~: a) -> (b :~: t) -> r) -> r
- type AnIso' s a = AnIso s s a a
- type AnIso s t a b = Exchange a b a (Identity b) -> Exchange a b s (Identity t)
- pattern List :: IsList l => [Item l] -> l
- pattern Reversed :: Reversing t => t -> t
- pattern Swapped :: Swap p => p b a -> p a b
- pattern Lazy :: Strict t s => t -> s
- pattern Strict :: Strict s t => t -> s
- iso :: (s -> a) -> (b -> t) -> Iso s t a b
- from :: AnIso s t a b -> Iso b a t s
- withIso :: forall s t a b rep (r :: TYPE rep). AnIso s t a b -> ((s -> a) -> (b -> t) -> r) -> r
- cloneIso :: AnIso s t a b -> Iso s t a b
- au :: Functor f => AnIso s t a b -> ((b -> t) -> f s) -> f a
- auf :: (Functor f, Functor g) => AnIso s t a b -> (f t -> g s) -> f b -> g a
- xplat :: Optic (Costar ((->) s)) g s t a b -> ((s -> a) -> g b) -> g t
- xplatf :: Optic (Costar f) g s t a b -> (f a -> g b) -> f s -> g t
- under :: AnIso s t a b -> (t -> s) -> b -> a
- enum :: Enum a => Iso' Int a
- mapping :: (Functor f, Functor g) => AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
- non :: Eq a => a -> Iso' (Maybe a) a
- non' :: APrism' a () -> Iso' (Maybe a) a
- anon :: a -> (a -> Bool) -> Iso' (Maybe a) a
- curried :: Iso ((a, b) -> c) ((d, e) -> f) (a -> b -> c) (d -> e -> f)
- uncurried :: Iso (a -> b -> c) (d -> e -> f) ((a, b) -> c) ((d, e) -> f)
- flipped :: Iso (a -> b -> c) (a' -> b' -> c') (b -> a -> c) (b' -> a' -> c')
- swapped :: Swap p => Iso (p a b) (p c d) (p b a) (p d c)
- strict :: Strict lazy strict => Iso' lazy strict
- lazy :: Strict lazy strict => Iso' strict lazy
- reversed :: Reversing a => Iso' a a
- involuted :: (a -> a) -> Iso' a a
- magma :: LensLike (Mafic a b) s t a b -> Iso s u (Magma Int t b a) (Magma j u c c)
- imagma :: Over (Indexed i) (Molten i a b) s t a b -> Iso s t' (Magma i t b a) (Magma j t' c c)
- contramapping :: Contravariant f => AnIso s t a b -> Iso (f a) (f b) (f s) (f t)
- dimapping :: (Profunctor p, Profunctor q) => AnIso s t a b -> AnIso s' t' a' b' -> Iso (p a s') (q b t') (p s a') (q t b')
- lmapping :: (Profunctor p, Profunctor q) => AnIso s t a b -> Iso (p a x) (q b y) (p s x) (q t y)
- rmapping :: (Profunctor p, Profunctor q) => AnIso s t a b -> Iso (p x s) (q y t) (p x a) (q y b)
- bimapping :: (Bifunctor f, Bifunctor g) => AnIso s t a b -> AnIso s' t' a' b' -> Iso (f s s') (g t t') (f a a') (g b b')
- firsting :: (Bifunctor f, Bifunctor g) => AnIso s t a b -> Iso (f s x) (g t y) (f a x) (g b y)
- seconding :: (Bifunctor f, Bifunctor g) => AnIso s t a b -> Iso (f x s) (g y t) (f x a) (g y b)
- coerced :: forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
- class AsEmpty a where
- pattern Empty :: AsEmpty s => s
- class Snoc s t a b | s -> a, t -> b, s b -> t, t a -> s where
- class Cons s t a b | s -> a, t -> b, s b -> t, t a -> s where
- cons :: Cons s s a a => a -> s -> s
- uncons :: Cons s s a a => s -> Maybe (a, s)
- _head :: Cons s s a a => Traversal' s a
- _tail :: Cons s s a a => Traversal' s s
- _init :: Snoc s s a a => Traversal' s s
- _last :: Snoc s s a a => Traversal' s a
- snoc :: Snoc s s a a => s -> a -> s
- unsnoc :: Snoc s s a a => s -> Maybe (s, a)
- class (Rewrapped s t, Rewrapped t s) => Rewrapping s t
- class Wrapped s => Rewrapped (s :: Type) (t :: Type)
- class Wrapped s where
- pattern Unwrapped :: Rewrapped t t => t -> Unwrapped t
- pattern Wrapped :: Rewrapped s s => Unwrapped s -> s
- _GWrapped' :: (Generic s, D1 d (C1 c (S1 s' (Rec0 a))) ~ Rep s, Unwrapped s ~ GUnwrapped (Rep s)) => Iso' s (Unwrapped s)
- _Unwrapped' :: Wrapped s => Iso' (Unwrapped s) s
- _Wrapped :: Rewrapping s t => Iso s t (Unwrapped s) (Unwrapped t)
- _Unwrapped :: Rewrapping s t => Iso (Unwrapped t) (Unwrapped s) t s
- op :: Wrapped s => (Unwrapped s -> s) -> s -> Unwrapped s
- _Wrapping' :: Wrapped s => (Unwrapped s -> s) -> Iso' s (Unwrapped s)
- _Unwrapping' :: Wrapped s => (Unwrapped s -> s) -> Iso' (Unwrapped s) s
- _Wrapping :: Rewrapping s t => (Unwrapped s -> s) -> Iso s t (Unwrapped s) (Unwrapped t)
- _Unwrapping :: Rewrapping s t => (Unwrapped s -> s) -> Iso (Unwrapped t) (Unwrapped s) t s
- ala :: (Functor f, Rewrapping s t) => (Unwrapped s -> s) -> ((Unwrapped t -> t) -> f s) -> f (Unwrapped s)
- alaf :: (Functor f, Functor g, Rewrapping s t) => (Unwrapped s -> s) -> (f t -> g s) -> f (Unwrapped t) -> g (Unwrapped s)
- class (Magnified m ~ Magnified n, MonadReader b m, MonadReader a n) => Magnify m n b a | m -> b, n -> a, m a -> n, n b -> m where
- class (MonadState s m, MonadState t n) => Zoom m n s t | m -> s, n -> t, m t -> n, n s -> m where
- type family Magnified (m :: Type -> Type) :: Type -> Type -> Type
- type family Zoomed (m :: Type -> Type) :: Type -> Type -> Type
- class GPlated1 f g
- class GPlated a g
- class Plated a where
- plate :: Traversal' a a
- deep :: (Conjoined p, Applicative f, Plated s) => Traversing p f s s a b -> Over p f s s a b
- children :: Plated a => a -> [a]
- rewrite :: Plated a => (a -> Maybe a) -> a -> a
- rewriteOf :: ASetter a b a b -> (b -> Maybe a) -> a -> b
- rewriteOn :: Plated a => ASetter s t a a -> (a -> Maybe a) -> s -> t
- rewriteOnOf :: ASetter s t a b -> ASetter a b a b -> (b -> Maybe a) -> s -> t
- rewriteM :: (Monad m, Plated a) => (a -> m (Maybe a)) -> a -> m a
- rewriteMOf :: Monad m => LensLike (WrappedMonad m) a b a b -> (b -> m (Maybe a)) -> a -> m b
- rewriteMOn :: (Monad m, Plated a) => LensLike (WrappedMonad m) s t a a -> (a -> m (Maybe a)) -> s -> m t
- rewriteMOnOf :: Monad m => LensLike (WrappedMonad m) s t a b -> LensLike (WrappedMonad m) a b a b -> (b -> m (Maybe a)) -> s -> m t
- universe :: Plated a => a -> [a]
- universeOf :: Getting (Endo [a]) a a -> a -> [a]
- universeOn :: Plated a => Getting (Endo [a]) s a -> s -> [a]
- universeOnOf :: Getting (Endo [a]) s a -> Getting (Endo [a]) a a -> s -> [a]
- cosmos :: Plated a => Fold a a
- cosmosOf :: (Applicative f, Contravariant f) => LensLike' f a a -> LensLike' f a a
- cosmosOn :: (Applicative f, Contravariant f, Plated a) => LensLike' f s a -> LensLike' f s a
- cosmosOnOf :: (Applicative f, Contravariant f) => LensLike' f s a -> LensLike' f a a -> LensLike' f s a
- transform :: Plated a => (a -> a) -> a -> a
- transformOn :: Plated a => ASetter s t a a -> (a -> a) -> s -> t
- transformOf :: ASetter a b a b -> (b -> b) -> a -> b
- transformOnOf :: ASetter s t a b -> ASetter a b a b -> (b -> b) -> s -> t
- transformM :: (Monad m, Plated a) => (a -> m a) -> a -> m a
- transformMOn :: (Monad m, Plated a) => LensLike (WrappedMonad m) s t a a -> (a -> m a) -> s -> m t
- transformMOf :: Monad m => LensLike (WrappedMonad m) a b a b -> (b -> m b) -> a -> m b
- transformMOnOf :: Monad m => LensLike (WrappedMonad m) s t a b -> LensLike (WrappedMonad m) a b a b -> (b -> m b) -> s -> m t
- contexts :: Plated a => a -> [Context a a a]
- contextsOf :: ATraversal' a a -> a -> [Context a a a]
- contextsOn :: Plated a => ATraversal s t a a -> s -> [Context a a t]
- contextsOnOf :: ATraversal s t a a -> ATraversal' a a -> s -> [Context a a t]
- holes :: Plated a => a -> [Pretext (->) a a a]
- holesOn :: Conjoined p => Over p (Bazaar p a a) s t a a -> s -> [Pretext p a a t]
- holesOnOf :: Conjoined p => LensLike (Bazaar p r r) s t a b -> Over p (Bazaar p r r) a b r r -> s -> [Pretext p r r t]
- paraOf :: Getting (Endo [a]) a a -> (a -> [r] -> r) -> a -> r
- para :: Plated a => (a -> [r] -> r) -> a -> r
- composOpFold :: Plated a => b -> (b -> b -> b) -> (a -> b) -> a -> b
- parts :: Plated a => Lens' a [a]
- gplate :: (Generic a, GPlated a (Rep a)) => Traversal' a a
- gplate1 :: (Generic1 f, GPlated1 f (Rep1 f)) => Traversal' (f a) (f a)
- class Each s t a b | s -> a, t -> b, s b -> t, t a -> s where
- class Ixed m => At m where
- class Ixed m where
- ix :: Index m -> Traversal' m (IxValue m)
- type family IxValue (m :: Type) :: Type
- class Contains m where
- type family Index (s :: Type) :: Type
- icontains :: Contains m => Index m -> IndexedLens' (Index m) m Bool
- iix :: Ixed m => Index m -> IndexedTraversal' (Index m) m (IxValue m)
- ixAt :: At m => Index m -> Traversal' m (IxValue m)
- sans :: At m => Index m -> m -> m
- iat :: At m => Index m -> IndexedLens' (Index m) m (Maybe (IxValue m))
- makePrisms :: Name -> DecsQ
- makeClassyPrisms :: Name -> DecsQ
- type ClassyNamer = Name -> Maybe (Name, Name)
- data DefName
- type FieldNamer = Name -> [Name] -> Name -> [DefName]
- data LensRules
- simpleLenses :: Lens' LensRules Bool
- generateSignatures :: Lens' LensRules Bool
- generateUpdateableOptics :: Lens' LensRules Bool
- generateLazyPatterns :: Lens' LensRules Bool
- createClass :: Lens' LensRules Bool
- lensField :: Lens' LensRules FieldNamer
- lensClass :: Lens' LensRules ClassyNamer
- lensRules :: LensRules
- underscoreNoPrefixNamer :: FieldNamer
- lensRulesFor :: [(String, String)] -> LensRules
- lookingupNamer :: [(String, String)] -> FieldNamer
- mappingNamer :: (String -> [String]) -> FieldNamer
- classyRules :: LensRules
- classyRules_ :: LensRules
- makeLenses :: Name -> DecsQ
- makeClassy :: Name -> DecsQ
- makeClassy_ :: Name -> DecsQ
- makeLensesFor :: [(String, String)] -> Name -> DecsQ
- makeClassyFor :: String -> String -> [(String, String)] -> Name -> DecsQ
- makeLensesWith :: LensRules -> Name -> DecsQ
- declareLenses :: DecsQ -> DecsQ
- declareLensesFor :: [(String, String)] -> DecsQ -> DecsQ
- declareClassy :: DecsQ -> DecsQ
- declareClassyFor :: [(String, (String, String))] -> [(String, String)] -> DecsQ -> DecsQ
- declarePrisms :: DecsQ -> DecsQ
- declareWrapped :: DecsQ -> DecsQ
- declareFields :: DecsQ -> DecsQ
- declareLensesWith :: LensRules -> DecsQ -> DecsQ
- makeWrapped :: Name -> DecsQ
- underscoreFields :: LensRules
- underscoreNamer :: FieldNamer
- camelCaseFields :: LensRules
- camelCaseNamer :: FieldNamer
- classUnderscoreNoPrefixFields :: LensRules
- classUnderscoreNoPrefixNamer :: FieldNamer
- abbreviatedFields :: LensRules
- abbreviatedNamer :: FieldNamer
- makeFields :: Name -> DecsQ
- makeFieldsNoPrefix :: Name -> DecsQ
- defaultFieldRules :: LensRules
Documentation
class (Functor t, Foldable t) => Traversable (t :: Type -> Type) where #
Functors representing data structures that can be traversed from left to right.
A definition of traverse
must satisfy the following laws:
- Naturality
t .
for every applicative transformationtraverse
f =traverse
(t . f)t
- Identity
traverse
Identity
=Identity
- Composition
traverse
(Compose
.fmap
g . f) =Compose
.fmap
(traverse
g) .traverse
f
A definition of sequenceA
must satisfy the following laws:
- Naturality
t .
for every applicative transformationsequenceA
=sequenceA
.fmap
tt
- Identity
sequenceA
.fmap
Identity
=Identity
- Composition
sequenceA
.fmap
Compose
=Compose
.fmap
sequenceA
.sequenceA
where an applicative transformation is a function
t :: (Applicative f, Applicative g) => f a -> g a
preserving the Applicative
operations, i.e.
t (pure
x) =pure
x t (f<*>
x) = t f<*>
t x
and the identity functor Identity
and composition functors
Compose
are from Data.Functor.Identity and
Data.Functor.Compose.
A result of the naturality law is a purity law for traverse
traverse
pure
=pure
(The naturality law is implied by parametricity and thus so is the purity law [1, p15].)
Instances are similar to Functor
, e.g. given a data type
data Tree a = Empty | Leaf a | Node (Tree a) a (Tree a)
a suitable instance would be
instance Traversable Tree where traverse f Empty = pure Empty traverse f (Leaf x) = Leaf <$> f x traverse f (Node l k r) = Node <$> traverse f l <*> f k <*> traverse f r
This is suitable even for abstract types, as the laws for <*>
imply a form of associativity.
The superclass instances should satisfy the following:
- In the
Functor
instance,fmap
should be equivalent to traversal with the identity applicative functor (fmapDefault
). - In the
Foldable
instance,foldMap
should be equivalent to traversal with a constant applicative functor (foldMapDefault
).
References: [1] The Essence of the Iterator Pattern, Jeremy Gibbons and Bruno C. d. S. Oliveira
traverse :: Applicative f => (a -> f b) -> t a -> f (t b) #
Map each element of a structure to an action, evaluate these actions
from left to right, and collect the results. For a version that ignores
the results see traverse_
.
Instances
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:
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.
Instances
class Bifunctor (p :: Type -> Type -> Type) where #
A bifunctor is a type constructor that takes
two type arguments and is a functor in both arguments. That
is, unlike with Functor
, a type constructor such as Either
does not need to be partially applied for a Bifunctor
instance, and the methods in this class permit mapping
functions over the Left
value or the Right
value,
or both at the same time.
Formally, the class Bifunctor
represents a bifunctor
from Hask
-> Hask
.
Intuitively it is a bifunctor where both the first and second arguments are covariant.
You can define a Bifunctor
by either defining bimap
or by
defining both first
and second
.
If you supply bimap
, you should ensure that:
bimap
id
id
≡id
If you supply first
and second
, ensure:
first
id
≡id
second
id
≡id
If you supply both, you should also ensure:
bimap
f g ≡first
f.
second
g
These ensure by parametricity:
bimap
(f.
g) (h.
i) ≡bimap
f h.
bimap
g ifirst
(f.
g) ≡first
f.
first
gsecond
(f.
g) ≡second
f.
second
g
Since: base-4.8.0.0
Instances
Identity functor and monad. (a non-strict monad)
Since: base-4.8.0.0
Identity | |
|
Instances
The Const
functor.
Instances
Generic1 (Const a :: k -> Type) | Since: base-4.9.0.0 |
FunctorWithIndex Void (Const e :: Type -> Type) | |
FoldableWithIndex Void (Const e :: Type -> Type) | |
Defined in WithIndex | |
TraversableWithIndex Void (Const e :: Type -> Type) | |
Unbox a => Vector Vector (Const a b) | |
Defined in Data.Vector.Unboxed.Base basicUnsafeFreeze :: Mutable Vector s (Const a b) -> ST s (Vector (Const a b)) # basicUnsafeThaw :: Vector (Const a b) -> ST s (Mutable Vector s (Const a b)) # basicLength :: Vector (Const a b) -> Int # basicUnsafeSlice :: Int -> Int -> Vector (Const a b) -> Vector (Const a b) # basicUnsafeIndexM :: Vector (Const a b) -> Int -> Box (Const a b) # basicUnsafeCopy :: Mutable Vector s (Const a b) -> Vector (Const a b) -> ST s () # | |
Unbox a => MVector MVector (Const a b) | |
Defined in Data.Vector.Unboxed.Base 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 :: Int -> ST s (MVector s (Const a b)) # basicInitialize :: MVector s (Const a b) -> ST s () # basicUnsafeReplicate :: Int -> Const a b -> ST s (MVector s (Const a b)) # basicUnsafeRead :: MVector s (Const a b) -> Int -> ST s (Const a b) # basicUnsafeWrite :: MVector s (Const a b) -> Int -> Const a b -> ST s () # basicClear :: MVector s (Const a b) -> ST s () # basicSet :: MVector s (Const a b) -> Const a b -> ST s () # basicUnsafeCopy :: MVector s (Const a b) -> MVector s (Const a b) -> ST s () # basicUnsafeMove :: MVector s (Const a b) -> MVector s (Const a b) -> ST s () # basicUnsafeGrow :: MVector s (Const a b) -> Int -> ST s (MVector s (Const a b)) # | |
Bifunctor (Const :: Type -> Type -> Type) | Since: base-4.8.0.0 |
Bitraversable (Const :: Type -> Type -> Type) | Since: base-4.10.0.0 |
Defined in Data.Bitraversable 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 |
Eq2 (Const :: Type -> Type -> Type) | Since: base-4.9.0.0 |
Ord2 (Const :: Type -> Type -> Type) | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes | |
Read2 (Const :: Type -> Type -> Type) | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes 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 |
Biapplicative (Const :: Type -> Type -> Type) | |
NFData2 (Const :: Type -> Type -> Type) | Since: deepseq-1.4.3.0 |
Defined in Control.DeepSeq | |
Hashable2 (Const :: Type -> Type -> Type) | |
Defined in Data.Hashable.Class | |
Bitraversable1 (Const :: Type -> Type -> Type) | |
Defined in Data.Semigroup.Traversable.Class 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) # | |
Biapply (Const :: Type -> Type -> Type) | |
Bifoldable1 (Const :: Type -> Type -> Type) | |
Defined in Data.Semigroup.Foldable.Class | |
Semigroupoid (Const :: Type -> Type -> Type) | |
Functor (Const m :: Type -> Type) | Since: base-2.1 |
Monoid m => Applicative (Const m :: Type -> Type) | Since: base-2.0.1 |
Foldable (Const m :: Type -> Type) | Since: base-4.7.0.0 |
Defined in Data.Functor.Const fold :: Monoid m0 => Const m m0 -> m0 # foldMap :: Monoid m0 => (a -> m0) -> Const m a -> 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 # elem :: Eq a => a -> Const m a -> Bool # maximum :: Ord a => Const m a -> a # minimum :: Ord a => Const m a -> a # | |
Traversable (Const m :: Type -> Type) | Since: base-4.7.0.0 |
Contravariant (Const a :: Type -> Type) | |
Eq a => Eq1 (Const a :: Type -> Type) | Since: base-4.9.0.0 |
Ord a => Ord1 (Const a :: Type -> Type) | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes | |
Read a => Read1 (Const a :: Type -> Type) | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes | |
Show a => Show1 (Const a :: Type -> Type) | Since: base-4.9.0.0 |
NFData a => NFData1 (Const a :: Type -> Type) | Since: deepseq-1.4.3.0 |
Defined in Control.DeepSeq | |
Hashable a => Hashable1 (Const a :: Type -> Type) | |
Defined in Data.Hashable.Class | |
Semigroup m => Apply (Const m :: Type -> Type) | A |
ComonadCofree (Const b :: Type -> Type) ((,) b) | |
Defined in Control.Comonad.Cofree.Class | |
Sieve (Forget r :: Type -> Type -> Type) (Const r :: Type -> Type) | |
Defined in Data.Profunctor.Sieve | |
Bounded a => Bounded (Const a b) | Since: base-4.9.0.0 |
Enum a => Enum (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const succ :: Const a b -> Const a b # pred :: Const a b -> 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 |
Floating a => Floating (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const 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 # | |
Fractional a => Fractional (Const a b) | Since: base-4.9.0.0 |
Integral a => Integral (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const | |
(Typeable k, Data a, Typeable b) => Data (Const a b) | Since: base-4.10.0.0 |
Defined in Data.Data 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 :: forall r r'. (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 |
Ord a => Ord (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const | |
Read a => Read (Const a b) | This instance would be equivalent to the derived instances of the
Since: base-4.8.0.0 |
Real a => Real (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const toRational :: Const a b -> Rational # | |
RealFloat a => RealFloat (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const 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 # isInfinite :: Const a b -> Bool # isDenormalized :: Const a b -> Bool # isNegativeZero :: Const a b -> Bool # | |
RealFrac a => RealFrac (Const a b) | Since: base-4.9.0.0 |
Show a => Show (Const a b) | This instance would be equivalent to the derived instances of the
Since: base-4.8.0.0 |
Ix a => Ix (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const 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) | Since: base-4.9.0.0 |
Semigroup a => Semigroup (Const a b) | Since: base-4.9.0.0 |
Monoid a => Monoid (Const a b) | Since: base-4.9.0.0 |
Storable a => Storable (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const | |
Bits a => Bits (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const (.&.) :: 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 # 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 # 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 # | |
FiniteBits a => FiniteBits (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const finiteBitSize :: Const a b -> Int # countLeadingZeros :: Const a b -> Int # countTrailingZeros :: Const a b -> Int # | |
NFData a => NFData (Const a b) | Since: deepseq-1.4.0.0 |
Defined in Control.DeepSeq | |
Hashable a => Hashable (Const a b) | |
Defined in Data.Hashable.Class | |
Prim a => Prim (Const a b) | Since: primitive-0.6.5.0 |
Defined in Data.Primitive.Types 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) | |
Defined in Data.Vector.Unboxed.Base | |
Wrapped (Const a x) Source # | |
t ~ Const a' x' => Rewrapped (Const a x) t Source # | |
Defined in Control.Lens.Wrapped | |
type Rep1 (Const a :: k -> Type) | |
Defined in Data.Functor.Const | |
newtype MVector s (Const a b) | |
Defined in Data.Vector.Unboxed.Base | |
type Rep (Const a b) | |
Defined in Data.Functor.Const | |
newtype Vector (Const a b) | |
Defined in Data.Vector.Unboxed.Base | |
type Unwrapped (Const a x) Source # | |
Defined in Control.Lens.Wrapped |
data (a :: k) :~: (b :: k) where infix 4 #
Propositional equality. If a :~: b
is inhabited by some terminating
value, then the type a
is the same as the type b
. To use this equality
in practice, pattern-match on the a :~: b
to get out the Refl
constructor;
in the body of the pattern-match, the compiler knows that a ~ b
.
Since: base-4.7.0.0
Instances
Category ((:~:) :: k -> k -> Type) | Since: base-4.7.0.0 |
Semigroupoid ((:~:) :: k -> k -> Type) | |
TestCoercion ((:~:) a :: k -> Type) | Since: base-4.7.0.0 |
Defined in Data.Type.Coercion | |
TestEquality ((:~:) a :: k -> Type) | Since: base-4.7.0.0 |
Defined in Data.Type.Equality | |
NFData2 ((:~:) :: Type -> Type -> Type) | Since: deepseq-1.4.3.0 |
Defined in Control.DeepSeq | |
NFData1 ((:~:) a) | Since: deepseq-1.4.3.0 |
Defined in Control.DeepSeq | |
a ~ b => Bounded (a :~: b) | Since: base-4.7.0.0 |
a ~ b => Enum (a :~: b) | Since: base-4.7.0.0 |