{-# LANGUAGE CPP #-}
{-# LANGUAGE Rank2Types #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FunctionalDependencies #-}
#ifdef TRUSTWORTHY
{-# LANGUAGE Trustworthy #-}
#endif
#ifndef MIN_VERSION_bytestring
#define MIN_VERSION_bytestring(x,y,z) 1
#endif
module Control.Lens.Iso
(
Iso, Iso'
, AnIso, AnIso'
, iso
, from
, cloneIso
, withIso
, au
, auf
, under
, mapping
, simple
, non, non'
, anon
, enum
, curried, uncurried
, flipped
, Swapped(..)
, Strict(..)
, lazy
, Reversing(..), reversed
, involuted
, magma
, imagma
, Magma
, contramapping
, Profunctor(dimap,rmap,lmap)
, dimapping
, lmapping
, rmapping
, bimapping
) where
import Control.Lens.Equality (simple)
import Control.Lens.Fold
import Control.Lens.Internal.Context
import Control.Lens.Internal.Indexed
import Control.Lens.Internal.Iso as Iso
import Control.Lens.Internal.Magma
import Control.Lens.Prism
import Control.Lens.Review
import Control.Lens.Type
import Control.Monad.State.Lazy as Lazy
import Control.Monad.State.Strict as Strict
import Control.Monad.Writer.Lazy as Lazy
import Control.Monad.Writer.Strict as Strict
import Control.Monad.RWS.Lazy as Lazy
import Control.Monad.RWS.Strict as Strict
import Data.ByteString as StrictB hiding (reverse)
import Data.ByteString.Lazy as LazyB hiding (reverse)
import Data.Functor.Contravariant
import Data.Functor.Identity
import Data.Text as StrictT hiding (reverse)
import Data.Text.Lazy as LazyT hiding (reverse)
import Data.Tuple (swap)
import Data.Maybe
import Data.Profunctor
import Data.Profunctor.Unsafe
#ifdef HLINT
{-# ANN module "HLint: ignore Use on" #-}
#endif
type AnIso s t a b = Exchange a b a (Identity b) -> Exchange a b s (Identity t)
type AnIso' s a = AnIso s s a a
iso :: (s -> a) -> (b -> t) -> Iso s t a b
iso sa bt = dimap sa (fmap bt)
{-# INLINE iso #-}
from :: AnIso s t a b -> Iso b a t s
from l = withIso l $ \ sa bt -> iso bt sa
{-# INLINE from #-}
withIso :: AnIso s t a b -> ((s -> a) -> (b -> t) -> r) -> r
withIso ai k = case ai (Exchange id Identity) of
Exchange sa bt -> k sa (runIdentity #. bt)
{-# INLINE withIso #-}
cloneIso :: AnIso s t a b -> Iso s t a b
cloneIso k = withIso k iso
{-# INLINE cloneIso #-}
au :: AnIso s t a b -> ((b -> t) -> e -> s) -> e -> a
au k = withIso k $ \ sa bt f e -> sa (f bt e)
{-# INLINE au #-}
auf :: Profunctor p => AnIso s t a b -> (p r a -> e -> b) -> p r s -> e -> t
auf k = withIso k $ \ sa bt f g e -> bt (f (rmap sa g) e)
{-# INLINE auf #-}
under :: AnIso s t a b -> (t -> s) -> b -> a
under k = withIso k $ \ sa bt ts -> sa . ts . bt
{-# INLINE under #-}
enum :: Enum a => Iso' Int a
enum = iso toEnum fromEnum
{-# INLINE enum #-}
mapping :: (Functor f, Functor g) => AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
mapping k = withIso k $ \ sa bt -> iso (fmap sa) (fmap bt)
{-# INLINE mapping #-}
non :: Eq a => a -> Iso' (Maybe a) a
non = non' . only
{-# INLINE non #-}
non' :: APrism' a () -> Iso' (Maybe a) a
non' p = iso (fromMaybe def) go where
def = review (clonePrism p) ()
go b | has (clonePrism p) b = Nothing
| otherwise = Just b
{-# INLINE non' #-}
anon :: a -> (a -> Bool) -> Iso' (Maybe a) a
anon a p = iso (fromMaybe a) go where
go b | p b = Nothing
| otherwise = Just b
{-# INLINE anon #-}
curried :: Iso ((a,b) -> c) ((d,e) -> f) (a -> b -> c) (d -> e -> f)
curried = iso curry uncurry
{-# INLINE curried #-}
uncurried :: Iso (a -> b -> c) (d -> e -> f) ((a,b) -> c) ((d,e) -> f)
uncurried = iso uncurry curry
{-# INLINE uncurried #-}
flipped :: Iso (a -> b -> c) (a' -> b' -> c') (b -> a -> c) (b' -> a' -> c')
flipped = iso flip flip
{-# INLINE flipped #-}
class Bifunctor p => Swapped p where
swapped :: Iso (p a b) (p c d) (p b a) (p d c)
instance Swapped (,) where
swapped = iso swap swap
instance Swapped Either where
swapped = iso (either Right Left) (either Right Left)
class Strict lazy strict | lazy -> strict, strict -> lazy where
strict :: Iso' lazy strict
instance Strict LazyB.ByteString StrictB.ByteString where
#if MIN_VERSION_bytestring(0,10,0)
strict = iso LazyB.toStrict LazyB.fromStrict
#else
strict = iso (StrictB.concat . LazyB.toChunks) (LazyB.fromChunks . return)
#endif
{-# INLINE strict #-}
instance Strict LazyT.Text StrictT.Text where
strict = iso LazyT.toStrict LazyT.fromStrict
{-# INLINE strict #-}
instance Strict (Lazy.StateT s m a) (Strict.StateT s m a) where
strict = iso (Strict.StateT . Lazy.runStateT) (Lazy.StateT . Strict.runStateT)
{-# INLINE strict #-}
instance Strict (Lazy.WriterT w m a) (Strict.WriterT w m a) where
strict = iso (Strict.WriterT . Lazy.runWriterT) (Lazy.WriterT . Strict.runWriterT)
{-# INLINE strict #-}
instance Strict (Lazy.RWST r w s m a) (Strict.RWST r w s m a) where
strict = iso (Strict.RWST . Lazy.runRWST) (Lazy.RWST . Strict.runRWST)
{-# INLINE strict #-}
lazy :: Strict lazy strict => Iso' strict lazy
lazy = from strict
reversed :: Reversing a => Iso' a a
reversed = involuted Iso.reversing
involuted :: (a -> a) -> Iso' a a
involuted a = iso a a
{-# INLINE involuted #-}
magma :: LensLike (Mafic a b) s t a b -> Iso s u (Magma Int t b a) (Magma j u c c)
magma l = iso (runMafic `rmap` l sell) runMagma
{-# INLINE magma #-}
imagma :: Over (Indexed i) (Molten i a b) s t a b -> Iso s t' (Magma i t b a) (Magma j t' c c)
imagma l = iso (runMolten #. l sell) (iextract .# Molten)
{-# INLINE imagma #-}
contramapping :: Contravariant f => AnIso s t a b -> Iso (f a) (f b) (f s) (f t)
contramapping f = withIso f $ \ sa bt -> iso (contramap sa) (contramap bt)
{-# INLINE contramapping #-}
dimapping :: (Profunctor p, Profunctor q) => AnIso s t a b -> AnIso s' t' a' b' -> Iso (p a s') (q b t') (p s a') (q t b')
dimapping f g = withIso f $ \ sa bt -> withIso g $ \ s'a' b't' ->
iso (dimap sa s'a') (dimap bt b't')
{-# INLINE dimapping #-}
lmapping :: (Profunctor p, Profunctor q) => AnIso s t a b -> Iso (p a x) (q b y) (p s x) (q t y)
lmapping f = withIso f $ \ sa bt -> iso (lmap sa) (lmap bt)
{-# INLINE lmapping #-}
rmapping :: (Profunctor p, Profunctor q) => AnIso s t a b -> Iso (p x s) (q y t) (p x a) (q y b)
rmapping g = withIso g $ \ sa bt -> iso (rmap sa) (rmap bt)
{-# INLINE rmapping #-}
bimapping :: (Bifunctor f, Bifunctor g) => AnIso s t a b -> AnIso s' t' a' b' -> Iso (f s s') (g t t') (f a a') (g b b')
bimapping f g = withIso f $ \ sa bt -> withIso g $ \s'a' b't' ->
iso (bimap sa s'a') (bimap bt b't')
{-# INLINE bimapping #-}