{-# LANGUAGE CPP #-}
#if __GLASGOW_HASKELL__ < 708
{-# LANGUAGE Trustworthy #-}
#endif
module Control.Lens.Internal.Setter
(
Settable(..)
) where
import Control.Applicative
import Control.Applicative.Backwards
import Data.Distributive
import Data.Functor.Compose
import Data.Functor.Identity
import Data.Profunctor
import Data.Profunctor.Unsafe
import Data.Traversable
import Prelude
class (Applicative f, Distributive f, Traversable f) => Settable f where
untainted :: f a -> a
untaintedDot :: Profunctor p => p a (f b) -> p a b
untaintedDot g = g `seq` rmap untainted g
{-# INLINE untaintedDot #-}
taintedDot :: Profunctor p => p a b -> p a (f b)
taintedDot g = g `seq` rmap pure g
{-# INLINE taintedDot #-}
instance Settable Identity where
untainted = runIdentity
{-# INLINE untainted #-}
untaintedDot = (runIdentity #.)
{-# INLINE untaintedDot #-}
taintedDot = (Identity #.)
{-# INLINE taintedDot #-}
instance Settable f => Settable (Backwards f) where
untainted = untaintedDot forwards
{-# INLINE untainted #-}
instance (Settable f, Settable g) => Settable (Compose f g) where
untainted = untaintedDot (untaintedDot getCompose)
{-# INLINE untainted #-}