{-# LANGUAGE CPP #-}
{-# LANGUAGE DataKinds #-}
module Optics.IxFold
  (
  
    IxFold
  
  , ifoldVL
  
  , ifoldMapOf
  , ifoldrOf
  , ifoldlOf'
  , itoListOf
  , itraverseOf_
  , iforOf_
  
  , ifolded
  , ifolding
  , ifoldring
  
  
  , iheadOf
  , ilastOf
  , ianyOf
  , iallOf
  , inoneOf
  , ifindOf
  , ifindMOf
  
  , ipre
  , ifiltered
  , ibackwards_
  
  , isumming
  , ifailing
  
  , A_Fold
  
  , FoldableWithIndex(..)
  ) where
import Control.Applicative.Backwards
import Data.Monoid
import Optics.Internal.Bi
import Optics.Internal.Indexed
import Optics.Internal.Fold
import Optics.Internal.IxFold
import Optics.Internal.Optic
import Optics.Internal.Profunctor
import Optics.Internal.Utils
import Optics.IxAffineFold
import Optics.Fold
type IxFold i s a = Optic' A_Fold (WithIx i) s a
ifoldVL
  :: (forall f. Applicative f => (i -> a -> f u) -> s -> f v)
  -> IxFold i s a
ifoldVL f = Optic (ifoldVL__ f)
{-# INLINE ifoldVL #-}
ifoldMapOf
  :: (Is k A_Fold, Monoid m, is `HasSingleIndex` i)
  => Optic' k is s a
  -> (i -> a -> m) -> s -> m
ifoldMapOf o = \f -> runIxForget (getOptic (castOptic @A_Fold o) (IxForget f)) id
{-# INLINE ifoldMapOf #-}
ifoldrOf
  :: (Is k A_Fold, is `HasSingleIndex` i)
  => Optic' k is s a
  -> (i -> a -> r -> r) -> r -> s -> r
ifoldrOf o = \iarr r0 s -> (\e -> appEndo e r0) $ ifoldMapOf o (\i -> Endo #. iarr i) s
{-# INLINE ifoldrOf #-}
ifoldlOf'
  :: (Is k A_Fold, is `HasSingleIndex` i)
  => Optic' k is s a
  -> (i -> r -> a -> r) -> r -> s -> r
ifoldlOf' o = \irar r0 s -> ifoldrOf o (\i a rr r -> rr $! irar i r a) id s r0
{-# INLINE ifoldlOf' #-}
itoListOf
  :: (Is k A_Fold, is `HasSingleIndex` i)
  => Optic' k is s a
  -> s -> [(i, a)]
itoListOf o = ifoldrOf o (\i -> (:) . (i, )) []
{-# INLINE itoListOf #-}
itraverseOf_
  :: (Is k A_Fold, Applicative f, is `HasSingleIndex` i)
  => Optic' k is s a
  -> (i -> a -> f r) -> s -> f ()
#if __GLASGOW_HASKELL__ == 802
itraverseOf_ o = \f ->
#else
itraverseOf_ o f =
#endif
  runTraversed . ifoldMapOf o (\i -> Traversed #. f i)
{-# INLINE itraverseOf_ #-}
iforOf_
  :: (Is k A_Fold, Applicative f, is `HasSingleIndex` i)
  => Optic' k is s a
  -> s -> (i -> a -> f r) -> f ()
iforOf_ = flip . itraverseOf_
{-# INLINE iforOf_ #-}
ifolded :: FoldableWithIndex i f => IxFold i (f a) a
ifolded = Optic ifolded__
{-# INLINE ifolded #-}
ifolding :: FoldableWithIndex i f => (s -> f a) -> IxFold i s a
ifolding f = Optic $ contrafirst f . ifolded__
{-# INLINE ifolding #-}
ifoldring
  :: (forall f. Applicative f => (i -> a -> f u -> f u) -> f v -> s -> f w)
  -> IxFold i s a
ifoldring fr = Optic (ifoldring__ fr)
{-# INLINE ifoldring #-}
ipre
  :: (Is k A_Fold, is `HasSingleIndex` i)
  => Optic' k is s a
  -> IxAffineFold i s a
ipre = iafolding . iheadOf
{-# INLINE ipre #-}
ifiltered
  :: (Is k A_Fold, is `HasSingleIndex` i)
  => (i -> a -> Bool)
  -> Optic' k is s a
  -> IxFold i s a
ifiltered p o = ifoldVL $ \f ->
  itraverseOf_ o (\i a -> if p i a then f i a else pure ())
{-# INLINE ifiltered #-}
ibackwards_
  :: (Is k A_Fold, is `HasSingleIndex` i)
  => Optic' k is s a
  -> IxFold i s a
ibackwards_ o = conjoined (backwards_ o) $ ifoldVL $ \f ->
  forwards #. itraverseOf_ o (\i -> Backwards #. f i)
{-# INLINE ibackwards_ #-}
isumming
  :: (Is k A_Fold, Is l A_Fold,
      is1 `HasSingleIndex` i, is2 `HasSingleIndex` i)
  => Optic' k is1 s a
  -> Optic' l is2 s a
  -> IxFold i s a
isumming a b = conjoined (summing a b) $ ifoldVL $ \f s ->
  itraverseOf_ a f s *> itraverseOf_ b f s
infixr 6 `isumming` 
{-# INLINE isumming #-}
ifailing
  :: (Is k A_Fold, Is l A_Fold, is1 `HasSingleIndex` i, is2 `HasSingleIndex` i)
  => Optic' k is1 s a
  -> Optic' l is2 s a
  -> IxFold i s a
ifailing a b = conjoined (failing a b) $ ifoldVL $ \f s ->
  let OrT visited fu = itraverseOf_ a (\i -> wrapOrT . f i) s
  in if visited
     then fu
     else itraverseOf_ b f s
infixl 3 `ifailing` 
{-# INLINE ifailing #-}
iheadOf
  :: (Is k A_Fold, is `HasSingleIndex` i)
  => Optic' k is s a -> s -> Maybe (i, a)
iheadOf o = getLeftmost . ifoldMapOf o (\i -> LLeaf . (i, ))
{-# INLINE iheadOf #-}
ilastOf
  :: (Is k A_Fold, is `HasSingleIndex` i)
  => Optic' k is s a -> s -> Maybe (i, a)
ilastOf o = getRightmost . ifoldMapOf o (\i -> RLeaf . (i, ))
{-# INLINE ilastOf #-}
ianyOf
  :: (Is k A_Fold, is `HasSingleIndex` i)
  => Optic' k is s a -> (i -> a -> Bool) -> s -> Bool
ianyOf o = \f -> getAny #. ifoldMapOf o (\i -> Any #. f i)
{-# INLINE ianyOf #-}
iallOf
  :: (Is k A_Fold, is `HasSingleIndex` i)
  => Optic' k is s a -> (i -> a -> Bool) -> s -> Bool
iallOf o = \f -> getAll #. ifoldMapOf o (\i -> All #. f i)
{-# INLINE iallOf #-}
inoneOf
  :: (Is k A_Fold, is `HasSingleIndex` i)
  => Optic' k is s a -> (i -> a -> Bool) -> s -> Bool
inoneOf o = \f -> not . ianyOf o f
{-# INLINE inoneOf #-}
ifindOf
 :: (Is k A_Fold, is `HasSingleIndex` i)
 => Optic' k is s a -> (i -> a -> Bool) -> s -> Maybe (i, a)
ifindOf o = \p -> iheadOf (ifiltered p o)
{-# INLINE ifindOf #-}
ifindMOf
  :: (Is k A_Fold, Monad m, is `HasSingleIndex` i)
  => Optic' k is s a -> (i -> a -> m Bool) -> s -> m (Maybe (i, a))
ifindMOf o = \f -> ifoldrOf o
  (\i a y -> f i a >>= \r -> if r then pure (Just (i, a)) else y)
  (pure Nothing)
{-# INLINE ifindMOf #-}