{-# LANGUAGE PackageImports #-}
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE FlexibleContexts #-}
module Data.Generics.Sum.Constructors
(
AsConstructor (..)
, AsConstructor_ (..)
, AsConstructor' (..)
, AsConstructor0 (..)
) where
import "this" Data.Generics.Internal.VL.Prism
import "generic-lens-core" Data.Generics.Internal.Void
import qualified "generic-lens-core" Data.Generics.Sum.Internal.Constructors as Core
import GHC.TypeLits (Symbol)
class AsConstructor (ctor :: Symbol) s t a b | ctor s -> a, ctor t -> b where
_Ctor :: Prism s t a b
class AsConstructor_ (ctor :: Symbol) s t a b where
_Ctor_ :: Prism s t a b
class AsConstructor' (ctor :: Symbol) s a | ctor s -> a where
_Ctor' :: Prism s s a a
class AsConstructor0 (ctor :: Symbol) s t a b where
_Ctor0 :: Prism s t a b
instance (Core.Context' ctor s a, AsConstructor0 ctor s s a a) => AsConstructor' ctor s a where
_Ctor' :: Prism s s a a
_Ctor' p a (f a)
eta = forall (ctor :: Symbol) s t a b.
AsConstructor0 ctor s t a b =>
Prism s t a b
_Ctor0 @ctor p a (f a)
eta
{-# INLINE _Ctor' #-}
instance (Core.Context ctor s t a b, AsConstructor0 ctor s t a b) => AsConstructor ctor s t a b where
_Ctor :: Prism s t a b
_Ctor p a (f b)
eta = forall (ctor :: Symbol) s t a b.
AsConstructor0 ctor s t a b =>
Prism s t a b
_Ctor0 @ctor p a (f b)
eta
{-# INLINE _Ctor #-}
instance {-# OVERLAPPING #-} AsConstructor ctor (Void1 a) (Void1 b) a b where
_Ctor :: Prism (Void1 a) (Void1 b) a b
_Ctor = forall a. HasCallStack => a
undefined
instance (Core.Context_ ctor s t a b, AsConstructor0 ctor s t a b) => AsConstructor_ ctor s t a b where
_Ctor_ :: Prism s t a b
_Ctor_ = forall (ctor :: Symbol) s t a b.
AsConstructor0 ctor s t a b =>
Prism s t a b
_Ctor0 @ctor
{-# INLINE _Ctor_ #-}
instance {-# OVERLAPPING #-} AsConstructor_ ctor (Void1 a) (Void1 b) a b where
_Ctor_ :: Prism (Void1 a) (Void1 b) a b
_Ctor_ = forall a. HasCallStack => a
undefined
instance Core.Context0 ctor s t a b => AsConstructor0 ctor s t a b where
_Ctor0 :: Prism s t a b
_Ctor0 p a (f b)
eta = forall i s t a b. APrism i s t a b -> Prism s t a b
prism2prismvl (forall (ctor :: Symbol) s t a b.
Context0 ctor s t a b =>
Prism s t a b
Core.derived0 @ctor) p a (f b)
eta
{-# INLINE _Ctor0 #-}