Copyright | (c) 2011-2015 diagrams-lib team (see LICENSE) |
---|---|
License | BSD-style (see LICENSE) |
Maintainer | diagrams-discuss@googlegroups.com |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
A module to re-export most of the functionality of the diagrams core and standard library.
Synopsis
- module Diagrams
- module Data.Default.Class
- class ColourOps (f :: Type -> Type) where
- data AlphaColour a
- data Colour a
- colourConvert :: (Fractional b, Real a) => Colour a -> Colour b
- black :: Num a => Colour a
- transparent :: Num a => AlphaColour a
- alphaColourConvert :: (Fractional b, Real a) => AlphaColour a -> AlphaColour b
- opaque :: Num a => Colour a -> AlphaColour a
- dissolve :: Num a => a -> AlphaColour a -> AlphaColour a
- withOpacity :: Num a => Colour a -> a -> AlphaColour a
- blend :: (Num a, AffineSpace f) => a -> f a -> f a -> f a
- alphaChannel :: AlphaColour a -> a
- black :: Num a => Colour a
- readColourName :: (MonadFail m, Monad m, Ord a, Floating a) => String -> m (Colour a)
- aliceblue :: (Ord a, Floating a) => Colour a
- antiquewhite :: (Ord a, Floating a) => Colour a
- aqua :: (Ord a, Floating a) => Colour a
- aquamarine :: (Ord a, Floating a) => Colour a
- azure :: (Ord a, Floating a) => Colour a
- beige :: (Ord a, Floating a) => Colour a
- bisque :: (Ord a, Floating a) => Colour a
- blanchedalmond :: (Ord a, Floating a) => Colour a
- blue :: (Ord a, Floating a) => Colour a
- blueviolet :: (Ord a, Floating a) => Colour a
- brown :: (Ord a, Floating a) => Colour a
- burlywood :: (Ord a, Floating a) => Colour a
- cadetblue :: (Ord a, Floating a) => Colour a
- chartreuse :: (Ord a, Floating a) => Colour a
- chocolate :: (Ord a, Floating a) => Colour a
- coral :: (Ord a, Floating a) => Colour a
- cornflowerblue :: (Ord a, Floating a) => Colour a
- cornsilk :: (Ord a, Floating a) => Colour a
- crimson :: (Ord a, Floating a) => Colour a
- cyan :: (Ord a, Floating a) => Colour a
- darkblue :: (Ord a, Floating a) => Colour a
- darkcyan :: (Ord a, Floating a) => Colour a
- darkgoldenrod :: (Ord a, Floating a) => Colour a
- darkgray :: (Ord a, Floating a) => Colour a
- darkgreen :: (Ord a, Floating a) => Colour a
- darkgrey :: (Ord a, Floating a) => Colour a
- darkkhaki :: (Ord a, Floating a) => Colour a
- darkmagenta :: (Ord a, Floating a) => Colour a
- darkolivegreen :: (Ord a, Floating a) => Colour a
- darkorange :: (Ord a, Floating a) => Colour a
- darkorchid :: (Ord a, Floating a) => Colour a
- darkred :: (Ord a, Floating a) => Colour a
- darksalmon :: (Ord a, Floating a) => Colour a
- darkseagreen :: (Ord a, Floating a) => Colour a
- darkslateblue :: (Ord a, Floating a) => Colour a
- darkslategray :: (Ord a, Floating a) => Colour a
- darkslategrey :: (Ord a, Floating a) => Colour a
- darkturquoise :: (Ord a, Floating a) => Colour a
- darkviolet :: (Ord a, Floating a) => Colour a
- deeppink :: (Ord a, Floating a) => Colour a
- deepskyblue :: (Ord a, Floating a) => Colour a
- dimgray :: (Ord a, Floating a) => Colour a
- dimgrey :: (Ord a, Floating a) => Colour a
- dodgerblue :: (Ord a, Floating a) => Colour a
- firebrick :: (Ord a, Floating a) => Colour a
- floralwhite :: (Ord a, Floating a) => Colour a
- forestgreen :: (Ord a, Floating a) => Colour a
- fuchsia :: (Ord a, Floating a) => Colour a
- gainsboro :: (Ord a, Floating a) => Colour a
- ghostwhite :: (Ord a, Floating a) => Colour a
- gold :: (Ord a, Floating a) => Colour a
- goldenrod :: (Ord a, Floating a) => Colour a
- gray :: (Ord a, Floating a) => Colour a
- grey :: (Ord a, Floating a) => Colour a
- green :: (Ord a, Floating a) => Colour a
- greenyellow :: (Ord a, Floating a) => Colour a
- honeydew :: (Ord a, Floating a) => Colour a
- hotpink :: (Ord a, Floating a) => Colour a
- indianred :: (Ord a, Floating a) => Colour a
- indigo :: (Ord a, Floating a) => Colour a
- ivory :: (Ord a, Floating a) => Colour a
- khaki :: (Ord a, Floating a) => Colour a
- lavender :: (Ord a, Floating a) => Colour a
- lavenderblush :: (Ord a, Floating a) => Colour a
- lawngreen :: (Ord a, Floating a) => Colour a
- lemonchiffon :: (Ord a, Floating a) => Colour a
- lightblue :: (Ord a, Floating a) => Colour a
- lightcoral :: (Ord a, Floating a) => Colour a
- lightcyan :: (Ord a, Floating a) => Colour a
- lightgoldenrodyellow :: (Ord a, Floating a) => Colour a
- lightgray :: (Ord a, Floating a) => Colour a
- lightgreen :: (Ord a, Floating a) => Colour a
- lightgrey :: (Ord a, Floating a) => Colour a
- lightpink :: (Ord a, Floating a) => Colour a
- lightsalmon :: (Ord a, Floating a) => Colour a
- lightseagreen :: (Ord a, Floating a) => Colour a
- lightskyblue :: (Ord a, Floating a) => Colour a
- lightslategray :: (Ord a, Floating a) => Colour a
- lightslategrey :: (Ord a, Floating a) => Colour a
- lightsteelblue :: (Ord a, Floating a) => Colour a
- lightyellow :: (Ord a, Floating a) => Colour a
- lime :: (Ord a, Floating a) => Colour a
- limegreen :: (Ord a, Floating a) => Colour a
- linen :: (Ord a, Floating a) => Colour a
- magenta :: (Ord a, Floating a) => Colour a
- maroon :: (Ord a, Floating a) => Colour a
- mediumaquamarine :: (Ord a, Floating a) => Colour a
- mediumblue :: (Ord a, Floating a) => Colour a
- mediumorchid :: (Ord a, Floating a) => Colour a
- mediumpurple :: (Ord a, Floating a) => Colour a
- mediumseagreen :: (Ord a, Floating a) => Colour a
- mediumslateblue :: (Ord a, Floating a) => Colour a
- mediumspringgreen :: (Ord a, Floating a) => Colour a
- mediumturquoise :: (Ord a, Floating a) => Colour a
- mediumvioletred :: (Ord a, Floating a) => Colour a
- midnightblue :: (Ord a, Floating a) => Colour a
- mintcream :: (Ord a, Floating a) => Colour a
- mistyrose :: (Ord a, Floating a) => Colour a
- moccasin :: (Ord a, Floating a) => Colour a
- navajowhite :: (Ord a, Floating a) => Colour a
- navy :: (Ord a, Floating a) => Colour a
- oldlace :: (Ord a, Floating a) => Colour a
- olive :: (Ord a, Floating a) => Colour a
- olivedrab :: (Ord a, Floating a) => Colour a
- orange :: (Ord a, Floating a) => Colour a
- orangered :: (Ord a, Floating a) => Colour a
- orchid :: (Ord a, Floating a) => Colour a
- palegoldenrod :: (Ord a, Floating a) => Colour a
- palegreen :: (Ord a, Floating a) => Colour a
- paleturquoise :: (Ord a, Floating a) => Colour a
- palevioletred :: (Ord a, Floating a) => Colour a
- papayawhip :: (Ord a, Floating a) => Colour a
- peachpuff :: (Ord a, Floating a) => Colour a
- peru :: (Ord a, Floating a) => Colour a
- pink :: (Ord a, Floating a) => Colour a
- plum :: (Ord a, Floating a) => Colour a
- powderblue :: (Ord a, Floating a) => Colour a
- purple :: (Ord a, Floating a) => Colour a
- red :: (Ord a, Floating a) => Colour a
- rosybrown :: (Ord a, Floating a) => Colour a
- royalblue :: (Ord a, Floating a) => Colour a
- saddlebrown :: (Ord a, Floating a) => Colour a
- salmon :: (Ord a, Floating a) => Colour a
- sandybrown :: (Ord a, Floating a) => Colour a
- seagreen :: (Ord a, Floating a) => Colour a
- seashell :: (Ord a, Floating a) => Colour a
- sienna :: (Ord a, Floating a) => Colour a
- silver :: (Ord a, Floating a) => Colour a
- skyblue :: (Ord a, Floating a) => Colour a
- slateblue :: (Ord a, Floating a) => Colour a
- slategray :: (Ord a, Floating a) => Colour a
- slategrey :: (Ord a, Floating a) => Colour a
- snow :: (Ord a, Floating a) => Colour a
- springgreen :: (Ord a, Floating a) => Colour a
- steelblue :: (Ord a, Floating a) => Colour a
- teal :: (Ord a, Floating a) => Colour a
- thistle :: (Ord a, Floating a) => Colour a
- tomato :: (Ord a, Floating a) => Colour a
- turquoise :: (Ord a, Floating a) => Colour a
- violet :: (Ord a, Floating a) => Colour a
- wheat :: (Ord a, Floating a) => Colour a
- white :: (Ord a, Floating a) => Colour a
- whitesmoke :: (Ord a, Floating a) => Colour a
- yellow :: (Ord a, Floating a) => Colour a
- yellowgreen :: (Ord a, Floating a) => Colour a
- module Data.Colour.SRGB
- module Data.Semigroup
- module Linear.Vector
- module Linear.Affine
- module Linear.Metric
- module Data.Active
- type Traversal s t a b = forall (f :: Type -> Type). Applicative f => (a -> f b) -> s -> f t
- type Fold s a = forall (f :: Type -> Type). (Contravariant f, Applicative f) => (a -> f a) -> s -> f s
- class Contravariant (f :: Type -> Type) where
- class (forall a. Functor (p a)) => Bifunctor (p :: Type -> Type -> Type) where
- bimap :: (a -> b) -> (c -> d) -> p a c -> p b d
- class (Functor t, Foldable t) => Traversable (t :: Type -> Type) where
- traverse :: Applicative f => (a -> f b) -> t a -> f (t b)
- data (a :: k) :~: (b :: k) where
- newtype Const a (b :: k) = Const {
- getConst :: a
- newtype Identity a = Identity {
- runIdentity :: a
- type IndexedTraversal i s t a b = forall (p :: Type -> Type -> Type) (f :: Type -> Type). (Indexable i p, Applicative f) => p a (f b) -> s -> f t
- 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 Foldable f => FoldableWithIndex i (f :: Type -> Type) | f -> i where
- class Functor f => FunctorWithIndex i (f :: Type -> Type) | f -> i where
- imap :: (i -> a -> b) -> f a -> f b
- data Sequenced a (m :: Type -> Type)
- data Traversed a (f :: Type -> Type)
- class Profunctor (p :: Type -> Type -> Type) where
- type Iso s t a b = forall (p :: Type -> Type -> Type) (f :: Type -> Type). (Profunctor p, Functor f) => p a (f b) -> p s (f t)
- type IndexedFold i s a = forall (p :: Type -> Type -> Type) (f :: Type -> Type). (Indexable i p, Contravariant f, Applicative f) => p a (f a) -> s -> f s
- type Prism s t a b = forall (p :: Type -> Type -> Type) (f :: Type -> Type). (Choice p, Applicative f) => p a (f b) -> p s (f t)
- type Lens s t a b = forall (f :: Type -> Type). Functor f => (a -> f b) -> s -> f t
- type IndexedLens i s t a b = forall (f :: Type -> Type) (p :: Type -> Type -> Type). (Indexable i p, Functor f) => p a (f b) -> s -> f t
- type Getter s a = forall (f :: Type -> Type). (Contravariant f, Functor f) => (a -> f a) -> s -> f s
- type IndexedGetter i s a = forall (p :: Type -> Type -> Type) (f :: Type -> Type). (Indexable i p, Contravariant f, Functor f) => p a (f a) -> s -> f s
- type LensLike (f :: k -> Type) s (t :: k) a (b :: k) = (a -> f b) -> s -> f t
- type Over (p :: k -> Type -> Type) (f :: k1 -> Type) s (t :: k1) (a :: k) (b :: k1) = p a (f b) -> s -> f t
- newtype Bazaar (p :: Type -> Type -> Type) a b t = Bazaar {
- runBazaar :: forall (f :: Type -> Type). Applicative f => p a (f b) -> f t
- type Setter s t a b = forall (f :: Type -> Type). Settable f => (a -> f b) -> s -> f t
- class (MonadState s m, MonadState t n) => Zoom (m :: Type -> Type) (n :: Type -> Type) s t | m -> s, n -> t, m t -> n, n s -> m where
- type Getting r s a = (a -> Const r a) -> s -> Const r s
- type Traversal' s a = Traversal s s a a
- type Setter' s a = Setter s s a a
- type Iso' s a = Iso s s a a
- class AsEmpty a where
- newtype ReifiedTraversal s t a b = Traversal {
- runTraversal :: Traversal s t a b
- type Prism' s a = Prism s s a a
- type Lens' s a = Lens s s a a
- newtype Indexed i a b = Indexed {
- runIndexed :: i -> a -> b
- type Simple (f :: k1 -> k1 -> k2 -> k2 -> k) (s :: k1) (a :: k2) = f s s a a
- class Wrapped s where
- class Profunctor p => Choice (p :: Type -> Type -> Type) where
- class (Foldable1 t, Traversable t) => Traversable1 (t :: Type -> Type) where
- class Reversing t where
- reversing :: t -> t
- data Level i a
- class Conjoined p => Indexable i (p :: Type -> Type -> Type)
- 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 :: Type -> Type -> Type) where
- data Rightmost a
- data Leftmost a
- type Context' a = Context a a
- data Context a b t = Context (b -> t) a
- type Bazaar1' (p :: Type -> Type -> Type) a = Bazaar1 p a a
- newtype Bazaar1 (p :: Type -> Type -> Type) a b t = Bazaar1 {
- runBazaar1 :: forall (f :: Type -> Type). Apply f => p a (f b) -> f t
- type Bazaar' (p :: Type -> Type -> Type) a = Bazaar p a a
- data Magma i t b a
- class (Profunctor p, Bifunctor p) => Reviewable (p :: Type -> Type -> Type)
- class (Applicative f, Distributive f, Traversable f) => Settable (f :: Type -> Type)
- type Over' (p :: Type -> Type -> Type) (f :: Type -> Type) s a = Over p f s s a a
- type IndexedLensLike' i (f :: Type -> Type) s a = IndexedLensLike i f s s a a
- type IndexedLensLike i (f :: k -> Type) s (t :: k) a (b :: k) = forall (p :: Type -> Type -> Type). Indexable i p => p a (f b) -> s -> f t
- type LensLike' (f :: Type -> Type) s a = LensLike f s s a a
- type Optical' (p :: k -> k1 -> Type) (q :: k -> k1 -> Type) (f :: k -> k1) (s :: k) (a :: k) = Optical p q f s s a a
- type Optical (p :: k -> k1 -> Type) (q :: k2 -> k1 -> Type) (f :: k3 -> k1) (s :: k2) (t :: k3) (a :: k) (b :: k3) = p a (f b) -> q s (f t)
- type Optic' (p :: k -> k1 -> Type) (f :: k -> k1) (s :: k) (a :: k) = Optic p f s s a a
- type Optic (p :: k -> k1 -> Type) (f :: k2 -> k1) (s :: k) (t :: k2) (a :: k) (b :: k2) = p a (f b) -> p s (f t)
- type IndexPreservingFold1 s a = forall (p :: Type -> Type -> Type) (f :: Type -> Type). (Conjoined p, Contravariant f, Apply f) => p a (f a) -> p s (f s)
- type IndexedFold1 i s a = forall (p :: Type -> Type -> Type) (f :: Type -> Type). (Indexable i p, Contravariant f, Apply f) => p a (f a) -> s -> f s
- type Fold1 s a = forall (f :: Type -> Type). (Contravariant f, Apply f) => (a -> f a) -> s -> f s
- type IndexPreservingFold s a = forall (p :: Type -> Type -> Type) (f :: Type -> Type). (Conjoined p, Contravariant f, Applicative f) => p a (f a) -> p s (f s)
- type IndexPreservingGetter s a = forall (p :: Type -> Type -> Type) (f :: Type -> Type). (Conjoined p, Contravariant f, Functor f) => p a (f a) -> p s (f s)
- type As (a :: k2) = Equality' a a
- type Equality' (s :: k2) (a :: k2) = 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 AReview t b = Optic' (Tagged :: Type -> Type -> Type) Identity t b
- type Review t b = forall (p :: Type -> Type -> Type) (f :: Type -> Type). (Choice p, Bifunctor p, Settable f) => Optic' p f t b
- type IndexPreservingSetter' s a = IndexPreservingSetter s s a a
- type IndexPreservingSetter s t a b = forall (p :: Type -> Type -> Type) (f :: Type -> Type). (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 :: Type -> Type) (p :: Type -> Type -> Type). (Indexable i p, Settable f) => p a (f b) -> s -> f t
- type IndexPreservingTraversal1' s a = IndexPreservingTraversal1 s s a a
- type IndexPreservingTraversal1 s t a b = forall (p :: Type -> Type -> Type) (f :: Type -> Type). (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 :: Type -> Type -> Type) (f :: Type -> Type). (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 :: Type -> Type -> Type) (f :: Type -> Type). (Indexable i p, Apply f) => p a (f b) -> s -> f t
- type IndexedTraversal' i s a = IndexedTraversal i s s a a
- type Traversal1' s a = Traversal1 s s a a
- type Traversal1 s t a b = forall (f :: Type -> Type). Apply f => (a -> f b) -> s -> f t
- type IndexPreservingLens' s a = IndexPreservingLens s s a a
- type IndexPreservingLens s t a b = forall (p :: Type -> Type -> Type) (f :: Type -> Type). (Conjoined p, Functor f) => p a (f b) -> p s (f t)
- type IndexedLens' i s a = IndexedLens i s s a a
- type Setting' (p :: Type -> Type -> Type) s a = Setting p s s a a
- type Setting (p :: Type -> Type -> Type) 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
- 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
- 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
- type Accessing (p :: Type -> Type -> Type) 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
- 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)
- class Ord k => TraverseMax k (m :: Type -> Type) | m -> k where
- traverseMax :: IndexedTraversal' k (m v) v
- class Ord k => TraverseMin k (m :: Type -> Type) | m -> k where
- traverseMin :: IndexedTraversal' k (m v) v
- type Traversing1' (p :: Type -> Type -> Type) (f :: Type -> Type) s a = Traversing1 p f s s a a
- type Traversing' (p :: Type -> Type -> Type) (f :: Type -> Type) s a = Traversing p f s s a a
- type Traversing1 (p :: Type -> Type -> Type) (f :: Type -> Type) s t a b = Over p (BazaarT1 p f a b) s t a b
- type Traversing (p :: Type -> Type -> Type) (f :: Type -> Type) 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
- 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
- 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 {}
- type AnEquality' (s :: k) (a :: k) = AnEquality s s a a
- type AnEquality (s :: k) (t :: k1) (a :: k) (b :: k2) = Identical a (Proxy b) a (Proxy b) -> Identical a (Proxy b) s (Proxy t)
- data Identical (a :: k) (b :: k1) (s :: k) (t :: k1) where
- 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)
- 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
- class (Rewrapped s t, Rewrapped t s) => Rewrapping s t
- class Wrapped s => Rewrapped s t
- type family Unwrapped s
- class (Magnified m ~ Magnified n, MonadReader b m, MonadReader a n) => Magnify (m :: Type -> Type) (n :: Type -> Type) b a | m -> b, n -> a, m a -> n, n b -> m where
- type family Magnified (m :: Type -> Type) :: Type -> Type -> Type
- type family Zoomed (m :: Type -> Type) :: Type -> Type -> Type
- class GPlated1 (f :: k -> Type) (g :: k -> Type)
- class GPlated a (g :: k -> Type)
- class Plated a where
- plate :: Traversal' a a
- class Each s t a b | s -> a, t -> b, s b -> t, t a -> s where
- class Ixed m => At m
- class Ixed m where
- ix :: Index m -> Traversal' m (IxValue m)
- type family IxValue m
- class Contains m
- type family Index s
- type ClassyNamer = Name -> Maybe (Name, Name)
- data DefName
- type FieldNamer = Name -> [Name] -> Name -> [DefName]
- data LensRules
- pattern Empty :: AsEmpty s => s
- pattern List :: IsList l => [Item l] -> l
- pattern (:>) :: Snoc a a b b => a -> b -> a
- pattern (:<) :: Cons b b a a => a -> b -> b
- pattern Strict :: Strict s t => t -> s
- pattern Lazy :: Strict t s => t -> s
- pattern Wrapped :: Rewrapped s s => Unwrapped s -> s
- pattern Reversed :: Reversing t => t -> t
- pattern Swapped :: Swap p => p b a -> p a b
- pattern Unwrapped :: Rewrapped t t => t -> Unwrapped t
- lens :: (s -> a) -> (s -> b -> t) -> Lens s t a b
- strict :: Strict lazy strict => Iso' lazy strict
- only :: Eq a => a -> Prism' a ()
- index :: (Indexable i p, Eq i, Applicative f) => i -> Optical' p (Indexed i) f a a
- lazy :: Strict lazy strict => Iso' strict lazy
- uncons :: Cons s s a a => s -> Maybe (a, s)
- (<&>) :: Functor f => f a -> (a -> b) -> f b
- (&) :: a -> (a -> b) -> b
- from :: AnIso s t a b -> Iso b a t s
- to :: (Profunctor p, Contravariant f) => (s -> a) -> Optic' p f s a
- (<|) :: Cons s s a a => a -> s -> s
- cons :: Cons s s a a => a -> s -> s
- snoc :: Snoc s s a a => s -> a -> s
- unsnoc :: Snoc s s a a => s -> Maybe (s, a)
- over :: ASetter s t a b -> (a -> b) -> s -> t
- (|>) :: Snoc s s a a => s -> a -> s
- chosen :: forall a b p f. (Conjoined p, Functor f) => p a (f b) -> p (Either a a) (f (Either b b))
- traverseOf_ :: Functor f => Getting (Traversed r f) s a -> (a -> f r) -> s -> f ()
- foldlOf' :: Getting (Endo (Endo r)) s a -> (r -> a -> r) -> r -> s -> r
- mapMOf_ :: Monad m => Getting (Sequenced r m) s a -> (a -> m r) -> s -> m ()
- ifor :: (TraversableWithIndex i t, Applicative f) => t a -> (i -> a -> f b) -> f (t b)
- imapM :: (TraversableWithIndex i t, Monad m) => (i -> a -> m b) -> t a -> m (t b)
- iforM :: (TraversableWithIndex i t, Monad m) => t a -> (i -> a -> m b) -> m (t b)
- imapAccumR :: TraversableWithIndex i t => (i -> s -> a -> (s, b)) -> s -> t a -> (s, t b)
- imapAccumL :: TraversableWithIndex i t => (i -> s -> a -> (s, b)) -> s -> t a -> (s, t b)
- iany :: FoldableWithIndex i f => (i -> a -> Bool) -> f a -> Bool
- iall :: FoldableWithIndex i f => (i -> a -> Bool) -> f a -> Bool
- inone :: FoldableWithIndex i f => (i -> a -> Bool) -> f a -> Bool
- itraverse_ :: (FoldableWithIndex i t, Applicative f) => (i -> a -> f b) -> t a -> f ()
- ifor_ :: (FoldableWithIndex i t, Applicative f) => t a -> (i -> a -> f b) -> f ()
- imapM_ :: (FoldableWithIndex i t, Monad m) => (i -> a -> m b) -> t a -> m ()
- iforM_ :: (FoldableWithIndex i t, Monad m) => t a -> (i -> a -> m b) -> m ()
- iconcatMap :: FoldableWithIndex i f => (i -> a -> [b]) -> f a -> [b]
- ifind :: FoldableWithIndex i f => (i -> a -> Bool) -> f a -> Maybe (i, a)
- ifoldrM :: (FoldableWithIndex i f, Monad m) => (i -> a -> b -> m b) -> b -> f a -> m b
- ifoldlM :: (FoldableWithIndex i f, Monad m) => (i -> b -> a -> m b) -> b -> f a -> m b
- itoList :: FoldableWithIndex i f => f a -> [(i, a)]
- swapped :: forall (p :: Type -> Type -> Type) a b c d. Swap p => Iso (p a b) (p c d) (p b a) (p d c)
- lastOf :: Getting (Rightmost a) s a -> s -> Maybe a
- firstOf :: Getting (Leftmost a) s a -> s -> Maybe a
- traverse1Of_ :: Functor f => Getting (TraversedF r f) s a -> (a -> f r) -> s -> f ()
- cloneLens :: ALens s t a b -> Lens s t a b
- taking :: (Conjoined p, Applicative f) => Int -> Traversing p f s t a a -> Over p f s t a a
- traversed :: forall (f :: Type -> Type) a b. Traversable f => IndexedTraversal Int (f a) (f b) a b
- foldMapOf :: Getting r s a -> (a -> r) -> s -> r
- re :: AReview t b -> Getter b t
- review :: MonadReader b m => AReview t b -> m t
- preview :: MonadReader s m => Getting (First a) s a -> m (Maybe a)
- (^?) :: s -> Getting (First a) s a -> Maybe a
- matching :: APrism s t a b -> s -> Either t a
- lengthOf :: Getting (Endo (Endo Int)) s a -> s -> Int
- prism :: (b -> t) -> (s -> Either t a) -> Prism s t a b
- set :: ASetter s t a b -> b -> s -> t
- view :: MonadReader s m => Getting a s a -> m a
- cloneTraversal :: ATraversal s t a b -> Traversal s t a b
- use :: MonadState s m => Getting a s a -> m a
- (^.) :: s -> Getting a s a -> a
- (.~) :: ASetter s t a b -> b -> s -> t
- (%~) :: ASetter s t a b -> (a -> b) -> s -> t
- (+~) :: Num a => ASetter s t a a -> a -> s -> t
- (-~) :: Num a => ASetter s t a a -> a -> s -> t
- (*~) :: Num a => ASetter s t a a -> a -> s -> t
- (//~) :: Fractional a => ASetter s t a a -> a -> s -> t
- (^~) :: (Num a, Integral e) => ASetter s t a a -> e -> s -> t
- (^^~) :: (Fractional a, Integral e) => ASetter s t a a -> e -> s -> t
- (**~) :: Floating a => ASetter s t a a -> a -> s -> t
- (||~) :: ASetter s t Bool Bool -> Bool -> s -> t
- (&&~) :: ASetter s t Bool Bool -> Bool -> s -> t
- (?~) :: ASetter s t a (Maybe b) -> b -> s -> t
- (<>~) :: Semigroup a => ASetter s t a a -> a -> s -> t
- (%=) :: MonadState s m => ASetter s s a b -> (a -> b) -> m ()
- (+=) :: (MonadState s m, Num a) => ASetter' s a -> a -> m ()
- (-=) :: (MonadState s m, Num a) => ASetter' s a -> a -> m ()
- (*=) :: (MonadState s m, Num a) => ASetter' s a -> a -> m ()
- (//=) :: (MonadState s m, Fractional a) => ASetter' s a -> a -> m ()
- (^=) :: (MonadState s m, Num a, Integral e) => ASetter' s a -> e -> m ()
- (^^=) :: (MonadState s m, Fractional a, Integral e) => ASetter' s a -> e -> m ()
- (**=) :: (MonadState s m, Floating a) => ASetter' s a -> a -> m ()
- (||=) :: MonadState s m => ASetter' s Bool -> Bool -> m ()
- (&&=) :: MonadState s m => ASetter' s Bool -> Bool -> m ()
- (.=) :: MonadState s m => ASetter s s a b -> b -> m ()
- (?=) :: MonadState s m => ASetter s s a (Maybe b) -> b -> m ()
- (<>=) :: (MonadState s m, Semigroup a) => ASetter' s a -> a -> m ()
- (%@~) :: AnIndexedSetter i s t a b -> (i -> a -> b) -> s -> t
- withIndex :: (Indexable i p, Functor f) => p (i, s) (f (j, t)) -> Indexed i s (f t)
- (<.~) :: ASetter s t a b -> b -> s -> (b, t)
- (<.=) :: MonadState s m => ASetter s s a b -> b -> m b
- anyOf :: Getting Any s a -> (a -> Bool) -> s -> Bool
- ifoldMapOf :: IndexedGetting i m s a -> (i -> a -> m) -> s -> m
- dropping :: (Conjoined p, Applicative f) => Int -> Over p (Indexing f) s t a a -> Over p f s t a a
- traverseOf :: LensLike f s t a b -> (a -> f b) -> s -> f t
- _Left :: forall a c b p f. (Choice p, Applicative f) => p a (f b) -> p (Either a c) (f (Either b c))
- forOf :: LensLike f s t a b -> s -> (a -> f b) -> f t
- itraverseOf :: (Indexed i a (f b) -> s -> f t) -> (i -> a -> f b) -> s -> 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
- contextsOf :: ATraversal' a a -> a -> [Context a a a]
- 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)
- folded :: forall (f :: Type -> Type) a. Foldable f => IndexedFold Int (f a) a
- 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')
- without :: APrism s t a b -> APrism u v c d -> Prism (Either s u) (Either t v) (Either a c) (Either b d)
- 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
- foldBy :: Foldable t => (a -> a -> a) -> a -> t a -> a
- foldMapBy :: Foldable t => (r -> r -> r) -> r -> (a -> r) -> t a -> r
- 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)
- sequenceBy :: Traversable t => (forall x. x -> f x) -> (forall x y. f (x -> y) -> f x -> f y) -> t (f a) -> f (t a)
- 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
- asIndex :: (Indexable i p, Contravariant f, Functor f) => p i (f i) -> Indexed i s (f s)
- retagged :: (Profunctor p, Bifunctor p) => p a b -> p s b
- mapped :: forall (f :: Type -> Type) a b. Functor f => Setter (f a) (f b) a b
- lifted :: forall (m :: Type -> Type) a b. Monad m => Setter (m a) (m b) a b
- contramapped :: forall (f :: Type -> Type) b a. Contravariant f => Setter (f b) (f a) 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
- set' :: ASetter' s a -> a -> s -> s
- (<?~) :: ASetter s t a (Maybe b) -> b -> s -> (b, t)
- assign :: MonadState s m => ASetter s s a b -> b -> m ()
- modifying :: MonadState s m => ASetter s s a b -> (a -> b) -> m ()
- (<~) :: MonadState s m => ASetter s s a b -> m b -> m ()
- (<?=) :: MonadState s m => ASetter s s a (Maybe b) -> b -> m b
- 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
- (.@~) :: AnIndexedSetter i s t a b -> (i -> b) -> s -> t
- (%@=) :: MonadState s m => AnIndexedSetter i s s a b -> (i -> a -> b) -> m ()
- imodifying :: MonadState s m => AnIndexedSetter i s s a b -> (i -> a -> b) -> m ()
- (.@=) :: MonadState s m => AnIndexedSetter i s s a b -> (i -> 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
- withLens :: forall s t a b (rep :: RuntimeRep) (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
- (&~) :: s -> State s a -> s
- (%%~) :: forall {k} f s (t :: k) a (b :: k). LensLike f s t a b -> (a -> f b) -> s -> f t
- (%%=) :: forall {k} s m p r (a :: k) b. MonadState s m => Over p ((,) r) s s a b -> p a (r, b) -> m r
- (??) :: Functor f => f (a -> b) -> a -> f 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
- locus :: forall (p :: Type -> Type -> Type -> Type) a c s b. IndexedComonadStore p => Lens (p a c s) (p b c s) 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
- (<%~) :: LensLike ((,) b) s t a b -> (a -> b) -> s -> (b, t)
- (<+~) :: Num a => LensLike ((,) a) s t a a -> a -> s -> (a, t)
- (<-~) :: Num a => LensLike ((,) a) s t a a -> a -> s -> (a, t)
- (<*~) :: Num a => LensLike ((,) a) s t a a -> a -> s -> (a, t)
- (<//~) :: Fractional a => LensLike ((,) a) s t a a -> a -> s -> (a, t)
- (<^~) :: (Num a, Integral e) => LensLike ((,) a) s t a a -> e -> s -> (a, t)
- (<^^~) :: (Fractional a, Integral e) => LensLike ((,) a) s t a a -> e -> s -> (a, t)
- (<**~) :: Floating a => LensLike ((,) a) s t a a -> a -> s -> (a, t)
- (<||~) :: LensLike ((,) Bool) s t Bool Bool -> Bool -> s -> (Bool, t)
- (<&&~) :: LensLike ((,) Bool) s t Bool Bool -> Bool -> s -> (Bool, t)
- (<<%~) :: LensLike ((,) a) s t a b -> (a -> b) -> s -> (a, t)
- (<<.~) :: LensLike ((,) a) s t a b -> b -> s -> (a, t)
- (<<?~) :: LensLike ((,) a) s t a (Maybe b) -> b -> s -> (a, t)
- (<<+~) :: Num a => LensLike' ((,) a) s a -> a -> s -> (a, s)
- (<<-~) :: Num a => LensLike' ((,) a) s a -> a -> s -> (a, s)
- (<<*~) :: Num a => LensLike' ((,) a) s a -> a -> s -> (a, s)
- (<<//~) :: Fractional a => LensLike' ((,) a) s a -> a -> s -> (a, s)
- (<<^~) :: (Num a, Integral e) => LensLike' ((,) a) s a -> e -> s -> (a, s)
- (<<^^~) :: (Fractional a, Integral e) => LensLike' ((,) a) s a -> e -> s -> (a, s)
- (<<**~) :: Floating a => LensLike' ((,) a) s a -> a -> s -> (a, s)
- (<<||~) :: LensLike' ((,) Bool) s Bool -> Bool -> s -> (Bool, s)
- (<<&&~) :: LensLike' ((,) Bool) s Bool -> Bool -> s -> (Bool, s)
- (<<<>~) :: Semigroup r => LensLike' ((,) r) s r -> r -> s -> (r, s)
- (<%=) :: MonadState s m => LensLike ((,) b) s s a b -> (a -> b) -> m b
- (<+=) :: (MonadState s m, Num a) => LensLike' ((,) a) s a -> a -> m a
- (<-=) :: (MonadState s m, Num a) => LensLike' ((,) a) s a -> a -> m a
- (<*=) :: (MonadState s m, Num a) => LensLike' ((,) a) s a -> a -> m a
- (<//=) :: (MonadState s m, Fractional a) => LensLike' ((,) a) s a -> a -> m a
- (<^=) :: (MonadState s m, Num a, Integral e) => LensLike' ((,) a) s a -> e -> m a
- (<^^=) :: (MonadState s m, Fractional a, Integral e) => LensLike' ((,) a) s a -> e -> m a
- (<**=) :: (MonadState s m, Floating a) => LensLike' ((,) a) s a -> a -> m a
- (<||=) :: MonadState s m => LensLike' ((,) Bool) s Bool -> Bool -> m Bool
- (<&&=) :: MonadState s m => LensLike' ((,) Bool) s Bool -> Bool -> m Bool
- (<<%=) :: (Strong p, MonadState s m) => Over p ((,) a) s s a b -> p a b -> m a
- (<<.=) :: MonadState s m => LensLike ((,) a) s s a b -> b -> m a
- (<<?=) :: MonadState s m => LensLike ((,) a) s s a (Maybe b) -> b -> m a
- (<<+=) :: (MonadState s m, Num a) => LensLike' ((,) a) s a -> a -> m a
- (<<-=) :: (MonadState s m, Num a) => LensLike' ((,) a) s a -> a -> m a
- (<<*=) :: (MonadState s m, Num a) => LensLike' ((,) a) s a -> a -> m a
- (<<//=) :: (MonadState s m, Fractional a) => LensLike' ((,) a) s a -> a -> m a
- (<<^=) :: (MonadState s m, Num a, Integral e) => LensLike' ((,) a) s a -> e -> m a
- (<<^^=) :: (MonadState s m, Fractional a, Integral e) => LensLike' ((,) a) s a -> e -> m a
- (<<**=) :: (MonadState s m, Floating a) => LensLike' ((,) a) s a -> a -> m a
- (<<||=) :: MonadState s m => LensLike' ((,) Bool) s Bool -> Bool -> m Bool
- (<<&&=) :: MonadState s m => LensLike' ((,) Bool) s Bool -> Bool -> m Bool
- (<<<>=) :: (MonadState s m, Semigroup r) => LensLike' ((,) r) s r -> r -> m r
- (<<~) :: MonadState s m => ALens s s a b -> m b -> m b
- (<<>~) :: Semigroup m => LensLike ((,) m) s t m m -> m -> s -> (m, t)
- (<<>=) :: (MonadState s m, Semigroup r) => LensLike' ((,) r) s r -> r -> m r
- overA :: Arrow ar => LensLike (Context a b) s t a b -> ar a b -> ar s t
- (<%@~) :: Over (Indexed i) ((,) b) s t a b -> (i -> a -> b) -> s -> (b, t)
- (<<%@~) :: Over (Indexed i) ((,) a) s t a b -> (i -> a -> b) -> s -> (a, t)
- (%%@~) :: forall {k1} i f s (t :: k1) a (b :: k1). Over (Indexed i) f s t a b -> (i -> a -> f b) -> s -> f t
- (%%@=) :: MonadState s m => Over (Indexed i) ((,) r) s s a b -> (i -> a -> (r, b)) -> m r
- (<%@=) :: MonadState s m => Over (Indexed i) ((,) b) s s a b -> (i -> a -> b) -> m b
- (<<%@=) :: MonadState s m => Over (Indexed i) ((,) a) s s a b -> (i -> a -> b) -> m a
- (^#) :: s -> ALens s t a b -> a
- storing :: ALens s t a b -> b -> s -> t
- (#~) :: ALens s t a b -> b -> s -> t
- (#%~) :: ALens s t a b -> (a -> b) -> s -> t
- (#%%~) :: Functor f => ALens s t a b -> (a -> f b) -> s -> f t
- (#=) :: MonadState s m => ALens s s a b -> b -> m ()
- (#%=) :: MonadState s m => ALens s s a b -> (a -> b) -> m ()
- (<#%~) :: ALens s t a b -> (a -> b) -> s -> (b, t)
- (<#%=) :: MonadState s m => ALens s s a b -> (a -> b) -> m b
- (#%%=) :: MonadState s m => ALens s s a b -> (a -> (r, b)) -> m r
- (<#~) :: ALens s t a b -> b -> s -> (b, t)
- (<#=) :: MonadState s m => ALens s s a b -> b -> m b
- devoid :: forall {k} p f (a :: k) b. Over p f Void Void a b
- united :: forall a f. Functor f => (() -> f ()) -> a -> f a
- head1 :: forall (t :: Type -> Type) a. Traversable1 t => Lens' (t a) a
- last1 :: forall (t :: Type -> Type) a. Traversable1 t => Lens' (t a) a
- fusing :: Functor f => LensLike (Yoneda f) s t a b -> LensLike f s t a b
- _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
- 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
- views :: MonadReader s m => LensLike' (Const r :: Type -> Type) s a -> (a -> r) -> m r
- uses :: MonadState s m => LensLike' (Const r :: Type -> Type) 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
- (^@.) :: s -> IndexedGetting i (i, a) s a -> (i, a)
- 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
- 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 :: Type -> Type -> Type) Identity s t a b -> Optic' p f t b
- 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 -> s) -> (s -> Maybe a) -> Prism s s a b
- aside :: APrism s t a b -> Prism (e, s) (e, t) (e, a) (e, b)
- below :: forall (f :: Type -> Type) s a. Traversable f => APrism' s a -> Prism' (f s) (f a)
- isn't :: APrism s t a b -> s -> Bool
- matching' :: LensLike (Either a) s t a b -> s -> Either t a
- _Right :: forall c a b p f. (Choice p, Applicative f) => p a (f b) -> p (Either c a) (f (Either c b))
- _Just :: forall a b p f. (Choice p, Applicative f) => p a (f b) -> p (Maybe a) (f (Maybe b))
- _Nothing :: forall a p f. (Choice p, Applicative f) => p () (f ()) -> p (Maybe a) (f (Maybe a))
- _Void :: forall s a p f. (Choice p, Applicative f) => p a (f Void) -> p s (f s)
- 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
- folded64 :: forall (f :: Type -> Type) a. 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 :: forall (f :: Type -> Type). Applicative f => IndexedLensLike' Int f String String
- lined :: forall (f :: Type -> Type). Applicative f => IndexedLensLike' Int f String String
- 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
- altOf :: Applicative f => Getting (Alt f a) s a -> s -> f a
- (^..) :: s -> Getting (Endo [a]) s a -> [a]
- andOf :: Getting All s Bool -> s -> Bool
- orOf :: Getting Any s 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
- 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 ()
- 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 ()
- 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]
- (^?!) :: HasCallStack => s -> Getting (Endo a) s a -> a
- first1Of :: Getting (First a) s a -> s -> 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
- 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))
- 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)
- 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)]
- (^@..) :: s -> IndexedGetting i (Endo [(i, a)]) s a -> [(i, a)]
- (^@?) :: s -> IndexedGetting i (Endo (Maybe (i, a))) s a -> Maybe (i, a)
- (^@?!) :: HasCallStack => s -> IndexedGetting i (Endo (i, a)) s a -> (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)) :: Type -> Type) 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
- traversal :: ((a -> f b) -> s -> f t) -> LensLike f s t a b
- 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 :: forall a c s b f. Applicative f => (a -> f b) -> Bazaar (->) a c s -> f (Bazaar (->) b c s)
- iloci :: forall i a c s b p f. (Indexable i p, Applicative f) => p a (f b) -> Bazaar (Indexed i) a c s -> f (Bazaar (Indexed i) b c s)
- partsOf :: Functor f => Traversing (->) f s t a a -> LensLike f s t [a] [a]
- ipartsOf :: (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 :: (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]
- 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 :: forall (r :: Type -> Type -> Type) a b. Bitraversable r => Traversal (r a a) (r b b) a b
- both1 :: forall (r :: Type -> Type -> Type) a b. Bitraversable1 r => Traversal1 (r a a) (r b b) 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
- iforOf :: (Indexed i a (f b) -> s -> f t) -> s -> (i -> a -> f b) -> f 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)
- traversed1 :: forall (f :: Type -> Type) a b. Traversable1 f => IndexedTraversal1 Int (f a) (f b) a b
- traversed64 :: forall (f :: Type -> Type) a b. Traversable f => IndexedTraversal Int64 (f a) (f b) a b
- ignored :: Applicative f => pafb -> s -> f s
- elementOf :: forall (f :: Type -> Type) s t a. Applicative f => LensLike (Indexing f) s t a a -> Int -> IndexedLensLike Int f s t a a
- element :: forall (t :: Type -> Type) a. Traversable t => Int -> IndexedTraversal' Int (t a) a
- elementsOf :: forall (f :: Type -> Type) s t a. Applicative f => LensLike (Indexing f) s t a a -> (Int -> Bool) -> IndexedLensLike Int f s t a a
- elements :: forall (t :: Type -> Type) a. 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
- 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
- ilevels :: forall (f :: Type -> Type) i s t a b j. Applicative f => Traversing (Indexed i) f s t a b -> IndexedLensLike Int f s t (Level i a) (Level j b)
- (<.) :: Indexable i p => (Indexed i s t -> r) -> ((a -> b) -> s -> t) -> p a b -> r
- 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
- imapped :: forall i (f :: Type -> Type) a b. FunctorWithIndex i f => IndexedSetter i (f a) (f b) a b
- ifolded :: forall i (f :: Type -> Type) a. FoldableWithIndex i f => IndexedFold i (f a) a
- itraversed :: forall i (t :: Type -> Type) a b. 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
- runEq :: forall {k1} {k2} (s :: k1) (t :: k2) (a :: k1) (b :: k2). AnEquality s t a b -> Identical s t a b
- substEq :: forall {k1} {k2} (s :: k1) (t :: k2) (a :: k1) (b :: k2) (rep :: RuntimeRep) (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. AnEquality s t a b -> f s -> f a
- fromEq :: forall {k2} {k1} (s :: k2) (t :: k1) (a :: k2) (b :: k1). AnEquality s t a b -> Equality b a t s
- simply :: forall {k} {k1} p (f :: k -> k1) (s :: k) (a :: k) (rep :: RuntimeRep) (r :: TYPE rep). (Optic' p f s a -> r) -> Optic' p f s a -> r
- simple :: forall {k2} (a :: k2) k3 p (f :: k2 -> k3). p a (f a) -> p a (f a)
- cloneEquality :: forall {k1} {k2} (s :: k1) (t :: k2) (a :: k1) (b :: k2). AnEquality s t a b -> Equality s t a b
- equality :: forall {k1} {k2} (s :: k1) (a :: k1) (b :: k2) (t :: k2). (s :~: a) -> (b :~: t) -> Equality s t a b
- equality' :: forall {k2} (a :: k2) (b :: k2). (a :~: b) -> Equality' a b
- overEquality :: forall {k1} {k2} (s :: k1) (t :: k2) (a :: k1) (b :: k2) p. AnEquality s t a b -> p a b -> p s t
- underEquality :: forall {k1} {k2} (s :: k1) (t :: k2) (a :: k1) (b :: k2) p. AnEquality s t a b -> p t s -> p b a
- fromLeibniz :: forall {k1} {k2} (a :: k1) (b :: k2) (s :: k1) (t :: k2). (Identical a b a b -> Identical a b s t) -> Equality s t a b
- fromLeibniz' :: forall {k2} (s :: k2) (a :: k2). ((s :~: s) -> s :~: a) -> Equality' s a
- withEquality :: forall {k1} {k2} (s :: k1) (t :: k2) (a :: k1) (b :: k2) (rep :: RuntimeRep) (r :: TYPE rep). AnEquality s t a b -> ((s :~: a) -> (b :~: t) -> r) -> r
- iso :: (s -> a) -> (b -> t) -> Iso s t a b
- withIso :: forall s t a b (rep :: RuntimeRep) (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 :: forall {k2} s g (t :: k2) a (b :: k2). Optic (Costar ((->) s)) g s t a b -> ((s -> a) -> g b) -> g t
- xplatf :: forall {k} {k2} f g (s :: k) (t :: k2) (a :: k) (b :: k2). 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 :: forall (f :: Type -> Type) (g :: Type -> Type) s t a b. (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 :: forall a b c d e f1 p f2. (Profunctor p, Functor f2) => p (a -> b -> c) (f2 (d -> e -> f1)) -> p ((a, b) -> c) (f2 ((d, e) -> f1))
- uncurried :: forall a b c d e f1 p f2. (Profunctor p, Functor f2) => p ((a, b) -> c) (f2 ((d, e) -> f1)) -> p (a -> b -> c) (f2 (d -> e -> f1))
- flipped :: forall a b c a' b' c' p f. (Profunctor p, Functor f) => p (b -> a -> c) (f (b' -> a' -> c')) -> p (a -> b -> c) (f (a' -> b' -> c'))
- 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 :: forall (f :: Type -> Type) s t a b. Contravariant f => AnIso s t a b -> Iso (f a) (f b) (f s) (f t)
- dimapping :: forall (p :: Type -> Type -> Type) (q :: Type -> Type -> Type) s t a b s' t' a' b'. (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 :: forall (p :: Type -> Type -> Type) (q :: Type -> Type -> Type) s t a b x y. (Profunctor p, Profunctor q) => AnIso s t a b -> Iso (p a x) (q b y) (p s x) (q t y)
- rmapping :: forall (p :: Type -> Type -> Type) (q :: Type -> Type -> Type) s t a b x y. (Profunctor p, Profunctor q) => AnIso s t a b -> Iso (p x s) (q y t) (p x a) (q y b)
- bimapping :: forall (f :: Type -> Type -> Type) (g :: Type -> Type -> Type) s t a b s' t' a' b'. (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 :: forall (f :: Type -> Type -> Type) (g :: Type -> Type -> Type) s t a b x y. (Bifunctor f, Bifunctor g) => AnIso s t a b -> Iso (f s x) (g t y) (f a x) (g b y)
- seconding :: forall (f :: Type -> Type -> Type) (g :: Type -> Type -> Type) s t a b x y. (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
- _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
- _GWrapped' :: forall s (d :: Meta) (c :: Meta) (s' :: Meta) a. (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
- deep :: (Conjoined p, Applicative f, Plated s) => Traversing p f s s a b -> Over p f s s a b
- 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
- 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]
- 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 :: forall {k} (f :: k -> Type) (a :: k). (Generic1 f, GPlated1 f (Rep1 f)) => Traversal' (f a) (f a)
- 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
- simpleLenses :: Lens' LensRules Bool
- generateSignatures :: Lens' LensRules Bool
- generateUpdateableOptics :: Lens' LensRules Bool
- generateLazyPatterns :: Lens' LensRules Bool
- generateRecordSyntax :: 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
- class Functor f => Applicative (f :: Type -> Type) where
- (*>) :: Applicative f => f a -> f b -> f b
- (<*) :: Applicative f => f a -> f b -> f a
- (<$>) :: Functor f => (a -> b) -> f a -> f b
- (<$) :: Functor f => a -> f b -> f a
- liftA :: Applicative f => (a -> b) -> f a -> f b
- liftA2 :: Applicative f => (a -> b -> c) -> f a -> f b -> f c
- liftA3 :: Applicative f => (a -> b -> c -> d) -> f a -> f b -> f c -> f d
Diagrams library
Exports from this library for working with diagrams.
module Diagrams
Convenience re-exports from other packages
module Data.Default.Class
For representing and operating on colors.
class ColourOps (f :: Type -> Type) where #
darken :: Num a => a -> f a -> f a #
darken s c
blends a colour with black without changing it's opacity.
For Colour
, darken s c = blend s c mempty
Instances
ColourOps AlphaColour | |
Defined in Data.Colour.Internal over :: Num a => AlphaColour a -> AlphaColour a -> AlphaColour a # darken :: Num a => a -> AlphaColour a -> AlphaColour a # | |
ColourOps Colour | |
data AlphaColour a #
This type represents a Colour
that may be semi-transparent.
The Monoid
instance allows you to composite colours.
x `mappend` y == x `over` y
To get the (pre-multiplied) colour channel of an AlphaColour
c
,
simply composite c
over black.
c `over` black
Instances
This type represents the human preception of colour.
The a
parameter is a numeric type used internally for the
representation.
The Monoid
instance allows one to add colours, but beware that adding
colours can take you out of gamut. Consider using blend
whenever
possible.
Instances
AffineSpace Colour | |
Defined in Data.Colour.Internal | |
ColourOps Colour | |
Num a => Monoid (Colour a) | |
Num a => Semigroup (Colour a) | |
a ~ Double => Color (Colour a) Source # | |
Defined in Diagrams.Attributes toAlphaColour :: Colour a -> AlphaColour Double Source # fromAlphaColour :: AlphaColour Double -> Colour a Source # | |
Parseable (Colour Double) Source # | Parse |
Eq a => Eq (Colour a) | |
colourConvert :: (Fractional b, Real a) => Colour a -> Colour b #
Change the type used to represent the colour coordinates.
transparent :: Num a => AlphaColour a #
This AlphaColour
is entirely transparent and has no associated
colour channel.
alphaColourConvert :: (Fractional b, Real a) => AlphaColour a -> AlphaColour b #
Change the type used to represent the colour coordinates.
opaque :: Num a => Colour a -> AlphaColour a #
Creates an opaque AlphaColour
from a Colour
.
dissolve :: Num a => a -> AlphaColour a -> AlphaColour a #
Returns an AlphaColour
more transparent by a factor of o
.
withOpacity :: Num a => Colour a -> a -> AlphaColour a #
Creates an AlphaColour
from a Colour
with a given opacity.
c `withOpacity` o == dissolve o (opaque c)
blend :: (Num a, AffineSpace f) => a -> f a -> f a -> f a #
Compute the weighted average of two points. e.g.
blend 0.4 a b = 0.4*a + 0.6*b
The weight can be negative, or greater than 1.0; however, be aware that non-convex combinations may lead to out of gamut colours.
alphaChannel :: AlphaColour a -> a #
Returns the opacity of an AlphaColour
.
A large list of color names.
antiquewhite :: (Ord a, Floating a) => Colour a #
aquamarine :: (Ord a, Floating a) => Colour a #
blanchedalmond :: (Ord a, Floating a) => Colour a #
blueviolet :: (Ord a, Floating a) => Colour a #
chartreuse :: (Ord a, Floating a) => Colour a #
cornflowerblue :: (Ord a, Floating a) => Colour a #
darkgoldenrod :: (Ord a, Floating a) => Colour a #
darkmagenta :: (Ord a, Floating a) => Colour a #
darkolivegreen :: (Ord a, Floating a) => Colour a #
darkorange :: (Ord a, Floating a) => Colour a #
darkorchid :: (Ord a, Floating a) => Colour a #
darksalmon :: (Ord a, Floating a) => Colour a #
darkseagreen :: (Ord a, Floating a) => Colour a #
darkslateblue :: (Ord a, Floating a) => Colour a #
darkslategray :: (Ord a, Floating a) => Colour a #
darkslategrey :: (Ord a, Floating a) => Colour a #
darkturquoise :: (Ord a, Floating a) => Colour a #
darkviolet :: (Ord a, Floating a) => Colour a #
deepskyblue :: (Ord a, Floating a) => Colour a #
dodgerblue :: (Ord a, Floating a) => Colour a #
floralwhite :: (Ord a, Floating a) => Colour a #
forestgreen :: (Ord a, Floating a) => Colour a #
ghostwhite :: (Ord a, Floating a) => Colour a #
greenyellow :: (Ord a, Floating a) => Colour a #
lavenderblush :: (Ord a, Floating a) => Colour a #
lemonchiffon :: (Ord a, Floating a) => Colour a #
lightcoral :: (Ord a, Floating a) => Colour a #
lightgoldenrodyellow :: (Ord a, Floating a) => Colour a #
lightgreen :: (Ord a, Floating a) => Colour a #
lightsalmon :: (Ord a, Floating a) => Colour a #
lightseagreen :: (Ord a, Floating a) => Colour a #
lightskyblue :: (Ord a, Floating a) => Colour a #
lightslategray :: (Ord a, Floating a) => Colour a #
lightslategrey :: (Ord a, Floating a) => Colour a #
lightsteelblue :: (Ord a, Floating a) => Colour a #
lightyellow :: (Ord a, Floating a) => Colour a #
mediumaquamarine :: (Ord a, Floating a) => Colour a #
mediumblue :: (Ord a, Floating a) => Colour a #
mediumorchid :: (Ord a, Floating a) => Colour a #
mediumpurple :: (Ord a, Floating a) => Colour a #
mediumseagreen :: (Ord a, Floating a) => Colour a #
mediumslateblue :: (Ord a, Floating a) => Colour a #
mediumspringgreen :: (Ord a, Floating a) => Colour a #
mediumturquoise :: (Ord a, Floating a) => Colour a #
mediumvioletred :: (Ord a, Floating a) => Colour a #
midnightblue :: (Ord a, Floating a) => Colour a #
navajowhite :: (Ord a, Floating a) => Colour a #
palegoldenrod :: (Ord a, Floating a) => Colour a #
paleturquoise :: (Ord a, Floating a) => Colour a #
palevioletred :: (Ord a, Floating a) => Colour a #
papayawhip :: (Ord a, Floating a) => Colour a #
powderblue :: (Ord a, Floating a) => Colour a #
saddlebrown :: (Ord a, Floating a) => Colour a #
sandybrown :: (Ord a, Floating a) => Colour a #
springgreen :: (Ord a, Floating a) => Colour a #
whitesmoke :: (Ord a, Floating a) => Colour a #
yellowgreen :: (Ord a, Floating a) => Colour a #
Specify your own colours.
module Data.Colour.SRGB
Semigroups and monoids show up all over the place, so things from Data.Semigroup and Data.Monoid often come in handy.
module Data.Semigroup
For computing with vectors.
module Linear.Vector
For computing with points and vectors.
module Linear.Affine
For computing with dot products and norm.
module Linear.Metric
For working with Active
(i.e. animated) things.
module Data.Active
Most of the lens package. The following functions are not exported from lens because they either conflict with diagrams or may conflict with other libraries:
type Traversal s t a b = forall (f :: Type -> Type). Applicative f => (a -> f b) -> s -> f t #
A Traversal
can be used directly as a Setter
or a Fold
(but not as a Lens
) and provides
the ability to both read and update multiple fields, subject to some relatively weak Traversal
laws.
These have also been known as multilenses, but they have the signature and spirit of
traverse
::Traversable
f =>Traversal
(f a) (f b) a b
and the more evocative name suggests their application.
Most of the time the Traversal
you will want to use is just traverse
, but you can also pass any
Lens
or Iso
as a Traversal
, and composition of a Traversal
(or Lens
or Iso
) with a Traversal
(or Lens
or Iso
)
using (.
) forms a valid Traversal
.
The laws for a Traversal
t
follow from the laws for Traversable
as stated in "The Essence of the Iterator Pattern".
tpure
≡pure
fmap
(t f).
t g ≡getCompose
.
t (Compose
.
fmap
f.
g)
One consequence of this requirement is that a Traversal
needs to leave the same number of elements as a
candidate for subsequent Traversal
that it started with. Another testament to the strength of these laws
is that the caveat expressed in section 5.5 of the "Essence of the Iterator Pattern" about exotic
Traversable
instances that traverse
the same entry multiple times was actually already ruled out by the
second law in that same paper!
type Fold s a = forall (f :: Type -> Type). (Contravariant f, Applicative f) => (a -> f a) -> s -> f s #
A Fold
describes how to retrieve multiple values in a way that can be composed
with other LensLike
constructions.
A
provides a structure with operations very similar to those of the Fold
s aFoldable
typeclass, see foldMapOf
and the other Fold
combinators.
By convention, if there exists a foo
method that expects a
, then there should be a
Foldable
(f a)fooOf
method that takes a
and a value of type Fold
s as
.
A Getter
is a legal Fold
that just ignores the supplied Monoid
.
Unlike a Traversal
a Fold
is read-only. Since a Fold
cannot be used to write back
there are no Lens
laws that apply.
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 :: (a' -> a) -> (Predicate a -> Predicate a') 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 (forall a. Functor (p a)) => 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
. A partially applied Bifunctor
must be a Functor
and the second
method must agree with fmap
.
From this it follows that:
second
id
=id
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 4.18.0.0 Functor
is a superclass of 'Bifunctor.
Since: base-4.8.0.0
Instances
Bifunctor Either | Since: base-4.8.0.0 |
Bifunctor Arg | Since: base-4.9.0.0 |
Bifunctor Either | |
Bifunctor These | |
Bifunctor Pair | |
Bifunctor These | |
Bifunctor (,) | Class laws for tuples hold only up to laziness. Both
Since: base-4.8.0.0 |
Bifunctor (Const :: Type -> Type -> Type) | Since: base-4.8.0.0 |
Functor f => Bifunctor (CofreeF f) | |
Functor f => Bifunctor (FreeF f) | |
Functor f => Bifunctor (AlongsideLeft f) | |
Defined in Control.Lens.Internal.Getter bimap :: (a -> b) -> (c -> d) -> AlongsideLeft f a c -> AlongsideLeft f b d # first :: (a -> b) -> AlongsideLeft f a c -> AlongsideLeft f b c # second :: (b -> c) -> AlongsideLeft f a b -> AlongsideLeft f a c # | |
Functor f => Bifunctor (AlongsideRight f) | |
Defined in Control.Lens.Internal.Getter bimap :: (a -> b) -> (c -> d) -> AlongsideRight f a c -> AlongsideRight f b d # first :: (a -> b) -> AlongsideRight f a c -> AlongsideRight f b c # second :: (b -> c) -> AlongsideRight f a b -> AlongsideRight f a c # | |
Bifunctor (Tagged :: Type -> Type -> Type) | |
Bifunctor (Constant :: Type -> Type -> Type) | |
Bifunctor ((,,) x1) | Since: base-4.8.0.0 |
Bifunctor (K1 i :: Type -> Type -> Type) | Since: base-4.9.0.0 |
Bifunctor ((,,,) x1 x2) | Since: base-4.8.0.0 |
Functor f => Bifunctor (Clown f :: Type -> Type -> Type) | |
Bifunctor p => Bifunctor (Flip p) | |
Functor g => Bifunctor (Joker g :: Type -> Type -> Type) | |
Bifunctor p => Bifunctor (WrappedBifunctor p) | |
Defined in Data.Bifunctor.Wrapped bimap :: (a -> b) -> (c -> d) -> WrappedBifunctor p a c -> WrappedBifunctor p b d # first :: (a -> b) -> WrappedBifunctor p a c -> WrappedBifunctor p b c # second :: (b -> c) -> WrappedBifunctor p a b -> WrappedBifunctor p a c # | |
Bifunctor ((,,,,) x1 x2 x3) | Since: base-4.8.0.0 |
(Bifunctor f, Bifunctor g) => Bifunctor (Product f g) | |
(Bifunctor p, Bifunctor q) => Bifunctor (Sum p q) | |
Bifunctor ((,,,,,) x1 x2 x3 x4) | Since: base-4.8.0.0 |
(Functor f, Bifunctor p) => Bifunctor (Tannen f p) | |
Bifunctor ((,,,,,,) x1 x2 x3 x4 x5) | Since: base-4.8.0.0 |
(Bifunctor p, Functor f, Functor g) => Bifunctor (Biff p f g) | |
class (Functor t, Foldable t) => Traversable (t :: Type -> Type) where #
Functors representing data structures that can be transformed to
structures of the same shape by performing an Applicative
(or,
therefore, Monad
) action on each element from left to right.
A more detailed description of what same shape means, the various methods, how traversals are constructed, and example advanced use-cases can be found in the Overview section of Data.Traversable.
For the class laws see the Laws section of Data.Traversable.
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_
.
Examples
Basic usage:
In the first two examples we show each evaluated action mapping to the output structure.
>>>
traverse Just [1,2,3,4]
Just [1,2,3,4]
>>>
traverse id [Right 1, Right 2, Right 3, Right 4]
Right [1,2,3,4]
In the next examples, we show that Nothing
and Left
values short
circuit the created structure.
>>>
traverse (const Nothing) [1,2,3,4]
Nothing
>>>
traverse (\x -> if odd x then Just x else Nothing) [1,2,3,4]
Nothing
>>>
traverse id [Right 1, Right 2, Right 3, Right 4, Left 0]
Left 0
Instances
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 |
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, Data a) => Data (a :~: b) | Since: base-4.7.0.0 |
Defined in Data.Data gfoldl :: (forall d b0. Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) -> (a :~: b) -> c (a :~: b) # gunfold :: (forall b0 r. Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (a :~: b) # toConstr :: (a :~: b) -> Constr # dataTypeOf :: (a :~: b) -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (a :~: b)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (a :~: b)) # gmapT :: (forall b0. Data b0 => b0 -> b0) -> (a :~: b) -> a :~: b # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> (a :~: b) -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> (a :~: b) -> r # gmapQ :: (forall d. Data d => d -> u) -> (a :~: b) -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> (a :~: b) -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> (a :~: b) -> m (a :~: b) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> (a :~: b) -> m (a :~: b) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> (a :~: b) -> m (a :~: b) # | |
a ~ b => Bounded (a :~: b) | Since: base-4.7.0.0 |
a ~ b => Enum (a :~: b) | Since: base-4.7.0.0 |
Defined in Data.Type.Equality | |
a ~ b => Read (a :~: b) | Since: base-4.7.0.0 |
Show (a :~: b) | Since: base-4.7.0.0 |
NFData (a :~: b) | Since: deepseq-1.4.3.0 |
Defined in Control.DeepSeq | |
Eq (a :~: b) | Since: base-4.7.0.0 |
Ord (a :~: b) | Since: base-4.7.0.0 |
Defined in Data.Type.Equality |
The Const
functor.
Instances
Generic1 (Const a :: k -> Type) | |
FoldableWithIndex Void (Const e :: Type -> Type) | |
Defined in WithIndex | |
FunctorWithIndex Void (Const e :: Type -> Type) | |
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)) # | |
Bifoldable (Const :: Type -> Type -> Type) | Since: base-4.10.0.0 |
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) # | |
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 | |
Biapply (Const :: Type -> Type -> Type) | |
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) # | |
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 # | |
Contravariant (Const a :: Type -> Type) | |
Traversable (Const m :: Type -> Type) | Since: base-4.7.0.0 |
Monoid m => Applicative (Const m :: Type -> Type) | Since: base-2.0.1 |
Functor (Const m :: Type -> Type) | Since: base-2.1 |
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 |
Sieve (Forget r :: Type -> Type -> Type) (Const r :: Type -> Type) | |
Defined in Data.Profunctor.Sieve | |
(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) # | |
IsString a => IsString (Const a b) | Since: base-4.9.0.0 |
Defined in Data.String fromString :: String -> Const a b # | |
Storable a => Storable (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const | |
Monoid a => Monoid (Const a b) | Since: base-4.9.0.0 |
Semigroup a => Semigroup (Const a b) | Since: base-4.9.0.0 |
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 # | |
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] # | |
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 # | |
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 # | |
Generic (Const a b) | |
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 # | |
Num a => Num (Const a b) | Since: base-4.9.0.0 |
Read a => Read (Const a b) | This instance would be equivalent to the derived instances of the
Since: base-4.8.0.0 |
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 | |
Real a => Real (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const toRational :: Const a b -> Rational # | |
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 |
NFData a => NFData (Const a b) | Since: deepseq-1.4.0.0 |
Defined in Control.DeepSeq | |
Eq a => Eq (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 | |
Hashable a => Hashable (Const a b) | |
Defined in Data.Hashable.Class | |
Wrapped (Const a x) | |
Pretty a => Pretty (Const a b) | |
Defined in Prettyprinter.Internal |