{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
{-# OPTIONS_GHC -fno-warn-redundant-constraints #-}
module Data.ProtoLens.Service.Types
( Service (..)
, HasAllMethods
, HasMethodImpl (..)
, HasMethod
, StreamingType (..)
) where
import qualified Data.ByteString as B
import Data.Kind (Constraint, Type)
import Data.ProtoLens.Message (Message)
import Data.Proxy (Proxy(..))
import GHC.TypeLits
class HasAllMethods s (ms :: [Symbol])
instance HasAllMethods s '[]
instance (HasAllMethods s ms, HasMethodImpl s m) => HasAllMethods s (m ': ms)
class ( KnownSymbol (ServiceName s)
, KnownSymbol (ServicePackage s)
, HasAllMethods s (ServiceMethods s)
) => Service s where
type ServiceName s :: Symbol
type ServicePackage s :: Symbol
type ServiceMethods s :: [Symbol]
packedServiceDescriptor :: Proxy s -> B.ByteString
data StreamingType
= NonStreaming
| ClientStreaming
| ServerStreaming
| BiDiStreaming
deriving (StreamingType -> StreamingType -> Bool
(StreamingType -> StreamingType -> Bool)
-> (StreamingType -> StreamingType -> Bool) -> Eq StreamingType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: StreamingType -> StreamingType -> Bool
== :: StreamingType -> StreamingType -> Bool
$c/= :: StreamingType -> StreamingType -> Bool
/= :: StreamingType -> StreamingType -> Bool
Eq, Eq StreamingType
Eq StreamingType =>
(StreamingType -> StreamingType -> Ordering)
-> (StreamingType -> StreamingType -> Bool)
-> (StreamingType -> StreamingType -> Bool)
-> (StreamingType -> StreamingType -> Bool)
-> (StreamingType -> StreamingType -> Bool)
-> (StreamingType -> StreamingType -> StreamingType)
-> (StreamingType -> StreamingType -> StreamingType)
-> Ord StreamingType
StreamingType -> StreamingType -> Bool
StreamingType -> StreamingType -> Ordering
StreamingType -> StreamingType -> StreamingType
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: StreamingType -> StreamingType -> Ordering
compare :: StreamingType -> StreamingType -> Ordering
$c< :: StreamingType -> StreamingType -> Bool
< :: StreamingType -> StreamingType -> Bool
$c<= :: StreamingType -> StreamingType -> Bool
<= :: StreamingType -> StreamingType -> Bool
$c> :: StreamingType -> StreamingType -> Bool
> :: StreamingType -> StreamingType -> Bool
$c>= :: StreamingType -> StreamingType -> Bool
>= :: StreamingType -> StreamingType -> Bool
$cmax :: StreamingType -> StreamingType -> StreamingType
max :: StreamingType -> StreamingType -> StreamingType
$cmin :: StreamingType -> StreamingType -> StreamingType
min :: StreamingType -> StreamingType -> StreamingType
Ord, Int -> StreamingType
StreamingType -> Int
StreamingType -> [StreamingType]
StreamingType -> StreamingType
StreamingType -> StreamingType -> [StreamingType]
StreamingType -> StreamingType -> StreamingType -> [StreamingType]
(StreamingType -> StreamingType)
-> (StreamingType -> StreamingType)
-> (Int -> StreamingType)
-> (StreamingType -> Int)
-> (StreamingType -> [StreamingType])
-> (StreamingType -> StreamingType -> [StreamingType])
-> (StreamingType -> StreamingType -> [StreamingType])
-> (StreamingType
-> StreamingType -> StreamingType -> [StreamingType])
-> Enum StreamingType
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: StreamingType -> StreamingType
succ :: StreamingType -> StreamingType
$cpred :: StreamingType -> StreamingType
pred :: StreamingType -> StreamingType
$ctoEnum :: Int -> StreamingType
toEnum :: Int -> StreamingType
$cfromEnum :: StreamingType -> Int
fromEnum :: StreamingType -> Int
$cenumFrom :: StreamingType -> [StreamingType]
enumFrom :: StreamingType -> [StreamingType]
$cenumFromThen :: StreamingType -> StreamingType -> [StreamingType]
enumFromThen :: StreamingType -> StreamingType -> [StreamingType]
$cenumFromTo :: StreamingType -> StreamingType -> [StreamingType]
enumFromTo :: StreamingType -> StreamingType -> [StreamingType]
$cenumFromThenTo :: StreamingType -> StreamingType -> StreamingType -> [StreamingType]
enumFromThenTo :: StreamingType -> StreamingType -> StreamingType -> [StreamingType]
Enum, StreamingType
StreamingType -> StreamingType -> Bounded StreamingType
forall a. a -> a -> Bounded a
$cminBound :: StreamingType
minBound :: StreamingType
$cmaxBound :: StreamingType
maxBound :: StreamingType
Bounded, ReadPrec [StreamingType]
ReadPrec StreamingType
Int -> ReadS StreamingType
ReadS [StreamingType]
(Int -> ReadS StreamingType)
-> ReadS [StreamingType]
-> ReadPrec StreamingType
-> ReadPrec [StreamingType]
-> Read StreamingType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS StreamingType
readsPrec :: Int -> ReadS StreamingType
$creadList :: ReadS [StreamingType]
readList :: ReadS [StreamingType]
$creadPrec :: ReadPrec StreamingType
readPrec :: ReadPrec StreamingType
$creadListPrec :: ReadPrec [StreamingType]
readListPrec :: ReadPrec [StreamingType]
Read, Int -> StreamingType -> ShowS
[StreamingType] -> ShowS
StreamingType -> String
(Int -> StreamingType -> ShowS)
-> (StreamingType -> String)
-> ([StreamingType] -> ShowS)
-> Show StreamingType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> StreamingType -> ShowS
showsPrec :: Int -> StreamingType -> ShowS
$cshow :: StreamingType -> String
show :: StreamingType -> String
$cshowList :: [StreamingType] -> ShowS
showList :: [StreamingType] -> ShowS
Show)
class ( KnownSymbol m
, KnownSymbol (MethodName s m)
, Service s
, Message (MethodInput s m)
, Message (MethodOutput s m)
) => HasMethodImpl s (m :: Symbol) where
type MethodName s m :: Symbol
type MethodInput s m :: Type
type MethodOutput s m :: Type
type MethodStreamingType s m :: StreamingType
type HasMethod s m =
( RequireHasMethod s m (ListContains m (ServiceMethods s))
, HasMethodImpl s m
)
type family RequireHasMethod s (m :: Symbol) (h :: Bool) :: Constraint where
RequireHasMethod s m 'False = TypeError
( 'Text "No method "
':<>: 'ShowType m
':<>: 'Text " available for service '"
':<>: 'ShowType s
':<>: 'Text "'."
':$$: 'Text "Available methods are: "
':<>: ShowList (ServiceMethods s)
)
RequireHasMethod s m 'True = ()
type family ListContains (n :: k) (hs :: [k]) :: Bool where
ListContains n '[] = 'False
ListContains n (n ': hs) = 'True
ListContains n (x ': hs) = ListContains n hs
type family ShowList (ls :: [k]) :: ErrorMessage where
ShowList '[] = 'Text ""
ShowList '[x] = 'ShowType x
ShowList (x ': xs) =
'ShowType x ':<>: 'Text ", " ':<>: ShowList xs