{-# LANGUAGE AllowAmbiguousTypes    #-}
{-# LANGUAGE CPP                    #-}
{-# 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 Data.Generics.Internal.Families
import Data.Generics.Internal.Void
import Data.Generics.Sum.Internal.Constructors
import Data.Kind    (Constraint, Type)
import GHC.Generics (Generic (Rep))
import GHC.TypeLits (Symbol, TypeError, ErrorMessage (..))
import Data.Generics.Internal.VL.Prism
import Data.Generics.Internal.Profunctor.Iso
import Data.Generics.Internal.Profunctor.Prism (prismPRavel)
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
  ( Generic s
  , ErrorUnless ctor s (HasCtorP ctor (Rep s))
  , GAsConstructor' ctor (Rep s) a
  ) => AsConstructor' ctor s a where
  _Ctor' eta = prismRavel (prismPRavel (repIso . _GCtor @ctor)) eta
  {-# INLINE[2] _Ctor' #-}
instance
  ( Generic s
  , Generic t
  , ErrorUnless ctor s (HasCtorP ctor (Rep s))
  , GAsConstructor' ctor (Rep s) a 
  , GAsConstructor' ctor (Rep (Indexed s)) a'
  , GAsConstructor ctor (Rep s) (Rep t) a b
  , t ~ Infer s a' b
  , GAsConstructor' ctor (Rep (Indexed t)) b'
  , s ~ Infer t b' a
  ) => AsConstructor ctor s t a b where
  _Ctor = _Ctor0 @ctor
  {-# INLINE[2] _Ctor #-}
instance {-# OVERLAPPING #-} AsConstructor ctor (Void1 a) (Void1 b) a b where
  _Ctor = undefined
instance
  ( Generic s
  , Generic t
  , ErrorUnless ctor s (HasCtorP ctor (Rep s))
  , GAsConstructor' ctor (Rep s) a 
  , GAsConstructor' ctor (Rep (Indexed s)) a'
  , GAsConstructor ctor (Rep s) (Rep t) a b
  , GAsConstructor' ctor (Rep (Indexed t)) b'
  , UnifyHead s t
  , UnifyHead t s
  ) => AsConstructor_ ctor s t a b where
  _Ctor_ = _Ctor0 @ctor
  {-# INLINE[2] _Ctor_ #-}
instance {-# OVERLAPPING #-} AsConstructor_ ctor (Void1 a) (Void1 b) a b where
  _Ctor_ = undefined
instance
  ( Generic s
  , Generic t
  , GAsConstructor ctor (Rep s) (Rep t) a b
  ) => AsConstructor0 ctor s t a b where
  _Ctor0 = prismRavel (prismPRavel (repIso . _GCtor @ctor))
  {-# INLINE[2] _Ctor0 #-}
type family ErrorUnless (ctor :: Symbol) (s :: Type) (contains :: Bool) :: Constraint where
  ErrorUnless ctor s 'False
    = TypeError
        (     'Text "The type "
        ':<>: 'ShowType s
        ':<>: 'Text " does not contain a constructor named "
        ':<>: 'ShowType ctor
        )
  ErrorUnless _ _ 'True
    = ()