{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DefaultSignatures #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE Rank2Types #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE NoImplicitPrelude #-}

module Data.Morpheus.Server.Types.GQLType
  ( GQLType
      ( KIND,
        implements,
        description,
        getDescriptions,
        typeOptions,
        getDirectives,
        getFieldContents
      ),
    GQLTypeOptions
      ( fieldLabelModifier,
        constructorTagModifier,
        typeNameModifier
      ),
    defaultTypeOptions,
    TypeData (..),
    __isObjectKind,
    __isEmptyType,
    __typeData,
  )
where

-- MORPHEUS

import Data.Morpheus.App.Internal.Resolving
  ( Resolver,
    SubscriptionField,
  )
import Data.Morpheus.Kind
  ( CUSTOM,
    DerivingKind,
    SCALAR,
    TYPE,
    ToValue,
    WRAPPER,
    isObject,
    toValue,
  )
import Data.Morpheus.Server.Types.SchemaT
  ( SchemaT,
    TypeFingerprint (..),
  )
import Data.Morpheus.Server.Types.Types
  ( Pair,
    Undefined (..),
  )
import Data.Morpheus.Types.ID (ID)
import Data.Morpheus.Types.Internal.AST
  ( ArgumentsDefinition,
    CONST,
    Description,
    Directives,
    FieldName,
    OUT,
    QUERY,
    TypeCategory (..),
    TypeName (..),
    TypeWrapper (..),
    Value,
    toNullable,
  )
import Data.Morpheus.Utils.Kinded (CategoryValue (..))
import Data.Text
  ( intercalate,
    pack,
    unpack,
  )
import Data.Typeable
  ( TyCon,
    TypeRep,
    splitTyConApp,
    tyConFingerprint,
    tyConName,
    typeRep,
    typeRepTyCon,
  )
import Relude hiding (Undefined, intercalate)

data TypeData = TypeData
  { TypeData -> TypeName
gqlTypeName :: TypeName,
    TypeData -> [TypeWrapper]
gqlWrappers :: [TypeWrapper],
    TypeData -> TypeFingerprint
gqlFingerprint :: TypeFingerprint
  }

data GQLTypeOptions = GQLTypeOptions
  { GQLTypeOptions -> String -> String
fieldLabelModifier :: String -> String,
    GQLTypeOptions -> String -> String
constructorTagModifier :: String -> String,
    -- Construct a new type name depending on whether it is an input,
    -- and being given the original type name
    GQLTypeOptions -> Bool -> String -> String
typeNameModifier :: Bool -> String -> String
  }

defaultTypeOptions :: GQLTypeOptions
defaultTypeOptions :: GQLTypeOptions
defaultTypeOptions =
  GQLTypeOptions :: (String -> String)
-> (String -> String)
-> (Bool -> String -> String)
-> GQLTypeOptions
GQLTypeOptions
    { fieldLabelModifier :: String -> String
fieldLabelModifier = String -> String
forall a. a -> a
id,
      constructorTagModifier :: String -> String
constructorTagModifier = String -> String
forall a. a -> a
id,
      -- default is just a pass through for the original type name
      typeNameModifier :: Bool -> String -> String
typeNameModifier = (String -> String) -> Bool -> String -> String
forall a b. a -> b -> a
const String -> String
forall a. a -> a
id
    }

__typeData ::
  forall kinded (kind :: TypeCategory) (a :: *).
  (GQLType a, CategoryValue kind) =>
  kinded kind a ->
  TypeData
__typeData :: kinded kind a -> TypeData
__typeData kinded kind a
proxy = kinded kind a -> TypeCategory -> TypeData
forall a (f :: * -> *).
GQLType a =>
f a -> TypeCategory -> TypeData
__type kinded kind a
proxy (Proxy kind -> TypeCategory
forall (c :: TypeCategory) (f :: TypeCategory -> *).
CategoryValue c =>
f c -> TypeCategory
categoryValue (Proxy kind
forall k (t :: k). Proxy t
Proxy @kind))

getTypename :: Typeable a => f a -> TypeName
getTypename :: f a -> TypeName
getTypename = Text -> TypeName
TypeName (Text -> TypeName) -> (f a -> Text) -> f a -> TypeName
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [Text] -> Text
intercalate Text
"" ([Text] -> Text) -> (f a -> [Text]) -> f a -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. f a -> [Text]
forall a (f :: * -> *). Typeable a => f a -> [Text]
getTypeConstructorNames

getTypeConstructorNames :: Typeable a => f a -> [Text]
getTypeConstructorNames :: f a -> [Text]
getTypeConstructorNames = (TyCon -> Text) -> [TyCon] -> [Text]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (String -> Text
pack (String -> Text) -> (TyCon -> String) -> TyCon -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TyCon -> String
tyConName (TyCon -> String) -> (TyCon -> TyCon) -> TyCon -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TyCon -> TyCon
replacePairCon) ([TyCon] -> [Text]) -> (f a -> [TyCon]) -> f a -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. f a -> [TyCon]
forall a (f :: * -> *). Typeable a => f a -> [TyCon]
getTypeConstructors

getTypeConstructors :: Typeable a => f a -> [TyCon]
getTypeConstructors :: f a -> [TyCon]
getTypeConstructors = (TyCon, [TypeRep]) -> [TyCon]
ignoreResolver ((TyCon, [TypeRep]) -> [TyCon])
-> (f a -> (TyCon, [TypeRep])) -> f a -> [TyCon]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TypeRep -> (TyCon, [TypeRep])
splitTyConApp (TypeRep -> (TyCon, [TypeRep]))
-> (f a -> TypeRep) -> f a -> (TyCon, [TypeRep])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. f a -> TypeRep
forall k (proxy :: k -> *) (a :: k).
Typeable a =>
proxy a -> TypeRep
typeRep

deriveTypeData :: Typeable a => f a -> (Bool -> String -> String) -> TypeCategory -> TypeData
deriveTypeData :: f a -> (Bool -> String -> String) -> TypeCategory -> TypeData
deriveTypeData f a
proxy Bool -> String -> String
typeNameModifier TypeCategory
cat =
  TypeData :: TypeName -> [TypeWrapper] -> TypeFingerprint -> TypeData
TypeData
    { gqlTypeName :: TypeName
gqlTypeName = Text -> TypeName
TypeName (Text -> TypeName) -> (String -> Text) -> String -> TypeName
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
pack (String -> TypeName) -> String -> TypeName
forall a b. (a -> b) -> a -> b
$ Bool -> String -> String
typeNameModifier (TypeCategory
cat TypeCategory -> TypeCategory -> Bool
forall a. Eq a => a -> a -> Bool
== TypeCategory
IN) String
originalTypeName,
      gqlWrappers :: [TypeWrapper]
gqlWrappers = [],
      gqlFingerprint :: TypeFingerprint
gqlFingerprint = TypeCategory -> f a -> TypeFingerprint
forall a (f :: * -> *).
Typeable a =>
TypeCategory -> f a -> TypeFingerprint
getFingerprint TypeCategory
cat f a
proxy
    }
  where
    originalTypeName :: String
originalTypeName = Text -> String
unpack (Text -> String) -> (TypeName -> Text) -> TypeName -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TypeName -> Text
readTypeName (TypeName -> String) -> TypeName -> String
forall a b. (a -> b) -> a -> b
$ f a -> TypeName
forall a (f :: * -> *). Typeable a => f a -> TypeName
getTypename f a
proxy

getFingerprint :: Typeable a => TypeCategory -> f a -> TypeFingerprint
getFingerprint :: TypeCategory -> f a -> TypeFingerprint
getFingerprint TypeCategory
category = TypeCategory -> [Fingerprint] -> TypeFingerprint
TypeableFingerprint TypeCategory
category ([Fingerprint] -> TypeFingerprint)
-> (f a -> [Fingerprint]) -> f a -> TypeFingerprint
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (TyCon -> Fingerprint) -> [TyCon] -> [Fingerprint]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap TyCon -> Fingerprint
tyConFingerprint ([TyCon] -> [Fingerprint])
-> (f a -> [TyCon]) -> f a -> [Fingerprint]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. f a -> [TyCon]
forall a (f :: * -> *). Typeable a => f a -> [TyCon]
getTypeConstructors

mkTypeData :: TypeName -> a -> TypeData
mkTypeData :: TypeName -> a -> TypeData
mkTypeData TypeName
name a
_ =
  TypeData :: TypeName -> [TypeWrapper] -> TypeFingerprint -> TypeData
TypeData
    { gqlTypeName :: TypeName
gqlTypeName = TypeName
name,
      gqlFingerprint :: TypeFingerprint
gqlFingerprint = TypeName -> TypeFingerprint
InternalFingerprint TypeName
name,
      gqlWrappers :: [TypeWrapper]
gqlWrappers = []
    }

list :: [TypeWrapper] -> [TypeWrapper]
list :: [TypeWrapper] -> [TypeWrapper]
list = (TypeWrapper
TypeList TypeWrapper -> [TypeWrapper] -> [TypeWrapper]
forall a. a -> [a] -> [a]
:)

wrapper :: ([TypeWrapper] -> [TypeWrapper]) -> TypeData -> TypeData
wrapper :: ([TypeWrapper] -> [TypeWrapper]) -> TypeData -> TypeData
wrapper [TypeWrapper] -> [TypeWrapper]
f TypeData {[TypeWrapper]
TypeName
TypeFingerprint
gqlFingerprint :: TypeFingerprint
gqlWrappers :: [TypeWrapper]
gqlTypeName :: TypeName
gqlFingerprint :: TypeData -> TypeFingerprint
gqlWrappers :: TypeData -> [TypeWrapper]
gqlTypeName :: TypeData -> TypeName
..} = TypeData :: TypeName -> [TypeWrapper] -> TypeFingerprint -> TypeData
TypeData {gqlWrappers :: [TypeWrapper]
gqlWrappers = [TypeWrapper] -> [TypeWrapper]
f [TypeWrapper]
gqlWrappers, TypeName
TypeFingerprint
gqlFingerprint :: TypeFingerprint
gqlTypeName :: TypeName
gqlFingerprint :: TypeFingerprint
gqlTypeName :: TypeName
..}

resolverCon :: TyCon
resolverCon :: TyCon
resolverCon = TypeRep -> TyCon
typeRepTyCon (TypeRep -> TyCon) -> TypeRep -> TyCon
forall a b. (a -> b) -> a -> b
$ Proxy (Resolver QUERY () Maybe) -> TypeRep
forall k (proxy :: k -> *) (a :: k).
Typeable a =>
proxy a -> TypeRep
typeRep (Proxy (Resolver QUERY () Maybe) -> TypeRep)
-> Proxy (Resolver QUERY () Maybe) -> TypeRep
forall a b. (a -> b) -> a -> b
$ Proxy (Resolver QUERY () Maybe)
forall k (t :: k). Proxy t
Proxy @(Resolver QUERY () Maybe)

-- | replaces typeName (A,B) with Pair_A_B
replacePairCon :: TyCon -> TyCon
replacePairCon :: TyCon -> TyCon
replacePairCon TyCon
x | TyCon
hsPair TyCon -> TyCon -> Bool
forall a. Eq a => a -> a -> Bool
== TyCon
x = TyCon
gqlPair
  where
    hsPair :: TyCon
hsPair = TypeRep -> TyCon
typeRepTyCon (TypeRep -> TyCon) -> TypeRep -> TyCon
forall a b. (a -> b) -> a -> b
$ Proxy (Int, Int) -> TypeRep
forall k (proxy :: k -> *) (a :: k).
Typeable a =>
proxy a -> TypeRep
typeRep (Proxy (Int, Int) -> TypeRep) -> Proxy (Int, Int) -> TypeRep
forall a b. (a -> b) -> a -> b
$ Proxy (Int, Int)
forall k (t :: k). Proxy t
Proxy @(Int, Int)
    gqlPair :: TyCon
gqlPair = TypeRep -> TyCon
typeRepTyCon (TypeRep -> TyCon) -> TypeRep -> TyCon
forall a b. (a -> b) -> a -> b
$ Proxy (Pair Int Int) -> TypeRep
forall k (proxy :: k -> *) (a :: k).
Typeable a =>
proxy a -> TypeRep
typeRep (Proxy (Pair Int Int) -> TypeRep)
-> Proxy (Pair Int Int) -> TypeRep
forall a b. (a -> b) -> a -> b
$ Proxy (Pair Int Int)
forall k (t :: k). Proxy t
Proxy @(Pair Int Int)
replacePairCon TyCon
x = TyCon
x

-- Ignores Resolver name  from typeName
ignoreResolver :: (TyCon, [TypeRep]) -> [TyCon]
ignoreResolver :: (TyCon, [TypeRep]) -> [TyCon]
ignoreResolver (TyCon
con, [TypeRep]
_) | TyCon
con TyCon -> TyCon -> Bool
forall a. Eq a => a -> a -> Bool
== TyCon
resolverCon = []
ignoreResolver (TyCon
con, [TypeRep]
args) =
  TyCon
con TyCon -> [TyCon] -> [TyCon]
forall a. a -> [a] -> [a]
: (TypeRep -> [TyCon]) -> [TypeRep] -> [TyCon]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap ((TyCon, [TypeRep]) -> [TyCon]
ignoreResolver ((TyCon, [TypeRep]) -> [TyCon])
-> (TypeRep -> (TyCon, [TypeRep])) -> TypeRep -> [TyCon]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TypeRep -> (TyCon, [TypeRep])
splitTyConApp) [TypeRep]
args

__isObjectKind :: forall f a. GQLType a => f a -> Bool
__isObjectKind :: f a -> Bool
__isObjectKind f a
_ = DerivingKind -> Bool
isObject (DerivingKind -> Bool) -> DerivingKind -> Bool
forall a b. (a -> b) -> a -> b
$ Proxy (KIND a) -> DerivingKind
forall (a :: DerivingKind) (f :: DerivingKind -> *).
ToValue a =>
f a -> DerivingKind
toValue (Proxy (KIND a)
forall k (t :: k). Proxy t
Proxy @(KIND a))

-- | GraphQL type, every graphQL type should have an instance of 'GHC.Generics.Generic' and 'GQLType'.
--
--  @
--    ... deriving (Generic, GQLType)
--  @
--
-- if you want to add description
--
--  @
--       ... deriving (Generic)
--
--     instance GQLType ... where
--       description = const "your description ..."
--  @
class ToValue (KIND a) => GQLType a where
  type KIND a :: DerivingKind
  type KIND a = TYPE

  implements :: f a -> [SchemaT OUT TypeName]
  implements f a
_ = []

  description :: f a -> Maybe Text
  description f a
_ = Maybe Text
forall a. Maybe a
Nothing

  getDescriptions :: f a -> Map Text Description
  getDescriptions f a
_ = Map Text Text
forall a. Monoid a => a
mempty

  typeOptions :: f a -> GQLTypeOptions -> GQLTypeOptions
  typeOptions f a
_ = GQLTypeOptions -> GQLTypeOptions
forall a. a -> a
id

  getDirectives :: f a -> Map Text (Directives CONST)
  getDirectives f a
_ = Map Text (Directives CONST)
forall a. Monoid a => a
mempty

  getFieldContents ::
    f a ->
    Map
      FieldName
      ( Maybe (Value CONST),
        Maybe (ArgumentsDefinition CONST)
      )
  getFieldContents f a
_ = Map
  FieldName (Maybe (Value CONST), Maybe (ArgumentsDefinition CONST))
forall a. Monoid a => a
mempty

  __isEmptyType :: f a -> Bool
  __isEmptyType f a
_ = Bool
False

  __type :: f a -> TypeCategory -> TypeData
  default __type :: Typeable a => f a -> TypeCategory -> TypeData
  __type f a
proxy = f a -> (Bool -> String -> String) -> TypeCategory -> TypeData
forall a (f :: * -> *).
Typeable a =>
f a -> (Bool -> String -> String) -> TypeCategory -> TypeData
deriveTypeData f a
proxy Bool -> String -> String
typeNameModifier
    where
      GQLTypeOptions {Bool -> String -> String
typeNameModifier :: Bool -> String -> String
typeNameModifier :: GQLTypeOptions -> Bool -> String -> String
typeNameModifier} = f a -> GQLTypeOptions -> GQLTypeOptions
forall a (f :: * -> *).
GQLType a =>
f a -> GQLTypeOptions -> GQLTypeOptions
typeOptions f a
proxy GQLTypeOptions
defaultTypeOptions

instance GQLType Int where
  type KIND Int = SCALAR
  __type :: f Int -> TypeCategory -> TypeData
__type f Int
_ = TypeName -> TypeCategory -> TypeData
forall a. TypeName -> a -> TypeData
mkTypeData TypeName
"Int"

instance GQLType Double where
  type KIND Double = SCALAR
  __type :: f Double -> TypeCategory -> TypeData
__type f Double
_ = TypeName -> TypeCategory -> TypeData
forall a. TypeName -> a -> TypeData
mkTypeData TypeName
"Float"

instance GQLType Float where
  type KIND Float = SCALAR
  __type :: f Float -> TypeCategory -> TypeData
__type f Float
_ = TypeName -> TypeCategory -> TypeData
forall a. TypeName -> a -> TypeData
mkTypeData TypeName
"Float32"

instance GQLType Text where
  type KIND Text = SCALAR
  __type :: f Text -> TypeCategory -> TypeData
__type f Text
_ = TypeName -> TypeCategory -> TypeData
forall a. TypeName -> a -> TypeData
mkTypeData TypeName
"String"

instance GQLType Bool where
  type KIND Bool = SCALAR
  __type :: f Bool -> TypeCategory -> TypeData
__type f Bool
_ = TypeName -> TypeCategory -> TypeData
forall a. TypeName -> a -> TypeData
mkTypeData TypeName
"Boolean"

instance GQLType ID where
  type KIND ID = SCALAR
  __type :: f ID -> TypeCategory -> TypeData
__type f ID
_ = TypeName -> TypeCategory -> TypeData
forall a. TypeName -> a -> TypeData
mkTypeData TypeName
"ID"

-- WRAPPERS
instance GQLType ()

instance Typeable m => GQLType (Undefined m) where
  type KIND (Undefined m) = WRAPPER
  __isEmptyType :: f (Undefined m) -> Bool
__isEmptyType f (Undefined m)
_ = Bool
True

instance GQLType a => GQLType (Maybe a) where
  type KIND (Maybe a) = WRAPPER
  __type :: f (Maybe a) -> TypeCategory -> TypeData
__type f (Maybe a)
_ = ([TypeWrapper] -> [TypeWrapper]) -> TypeData -> TypeData
wrapper [TypeWrapper] -> [TypeWrapper]
forall a. Nullable a => a -> a
toNullable (TypeData -> TypeData)
-> (TypeCategory -> TypeData) -> TypeCategory -> TypeData
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Proxy a -> TypeCategory -> TypeData
forall a (f :: * -> *).
GQLType a =>
f a -> TypeCategory -> TypeData
__type (Proxy a
forall k (t :: k). Proxy t
Proxy @a)

instance GQLType a => GQLType [a] where
  type KIND [a] = WRAPPER
  __type :: f [a] -> TypeCategory -> TypeData
__type f [a]
_ = ([TypeWrapper] -> [TypeWrapper]) -> TypeData -> TypeData
wrapper [TypeWrapper] -> [TypeWrapper]
list (TypeData -> TypeData)
-> (TypeCategory -> TypeData) -> TypeCategory -> TypeData
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Proxy a -> TypeCategory -> TypeData
forall a (f :: * -> *).
GQLType a =>
f a -> TypeCategory -> TypeData
__type (Proxy a
forall k (t :: k). Proxy t
Proxy @a)

instance GQLType a => GQLType (Set a) where
  type KIND (Set a) = WRAPPER
  __type :: f (Set a) -> TypeCategory -> TypeData
__type f (Set a)
_ = Proxy [a] -> TypeCategory -> TypeData
forall a (f :: * -> *).
GQLType a =>
f a -> TypeCategory -> TypeData
__type (Proxy [a] -> TypeCategory -> TypeData)
-> Proxy [a] -> TypeCategory -> TypeData
forall a b. (a -> b) -> a -> b
$ Proxy [a]
forall k (t :: k). Proxy t
Proxy @[a]

instance GQLType a => GQLType (SubscriptionField a) where
  type KIND (SubscriptionField a) = WRAPPER
  __type :: f (SubscriptionField a) -> TypeCategory -> TypeData
__type f (SubscriptionField a)
_ = Proxy a -> TypeCategory -> TypeData
forall a (f :: * -> *).
GQLType a =>
f a -> TypeCategory -> TypeData
__type (Proxy a -> TypeCategory -> TypeData)
-> Proxy a -> TypeCategory -> TypeData
forall a b. (a -> b) -> a -> b
$ Proxy a
forall k (t :: k). Proxy t
Proxy @a

instance (Typeable a, Typeable b, GQLType a, GQLType b) => GQLType (Pair a b)

-- Manual
instance GQLType b => GQLType (a -> b) where
  type KIND (a -> b) = CUSTOM
  __type :: f (a -> b) -> TypeCategory -> TypeData
__type f (a -> b)
_ = Proxy b -> TypeCategory -> TypeData
forall a (f :: * -> *).
GQLType a =>
f a -> TypeCategory -> TypeData
__type (Proxy b -> TypeCategory -> TypeData)
-> Proxy b -> TypeCategory -> TypeData
forall a b. (a -> b) -> a -> b
$ Proxy b
forall k (t :: k). Proxy t
Proxy @b

instance (GQLType k, GQLType v, Typeable k, Typeable v) => GQLType (Map k v) where
  type KIND (Map k v) = CUSTOM
  __type :: f (Map k v) -> TypeCategory -> TypeData
__type f (Map k v)
_ = Proxy [Pair k v] -> TypeCategory -> TypeData
forall a (f :: * -> *).
GQLType a =>
f a -> TypeCategory -> TypeData
__type (Proxy [Pair k v] -> TypeCategory -> TypeData)
-> Proxy [Pair k v] -> TypeCategory -> TypeData
forall a b. (a -> b) -> a -> b
$ Proxy [Pair k v]
forall k (t :: k). Proxy t
Proxy @[Pair k v]

instance GQLType a => GQLType (Resolver o e m a) where
  type KIND (Resolver o e m a) = CUSTOM
  __type :: f (Resolver o e m a) -> TypeCategory -> TypeData
__type f (Resolver o e m a)
_ = Proxy a -> TypeCategory -> TypeData
forall a (f :: * -> *).
GQLType a =>
f a -> TypeCategory -> TypeData
__type (Proxy a -> TypeCategory -> TypeData)
-> Proxy a -> TypeCategory -> TypeData
forall a b. (a -> b) -> a -> b
$ Proxy a
forall k (t :: k). Proxy t
Proxy @a

instance (Typeable a, Typeable b, GQLType a, GQLType b) => GQLType (a, b) where
  type KIND (a, b) = CUSTOM
  __type :: f (a, b) -> TypeCategory -> TypeData
__type f (a, b)
_ = Proxy (Pair a b) -> TypeCategory -> TypeData
forall a (f :: * -> *).
GQLType a =>
f a -> TypeCategory -> TypeData
__type (Proxy (Pair a b) -> TypeCategory -> TypeData)
-> Proxy (Pair a b) -> TypeCategory -> TypeData
forall a b. (a -> b) -> a -> b
$ Proxy (Pair a b)
forall k (t :: k). Proxy t
Proxy @(Pair a b)