Portability | Rank2Types |
---|---|
Stability | provisional |
Maintainer | Edward Kmett <ekmett@gmail.com> |
Safe Haskell | Trustworthy |
(The classes in here need to be defined together for DefaultSignatures
to work.)
- 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), ArrowLoop p, ArrowApply p, ArrowChoice p) => Conjoined p where
- newtype Indexed i a b = Indexed {
- runIndexed :: i -> a -> b
- (<.) :: Indexable i p => (Indexed i s t -> r) -> ((a -> b) -> s -> t) -> p a b -> r
- (<.>) :: Indexable (i, j) p => (Indexed i s t -> r) -> (Indexed j a b -> s -> t) -> p a b -> r
- (.>) :: (st -> r) -> (kab -> st) -> kab -> r
- 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
- 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
- class Functor f => FunctorWithIndex i f | f -> i where
- imap :: (i -> a -> b) -> f a -> f b
- imapped :: IndexedSetter i (f a) (f b) a b
- class Foldable f => FoldableWithIndex i f | f -> i where
- 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
- none :: Foldable f => (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)]
- withIndex :: (Indexable i p, Functor f) => Optical p (Indexed i) f s t (i, s) (j, t)
- asIndex :: (Indexable i p, Contravariant f, Functor f) => Optical' p (Indexed i) f s i
- 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
- class (FunctorWithIndex i t, FoldableWithIndex i t, Traversable t) => TraversableWithIndex i t | t -> i where
- itraverse :: Applicative f => (i -> a -> f b) -> t a -> f (t b)
- itraversed :: IndexedTraversal i (t a) (t b) a b
- 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)
- ifoldMapBy :: FoldableWithIndex i t => (r -> r -> r) -> r -> (i -> a -> r) -> t a -> r
- ifoldMapByOf :: (forall s. IndexedGetting i (M r s) t a) -> (r -> r -> r) -> r -> (i -> a -> r) -> t -> r
Indexing
class Conjoined p => Indexable i p whereSource
This class permits overloading of function application for things that also admit a notion of a key or index.
class (Choice p, Corepresentable p, Comonad (Corep p), Traversable (Corep p), Strong p, Representable p, Monad (Rep p), MonadFix (Rep p), Distributive (Rep p), ArrowLoop p, ArrowApply p, ArrowChoice p) => Conjoined p whereSource
This is a Profunctor
that is both Corepresentable
by f
and Representable
by g
such
that f
is left adjoint to g
. From this you can derive a lot of structure due
to the preservation of limits and colimits.
distrib :: Functor f => p a b -> p (f a) (f b)Source
Conjoined
is strong enough to let us distribute every Conjoined
Profunctor
over every Haskell Functor
. This is effectively a
generalization of fmap
.
conjoined :: (p ~ (->) => q (a -> b) r) -> q (p a b) r -> q (p a b) rSource
This permits us to make a decision at an outermost point about whether or not we use an index.
Ideally any use of this function should be done in such a way so that you compute the same answer, but this cannot be enforced at the type level.
Conjoined (->) | |
Conjoined ReifiedGetter | |
Conjoined (Indexed i) |
A function with access to a index. This constructor may be useful when you need to store
an Indexable
in a container to avoid ImpredicativeTypes
.
index :: Indexed i a b -> i -> a -> b
Indexed | |
|
~ * i j => Indexable i (Indexed j) | |
Arrow (Indexed i) | |
ArrowChoice (Indexed i) | |
ArrowApply (Indexed i) | |
ArrowLoop (Indexed i) | |
Category (Indexed i) | |
Representable (Indexed i) | |
Corepresentable (Indexed i) | |
Strong (Indexed i) | |
Choice (Indexed i) | |
Profunctor (Indexed i) | |
Conjoined (Indexed i) | |
Bizarre (Indexed Int) Mafic | |
Sellable (Indexed i) (Molten i) | |
Bizarre (Indexed i) (Molten i) | |
Monad (Indexed i a) | |
Functor (Indexed i a) | |
MonadFix (Indexed i a) | |
Applicative (Indexed i a) | |
Apply (Indexed i a) | |
Bind (Indexed i a) |
(<.) :: Indexable i p => (Indexed i s t -> r) -> ((a -> b) -> s -> t) -> p a b -> rSource
Compose an Indexed
function with a non-indexed function.
Mnemonically, the <
points to the indexing we want to preserve.
(<.>) :: Indexable (i, j) p => (Indexed i s t -> r) -> (Indexed j a b -> s -> t) -> p a b -> rSource
Composition of Indexed
functions.
Mnemonically, the <
and >
points to the fact that we want to preserve the indices.
icompose :: Indexable p c => (i -> j -> p) -> (Indexed i s t -> r) -> (Indexed j a b -> s -> t) -> c a b -> rSource
Composition of Indexed
functions with a user supplied function for combining indices.
indexing :: Indexable Int p => ((a -> Indexing f b) -> s -> Indexing f t) -> p a (f b) -> s -> f tSource
Transform a Traversal
into an IndexedTraversal
or
a Fold
into an IndexedFold
, etc.
indexing
::Traversal
s t a b ->IndexedTraversal
Int
s t a bindexing
::Prism
s t a b ->IndexedTraversal
Int
s t a bindexing
::Lens
s t a b ->IndexedLens
Int
s t a bindexing
::Iso
s t a b ->IndexedLens
Int
s t a bindexing
::Fold
s a ->IndexedFold
Int
s aindexing
::Getter
s a ->IndexedGetter
Int
s a
indexing
::Indexable
Int
p =>LensLike
(Indexing
f) s t a b ->Optical
p (->) f s t a b
indexing64 :: Indexable Int64 p => ((a -> Indexing64 f b) -> s -> Indexing64 f t) -> p a (f b) -> s -> f tSource
Transform a Traversal
into an IndexedTraversal
or
a Fold
into an IndexedFold
, etc.
This combinator is like indexing
except that it handles large traversals and folds gracefully.
indexing64
::Traversal
s t a b ->IndexedTraversal
Int64
s t a bindexing64
::Prism
s t a b ->IndexedTraversal
Int64
s t a bindexing64
::Lens
s t a b ->IndexedLens
Int64
s t a bindexing64
::Iso
s t a b ->IndexedLens
Int64
s t a bindexing64
::Fold
s a ->IndexedFold
Int64
s aindexing64
::Getter
s a ->IndexedGetter
Int64
s a
indexing64
::Indexable
Int64
p =>LensLike
(Indexing64
f) s t a b ->Over
p f s t a b
Indexed Functors
class Functor f => FunctorWithIndex i f | f -> i whereSource
A Functor
with an additional index.
Instances must satisfy a modified form of the Functor
laws:
imap
f.
imap
g ≡imap
(\i -> f i.
g i)imap
(\_ a -> a) ≡id
imap :: (i -> a -> b) -> f a -> f bSource
Map with access to the index.
imapped :: IndexedSetter i (f a) (f b) a bSource
The IndexedSetter
for a FunctorWithIndex
.
If you don't need access to the index, then mapped
is more flexible in what it accepts.
FunctorWithIndex Int [] | The position in the list is available as the index. |
FunctorWithIndex Int Seq | The position in the |
FunctorWithIndex Int IntMap | |
FunctorWithIndex Int NonEmpty | |
FunctorWithIndex Int Vector | |
FunctorWithIndex Int Deque | |
FunctorWithIndex () Maybe | |
FunctorWithIndex () Identity | |
FunctorWithIndex i (Level i) | |
FunctorWithIndex r ((->) r) | |
(Eq k, Hashable k) => FunctorWithIndex k (HashMap k) | |
FunctorWithIndex k (Map k) | |
FunctorWithIndex k ((,) k) | |
FunctorWithIndex i f => FunctorWithIndex i (Reverse f) | |
FunctorWithIndex i f => FunctorWithIndex i (Backwards f) | |
FunctorWithIndex i (Magma i t b) |
Indexed Foldables
class Foldable f => FoldableWithIndex i f | f -> i whereSource
A container that supports folding with an additional index.
ifoldMap :: Monoid m => (i -> a -> m) -> f a -> mSource
Fold a container by mapping value to an arbitrary Monoid
with access to the index i
.
When you don't need access to the index then foldMap
is more flexible in what it accepts.
foldMap
≡ifoldMap
.
const
ifolded :: IndexedFold i (f a) aSource
The IndexedFold
of a FoldableWithIndex
container.
ifoldr :: (i -> a -> b -> b) -> b -> f a -> bSource
Right-associative fold of an indexed container with access to the index i
.
When you don't need access to the index then foldr
is more flexible in what it accepts.
foldr
≡ifoldr
.
const
ifoldl :: (i -> b -> a -> b) -> b -> f a -> bSource
Left-associative fold of an indexed container with access to the index i
.
When you don't need access to the index then foldl
is more flexible in what it accepts.
foldl
≡ifoldl
.
const
FoldableWithIndex Int [] | |
FoldableWithIndex Int Seq | |
FoldableWithIndex Int IntMap | |
FoldableWithIndex Int NonEmpty | |
FoldableWithIndex Int Vector | |
FoldableWithIndex Int Deque | |
FoldableWithIndex () Maybe | |
FoldableWithIndex () Identity | |
FoldableWithIndex i (Level i) | |
(Eq k, Hashable k) => FoldableWithIndex k (HashMap k) | |
FoldableWithIndex k (Map k) | |
FoldableWithIndex k ((,) k) | |
FoldableWithIndex i f => FoldableWithIndex i (Reverse f) | |
FoldableWithIndex i f => FoldableWithIndex i (Backwards f) | |
FoldableWithIndex i (Magma i t b) |
Indexed Foldable Combinators
iany :: FoldableWithIndex i f => (i -> a -> Bool) -> f a -> BoolSource
iall :: FoldableWithIndex i f => (i -> a -> Bool) -> f a -> BoolSource
inone :: FoldableWithIndex i f => (i -> a -> Bool) -> f a -> BoolSource
itraverse_ :: (FoldableWithIndex i t, Applicative f) => (i -> a -> f b) -> t a -> f ()Source
ifor_ :: (FoldableWithIndex i t, Applicative f) => t a -> (i -> a -> f b) -> f ()Source
imapM_ :: (FoldableWithIndex i t, Monad m) => (i -> a -> m b) -> t a -> m ()Source
Run monadic actions for each target of an IndexedFold
or IndexedTraversal
with access to the index,
discarding the results.
When you don't need access to the index then mapMOf_
is more flexible in what it accepts.
mapM_
≡imapM
.
const
iforM_ :: (FoldableWithIndex i t, Monad m) => t a -> (i -> a -> m b) -> m ()Source
Run monadic actions for each target of an IndexedFold
or IndexedTraversal
with access to the index,
discarding the results (with the arguments flipped).
iforM_
≡flip
imapM_
When you don't need access to the index then forMOf_
is more flexible in what it accepts.
forMOf_
l a ≡iforMOf
l a.
const
iconcatMap :: FoldableWithIndex i f => (i -> a -> [b]) -> f a -> [b]Source
Concatenate the results of a function of the elements of an indexed container with access to the index.
When you don't need access to the index then concatMap
is more flexible in what it accepts.
concatMap
≡iconcatMap
.
const
iconcatMap
≡ifoldMap
ifind :: FoldableWithIndex i f => (i -> a -> Bool) -> f a -> Maybe (i, a)Source
ifoldrM :: (FoldableWithIndex i f, Monad m) => (i -> a -> b -> m b) -> b -> f a -> m bSource
ifoldlM :: (FoldableWithIndex i f, Monad m) => (i -> b -> a -> m b) -> b -> f a -> m bSource
itoList :: FoldableWithIndex i f => f a -> [(i, a)]Source
Converting to Folds
withIndex :: (Indexable i p, Functor f) => Optical p (Indexed i) f s t (i, s) (j, t)Source
Fold a container with indices returning both the indices and the values.
The result is only valid to compose in a Traversal
, if you don't edit the
index as edits to the index have no effect.
asIndex :: (Indexable i p, Contravariant f, Functor f) => Optical' p (Indexed i) f s iSource
When composed with an IndexedFold
or IndexedTraversal
this yields an
(Indexed
) Fold
of the indices.
Restricting by Index
indices :: (Indexable i p, Applicative f) => (i -> Bool) -> Optical' p (Indexed i) f a aSource
This allows you to filter an IndexedFold
, IndexedGetter
, IndexedTraversal
or IndexedLens
based on a predicate
on the indices.
>>>
["hello","the","world","!!!"]^..traversed.indices even
["hello","world"]
>>>
over (traversed.indices (>0)) Prelude.reverse $ ["He","was","stressed","o_O"]
["He","saw","desserts","O_o"]
index :: (Indexable i p, Eq i, Applicative f) => i -> Optical' p (Indexed i) f a aSource
This allows you to filter an IndexedFold
, IndexedGetter
, IndexedTraversal
or IndexedLens
based on an index.
>>>
["hello","the","world","!!!"]^?traversed.index 2
Just "world"
Indexed Traversables
class (FunctorWithIndex i t, FoldableWithIndex i t, Traversable t) => TraversableWithIndex i t | t -> i whereSource
A Traversable
with an additional index.
An instance must satisfy a (modified) form of the Traversable
laws:
itraverse
(const
Identity
) ≡Identity
fmap
(itraverse
f).
itraverse
g ≡getCompose
.
itraverse
(\i ->Compose
.
fmap
(f i).
g i)
itraverse :: Applicative f => (i -> a -> f b) -> t a -> f (t b)Source
Traverse an indexed container.
itraversed :: IndexedTraversal i (t a) (t b) a bSource
The IndexedTraversal
of a TraversableWithIndex
container.
TraversableWithIndex Int [] | |
TraversableWithIndex Int Seq | |
TraversableWithIndex Int IntMap | |
TraversableWithIndex Int NonEmpty | |
TraversableWithIndex Int Vector | |
TraversableWithIndex Int Deque | |
TraversableWithIndex () Maybe | |
TraversableWithIndex () Identity | |
TraversableWithIndex i (Level i) | |
(Eq k, Hashable k) => TraversableWithIndex k (HashMap k) | |
TraversableWithIndex k (Map k) | |
TraversableWithIndex k ((,) k) | |
TraversableWithIndex i f => TraversableWithIndex i (Reverse f) | |
TraversableWithIndex i f => TraversableWithIndex i (Backwards f) | |
TraversableWithIndex i (Magma i t b) |
Indexed Traversable Combinators
ifor :: (TraversableWithIndex i t, Applicative f) => t a -> (i -> a -> f b) -> f (t b)Source
imapM :: (TraversableWithIndex i t, Monad m) => (i -> a -> m b) -> t a -> m (t b)Source
iforM :: (TraversableWithIndex i t, Monad m) => t a -> (i -> a -> m b) -> m (t b)Source
imapAccumR :: TraversableWithIndex i t => (i -> s -> a -> (s, b)) -> s -> t a -> (s, t b)Source
Generalizes mapAccumR
to add access to the index.
imapAccumROf
accumulates state from right to left.
mapAccumR
≡imapAccumR
.
const
imapAccumL :: TraversableWithIndex i t => (i -> s -> a -> (s, b)) -> s -> t a -> (s, t b)Source
Generalizes mapAccumL
to add access to the index.
imapAccumLOf
accumulates state from left to right.
mapAccumLOf
≡imapAccumL
.
const
Indexed Folds with Reified Monoid
ifoldMapBy :: FoldableWithIndex i t => (r -> r -> r) -> r -> (i -> a -> r) -> t a -> rSource
ifoldMapByOf :: (forall s. IndexedGetting i (M r s) t a) -> (r -> r -> r) -> r -> (i -> a -> r) -> t -> rSource