-- | Get the constructor name of something
module Calamity.Internal.ConstructorName (
  CtorName (..),
  GCtorName (..),
) where

import GHC.Generics

class GCtorName f where
  gctorName :: f a -> String

instance (Constructor c) => GCtorName (C1 c f) where
  gctorName :: forall (a :: k). C1 c f a -> String
gctorName = M1 C c f a -> String
forall {k} (c :: k) k1 (t :: k -> (k1 -> *) -> k1 -> *)
       (f :: k1 -> *) (a :: k1).
Constructor c =>
t c f a -> String
forall k1 (t :: Meta -> (k1 -> *) -> k1 -> *) (f :: k1 -> *)
       (a :: k1).
t c f a -> String
conName

instance (GCtorName f) => GCtorName (D1 d f) where
  gctorName :: forall (a :: k). D1 d f a -> String
gctorName (M1 f a
a) = f a -> String
forall (a :: k). f a -> String
forall {k} (f :: k -> *) (a :: k). GCtorName f => f a -> String
gctorName f a
a

instance (GCtorName f, GCtorName g) => GCtorName (f :+: g) where
  gctorName :: forall (a :: k). (:+:) f g a -> String
gctorName (L1 f a
a) = f a -> String
forall (a :: k). f a -> String
forall {k} (f :: k -> *) (a :: k). GCtorName f => f a -> String
gctorName f a
a
  gctorName (R1 g a
a) = g a -> String
forall (a :: k). g a -> String
forall {k} (f :: k -> *) (a :: k). GCtorName f => f a -> String
gctorName g a
a

class CtorName a where
  ctorName :: a -> String
  default ctorName :: (Generic a, GCtorName (Rep a)) => a -> String
  ctorName = Rep a Any -> String
forall a. Rep a a -> String
forall {k} (f :: k -> *) (a :: k). GCtorName f => f a -> String
gctorName (Rep a Any -> String) -> (a -> Rep a Any) -> a -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Rep a Any
forall x. a -> Rep a x
forall a x. Generic a => a -> Rep a x
from