{-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE KindSignatures #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeApplications #-} {-# LANGUAGE TypeOperators #-} {-# LANGUAGE UndecidableInstances #-} {-# LANGUAGE NoImplicitPrelude #-} module Data.Morpheus.Generic.RefType ( RefType (..), ) where import Data.Morpheus.Generic.Proxy (CProxy (..)) import GHC.Generics ( K1 (..), M1 (..), S, U1 (..), (:*:) (..), ) import Relude hiding (undefined) class RefType con (f :: Type -> Type) where refType :: Proxy f -> Maybe (CProxy con) instance RefType con (f :*: g) where refType :: Proxy (f :*: g) -> Maybe (CProxy con) refType Proxy (f :*: g) _ = Maybe (CProxy con) forall a. Maybe a Nothing instance (con a) => RefType con (M1 S s (K1 i a)) where refType :: Proxy (M1 S s (K1 i a)) -> Maybe (CProxy con) refType Proxy (M1 S s (K1 i a)) _ = CProxy con -> Maybe (CProxy con) forall a. a -> Maybe a Just (CProxy con -> Maybe (CProxy con)) -> CProxy con -> Maybe (CProxy con) forall a b. (a -> b) -> a -> b $ Proxy a -> CProxy con forall {k} (f :: k -> *) (constraint :: k -> Constraint) (a :: k). constraint a => f a -> CProxy constraint CProxy (Proxy a -> CProxy con) -> Proxy a -> CProxy con forall a b. (a -> b) -> a -> b $ forall t. Proxy t forall {k} (t :: k). Proxy t Proxy @a instance RefType gql U1 where refType :: Proxy U1 -> Maybe (CProxy gql) refType Proxy U1 _ = Maybe (CProxy gql) forall a. Maybe a Nothing