{-# LANGUAGE DataKinds #-}
module Optics.Indexed.Core
  (
  
    IxOptic(..)
  , conjoined
  
  , (%)
  , (<%>)
  , (%>)
  , (<%)
  , reindexed
  , icompose
  , icompose3
  , icompose4
  , icompose5
  , icomposeN
    
  , module Optics.IxAffineFold
  , module Optics.IxAffineTraversal
  , module Optics.IxFold
  , module Optics.IxGetter
  , module Optics.IxLens
  , module Optics.IxSetter
  , module Optics.IxTraversal
  
  , FunctorWithIndex (..)
  
  , FoldableWithIndex (..)
  , itraverse_
  , ifor_
  
  , TraversableWithIndex (..)
  , ifor
  ) where
import Optics.Internal.Indexed
import Optics.Internal.Optic
import Optics.Internal.Profunctor
import Optics.AffineFold
import Optics.AffineTraversal
import Optics.Fold
import Optics.Getter
import Optics.IxAffineFold
import Optics.IxAffineTraversal
import Optics.IxFold
import Optics.IxGetter
import Optics.IxLens
import Optics.IxSetter
import Optics.IxTraversal
import Optics.Lens
import Optics.Setter
import Optics.Traversal
infixl 9 <%>
(<%>)
  :: (m ~ Join k l, Is k m, Is l m, IxOptic m s t a b,
      is `HasSingleIndex` i, js `HasSingleIndex` j)
  => Optic k is              s t u v
  -> Optic l js              u v a b
  -> Optic m (WithIx (i, j)) s t a b
o <%> o' = icompose (,) (o % o')
{-# INLINE (<%>) #-}
infixl 9 %>
(%>)
  :: (m ~ Join k l, Is k m, Is l m, IxOptic k s t u v, NonEmptyIndices is)
  => Optic k is s t u v
  -> Optic l js u v a b
  -> Optic m js s t a b
o %> o' = noIx o % o'
{-# INLINE (%>) #-}
infixl 9 <%
(<%)
  :: (m ~ Join k l, Is l m, Is k m, IxOptic l u v a b, NonEmptyIndices js)
  => Optic k is s t u v
  -> Optic l js u v a b
  -> Optic m is s t a b
o <% o' = o % noIx o'
{-# INLINE (<%) #-}
reindexed
  :: is `HasSingleIndex` i
  => (i -> j)
  -> Optic k is         s t a b
  -> Optic k (WithIx j) s t a b
reindexed = icomposeN
{-# INLINE reindexed #-}
icompose
  :: (i -> j -> ix)
  -> Optic k '[i, j]     s t a b
  -> Optic k (WithIx ix) s t a b
icompose = icomposeN
{-# INLINE icompose #-}
icompose3
  :: (i1 -> i2 -> i3 -> ix)
  -> Optic k '[i1, i2, i3] s t a b
  -> Optic k (WithIx ix)   s t a b
icompose3 = icomposeN
{-# INLINE icompose3 #-}
icompose4
  :: (i1 -> i2 -> i3 -> i4 -> ix)
  -> Optic k '[i1, i2, i3, i4] s t a b
  -> Optic k (WithIx ix)       s t a b
icompose4 = icomposeN
{-# INLINE icompose4 #-}
icompose5
  :: (i1 -> i2 -> i3 -> i4 -> i5 -> ix)
  -> Optic k '[i1, i2, i3, i4, i5] s t a b
  -> Optic k (WithIx ix)           s t a b
icompose5 = icomposeN
{-# INLINE icompose5 #-}
icomposeN
  :: forall k i is s t a b
  . (CurryCompose is, NonEmptyIndices is)
  => Curry is i
  -> Optic k is         s t a b
  -> Optic k (WithIx i) s t a b
icomposeN f (Optic o) = Optic (ixcontramap (\ij -> composeN @is ij f) . o)
{-# INLINE icomposeN #-}
class IxOptic k s t a b where
  
  noIx
    :: NonEmptyIndices is
    => Optic k is   s t a b
    -> Optic k NoIx s t a b
instance (s ~ t, a ~ b) => IxOptic A_Getter s t a b where
  noIx o = to (view o)
  {-# INLINE noIx #-}
instance IxOptic A_Lens s t a b where
  noIx o = lensVL (toLensVL o)
  {-# INLINE noIx #-}
instance IxOptic An_AffineTraversal s t a b where
  noIx o = atraversalVL (toAtraversalVL o)
  {-# INLINE noIx #-}
instance (s ~ t, a ~ b) => IxOptic An_AffineFold s t a b where
  noIx o = afolding (preview o)
  {-# INLINE noIx #-}
instance IxOptic A_Traversal s t a b where
  noIx o = traversalVL (traverseOf o)
  {-# INLINE noIx #-}
instance (s ~ t, a ~ b) => IxOptic A_Fold s t a b where
  noIx o = foldVL (traverseOf_ o)
  {-# INLINE noIx #-}
instance IxOptic A_Setter s t a b where
  noIx o = sets (over o)
  {-# INLINE noIx #-}