{-# language ConstraintKinds #-}
{-# language DataKinds #-}
{-# language ExistentialQuantification #-}
{-# language FlexibleInstances #-}
{-# language GADTs #-}
{-# language MultiParamTypeClasses #-}
{-# language OverloadedStrings #-}
{-# language PolyKinds #-}
{-# language ScopedTypeVariables #-}
{-# language TypeApplications #-}
{-# language TypeFamilies #-}
{-# language TypeOperators #-}
{-# language UndecidableInstances #-}
module Mu.Rpc (
Package', Package(..)
, Service', Service(..), Object, Union
, Method', Method(..), ObjectField
, LookupService, LookupMethod
, TypeRef(..), Argument', Argument(..), Return(..)
, TyInfo(..), RpcInfo(..), ReflectRpcInfo(..)
) where
import Data.Kind
import Data.Text (Text)
import qualified Data.Text as T
import GHC.TypeLits
import qualified Language.Haskell.TH as TH
import Network.HTTP.Types.Header
import Type.Reflection
import Mu.Schema
import Mu.Schema.Registry
type Package' = Package Symbol Symbol Symbol (TypeRef Symbol)
type Service' = Service Symbol Symbol Symbol (TypeRef Symbol)
type Method' = Method Symbol Symbol Symbol (TypeRef Symbol)
type Argument' = Argument Symbol Symbol (TypeRef Symbol)
data Package serviceName methodName argName tyRef
= Package (Maybe serviceName)
[Service serviceName methodName argName tyRef]
data Service serviceName methodName argName tyRef
= Service serviceName
[Method serviceName methodName argName tyRef]
| OneOf serviceName [serviceName]
data Method serviceName methodName argName tyRef
= Method methodName
[Argument serviceName argName tyRef]
(Return serviceName tyRef)
type Object = 'Service
type Union = 'OneOf
type ObjectField = 'Method
type family LookupService (ss :: [Service snm mnm anm tr]) (s :: snm)
:: Service snm mnm anm tr where
LookupService '[] s = TypeError ('Text "could not find method " ':<>: 'ShowType s)
LookupService ('Service s ms ': ss) s = 'Service s ms
LookupService ('OneOf s ms ': ss) s = 'OneOf s ms
LookupService (other ': ss) s = LookupService ss s
type family LookupMethod (s :: [Method snm mnm anm tr]) (m :: mnm)
:: Method snm mnm anm tr where
LookupMethod '[] m = TypeError ('Text "could not find method " ':<>: 'ShowType m)
LookupMethod ('Method m args r ': ms) m = 'Method m args r
LookupMethod (other ': ms) m = LookupMethod ms m
data TypeRef serviceName where
PrimitiveRef :: Type -> TypeRef serviceName
ObjectRef :: serviceName -> TypeRef serviceName
SchemaRef :: Schema typeName fieldName -> typeName -> TypeRef serviceName
RegistryRef :: Registry -> Type -> Nat -> TypeRef serviceName
THRef :: TH.Type -> TypeRef serviceName
ListRef :: TypeRef serviceName -> TypeRef serviceName
OptionalRef :: TypeRef serviceName -> TypeRef serviceName
instance Show (TypeRef s) where
show :: TypeRef s -> String
show TypeRef s
_ = String
"ty"
data Argument serviceName argName tyRef where
ArgSingle :: Maybe argName
-> tyRef
-> Argument serviceName argName tyRef
ArgStream :: Maybe argName
-> tyRef
-> Argument serviceName argName tyRef
data Return serviceName tyRef where
RetNothing :: Return serviceName tyRef
RetSingle :: tyRef -> Return serviceName tyRef
RetStream :: tyRef -> Return serviceName tyRef
RetThrows :: tyRef -> tyRef -> Return serviceName tyRef
data RpcInfo i
= NoRpcInfo
| RpcInfo { RpcInfo i -> Package Text Text Text TyInfo
packageInfo :: Package Text Text Text TyInfo
, RpcInfo i -> Service Text Text Text TyInfo
serviceInfo :: Service Text Text Text TyInfo
, RpcInfo i -> Maybe (Method Text Text Text TyInfo)
methodInfo :: Maybe (Method Text Text Text TyInfo)
, :: RequestHeaders
, :: i
}
data TyInfo
= TyList TyInfo
| TyOption TyInfo
| TyTy Text
deriving (Int -> TyInfo -> ShowS
[TyInfo] -> ShowS
TyInfo -> String
(Int -> TyInfo -> ShowS)
-> (TyInfo -> String) -> ([TyInfo] -> ShowS) -> Show TyInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TyInfo] -> ShowS
$cshowList :: [TyInfo] -> ShowS
show :: TyInfo -> String
$cshow :: TyInfo -> String
showsPrec :: Int -> TyInfo -> ShowS
$cshowsPrec :: Int -> TyInfo -> ShowS
Show, TyInfo -> TyInfo -> Bool
(TyInfo -> TyInfo -> Bool)
-> (TyInfo -> TyInfo -> Bool) -> Eq TyInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TyInfo -> TyInfo -> Bool
$c/= :: TyInfo -> TyInfo -> Bool
== :: TyInfo -> TyInfo -> Bool
$c== :: TyInfo -> TyInfo -> Bool
Eq)
instance Show (RpcInfo i) where
show :: RpcInfo i -> String
show RpcInfo i
NoRpcInfo
= String
"<no info>"
show (RpcInfo (Package Maybe Text
p [Service Text Text Text TyInfo]
_) Service Text Text Text TyInfo
s Maybe (Method Text Text Text TyInfo)
m RequestHeaders
_ i
_)
= Text -> String
T.unpack (Text -> String) -> Text -> String
forall a b. (a -> b) -> a -> b
$ Maybe Text -> Text -> Text
forall a. (Semigroup a, IsString a) => Maybe a -> a -> a
showPkg Maybe Text
p (Maybe (Method Text Text Text TyInfo) -> Text -> Text
forall k a (serviceName :: k) argName tyRef.
(Semigroup a, IsString a) =>
Maybe (Method serviceName a argName tyRef) -> a -> a
showMth Maybe (Method Text Text Text TyInfo)
m (Service Text Text Text TyInfo -> Text
forall p methodName argName tyRef.
Service p methodName argName tyRef -> p
showSvc Service Text Text Text TyInfo
s))
where
showPkg :: Maybe a -> a -> a
showPkg Maybe a
Nothing = a -> a
forall a. a -> a
id
showPkg (Just a
pkg) = ((a
pkg a -> a -> a
forall a. Semigroup a => a -> a -> a
<> a
":") a -> a -> a
forall a. Semigroup a => a -> a -> a
<>)
showMth :: Maybe (Method serviceName a argName tyRef) -> a -> a
showMth Maybe (Method serviceName a argName tyRef)
Nothing = a -> a
forall a. a -> a
id
showMth (Just (Method a
mt [Argument serviceName argName tyRef]
_ Return serviceName tyRef
_)) = (a -> a -> a
forall a. Semigroup a => a -> a -> a
<> (a
":" a -> a -> a
forall a. Semigroup a => a -> a -> a
<> a
mt))
showSvc :: Service p methodName argName tyRef -> p
showSvc (Service p
sv [Method p methodName argName tyRef]
_) = p
sv
showSvc (OneOf p
sv [p]
_) = p
sv
class ReflectRpcInfo (p :: Package') (s :: Service') (m :: Method') where
reflectRpcInfo :: Proxy p -> Proxy s -> Proxy m -> RequestHeaders -> i -> RpcInfo i
class ReflectService (s :: Service') where
reflectService :: Proxy s -> Service Text Text Text TyInfo
class ReflectMethod (m :: Method') where
reflectMethod :: Proxy m -> Method Text Text Text TyInfo
class ReflectArg (arg :: Argument') where
reflectArg :: Proxy arg -> Argument Text Text TyInfo
class ReflectReturn (r :: Return Symbol (TypeRef Symbol)) where
reflectReturn :: Proxy r -> Return Text TyInfo
class ReflectTyRef (r :: TypeRef Symbol) where
reflectTyRef :: Proxy r -> TyInfo
class KnownMaySymbol (m :: Maybe Symbol) where
maySymbolVal :: Proxy m -> Maybe Text
instance KnownMaySymbol 'Nothing where
maySymbolVal :: Proxy 'Nothing -> Maybe Text
maySymbolVal Proxy 'Nothing
_ = Maybe Text
forall a. Maybe a
Nothing
instance (KnownSymbol s) => KnownMaySymbol ('Just s) where
maySymbolVal :: Proxy ('Just s) -> Maybe Text
maySymbolVal Proxy ('Just s)
_ = Text -> Maybe Text
forall a. a -> Maybe a
Just (Text -> Maybe Text) -> Text -> Maybe Text
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ Proxy s -> String
forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> String
symbolVal (Proxy s
forall k (t :: k). Proxy t
Proxy @s)
class KnownSymbols (m :: [Symbol]) where
symbolsVal :: Proxy m -> [Text]
instance KnownSymbols '[] where
symbolsVal :: Proxy '[] -> [Text]
symbolsVal Proxy '[]
_ = []
instance (KnownSymbol s, KnownSymbols ss) => KnownSymbols (s ': ss) where
symbolsVal :: Proxy (s : ss) -> [Text]
symbolsVal Proxy (s : ss)
_ = String -> Text
T.pack (Proxy s -> String
forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> String
symbolVal (Proxy s
forall k (t :: k). Proxy t
Proxy @s)) Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
: Proxy ss -> [Text]
forall (m :: [Symbol]). KnownSymbols m => Proxy m -> [Text]
symbolsVal (Proxy ss
forall k (t :: k). Proxy t
Proxy @ss)
class ReflectServices (ss :: [Service']) where
reflectServices :: Proxy ss -> [Service Text Text Text TyInfo]
instance ReflectServices '[] where
reflectServices :: Proxy '[] -> [Service Text Text Text TyInfo]
reflectServices Proxy '[]
_ = []
instance (ReflectService s, ReflectServices ss)
=> ReflectServices (s ': ss) where
reflectServices :: Proxy (s : ss) -> [Service Text Text Text TyInfo]
reflectServices Proxy (s : ss)
_ = Proxy s -> Service Text Text Text TyInfo
forall (s :: Service').
ReflectService s =>
Proxy s -> Service Text Text Text TyInfo
reflectService (Proxy s
forall k (t :: k). Proxy t
Proxy @s) Service Text Text Text TyInfo
-> [Service Text Text Text TyInfo]
-> [Service Text Text Text TyInfo]
forall a. a -> [a] -> [a]
: Proxy ss -> [Service Text Text Text TyInfo]
forall (ss :: [Service']).
ReflectServices ss =>
Proxy ss -> [Service Text Text Text TyInfo]
reflectServices (Proxy ss
forall k (t :: k). Proxy t
Proxy @ss)
class ReflectMethods (ms :: [Method']) where
reflectMethods :: Proxy ms -> [Method Text Text Text TyInfo]
instance ReflectMethods '[] where
reflectMethods :: Proxy '[] -> [Method Text Text Text TyInfo]
reflectMethods Proxy '[]
_ = []
instance (ReflectMethod m, ReflectMethods ms)
=> ReflectMethods (m ': ms) where
reflectMethods :: Proxy (m : ms) -> [Method Text Text Text TyInfo]
reflectMethods Proxy (m : ms)
_ = Proxy m -> Method Text Text Text TyInfo
forall (m :: Method').
ReflectMethod m =>
Proxy m -> Method Text Text Text TyInfo
reflectMethod (Proxy m
forall k (t :: k). Proxy t
Proxy @m) Method Text Text Text TyInfo
-> [Method Text Text Text TyInfo] -> [Method Text Text Text TyInfo]
forall a. a -> [a] -> [a]
: Proxy ms -> [Method Text Text Text TyInfo]
forall (ms :: [Method']).
ReflectMethods ms =>
Proxy ms -> [Method Text Text Text TyInfo]
reflectMethods (Proxy ms
forall k (t :: k). Proxy t
Proxy @ms)
class ReflectArgs (ms :: [Argument']) where
reflectArgs :: Proxy ms -> [Argument Text Text TyInfo]
instance ReflectArgs '[] where
reflectArgs :: Proxy '[] -> [Argument Text Text TyInfo]
reflectArgs Proxy '[]
_ = []
instance (ReflectArg m, ReflectArgs ms)
=> ReflectArgs (m ': ms) where
reflectArgs :: Proxy (m : ms) -> [Argument Text Text TyInfo]
reflectArgs Proxy (m : ms)
_ = Proxy m -> Argument Text Text TyInfo
forall (arg :: Argument').
ReflectArg arg =>
Proxy arg -> Argument Text Text TyInfo
reflectArg (Proxy m
forall k (t :: k). Proxy t
Proxy @m) Argument Text Text TyInfo
-> [Argument Text Text TyInfo] -> [Argument Text Text TyInfo]
forall a. a -> [a] -> [a]
: Proxy ms -> [Argument Text Text TyInfo]
forall (ms :: [Argument']).
ReflectArgs ms =>
Proxy ms -> [Argument Text Text TyInfo]
reflectArgs (Proxy ms
forall k (t :: k). Proxy t
Proxy @ms)
instance (KnownMaySymbol pname, ReflectServices ss, ReflectService s, ReflectMethod m)
=> ReflectRpcInfo ('Package pname ss) s m where
reflectRpcInfo :: Proxy ('Package pname ss)
-> Proxy s -> Proxy m -> RequestHeaders -> i -> RpcInfo i
reflectRpcInfo Proxy ('Package pname ss)
_ Proxy s
ps Proxy m
pm RequestHeaders
req i
extra
= Package Text Text Text TyInfo
-> Service Text Text Text TyInfo
-> Maybe (Method Text Text Text TyInfo)
-> RequestHeaders
-> i
-> RpcInfo i
forall i.
Package Text Text Text TyInfo
-> Service Text Text Text TyInfo
-> Maybe (Method Text Text Text TyInfo)
-> RequestHeaders
-> i
-> RpcInfo i
RpcInfo (Maybe Text
-> [Service Text Text Text TyInfo] -> Package Text Text Text TyInfo
forall serviceName methodName argName tyRef.
Maybe serviceName
-> [Service serviceName methodName argName tyRef]
-> Package serviceName methodName argName tyRef
Package (Proxy pname -> Maybe Text
forall (m :: Maybe Symbol).
KnownMaySymbol m =>
Proxy m -> Maybe Text
maySymbolVal (Proxy pname
forall k (t :: k). Proxy t
Proxy @pname))
(Proxy ss -> [Service Text Text Text TyInfo]
forall (ss :: [Service']).
ReflectServices ss =>
Proxy ss -> [Service Text Text Text TyInfo]
reflectServices (Proxy ss
forall k (t :: k). Proxy t
Proxy @ss)))
(Proxy s -> Service Text Text Text TyInfo
forall (s :: Service').
ReflectService s =>
Proxy s -> Service Text Text Text TyInfo
reflectService Proxy s
ps) (Method Text Text Text TyInfo
-> Maybe (Method Text Text Text TyInfo)
forall a. a -> Maybe a
Just (Proxy m -> Method Text Text Text TyInfo
forall (m :: Method').
ReflectMethod m =>
Proxy m -> Method Text Text Text TyInfo
reflectMethod Proxy m
pm)) RequestHeaders
req i
extra
instance (KnownSymbol sname, ReflectMethods ms)
=> ReflectService ('Service sname ms) where
reflectService :: Proxy ('Service sname ms) -> Service Text Text Text TyInfo
reflectService Proxy ('Service sname ms)
_
= Text
-> [Method Text Text Text TyInfo] -> Service Text Text Text TyInfo
forall serviceName methodName argName tyRef.
serviceName
-> [Method serviceName methodName argName tyRef]
-> Service serviceName methodName argName tyRef
Service (String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ Proxy sname -> String
forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> String
symbolVal (Proxy sname
forall k (t :: k). Proxy t
Proxy @sname))
(Proxy ms -> [Method Text Text Text TyInfo]
forall (ms :: [Method']).
ReflectMethods ms =>
Proxy ms -> [Method Text Text Text TyInfo]
reflectMethods (Proxy ms
forall k (t :: k). Proxy t
Proxy @ms))
instance (KnownSymbol sname, KnownSymbols elts)
=> ReflectService ('OneOf sname elts) where
reflectService :: Proxy ('OneOf sname elts) -> Service Text Text Text TyInfo
reflectService Proxy ('OneOf sname elts)
_
= Text -> [Text] -> Service Text Text Text TyInfo
forall serviceName methodName argName tyRef.
serviceName
-> [serviceName] -> Service serviceName methodName argName tyRef
OneOf (String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ Proxy sname -> String
forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> String
symbolVal (Proxy sname
forall k (t :: k). Proxy t
Proxy @sname))
(Proxy elts -> [Text]
forall (m :: [Symbol]). KnownSymbols m => Proxy m -> [Text]
symbolsVal (Proxy elts
forall k (t :: k). Proxy t
Proxy @elts))
instance (KnownSymbol mname, ReflectArgs args, ReflectReturn r)
=> ReflectMethod ('Method mname args r) where
reflectMethod :: Proxy ('Method mname args r) -> Method Text Text Text TyInfo
reflectMethod Proxy ('Method mname args r)
_
= Text
-> [Argument Text Text TyInfo]
-> Return Text TyInfo
-> Method Text Text Text TyInfo
forall k (serviceName :: k) methodName argName tyRef.
methodName
-> [Argument serviceName argName tyRef]
-> Return serviceName tyRef
-> Method serviceName methodName argName tyRef
Method (String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ Proxy mname -> String
forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> String
symbolVal (Proxy mname
forall k (t :: k). Proxy t
Proxy @mname))
(Proxy args -> [Argument Text Text TyInfo]
forall (ms :: [Argument']).
ReflectArgs ms =>
Proxy ms -> [Argument Text Text TyInfo]
reflectArgs (Proxy args
forall k (t :: k). Proxy t
Proxy @args)) (Proxy r -> Return Text TyInfo
forall (r :: Return Symbol (TypeRef Symbol)).
ReflectReturn r =>
Proxy r -> Return Text TyInfo
reflectReturn (Proxy r
forall k (t :: k). Proxy t
Proxy @r))
instance (KnownMaySymbol aname, ReflectTyRef t)
=> ReflectArg ('ArgSingle aname t) where
reflectArg :: Proxy ('ArgSingle aname t) -> Argument Text Text TyInfo
reflectArg Proxy ('ArgSingle aname t)
_
= Maybe Text -> TyInfo -> Argument Text Text TyInfo
forall k argName tyRef (serviceName :: k).
Maybe argName -> tyRef -> Argument serviceName argName tyRef
ArgSingle (Proxy aname -> Maybe Text
forall (m :: Maybe Symbol).
KnownMaySymbol m =>
Proxy m -> Maybe Text
maySymbolVal (Proxy aname
forall k (t :: k). Proxy t
Proxy @aname)) (Proxy t -> TyInfo
forall (r :: TypeRef Symbol). ReflectTyRef r => Proxy r -> TyInfo
reflectTyRef (Proxy t
forall k (t :: k). Proxy t
Proxy @t))
instance (KnownMaySymbol aname, ReflectTyRef t)
=> ReflectArg ('ArgStream aname t) where
reflectArg :: Proxy ('ArgStream aname t) -> Argument Text Text TyInfo
reflectArg Proxy ('ArgStream aname t)
_
= Maybe Text -> TyInfo -> Argument Text Text TyInfo
forall k argName tyRef (serviceName :: k).
Maybe argName -> tyRef -> Argument serviceName argName tyRef
ArgStream (Proxy aname -> Maybe Text
forall (m :: Maybe Symbol).
KnownMaySymbol m =>
Proxy m -> Maybe Text
maySymbolVal (Proxy aname
forall k (t :: k). Proxy t
Proxy @aname)) (Proxy t -> TyInfo
forall (r :: TypeRef Symbol). ReflectTyRef r => Proxy r -> TyInfo
reflectTyRef (Proxy t
forall k (t :: k). Proxy t
Proxy @t))
instance ReflectReturn 'RetNothing where
reflectReturn :: Proxy 'RetNothing -> Return Text TyInfo
reflectReturn Proxy 'RetNothing
_ = Return Text TyInfo
forall k (serviceName :: k) tyRef. Return serviceName tyRef
RetNothing
instance (ReflectTyRef t)
=> ReflectReturn ('RetSingle t) where
reflectReturn :: Proxy ('RetSingle t) -> Return Text TyInfo
reflectReturn Proxy ('RetSingle t)
_ = TyInfo -> Return Text TyInfo
forall k tyRef (serviceName :: k).
tyRef -> Return serviceName tyRef
RetSingle (Proxy t -> TyInfo
forall (r :: TypeRef Symbol). ReflectTyRef r => Proxy r -> TyInfo
reflectTyRef (Proxy t
forall k (t :: k). Proxy t
Proxy @t))
instance (ReflectTyRef t)
=> ReflectReturn ('RetStream t) where
reflectReturn :: Proxy ('RetStream t) -> Return Text TyInfo
reflectReturn Proxy ('RetStream t)
_ = TyInfo -> Return Text TyInfo
forall k tyRef (serviceName :: k).
tyRef -> Return serviceName tyRef
RetStream (Proxy t -> TyInfo
forall (r :: TypeRef Symbol). ReflectTyRef r => Proxy r -> TyInfo
reflectTyRef (Proxy t
forall k (t :: k). Proxy t
Proxy @t))
instance (ReflectTyRef e, ReflectTyRef t)
=> ReflectReturn ('RetThrows e t) where
reflectReturn :: Proxy ('RetThrows e t) -> Return Text TyInfo
reflectReturn Proxy ('RetThrows e t)
_ = TyInfo -> TyInfo -> Return Text TyInfo
forall k tyRef (serviceName :: k).
tyRef -> tyRef -> Return serviceName tyRef
RetThrows (Proxy e -> TyInfo
forall (r :: TypeRef Symbol). ReflectTyRef r => Proxy r -> TyInfo
reflectTyRef (Proxy e
forall k (t :: k). Proxy t
Proxy @e))
(Proxy t -> TyInfo
forall (r :: TypeRef Symbol). ReflectTyRef r => Proxy r -> TyInfo
reflectTyRef (Proxy t
forall k (t :: k). Proxy t
Proxy @t))
instance ReflectTyRef t => ReflectTyRef ('ListRef t) where
reflectTyRef :: Proxy ('ListRef t) -> TyInfo
reflectTyRef Proxy ('ListRef t)
_ = TyInfo -> TyInfo
TyList (Proxy t -> TyInfo
forall (r :: TypeRef Symbol). ReflectTyRef r => Proxy r -> TyInfo
reflectTyRef (Proxy t
forall k (t :: k). Proxy t
Proxy @t))
instance ReflectTyRef t => ReflectTyRef ('OptionalRef t) where
reflectTyRef :: Proxy ('OptionalRef t) -> TyInfo
reflectTyRef Proxy ('OptionalRef t)
_ = TyInfo -> TyInfo
TyOption (Proxy t -> TyInfo
forall (r :: TypeRef Symbol). ReflectTyRef r => Proxy r -> TyInfo
reflectTyRef (Proxy t
forall k (t :: k). Proxy t
Proxy @t))
instance Typeable t => ReflectTyRef ('PrimitiveRef t) where
reflectTyRef :: Proxy ('PrimitiveRef t) -> TyInfo
reflectTyRef Proxy ('PrimitiveRef t)
_ = Text -> TyInfo
TyTy (String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ TypeRep t -> String
forall a. Show a => a -> String
show (TypeRep t -> String) -> TypeRep t -> String
forall a b. (a -> b) -> a -> b
$ Typeable t => TypeRep t
forall k (a :: k). Typeable a => TypeRep a
typeRep @t)
instance KnownSymbol s => ReflectTyRef ('ObjectRef s) where
reflectTyRef :: Proxy ('ObjectRef s) -> TyInfo
reflectTyRef Proxy ('ObjectRef s)
_ = Text -> TyInfo
TyTy (String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ Proxy s -> String
forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> String
symbolVal (Proxy s -> String) -> Proxy s -> String
forall a b. (a -> b) -> a -> b
$ Proxy s
forall k (t :: k). Proxy t
Proxy @s)
instance KnownSymbol s => ReflectTyRef ('SchemaRef sch s) where
reflectTyRef :: Proxy ('SchemaRef sch s) -> TyInfo
reflectTyRef Proxy ('SchemaRef sch s)
_ = Text -> TyInfo
TyTy (String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ Proxy s -> String
forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> String
symbolVal (Proxy s -> String) -> Proxy s -> String
forall a b. (a -> b) -> a -> b
$ Proxy s
forall k (t :: k). Proxy t
Proxy @s)
instance Typeable t => ReflectTyRef ('RegistryRef r t n) where
reflectTyRef :: Proxy ('RegistryRef r t n) -> TyInfo
reflectTyRef Proxy ('RegistryRef r t n)
_ = Text -> TyInfo
TyTy (String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ TypeRep t -> String
forall a. Show a => a -> String
show (TypeRep t -> String) -> TypeRep t -> String
forall a b. (a -> b) -> a -> b
$ Typeable t => TypeRep t
forall k (a :: k). Typeable a => TypeRep a
typeRep @t)