{-# LANGUAGE CPP #-}
#ifdef TRUSTWORTHY
{-# LANGUAGE Trustworthy #-}
#endif
------------------------------------------------------------------------------- |-- Module : Control.Lens.Internal.Iso-- Copyright : (C) 2012-2014 Edward Kmett-- License : BSD-style (see the file LICENSE)-- Maintainer : Edward Kmett <ekmett@gmail.com>-- Stability : experimental-- Portability : non-portable------------------------------------------------------------------------------
module Control.Lens.Internal.Iso
( Exchange(..)
, Reversing(..)
) where
import Data.Profunctor
#ifndef SAFE
import Data.Profunctor.Unsafe
import Unsafe.Coerce
#endif
import Data.ByteString as StrictB
import Data.ByteString.Lazy as LazyB
import Data.Text as StrictT
import Data.Text.Lazy as LazyT
import Data.Vector as Vector
import Data.Vector.Primitive as Prim
import Data.Vector.Storable as Storable
import Data.Vector.Unboxed as Unbox
import Data.Sequence as Seq
-------------------------------------------------------------------------------- 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 Exchangeabst = Exchange (s -> a) (b -> t)
instance Functor (Exchangeabs) where
fmapf (Exchangesabt) = Exchangesa (f.bt)
{-# INLINE fmap #-}
instance Profunctor (Exchangeab) where
dimapfg (Exchangesabt) = Exchange (sa.f) (g.bt)
{-# INLINE dimap #-}lmapf (Exchangesabt) = Exchange (sa.f) bt{-# INLINE lmap #-}rmapf (Exchangesabt) = Exchangesa (f.bt)
{-# INLINE rmap #-}
#ifndef SAFE
( #. ) _ = unsafeCoerce{-# INLINE ( #. ) #-}( .# )p _ = unsafeCoercep{-# INLINE ( .# ) #-}
#endif
-------------------------------------------------------------------------------- Reversible-------------------------------------------------------------------------------- | This class provides a generalized notion of list reversal extended to other containers.
class Reversingt where
reversing :: t -> t
instance Reversing [a] where
reversing = Prelude.reverse
instance ReversingStrictB.ByteString where
reversing = StrictB.reverse
instance ReversingLazyB.ByteString where
reversing = LazyB.reverse
instance ReversingStrictT.Text where
reversing = StrictT.reverse
instance ReversingLazyT.Text where
reversing = LazyT.reverse
instance Reversing (Vector.Vectora) where
reversing = Vector.reverse
instance Reversing (Seqa) where
reversing = Seq.reverse
instance Prim a =>Reversing (Prim.Vectora) where
reversing = Prim.reverse
instance Unbox a =>Reversing (Unbox.Vectora) where
reversing = Unbox.reverse
instance Storable a =>Reversing (Storable.Vectora) where
reversing = Storable.reverse