{-# LANGUAGE DataKinds #-}
module Optics.IxTraversal
(
IxTraversal
, IxTraversal'
, itraversalVL
, itraverseOf
, itraversed
, ignored
, elementsOf
, elements
, elementOf
, element
, iforOf
, imapAccumLOf
, imapAccumROf
, iscanl1Of
, iscanr1Of
, ifailover
, ifailover'
, indices
, ibackwards
, ipartsOf
, isingular
, A_Traversal
, IxTraversalVL
, IxTraversalVL'
, TraversableWithIndex(..)
) where
import Control.Applicative.Backwards
import Control.Monad.Trans.State
import Data.Functor.Identity
import Data.Profunctor.Indexed
import Optics.Internal.Indexed
import Optics.Internal.Indexed.Classes
import Optics.Internal.IxTraversal
import Optics.Internal.Optic
import Optics.Internal.Utils
import Optics.IxAffineTraversal
import Optics.IxLens
import Optics.IxFold
import Optics.ReadOnly
import Optics.Traversal
type IxTraversal i s t a b = Optic A_Traversal (WithIx i) s t a b
type IxTraversal' i s a = Optic' A_Traversal (WithIx i) s a
type IxTraversalVL i s t a b =
forall f. Applicative f => (i -> a -> f b) -> s -> f t
type IxTraversalVL' i s a = IxTraversalVL i s s a a
itraversalVL :: IxTraversalVL i s t a b -> IxTraversal i s t a b
itraversalVL t = Optic (iwander t)
{-# INLINE itraversalVL #-}
itraverseOf
:: (Is k A_Traversal, Applicative f, is `HasSingleIndex` i)
=> Optic k is s t a b
-> (i -> a -> f b) -> s -> f t
itraverseOf o = \f ->
runIxStar (getOptic (castOptic @A_Traversal o) (IxStar f)) id
{-# INLINE itraverseOf #-}
iforOf
:: (Is k A_Traversal, Applicative f, is `HasSingleIndex` i)
=> Optic k is s t a b
-> s -> (i -> a -> f b) -> f t
iforOf = flip . itraverseOf
{-# INLINE iforOf #-}
imapAccumLOf
:: (Is k A_Traversal, is `HasSingleIndex` i)
=> Optic k is s t a b
-> (i -> acc -> a -> (b, acc)) -> acc -> s -> (t, acc)
imapAccumLOf o = \f acc0 s ->
let g i a = state $ \acc -> f i acc a
in runState (itraverseOf o g s) acc0
{-# INLINE imapAccumLOf #-}
imapAccumROf
:: (Is k A_Traversal, is `HasSingleIndex` i)
=> Optic k is s t a b
-> (i -> acc -> a -> (b, acc)) -> acc -> s -> (t, acc)
imapAccumROf = imapAccumLOf . ibackwards
{-# INLINE imapAccumROf #-}
iscanl1Of
:: (Is k A_Traversal, is `HasSingleIndex` i)
=> Optic k is s t a a
-> (i -> a -> a -> a) -> s -> t
iscanl1Of o = \f ->
let step i ms a = case ms of
Nothing -> (a, Just a)
Just s -> let r = f i s a in (r, Just r)
in fst . imapAccumLOf o step Nothing
{-# INLINE iscanl1Of #-}
iscanr1Of
:: (Is k A_Traversal, is `HasSingleIndex` i)
=> Optic k is s t a a
-> (i -> a -> a -> a) -> s -> t
iscanr1Of o f = fst . imapAccumROf o step Nothing
where
step i ms a = case ms of
Nothing -> (a, Just a)
Just s -> let r = f i a s in (r, Just r)
{-# INLINE iscanr1Of #-}
ifailover
:: (Is k A_Traversal, is `HasSingleIndex` i)
=> Optic k is s t a b
-> (i -> a -> b) -> s -> Maybe t
ifailover o = \f s ->
let OrT visited t = itraverseOf o (\i -> wrapOrT . Identity #. f i) s
in if visited
then Just (runIdentity t)
else Nothing
{-# INLINE ifailover #-}
ifailover'
:: (Is k A_Traversal, is `HasSingleIndex` i)
=> Optic k is s t a b
-> (i -> a -> b) -> s -> Maybe t
ifailover' o = \f s ->
let OrT visited t = itraverseOf o (\i -> wrapOrT . wrapIdentity' . f i) s
in if visited
then Just (unwrapIdentity' t)
else Nothing
{-# INLINE ifailover' #-}
itraversed
:: TraversableWithIndex i f
=> IxTraversal i (f a) (f b) a b
itraversed = Optic itraversed__
{-# INLINE itraversed #-}
indices
:: (Is k A_Traversal, is `HasSingleIndex` i)
=> (i -> Bool)
-> Optic k is s t a a
-> IxTraversal i s t a a
indices p o = itraversalVL $ \f ->
itraverseOf o $ \i a -> if p i then f i a else pure a
{-# INLINE indices #-}
ibackwards
:: (Is k A_Traversal, is `HasSingleIndex` i)
=> Optic k is s t a b
-> IxTraversal i s t a b
ibackwards o = conjoined (backwards o) $ itraversalVL $ \f ->
forwards #. itraverseOf o (\i -> Backwards #. f i)
{-# INLINE ibackwards #-}
elementsOf
:: Is k A_Traversal
=> Optic k is s t a a
-> (Int -> Bool)
-> IxTraversal Int s t a a
elementsOf o = \p -> itraversalVL $ \f ->
indexing (traverseOf o) $ \i a -> if p i then f i a else pure a
{-# INLINE elementsOf #-}
elements :: Traversable f => (Int -> Bool) -> IxTraversal' Int (f a) a
elements = elementsOf traversed
{-# INLINE elements #-}
elementOf
:: Is k A_Traversal
=> Optic' k is s a
-> Int
-> IxAffineTraversal' Int s a
elementOf o = \i -> isingular $ elementsOf o (== i)
{-# INLINE elementOf #-}
element :: Traversable f => Int -> IxAffineTraversal' Int (f a) a
element = elementOf traversed
{-# INLINE element #-}
ipartsOf
:: forall k is i s t a. (Is k A_Traversal, is `HasSingleIndex` i)
=> Optic k is s t a a
-> IxLens [i] s t [a] [a]
ipartsOf o = conjoined (partsOf o) $ ilensVL $ \f s ->
evalState (traverseOf o update s)
<$> uncurry' f (unzip $ itoListOf (getting $ castOptic @A_Traversal o) s)
where
update a = get >>= \case
[] -> pure a
a' : as' -> put as' >> pure a'
{-# INLINE ipartsOf #-}
isingular
:: forall k is i s a. (Is k A_Traversal, is `HasSingleIndex` i)
=> Optic' k is s a
-> IxAffineTraversal' i s a
isingular o = conjoined (singular o) $ iatraversalVL $ \point f s ->
case iheadOf (castOptic @A_Traversal o) s of
Nothing -> point s
Just (i, a) -> evalState (traverseOf o update s) . Just <$> f i a
where
update a = get >>= \case
Just a' -> put Nothing >> pure a'
Nothing -> pure a
{-# INLINE isingular #-}