{-# 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 Data.Kind (Constraint)
import Data.ProtoLens.Message (Message)
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]
data StreamingType
= NonStreaming
| ClientStreaming
| ServerStreaming
| BiDiStreaming
deriving (Eq, Ord, Enum, Bounded, Read, 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 MethodOutput s m :: *
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