{-# LANGUAGE CPP #-} #ifdef TRUSTWORTHY {-# LANGUAGE Trustworthy #-} #endif ----------------------------------------------------------------------------- -- | -- Module : Control.Lens.Internal.Iso -- Copyright : (C) 2012-2013 Edward Kmett -- License : BSD-style (see the file LICENSE) -- Maintainer : Edward Kmett -- Stability : experimental -- Portability : non-portable -- ---------------------------------------------------------------------------- module Control.Lens.Internal.Iso ( Exchange(..) ) where import Data.Profunctor import Data.Profunctor.Unsafe #ifndef SAFE import Unsafe.Coerce #endif ------------------------------------------------------------------------------ -- Isomorphism: Exchange ------------------------------------------------------------------------------ -- | This is used internally by the 'Control.Lens.Iso.Iso' code to provide -- efficient access to the two functions that make up an isomorphism. data Exchange a b s t = Exchange (s -> a) (b -> t) instance Functor (Exchange a b s) where fmap f (Exchange sa bt) = Exchange sa (f . bt) {-# INLINE fmap #-} instance Profunctor (Exchange a b) where dimap f g (Exchange sa bt) = Exchange (sa . f) (g . bt) {-# INLINE dimap #-} lmap f (Exchange sa bt) = Exchange (sa . f) bt {-# INLINE lmap #-} rmap f (Exchange sa bt) = Exchange sa (f . bt) {-# INLINE rmap #-} ( #. ) _ = unsafeCoerce {-# INLINE ( #. ) #-} ( .# ) p _ = unsafeCoerce p {-# INLINE ( .# ) #-}