{-# LANGUAGE CPP #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE Rank2Types #-}
{-# LANGUAGE FlexibleContexts #-}
#ifdef TRUSTWORTHY
{-# LANGUAGE Trustworthy #-}
#endif
#include "lens-common.h"
module Control.Lens.Indexed
(
Indexable(..)
, Conjoined(..)
, Indexed(..)
, (<.), (<.>), (.>)
, selfIndex
, reindexed
, icompose
, indexing
, indexing64
, FunctorWithIndex(..)
, imapped
, FoldableWithIndex(..)
, ifolded
, iany
, iall
, inone, none
, itraverse_
, ifor_
, imapM_
, iforM_
, iconcatMap
, ifind
, ifoldrM
, ifoldlM
, itoList
, withIndex
, asIndex
, indices
, index
, TraversableWithIndex(..)
, itraversed
, ifor
, imapM
, iforM
, imapAccumR
, imapAccumL
, ifoldMapBy
, ifoldMapByOf
, itraverseBy
, itraverseByOf
) where
import Prelude ()
import Data.Functor.WithIndex
import Data.Foldable.WithIndex
import Data.Traversable.WithIndex
import Control.Lens.Fold
import Control.Lens.Getter
import Control.Lens.Internal.Fold
import Control.Lens.Internal.Indexed
import Control.Lens.Internal.Prelude
import Control.Lens.Setter
import Control.Lens.Traversal
import Control.Lens.Type
import Data.Reflection
import Data.HashMap.Lazy (HashMap)
import Data.IntMap (IntMap)
import Data.Map (Map)
import Data.Sequence (Seq)
import Data.Vector (Vector)
import qualified Data.HashMap.Lazy as HashMap
import qualified Data.IntMap as IntMap
import qualified Data.Map as Map
import qualified Data.Sequence as Seq
import qualified Data.Vector as Vector
infixr 9 <.>, <., .>
(<.) :: Indexable i p => (Indexed i s t -> r) -> ((a -> b) -> s -> t) -> p a b -> r
(<.) f g h = f . Indexed $ g . indexed h
{-# INLINE (<.) #-}
(.>) :: (st -> r) -> (kab -> st) -> kab -> r
(.>) = (.)
{-# INLINE (.>) #-}
selfIndex :: Indexable a p => p a fb -> a -> fb
selfIndex f a = indexed f a a
{-# INLINE selfIndex #-}
reindexed :: Indexable j p => (i -> j) -> (Indexed i a b -> r) -> p a b -> r
reindexed ij f g = f . Indexed $ indexed g . ij
{-# INLINE reindexed #-}
(<.>) :: Indexable (i, j) p => (Indexed i s t -> r) -> (Indexed j a b -> s -> t) -> p a b -> r
f <.> g = icompose (,) f g
{-# INLINE (<.>) #-}
icompose :: Indexable p c => (i -> j -> p) -> (Indexed i s t -> r) -> (Indexed j a b -> s -> t) -> c a b -> r
icompose ijk istr jabst cab = istr . Indexed $ \i -> jabst . Indexed $ \j -> indexed cab $ ijk i j
{-# INLINE icompose #-}
indices :: (Indexable i p, Applicative f) => (i -> Bool) -> Optical' p (Indexed i) f a a
indices p f = Indexed $ \i a -> if p i then indexed f i a else pure a
{-# INLINE indices #-}
index :: (Indexable i p, Eq i, Applicative f) => i -> Optical' p (Indexed i) f a a
index j f = Indexed $ \i a -> if j == i then indexed f i a else pure a
{-# INLINE index #-}
imapped :: FunctorWithIndex i f => IndexedSetter i (f a) (f b) a b
imapped = conjoined mapped (isets imap)
{-# INLINE imapped #-}
ifolded :: FoldableWithIndex i f => IndexedFold i (f a) a
ifolded = conjoined folded $ \f -> phantom . getFolding . ifoldMap (\i -> Folding #. indexed f i)
{-# INLINE ifolded #-}
itraversed :: TraversableWithIndex i t => IndexedTraversal i (t a) (t b) a b
itraversed = conjoined traverse (itraverse . indexed)
{-# INLINE [0] itraversed #-}
{-# RULES
"itraversed -> mapList" itraversed = sets fmap :: ASetter [a] [b] a b;
"itraversed -> imapList" itraversed = isets imap :: AnIndexedSetter Int [a] [b] a b;
"itraversed -> foldrList" itraversed = foldring foldr :: Getting (Endo r) [a] a;
"itraversed -> ifoldrList" itraversed = ifoldring ifoldr :: IndexedGetting Int (Endo r) [a] a;
#-}
{-# RULES
"itraversed -> mapIntMap" itraversed = sets IntMap.map :: ASetter (IntMap a) (IntMap b) a b;
"itraversed -> imapIntMap" itraversed = isets IntMap.mapWithKey :: AnIndexedSetter Int (IntMap a) (IntMap b) a b;
"itraversed -> foldrIntMap" itraversed = foldring IntMap.foldr :: Getting (Endo r) (IntMap a) a;
"itraversed -> ifoldrIntMap" itraversed = ifoldring IntMap.foldrWithKey :: IndexedGetting Int (Endo r) (IntMap a) a;
#-}
{-# RULES
"itraversed -> mapMap" itraversed = sets Map.map :: ASetter (Map k a) (Map k b) a b;
"itraversed -> imapMap" itraversed = isets Map.mapWithKey :: AnIndexedSetter k (Map k a) (Map k b) a b;
"itraversed -> foldrMap" itraversed = foldring Map.foldr :: Getting (Endo r) (Map k a) a;
"itraversed -> ifoldrMap" itraversed = ifoldring Map.foldrWithKey :: IndexedGetting k (Endo r) (Map k a) a;
#-}
{-# RULES
"itraversed -> mapHashMap" itraversed = sets HashMap.map :: ASetter (HashMap k a) (HashMap k b) a b;
"itraversed -> imapHashMap" itraversed = isets HashMap.mapWithKey :: AnIndexedSetter k (HashMap k a) (HashMap k b) a b;
"itraversed -> foldrHashMap" itraversed = foldring HashMap.foldr :: Getting (Endo r) (HashMap k a) a;
"itraversed -> ifoldrHashMap" itraversed = ifoldring HashMap.foldrWithKey :: IndexedGetting k (Endo r) (HashMap k a) a;
#-}
{-# RULES
"itraversed -> mapSeq" itraversed = sets fmap :: ASetter (Seq a) (Seq b) a b;
"itraversed -> imapSeq" itraversed = isets Seq.mapWithIndex :: AnIndexedSetter Int (Seq a) (Seq b) a b;
"itraversed -> foldrSeq" itraversed = foldring foldr :: Getting (Endo r) (Seq a) a;
"itraversed -> ifoldrSeq" itraversed = ifoldring Seq.foldrWithIndex :: IndexedGetting Int (Endo r) (Seq a) a;
#-}
{-# RULES
"itraversed -> mapVector" itraversed = sets Vector.map :: ASetter (Vector a) (Vector b) a b;
"itraversed -> imapVector" itraversed = isets Vector.imap :: AnIndexedSetter Int (Vector a) (Vector b) a b;
"itraversed -> foldrVector" itraversed = foldring Vector.foldr :: Getting (Endo r) (Vector a) a;
"itraversed -> ifoldrVector" itraversed = ifoldring Vector.ifoldr :: IndexedGetting Int (Endo r) (Vector a) a;
#-}
ifoldMapBy :: FoldableWithIndex i t => (r -> r -> r) -> r -> (i -> a -> r) -> t a -> r
ifoldMapBy f z g = reifyMonoid f z (ifoldMap (\i a -> ReflectedMonoid (g i a)))
ifoldMapByOf :: IndexedFold i t a -> (r -> r -> r) -> r -> (i -> a -> r) -> t -> r
ifoldMapByOf l f z g = reifyMonoid f z (ifoldMapOf l (\i a -> ReflectedMonoid (g i a)))
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)
itraverseBy pur app f = reifyApplicative pur app (itraverse (\i a -> ReflectedApplicative (f i a)))
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
itraverseByOf l pur app f = reifyApplicative pur app (itraverseOf l (\i a -> ReflectedApplicative (f i a)))