module Optics.ReadOnly
( ToReadOnly(..)
) where
import Data.Profunctor.Indexed
import Optics.Internal.Bi
import Optics.Internal.Optic
class ToReadOnly k s t a b where
getting :: Optic k is s t a b -> Optic' (Join A_Getter k) is s a
instance ToReadOnly An_Iso s t a b where
getting o = Optic (getting__ o)
{-# INLINE getting #-}
instance ToReadOnly A_Lens s t a b where
getting o = Optic (getting__ o)
{-# INLINE getting #-}
instance ToReadOnly A_Prism s t a b where
getting o = Optic (getting__ o)
{-# INLINE getting #-}
instance ToReadOnly An_AffineTraversal s t a b where
getting o = Optic (getting__ o)
{-# INLINE getting #-}
instance ToReadOnly A_Traversal s t a b where
getting o = Optic (getting__ o)
{-# INLINE getting #-}
instance ToReadOnly A_ReversedPrism s t a b where
getting o = Optic (getting__ o)
{-# INLINE getting #-}
instance (s ~ t, a ~ b) => ToReadOnly A_Getter s t a b where
getting = id
{-# INLINE getting #-}
instance (s ~ t, a ~ b) => ToReadOnly An_AffineFold s t a b where
getting = id
{-# INLINE getting #-}
instance (s ~ t, a ~ b) => ToReadOnly A_Fold s t a b where
getting = id
{-# INLINE getting #-}
getting__
:: (Profunctor p, Bicontravariant p, Constraints k p)
=> Optic k is s t a b
-> Optic__ p i (Curry is i) s s a a
getting__ (Optic o) = rphantom . o . rphantom
{-# INLINE getting__ #-}