{-# OPTIONS_HADDOCK not-home #-}
module Optics.Internal.Fold where
import Data.Functor
import Data.Foldable
import Data.Maybe
import qualified Data.Semigroup as SG
import Data.Profunctor.Indexed
import Optics.Internal.Bi
import Optics.Internal.Optic
foldVL__
:: (Bicontravariant p, Traversing p)
=> (forall f. Applicative f => (a -> f u) -> s -> f v)
-> Optic__ p i i s t a b
foldVL__ f = rphantom . wander f . rphantom
{-# INLINE foldVL__ #-}
folded__
:: (Bicontravariant p, Traversing p, Foldable f)
=> Optic__ p i i (f a) (f b) a b
folded__ = foldVL__ traverse_
{-# INLINE folded__ #-}
foldring__
:: (Bicontravariant p, Traversing p)
=> (forall f. Applicative f => (a -> f u -> f u) -> f v -> s -> f w)
-> Optic__ p i i s t a b
foldring__ fr = foldVL__ $ \f -> void . fr (\a -> (f a *>)) (pure v)
where
v = error "foldring__: value used"
{-# INLINE foldring__ #-}
data Leftmost a = LPure | LLeaf a | LStep (Leftmost a)
instance SG.Semigroup (Leftmost a) where
x <> y = LStep $ case x of
LPure -> y
LLeaf _ -> x
LStep x' -> case y of
LPure -> x'
LLeaf a -> LLeaf $ fromMaybe a (getLeftmost x')
LStep y' -> x' SG.<> y'
instance Monoid (Leftmost a) where
mempty = LPure
mappend = (SG.<>)
{-# INLINE mempty #-}
{-# INLINE mappend #-}
getLeftmost :: Leftmost a -> Maybe a
getLeftmost LPure = Nothing
getLeftmost (LLeaf a) = Just a
getLeftmost (LStep x) = go x
where
go LPure = Nothing
go (LLeaf a) = Just a
go (LStep a) = go a
data Rightmost a = RPure | RLeaf a | RStep (Rightmost a)
instance SG.Semigroup (Rightmost a) where
x <> y = RStep $ case y of
RPure -> x
RLeaf _ -> y
RStep y' -> case x of
RPure -> y'
RLeaf a -> RLeaf $ fromMaybe a (getRightmost y')
RStep x' -> mappend x' y'
instance Monoid (Rightmost a) where
mempty = RPure
mappend = (SG.<>)
{-# INLINE mempty #-}
{-# INLINE mappend #-}
getRightmost :: Rightmost a -> Maybe a
getRightmost RPure = Nothing
getRightmost (RLeaf a) = Just a
getRightmost (RStep x) = go x
where
go RPure = Nothing
go (RLeaf a) = Just a
go (RStep a) = go a