{-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE KindSignatures #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeApplications #-} {-# LANGUAGE TypeOperators #-} {-# LANGUAGE UndecidableInstances #-} {-# LANGUAGE NoImplicitPrelude #-} module Data.Morpheus.Generic.Cons ( RefType (..), DescribeCons (..), ) where import Data.Morpheus.Generic.Fields (CountFields) import Data.Morpheus.Generic.Proxy (CProxy, conNameP) import Data.Morpheus.Generic.RefType (RefType (..)) import GHC.Generics import Relude class DescribeCons con (f :: Type -> Type) where describeCons :: (IsString t) => Proxy f -> [(t, Maybe (CProxy con))] instance (DescribeCons gql f) => DescribeCons gql (M1 D d f) where describeCons :: forall t. IsString t => Proxy (M1 D d f) -> [(t, Maybe (CProxy gql))] describeCons Proxy (M1 D d f) _ = Proxy f -> [(t, Maybe (CProxy gql))] forall t. IsString t => Proxy f -> [(t, Maybe (CProxy gql))] forall (con :: * -> Constraint) (f :: * -> *) t. (DescribeCons con f, IsString t) => Proxy f -> [(t, Maybe (CProxy con))] describeCons (forall {k} (t :: k). Proxy t forall (t :: * -> *). Proxy t Proxy @f) instance (DescribeCons con a, DescribeCons con b) => DescribeCons con (a :+: b) where describeCons :: forall t. IsString t => Proxy (a :+: b) -> [(t, Maybe (CProxy con))] describeCons Proxy (a :+: b) _ = Proxy a -> [(t, Maybe (CProxy con))] forall t. IsString t => Proxy a -> [(t, Maybe (CProxy con))] forall (con :: * -> Constraint) (f :: * -> *) t. (DescribeCons con f, IsString t) => Proxy f -> [(t, Maybe (CProxy con))] describeCons (forall {k} (t :: k). Proxy t forall (t :: * -> *). Proxy t Proxy @a) [(t, Maybe (CProxy con))] -> [(t, Maybe (CProxy con))] -> [(t, Maybe (CProxy con))] forall a. Semigroup a => a -> a -> a <> Proxy b -> [(t, Maybe (CProxy con))] forall t. IsString t => Proxy b -> [(t, Maybe (CProxy con))] forall (con :: * -> Constraint) (f :: * -> *) t. (DescribeCons con f, IsString t) => Proxy f -> [(t, Maybe (CProxy con))] describeCons (forall {k} (t :: k). Proxy t forall (t :: * -> *). Proxy t Proxy @b) instance (Constructor c, CountFields a, RefType con a) => DescribeCons con (M1 C c a) where describeCons :: forall t. IsString t => Proxy (M1 C c a) -> [(t, Maybe (CProxy con))] describeCons Proxy (M1 C c a) _ = [(Proxy c -> t forall (f :: Meta -> *) t (c :: Meta). (Constructor c, IsString t) => f c -> t conNameP (forall {k} (t :: k). Proxy t forall (t :: Meta). Proxy t Proxy @c), Proxy a -> Maybe (CProxy con) forall (con :: * -> Constraint) (f :: * -> *). RefType con f => Proxy f -> Maybe (CProxy con) refType (forall {k} (t :: k). Proxy t forall (t :: * -> *). Proxy t Proxy @a))]