{-# LANGUAGE PackageImports #-}
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE NoMonomorphismRestriction #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE Rank2Types #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
module Data.Generics.Product.Subtype
(
Subtype (..)
) where
import Optics.Core hiding (to)
import Optics.Internal.Optic
import "generic-lens-core" Data.Generics.Internal.Void
import qualified "generic-lens-core" Data.Generics.Product.Internal.Subtype as Core
import GHC.Generics (Generic (to, from) )
class Subtype sup sub where
super :: Lens sub sub sup sup
super
= (sub -> sup) -> (sub -> sup -> sub) -> Lens sub sub sup sup
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens sub -> sup
forall sup sub. Subtype sup sub => sub -> sup
upcast ((sup -> sub -> sub) -> sub -> sup -> sub
forall a b c. (a -> b -> c) -> b -> a -> c
flip sup -> sub -> sub
forall sup sub. Subtype sup sub => sup -> sub -> sub
smash)
{-# INLINE super #-}
upcast :: sub -> sup
upcast sub
s = sub
s sub -> Lens sub sub sup sup -> sup
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. forall sub. Subtype sup sub => Lens sub sub sup sup
forall sup sub. Subtype sup sub => Lens sub sub sup sup
super @sup
{-# INLINE upcast #-}
smash :: sup -> sub -> sub
smash = Lens sub sub sup sup -> sup -> sub -> sub
forall k (is :: IxList) s t a b.
Is k A_Setter =>
Optic k is s t a b -> b -> s -> t
set (forall sub. Subtype sup sub => Lens sub sub sup sup
forall sup sub. Subtype sup sub => Lens sub sub sup sup
super @sup)
{-# INLINE smash #-}
{-# MINIMAL super | smash, upcast #-}
instance Core.Context a b => Subtype b a where
smash :: b -> a -> a
smash b
p a
b = Rep a Any -> a
forall a x. Generic a => Rep a x -> a
to (Rep a Any -> a) -> Rep a Any -> a
forall a b. (a -> b) -> a -> b
$ Rep b Any -> Rep a Any -> Rep a Any
forall k (sub :: k -> *) (sup :: k -> *) (p :: k).
GSmash sub sup =>
sup p -> sub p -> sub p
Core.gsmash (b -> Rep b Any
forall a x. Generic a => a -> Rep a x
from b
p) (a -> Rep a Any
forall a x. Generic a => a -> Rep a x
from a
b)
upcast :: a -> b
upcast = Rep b Any -> b
forall a x. Generic a => Rep a x -> a
to (Rep b Any -> b) -> (a -> Rep b Any) -> a -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Rep a Any -> Rep b Any
forall (sub :: * -> *) (sup :: * -> *) p.
GUpcast sub sup =>
sub p -> sup p
Core.gupcast (Rep a Any -> Rep b Any) -> (a -> Rep a Any) -> a -> Rep b Any
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Rep a Any
forall a x. Generic a => a -> Rep a x
from
instance {-# OVERLAPPING #-} Subtype a a where
super :: Lens a a a a
super = (forall (p :: * -> * -> * -> *) i.
Profunctor p =>
Optic_ A_Lens p i (Curry NoIx i) a a a a)
-> Lens a a a a
forall k (is :: IxList) s t a b.
(forall (p :: * -> * -> * -> *) i.
Profunctor p =>
Optic_ k p i (Curry is i) s t a b)
-> Optic k is s t a b
Optic forall a. a -> a
forall (p :: * -> * -> * -> *) i.
Profunctor p =>
Optic_ A_Lens p i (Curry NoIx i) a a a a
id
instance {-# OVERLAPPING #-} Subtype a Void where
super :: Lens Void Void a a
super = Lens Void Void a a
forall a. HasCallStack => a
undefined
instance {-# OVERLAPPING #-} Subtype Void a where
super :: Lens a a Void Void
super = Lens a a Void Void
forall a. HasCallStack => a
undefined