{-# OPTIONS_HADDOCK not-home #-}
module Optics.Internal.IxFold where
import Data.Functor
import Data.Foldable
import Data.Profunctor.Indexed
import Optics.Internal.Bi
import Optics.Internal.Indexed.Classes
import Optics.Internal.Optic
import Optics.Internal.Fold
ifoldVL__
:: (Bicontravariant p, Traversing p)
=> (forall f. Applicative f => (i -> a -> f u) -> s -> f v)
-> Optic__ p j (i -> j) s t a b
ifoldVL__ f = rphantom . iwander f . rphantom
{-# INLINE ifoldVL__ #-}
ifolded__
:: (Bicontravariant p, Traversing p, FoldableWithIndex i f)
=> Optic__ p j (i -> j) (f a) t a b
ifolded__ = conjoined__ (foldVL__ traverse_) (ifoldVL__ itraverse_)
{-# INLINE ifolded__ #-}
ifoldring__
:: (Bicontravariant p, Traversing p)
=> (forall f. Applicative f => (i -> a -> f u -> f u) -> f v -> s -> f w)
-> Optic__ p j (i -> j) s t a b
ifoldring__ fr = ifoldVL__ $ \f -> void . fr (\i a -> (f i a *>)) (pure v)
where
v = error "ifoldring__: value used"
{-# INLINE ifoldring__ #-}