{-# LANGUAGE PolyKinds #-}
module GHC.Generics.Optics
( generic
, generic1
, _V1
, _U1
, _Par1
, _Rec1
, _K1
, _M1
, _L1
, _R1
) where
import qualified GHC.Generics as GHC (to, from, to1, from1)
import GHC.Generics (Generic, Rep, Generic1, Rep1, (:+:) (..), V1, U1 (..),
K1 (..), M1 (..), Par1 (..), Rec1 (..))
import Optics.Iso
import Optics.Lens
import Optics.Prism
generic :: (Generic a, Generic b) => Iso a b (Rep a c) (Rep b c)
generic :: Iso a b (Rep a c) (Rep b c)
generic = (a -> Rep a c) -> (Rep b c -> b) -> Iso a b (Rep a c) (Rep b c)
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso a -> Rep a c
forall a x. Generic a => a -> Rep a x
GHC.from Rep b c -> b
forall a x. Generic a => Rep a x -> a
GHC.to
{-# INLINE generic #-}
generic1 :: (Generic1 f, Generic1 g) => Iso (f a) (g b) (Rep1 f a) (Rep1 g b)
generic1 :: Iso (f a) (g b) (Rep1 f a) (Rep1 g b)
generic1 = (f a -> Rep1 f a)
-> (Rep1 g b -> g b) -> Iso (f a) (g b) (Rep1 f a) (Rep1 g b)
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso f a -> Rep1 f a
forall k (f :: k -> *) (a :: k). Generic1 f => f a -> Rep1 f a
GHC.from1 Rep1 g b -> g b
forall k (f :: k -> *) (a :: k). Generic1 f => Rep1 f a -> f a
GHC.to1
{-# INLINE generic1 #-}
_V1 :: Lens (V1 s) (V1 t) a b
_V1 :: Lens (V1 s) (V1 t) a b
_V1 = (V1 s -> a) -> (V1 s -> b -> V1 t) -> Lens (V1 s) (V1 t) a b
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens V1 s -> a
forall p a. p -> a
absurd V1 s -> b -> V1 t
forall p a. p -> a
absurd where
absurd :: p -> a
absurd !p
_a = a
forall a. HasCallStack => a
undefined
{-# INLINE _V1 #-}
_U1 :: Iso (U1 p) (U1 q) () ()
_U1 :: Iso (U1 p) (U1 q) () ()
_U1 = (U1 p -> ()) -> (() -> U1 q) -> Iso (U1 p) (U1 q) () ()
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso (() -> U1 p -> ()
forall a b. a -> b -> a
const ()) (U1 q -> () -> U1 q
forall a b. a -> b -> a
const U1 q
forall k (p :: k). U1 p
U1)
{-# INLINE _U1 #-}
_Par1 :: Iso (Par1 p) (Par1 q) p q
_Par1 :: Iso (Par1 p) (Par1 q) p q
_Par1 = (Par1 p -> p) -> (q -> Par1 q) -> Iso (Par1 p) (Par1 q) p q
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso Par1 p -> p
forall p. Par1 p -> p
unPar1 q -> Par1 q
forall p. p -> Par1 p
Par1
{-# INLINE _Par1 #-}
_Rec1 :: Iso (Rec1 f p) (Rec1 g q) (f p) (g q)
_Rec1 :: Iso (Rec1 f p) (Rec1 g q) (f p) (g q)
_Rec1 = (Rec1 f p -> f p)
-> (g q -> Rec1 g q) -> Iso (Rec1 f p) (Rec1 g q) (f p) (g q)
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso Rec1 f p -> f p
forall k (f :: k -> *) (p :: k). Rec1 f p -> f p
unRec1 g q -> Rec1 g q
forall k (f :: k -> *) (p :: k). f p -> Rec1 f p
Rec1
{-# INLINE _Rec1 #-}
_K1 :: Iso (K1 i c p) (K1 j d q) c d
_K1 :: Iso (K1 i c p) (K1 j d q) c d
_K1 = (K1 i c p -> c) -> (d -> K1 j d q) -> Iso (K1 i c p) (K1 j d q) c d
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso K1 i c p -> c
forall i c k (p :: k). K1 i c p -> c
unK1 d -> K1 j d q
forall k i c (p :: k). c -> K1 i c p
K1
{-# INLINE _K1 #-}
_M1 :: Iso (M1 i c f p) (M1 j d g q) (f p) (g q)
_M1 :: Iso (M1 i c f p) (M1 j d g q) (f p) (g q)
_M1 = (M1 i c f p -> f p)
-> (g q -> M1 j d g q) -> Iso (M1 i c f p) (M1 j d g q) (f p) (g q)
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso M1 i c f p -> f p
forall i (c :: Meta) k (f :: k -> *) (p :: k). M1 i c f p -> f p
unM1 g q -> M1 j d g q
forall k i (c :: Meta) (f :: k -> *) (p :: k). f p -> M1 i c f p
M1
{-# INLINE _M1 #-}
_L1 :: Prism ((a :+: c) t) ((b :+: c) t) (a t) (b t)
_L1 :: Prism ((:+:) a c t) ((:+:) b c t) (a t) (b t)
_L1 = (b t -> (:+:) b c t)
-> ((:+:) a c t -> Either ((:+:) b c t) (a t))
-> Prism ((:+:) a c t) ((:+:) b c t) (a t) (b t)
forall b t s a. (b -> t) -> (s -> Either t a) -> Prism s t a b
prism b t -> (:+:) b c t
forall k (f :: k -> *) (g :: k -> *) (p :: k). f p -> (:+:) f g p
L1 (:+:) a c t -> Either ((:+:) b c t) (a t)
forall k (f :: k -> *) (g :: k -> *) (p :: k) (f :: k -> *).
(:+:) f g p -> Either ((:+:) f g p) (f p)
reviewer
where
reviewer :: (:+:) f g p -> Either ((:+:) f g p) (f p)
reviewer (L1 f p
v) = f p -> Either ((:+:) f g p) (f p)
forall a b. b -> Either a b
Right f p
v
reviewer (R1 g p
v) = (:+:) f g p -> Either ((:+:) f g p) (f p)
forall a b. a -> Either a b
Left (g p -> (:+:) f g p
forall k (f :: k -> *) (g :: k -> *) (p :: k). g p -> (:+:) f g p
R1 g p
v)
{-# INLINE _L1 #-}
_R1 :: Prism ((c :+: a) t) ((c :+: b) t) (a t) (b t)
_R1 :: Prism ((:+:) c a t) ((:+:) c b t) (a t) (b t)
_R1 = (b t -> (:+:) c b t)
-> ((:+:) c a t -> Either ((:+:) c b t) (a t))
-> Prism ((:+:) c a t) ((:+:) c b t) (a t) (b t)
forall b t s a. (b -> t) -> (s -> Either t a) -> Prism s t a b
prism b t -> (:+:) c b t
forall k (f :: k -> *) (g :: k -> *) (p :: k). g p -> (:+:) f g p
R1 (:+:) c a t -> Either ((:+:) c b t) (a t)
forall k (f :: k -> *) (g :: k -> *) (p :: k) (g :: k -> *).
(:+:) f g p -> Either ((:+:) f g p) (g p)
reviewer
where
reviewer :: (:+:) f g p -> Either ((:+:) f g p) (g p)
reviewer (R1 g p
v) = g p -> Either ((:+:) f g p) (g p)
forall a b. b -> Either a b
Right g p
v
reviewer (L1 f p
v) = (:+:) f g p -> Either ((:+:) f g p) (g p)
forall a b. a -> Either a b
Left (f p -> (:+:) f g p
forall k (f :: k -> *) (g :: k -> *) (p :: k). f p -> (:+:) f g p
L1 f p
v)
{-# INLINE _R1 #-}