{-# LANGUAGE
    FlexibleContexts
  , FlexibleInstances
  , ScopedTypeVariables
  , TypeOperators
  #-}
module Generics.Generic.IsEnum
  ( isEnum
  , GIsEnum (..)
  ) where
import Data.Proxy
import GHC.Generics
class GIsEnum f where
  gIsEnum :: Proxy (f a) -> Bool
instance GIsEnum V1 where
  gIsEnum :: Proxy (V1 a) -> Bool
gIsEnum Proxy (V1 a)
_ = Bool
False
instance GIsEnum (K1 i a) where
  gIsEnum :: Proxy (K1 i a a) -> Bool
gIsEnum Proxy (K1 i a a)
_ = Bool
False
instance GIsEnum U1 where
  gIsEnum :: Proxy (U1 a) -> Bool
gIsEnum Proxy (U1 a)
_ = Bool
True
instance GIsEnum Par1 where
  gIsEnum :: Proxy (Par1 a) -> Bool
gIsEnum Proxy (Par1 a)
_ = Bool
False
instance GIsEnum (Rec1 f) where
  gIsEnum :: Proxy (Rec1 f a) -> Bool
gIsEnum Proxy (Rec1 f a)
_ = Bool
False
instance (GIsEnum f, GIsEnum g) => GIsEnum (f :+: g) where
  gIsEnum :: Proxy ((:+:) f g a) -> Bool
gIsEnum Proxy ((:+:) f g a)
_ = Proxy (f Any) -> Bool
forall (f :: * -> *) a. GIsEnum f => Proxy (f a) -> Bool
gIsEnum (forall a. Proxy (f a)
forall k (t :: k). Proxy t
Proxy :: Proxy (f a)) Bool -> Bool -> Bool
&& Proxy (g Any) -> Bool
forall (f :: * -> *) a. GIsEnum f => Proxy (f a) -> Bool
gIsEnum (forall a. Proxy (g a)
forall k (t :: k). Proxy t
Proxy :: Proxy (g a))
instance (GIsEnum f, GIsEnum g) => GIsEnum (f :*: g) where
  gIsEnum :: Proxy ((:*:) f g a) -> Bool
gIsEnum Proxy ((:*:) f g a)
_ = Bool
False
instance GIsEnum f => GIsEnum (M1 C c f) where
  gIsEnum :: Proxy (M1 C c f a) -> Bool
gIsEnum Proxy (M1 C c f a)
_ = Proxy (f Any) -> Bool
forall (f :: * -> *) a. GIsEnum f => Proxy (f a) -> Bool
gIsEnum (forall a. Proxy (f a)
forall k (t :: k). Proxy t
Proxy :: Proxy (f a))
instance GIsEnum (M1 S c a) where
  gIsEnum :: Proxy (M1 S c a a) -> Bool
gIsEnum Proxy (M1 S c a a)
_ = Bool
False
instance GIsEnum f => GIsEnum (M1 D c f) where
  gIsEnum :: Proxy (M1 D c f a) -> Bool
gIsEnum Proxy (M1 D c f a)
_ = Proxy (f Any) -> Bool
forall (f :: * -> *) a. GIsEnum f => Proxy (f a) -> Bool
gIsEnum (forall a. Proxy (f a)
forall k (t :: k). Proxy t
Proxy :: Proxy (f a))
isEnum :: forall a. (Generic a, GIsEnum (Rep a)) => Proxy a -> Bool
isEnum :: Proxy a -> Bool
isEnum Proxy a
_ = Proxy (Rep a a) -> Bool
forall (f :: * -> *) a. GIsEnum f => Proxy (f a) -> Bool
gIsEnum (Proxy (Rep a a)
forall k (t :: k). Proxy t
Proxy :: Proxy ((Rep a) a))