{-# LANGUAGE DataKinds #-}
module Optics.Mapping
( MappingOptic (..)
) where
import Optics.Getter
import Optics.Internal.Indexed
import Optics.Internal.Optic
import Optics.Iso
import Optics.Review
class MappingOptic k f g s t a b where
type MappedOptic k
mapping
:: "mapping" `AcceptsEmptyIndices` is
=> Optic k is s t a b
-> Optic (MappedOptic k) is (f s) (g t) (f a) (g b)
instance (Functor f, Functor g) => MappingOptic An_Iso f g s t a b where
type MappedOptic An_Iso = An_Iso
mapping k = withIso k $ \sa bt -> iso (fmap sa) (fmap bt)
{-# INLINE mapping #-}
instance (Functor f, f ~ g, s ~ t, a ~ b) => MappingOptic A_Getter f g s t a b where
type MappedOptic A_Getter = A_Getter
mapping o = to (fmap (view o))
{-# INLINE mapping #-}
instance (Functor f, f ~ g, s ~ t, a ~ b) => MappingOptic A_ReversedPrism f g s t a b where
type MappedOptic A_ReversedPrism = A_Getter
mapping o = to (fmap (view o))
{-# INLINE mapping #-}
instance (Functor f, f ~ g, s ~ t, a ~ b) => MappingOptic A_Lens f g s t a b where
type MappedOptic A_Lens = A_Getter
mapping o = to (fmap (view o))
{-# INLINE mapping #-}
instance (Functor f, f ~ g, s ~ t, a ~ b) => MappingOptic A_Review f g s t a b where
type MappedOptic A_Review = A_Review
mapping o = unto (fmap (review o))
{-# INLINE mapping #-}
instance (Functor f, f ~ g, s ~ t, a ~ b) => MappingOptic A_Prism f g s t a b where
type MappedOptic A_Prism = A_Review
mapping o = unto (fmap (review o))
{-# INLINE mapping #-}
instance (Functor f, f ~ g, s ~ t, a ~ b) => MappingOptic A_ReversedLens f g s t a b where
type MappedOptic A_ReversedLens = A_Review
mapping o = unto (fmap (review o))
{-# INLINE mapping #-}