{-# LANGUAGE AllowAmbiguousTypes #-}
module Generic.Data.Function.Common.Generic where
import GHC.Generics
datatypeName' :: forall d. Datatype d => String
datatypeName' :: forall {k} (d :: k). Datatype d => String
datatypeName' = forall (d :: k) k1 (t :: k -> (k1 -> Type) -> k1 -> Type)
       (f :: k1 -> Type) (a :: k1).
Datatype d =>
t d f a -> String
forall {k} (d :: k) k1 (t :: k -> (k1 -> Type) -> k1 -> Type)
       (f :: k1 -> Type) (a :: k1).
Datatype d =>
t d f a -> String
datatypeName @d Any d Any Any
forall a. HasCallStack => a
undefined
conName' :: forall c. Constructor c => String
conName' :: forall {k} (c :: k). Constructor c => String
conName' = forall (c :: k) k1 (t :: k -> (k1 -> Type) -> k1 -> Type)
       (f :: k1 -> Type) (a :: k1).
Constructor c =>
t c f a -> String
forall {k} (c :: k) k1 (t :: k -> (k1 -> Type) -> k1 -> Type)
       (f :: k1 -> Type) (a :: k1).
Constructor c =>
t c f a -> String
conName @c Any c Any Any
forall a. HasCallStack => a
undefined
selName' :: forall s. Selector s => String
selName' :: forall {k} (s :: k). Selector s => String
selName' = forall (s :: k) k1 (t :: k -> (k1 -> Type) -> k1 -> Type)
       (f :: k1 -> Type) (a :: k1).
Selector s =>
t s f a -> String
forall {k} (s :: k) k1 (t :: k -> (k1 -> Type) -> k1 -> Type)
       (f :: k1 -> Type) (a :: k1).
Selector s =>
t s f a -> String
selName @s Any s Any Any
forall a. HasCallStack => a
undefined
selName'' :: forall s. Selector s => Maybe String
selName'' :: forall {k} (s :: k). Selector s => Maybe String
selName'' = case forall (s :: k). Selector s => String
forall {k} (s :: k). Selector s => String
selName' @s of String
"" -> Maybe String
forall a. Maybe a
Nothing
                                String
s  -> String -> Maybe String
forall a. a -> Maybe a
Just String
s
absurdV1 :: forall {k} x a. V1 (x :: k) -> a
absurdV1 :: forall {k} (x :: k) a. V1 x -> a
absurdV1 V1 x
a = case V1 x
a of {}