wire-api-federation-0.1.0: The Wire server-to-server API for federation
Safe HaskellSafe-Inferred
LanguageGHC2021

Wire.API.Federation.API

Contents

Synopsis

Documentation

type family FedApi (comp :: Component) = (api :: Type) | api -> comp Source #

Instances

Instances details
type FedApi 'Brig Source # 
Instance details

Defined in Wire.API.Federation.API

type FedApi 'Cargohold Source # 
Instance details

Defined in Wire.API.Federation.API

type FedApi 'Galley Source # 
Instance details

Defined in Wire.API.Federation.API

type HasFedEndpoint comp api name = HasUnsafeFedEndpoint comp api name Source #

type HasUnsafeFedEndpoint comp api name = 'Just api ~ LookupEndpoint (FedApi comp) name Source #

Like HasFedEndpoint, but doesn't propagate a CallsFed constraint. Useful for tests, but unsafe in the sense that incorrect usage will allow you to forget about some federated calls.

class FederationMonad (fedM :: Component -> Type -> Type) where Source #

Methods

fedClientWithProxy :: forall (comp :: Component) name api. (HasClient (fedM comp) api, HasFedEndpoint comp api name, KnownComponent comp, IsNamed name, Typeable (Client (fedM comp) api)) => Proxy name -> Proxy api -> Proxy (fedM comp) -> Client (fedM comp) api Source #

Instances

Instances details
FederationMonad FederatorClient Source # 
Instance details

Defined in Wire.API.Federation.API

Methods

fedClientWithProxy :: forall {k} (comp :: Component) (name :: k) api. (HasClient (FederatorClient comp) api, HasFedEndpoint comp api name, KnownComponent comp, IsNamed name, Typeable (Client (FederatorClient comp) api)) => Proxy name -> Proxy api -> Proxy (FederatorClient comp) -> Client (FederatorClient comp) api Source #

class IsNamed (name :: k) where Source #

Methods

nameVal' :: Text Source #

Instances

Instances details
KnownSymbol name => IsNamed (name :: Symbol) Source # 
Instance details

Defined in Wire.API.Federation.API

Methods

nameVal' :: Text Source #

(IsNamed name, SingI v) => IsNamed (Versioned v name :: Type) Source # 
Instance details

Defined in Wire.API.Federation.API

Methods

nameVal' :: Text Source #

nameVal :: forall {k} (name :: k). IsNamed name => Text Source #

fedClient :: forall (comp :: Component) name fedM (showcomp :: Symbol) api x. (AddAnnotation 'Remote showcomp (FedPath name) x, showcomp ~ ShowComponent comp, HasFedEndpoint comp api name, HasClient (fedM comp) api, KnownComponent comp, IsNamed name, FederationMonad fedM, Typeable (Client (fedM comp) api)) => Client (fedM comp) api Source #

Return a client for a named endpoint.

This function introduces an AddAnnotation constraint, which is automatically solved by the transitive-anns plugin, and pushes the resulting information around in a side-channel. See the documentation at exposeAnnotations for a better understanding of the information flow here.

fedClientIn :: forall (comp :: Component) (name :: Symbol) m api. (HasFedEndpoint comp api name, HasClient m api) => Client m api Source #

data Annotation Source #

Instances

Instances details
Data Annotation 
Instance details

Defined in TransitiveAnns.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Annotation -> c Annotation #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Annotation #

toConstr :: Annotation -> Constr #

dataTypeOf :: Annotation -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Annotation) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Annotation) #

gmapT :: (forall b. Data b => b -> b) -> Annotation -> Annotation #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Annotation -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Annotation -> r #

gmapQ :: (forall d. Data d => d -> u) -> Annotation -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Annotation -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Annotation -> m Annotation #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Annotation -> m Annotation #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Annotation -> m Annotation #

Show Annotation 
Instance details

Defined in TransitiveAnns.Types

Eq Annotation 
Instance details

Defined in TransitiveAnns.Types

Ord Annotation 
Instance details

Defined in TransitiveAnns.Types

class AddAnnotation (loc :: Location) (api :: Symbol) (method :: Symbol) a Source #

AddAnnotation constraints are automatically solved by this plugin, but internally act as "unsolved" constraints, without you needing to propagate them by hand.

The unsolved constraints can be reintroduced via a ToHasAnnotations constraint, which will automatically be solved and replaced with a corresponding HasAnnotation for every AddAnnotation in the transitive closure.

The a parameter is intentionally ambiguous, existing as a unique skolem to prevent GHC from caching the results of solving AddAnnotation. Callers needn't worry about it.

class HasFeds (a :: k) where Source #

Methods

getFedCalls :: Proxy a -> State FedCallFrom [FedCallFrom] Source #

Instances

Instances details
HasFeds RawM 
Instance details

Defined in Wire.API.MakesFederatedCall

Methods

getFedCalls :: Proxy RawM -> State FedCallFrom [FedCallFrom] Source #

HasFeds EmptyAPI 
Instance details

Defined in Wire.API.MakesFederatedCall

Methods

getFedCalls :: Proxy EmptyAPI -> State FedCallFrom [FedCallFrom] Source #

HasFeds Raw 
Instance details

Defined in Wire.API.MakesFederatedCall

Methods

getFedCalls :: Proxy Raw -> State FedCallFrom [FedCallFrom] Source #

HasFeds WebSocketPending 
Instance details

Defined in Wire.API.MakesFederatedCall

Methods

getFedCalls :: Proxy WebSocketPending -> State FedCallFrom [FedCallFrom] Source #

(HasFeds route, HasFeds routes) => HasFeds (route :<|> routes :: Type) 
Instance details

Defined in Wire.API.MakesFederatedCall

Methods

getFedCalls :: Proxy (route :<|> routes) -> State FedCallFrom [FedCallFrom] Source #

ReflectMethod method => HasFeds (NoContentVerb method :: Type) 
Instance details

Defined in Wire.API.MakesFederatedCall

Methods

getFedCalls :: Proxy (NoContentVerb method) -> State FedCallFrom [FedCallFrom] Source #

(KnownSymbol seg, HasFeds rest) => HasFeds (seg :> rest :: Type) 
Instance details

Defined in Wire.API.MakesFederatedCall

Methods

getFedCalls :: Proxy (seg :> rest) -> State FedCallFrom [FedCallFrom] Source #

HasFeds rest => HasFeds (ReqBodyCustomError' mods cts tag a :> rest :: Type) 
Instance details

Defined in Wire.API.MakesFederatedCall

Methods

getFedCalls :: Proxy (ReqBodyCustomError' mods cts tag a :> rest) -> State FedCallFrom [FedCallFrom] Source #

(KnownSymbol capture, HasFeds rest) => HasFeds (Capture' mods capture a :> rest :: Type) 
Instance details

Defined in Wire.API.MakesFederatedCall

Methods

getFedCalls :: Proxy (Capture' mods capture a :> rest) -> State FedCallFrom [FedCallFrom] Source #

HasFeds rest => HasFeds (Description desc :> rest :: Type) 
Instance details

Defined in Wire.API.MakesFederatedCall

Methods

getFedCalls :: Proxy (Description desc :> rest) -> State FedCallFrom [FedCallFrom] Source #

HasFeds rest => HasFeds (Summary summary :> rest :: Type) 
Instance details

Defined in Wire.API.MakesFederatedCall

Methods

getFedCalls :: Proxy (Summary summary :> rest) -> State FedCallFrom [FedCallFrom] Source #

HasFeds rest => HasFeds (Header' mods name a :> rest :: Type) 
Instance details

Defined in Wire.API.MakesFederatedCall

Methods

getFedCalls :: Proxy (Header' mods name a :> rest) -> State FedCallFrom [FedCallFrom] Source #

HasFeds rest => HasFeds (QueryFlag a :> rest :: Type) 
Instance details

Defined in Wire.API.MakesFederatedCall

Methods

getFedCalls :: Proxy (QueryFlag a :> rest) -> State FedCallFrom [FedCallFrom] Source #

HasFeds rest => HasFeds (QueryParam' mods name a :> rest :: Type) 
Instance details

Defined in Wire.API.MakesFederatedCall

Methods

getFedCalls :: Proxy (QueryParam' mods name a :> rest) -> State FedCallFrom [FedCallFrom] Source #

HasFeds rest => HasFeds (ReqBody' mods cts a :> rest :: Type) 
Instance details

Defined in Wire.API.MakesFederatedCall

Methods

getFedCalls :: Proxy (ReqBody' mods cts a :> rest) -> State FedCallFrom [FedCallFrom] Source #

HasFeds rest => HasFeds (StreamBody' opts framing ct a :> rest :: Type) 
Instance details

Defined in Wire.API.MakesFederatedCall

Methods

getFedCalls :: Proxy (StreamBody' opts framing ct a :> rest) -> State FedCallFrom [FedCallFrom] Source #

HasFeds rest => HasFeds (MultipartForm tag a :> rest :: Type) 
Instance details

Defined in Wire.API.MakesFederatedCall

Methods

getFedCalls :: Proxy (MultipartForm tag a :> rest) -> State FedCallFrom [FedCallFrom] Source #

HasFeds rest => HasFeds (Deprecated :> rest :: Type) 
Instance details

Defined in Wire.API.MakesFederatedCall

Methods

getFedCalls :: Proxy (Deprecated :> rest) -> State FedCallFrom [FedCallFrom] Source #

HasFeds rest => HasFeds (CanThrow e :> rest :: Type) 
Instance details

Defined in Wire.API.MakesFederatedCall

Methods

getFedCalls :: Proxy (CanThrow e :> rest) -> State FedCallFrom [FedCallFrom] Source #

HasFeds rest => HasFeds (CanThrowMany es :> rest :: Type) 
Instance details

Defined in Wire.API.MakesFederatedCall

Methods

getFedCalls :: Proxy (CanThrowMany es :> rest) -> State FedCallFrom [FedCallFrom] Source #

(HasFeds rest, KnownSymbol (ShowComponent comp), KnownSymbol name) => HasFeds (MakesFederatedCall comp name :> rest :: Type) 
Instance details

Defined in Wire.API.MakesFederatedCall

Methods

getFedCalls :: Proxy (MakesFederatedCall comp name :> rest) -> State FedCallFrom [FedCallFrom] Source #

HasFeds rest => HasFeds (Bearer a :> rest :: Type) 
Instance details

Defined in Wire.API.MakesFederatedCall

Methods

getFedCalls :: Proxy (Bearer a :> rest) -> State FedCallFrom [FedCallFrom] Source #

HasFeds rest => HasFeds (Cookies cs :> rest :: Type) 
Instance details

Defined in Wire.API.MakesFederatedCall

Methods

getFedCalls :: Proxy (Cookies cs :> rest) -> State FedCallFrom [FedCallFrom] Source #

HasFeds rest => HasFeds (DescriptionOAuthScope scope :> rest :: Type) 
Instance details

Defined in Wire.API.MakesFederatedCall

Methods

getFedCalls :: Proxy (DescriptionOAuthScope scope :> rest) -> State FedCallFrom [FedCallFrom] Source #

HasFeds rest => HasFeds (ZAuthServant ztype opts :> rest :: Type) 
Instance details

Defined in Wire.API.MakesFederatedCall

Methods

getFedCalls :: Proxy (ZAuthServant ztype opts :> rest) -> State FedCallFrom [FedCallFrom] Source #

HasFeds rest => HasFeds (ZHostOpt :> rest :: Type) 
Instance details

Defined in Wire.API.MakesFederatedCall

Methods

getFedCalls :: Proxy (ZHostOpt :> rest) -> State FedCallFrom [FedCallFrom] Source #

(KnownSymbol capture, KnownSymbol (AppendSymbol capture "_domain"), HasFeds rest) => HasFeds (QualifiedCapture' mods capture a :> rest :: Type) 
Instance details

Defined in Wire.API.MakesFederatedCall

Methods

getFedCalls :: Proxy (QualifiedCapture' mods capture a :> rest) -> State FedCallFrom [FedCallFrom] Source #

HasFeds rest => HasFeds (VersionedReqBody v cts a :> rest :: Type) 
Instance details

Defined in Wire.API.MakesFederatedCall

Methods

getFedCalls :: Proxy (VersionedReqBody v cts a :> rest) -> State FedCallFrom [FedCallFrom] Source #

HasFeds rest => HasFeds (OmitDocs :> rest :: Type) 
Instance details

Defined in Wire.API.MakesFederatedCall

Methods

getFedCalls :: Proxy (OmitDocs :> rest) -> State FedCallFrom [FedCallFrom] Source #

(RenderableSymbol name, HasFeds rest) => HasFeds (Named name rest :: Type) 
Instance details

Defined in Wire.API.MakesFederatedCall

Methods

getFedCalls :: Proxy (Named name rest) -> State FedCallFrom [FedCallFrom] Source #

ReflectMethod method => HasFeds (Verb method status cts a :: Type) 
Instance details

Defined in Wire.API.MakesFederatedCall

Methods

getFedCalls :: Proxy (Verb method status cts a) -> State FedCallFrom [FedCallFrom] Source #

ReflectMethod method => HasFeds (MultiVerb method cs as r :: Type) 
Instance details

Defined in Wire.API.MakesFederatedCall

Methods

getFedCalls :: Proxy (MultiVerb method cs as r) -> State FedCallFrom [FedCallFrom] Source #

ReflectMethod method => HasFeds (Stream method status framing ct a :: Type) 
Instance details

Defined in Wire.API.MakesFederatedCall

Methods

getFedCalls :: Proxy (Stream method status framing ct a) -> State FedCallFrom [FedCallFrom] Source #

ReflectMethod method => HasFeds (LowLevelStream method status headers desc ctype :: Type) 
Instance details

Defined in Wire.API.MakesFederatedCall

Methods

getFedCalls :: Proxy (LowLevelStream method status headers desc ctype) -> State FedCallFrom [FedCallFrom] Source #

newtype Calls Source #

Constructors

Calls 

Fields

Instances

Instances details
Monoid Calls 
Instance details

Defined in Wire.API.MakesFederatedCall

Methods

mempty :: Calls #

mappend :: Calls -> Calls -> Calls #

mconcat :: [Calls] -> Calls #

Semigroup Calls 
Instance details

Defined in Wire.API.MakesFederatedCall

Methods

(<>) :: Calls -> Calls -> Calls #

sconcat :: NonEmpty Calls -> Calls #

stimes :: Integral b => b -> Calls -> Calls #

Show Calls 
Instance details

Defined in Wire.API.MakesFederatedCall

Methods

showsPrec :: Int -> Calls -> ShowS #

show :: Calls -> String #

showList :: [Calls] -> ShowS #

Eq Calls 
Instance details

Defined in Wire.API.MakesFederatedCall

Methods

(==) :: Calls -> Calls -> Bool #

(/=) :: Calls -> Calls -> Bool #

Ord Calls 
Instance details

Defined in Wire.API.MakesFederatedCall

Methods

compare :: Calls -> Calls -> Ordering #

(<) :: Calls -> Calls -> Bool #

(<=) :: Calls -> Calls -> Bool #

(>) :: Calls -> Calls -> Bool #

(>=) :: Calls -> Calls -> Bool #

max :: Calls -> Calls -> Calls #

min :: Calls -> Calls -> Calls #

type family ShowComponent (x :: Component) = (res :: Symbol) | res -> x where ... Source #

Get a symbol representation of our component.

Equations

ShowComponent 'Brig = "brig" 
ShowComponent 'Galley = "galley" 
ShowComponent 'Cargohold = "cargohold" 

data MakesFederatedCall (comp :: Component) (name :: Symbol) Source #

Servant combinator for tracking calls to federated calls. Annotating API endpoints with MakesFederatedCall is the only way to eliminate CallsFed constraints on handlers.

Instances

Instances details
RoutesToPaths api => RoutesToPaths (MakesFederatedCall comp name :> api :: Type) 
Instance details

Defined in Wire.API.MakesFederatedCall

HasLink api => HasLink (MakesFederatedCall comp name :> api :: Type) 
Instance details

Defined in Wire.API.MakesFederatedCall

Associated Types

type MkLink (MakesFederatedCall comp name :> api) a Source #

Methods

toLink :: (Link -> a) -> Proxy (MakesFederatedCall comp name :> api) -> Link -> MkLink (MakesFederatedCall comp name :> api) a Source #

HasClient m api => HasClient m (MakesFederatedCall comp name :> api) 
Instance details

Defined in Wire.API.MakesFederatedCall

Associated Types

type Client m (MakesFederatedCall comp name :> api) Source #

Methods

clientWithRoute :: Proxy m -> Proxy (MakesFederatedCall comp name :> api) -> Request -> Client m (MakesFederatedCall comp name :> api) Source #

hoistClientMonad :: Proxy m -> Proxy (MakesFederatedCall comp name :> api) -> (forall x. mon x -> mon' x) -> Client mon (MakesFederatedCall comp name :> api) -> Client mon' (MakesFederatedCall comp name :> api) Source #

(HasOpenApi api, KnownSymbol name, KnownSymbol (ShowComponent comp)) => HasOpenApi (MakesFederatedCall comp name :> api :: Type)

MakesFederatedCall annotates the swagger documentation with an extension tag x-wire-makes-federated-calls-to.

Instance details

Defined in Wire.API.MakesFederatedCall

Methods

toOpenApi :: Proxy (MakesFederatedCall comp name :> api) -> OpenApi Source #

(HasFeds rest, KnownSymbol (ShowComponent comp), KnownSymbol name) => HasFeds (MakesFederatedCall comp name :> rest :: Type) 
Instance details

Defined in Wire.API.MakesFederatedCall

Methods

getFedCalls :: Proxy (MakesFederatedCall comp name :> rest) -> State FedCallFrom [FedCallFrom] Source #

HasServer api ctx => HasServer (MakesFederatedCall comp name :> api :: Type) ctx 
Instance details

Defined in Wire.API.MakesFederatedCall

Associated Types

type ServerT (MakesFederatedCall comp name :> api) m Source #

Methods

route :: Proxy (MakesFederatedCall comp name :> api) -> Context ctx -> Delayed env (Server (MakesFederatedCall comp name :> api)) -> Router env Source #

hoistServerWithContext :: Proxy (MakesFederatedCall comp name :> api) -> Proxy ctx -> (forall x. m x -> n x) -> ServerT (MakesFederatedCall comp name :> api) m -> ServerT (MakesFederatedCall comp name :> api) n Source #

type SpecialiseToVersion (v :: k) (MakesFederatedCall comp rpc :> api) 
Instance details

Defined in Wire.API.Routes.SpecialiseToVersion

type Client m (MakesFederatedCall comp name :> api) 
Instance details

Defined in Wire.API.MakesFederatedCall

type Client m (MakesFederatedCall comp name :> api) = Client m api
type SpecialiseToVersion v (MakesFederatedCall comp name :> api) 
Instance details

Defined in Wire.API.MakesFederatedCall

type MkLink (MakesFederatedCall comp name :> api :: Type) x 
Instance details

Defined in Wire.API.MakesFederatedCall

type MkLink (MakesFederatedCall comp name :> api :: Type) x = MkLink api x
type ServerT (MakesFederatedCall comp name :> api :: Type) m 
Instance details

Defined in Wire.API.MakesFederatedCall

type ServerT (MakesFederatedCall comp name :> api :: Type) m = Dict (CallsFed comp name) -> ServerT api m

type CallsFed (comp :: Component) = HasAnnotation 'Remote (ShowComponent comp) Source #

A typeclass corresponding to calls to federated services. This class has no methods, and exists only to automatically propagate information up to servant.

The only way to discharge this constraint is via callsFed, which should be invoked for each federated call when connecting handlers to the server definition.

data Component Source #

Constructors

Brig 
Galley 
Cargohold 

Instances

Instances details
Arbitrary Component 
Instance details

Defined in Wire.API.MakesFederatedCall

FromJSON Component 
Instance details

Defined in Wire.API.MakesFederatedCall

ToJSON Component 
Instance details

Defined in Wire.API.MakesFederatedCall

Generic Component 
Instance details

Defined in Wire.API.MakesFederatedCall

Associated Types

type Rep Component :: Type -> Type #

Show Component 
Instance details

Defined in Wire.API.MakesFederatedCall

Eq Component 
Instance details

Defined in Wire.API.MakesFederatedCall

FromHttpApiData Component 
Instance details

Defined in Wire.API.MakesFederatedCall

ToHttpApiData Component 
Instance details

Defined in Wire.API.MakesFederatedCall

ToSchema Component 
Instance details

Defined in Wire.API.MakesFederatedCall

type Rep Component 
Instance details

Defined in Wire.API.MakesFederatedCall

type Rep Component = D1 ('MetaData "Component" "Wire.API.MakesFederatedCall" "wire-api-0.1.0-3915FetN8WgFcCGrbk6Vve" 'False) (C1 ('MetaCons "Brig" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Galley" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Cargohold" 'PrefixI 'False) (U1 :: Type -> Type)))

exposeAnnotations :: ToHasAnnotations x => a -> a Source #

This function exists only to provide a convenient place for the transitive-anns plugin to solve the ToHasAnnotations constraint. This is highly magical and warrants a note.

The call exposeAnnotations (some expr here) will expand to some expr here, additionally generating wanted HasAnnotation constraints for every AddAnnotation constraint in the _transitive call closure_ of some expr here.

The use case is always going to be callsFed (exposeAnnotations expr), where exposeAnnotations re-introduces all of the constraints we've been squirreling away, and callsFed is responsible for discharging them. It would be very desirable to combine these into one call, but the semantics of solving ToHasAnnotations attaches the wanted calls to the same place as the call itself, which means the wanteds appear just after our opportunity to solve them via callsFed. This is likely not a hard limitation.

The x parameter here is intentionally ambiguous, existing as a unique skolem to prevent GHC from caching the results of solving ToHasAnnotations. Callers needn't worry about it.

callsFed :: SolveCallsFed c r a => (c => r) -> a Source #

Safely discharge a CallsFed constraint. Intended to be used when connecting your handler to the server router.

This function should always be called with an argument of exposeAnnotations. See the documentation there for more information on why.

Re-exports

data Component Source #

Constructors

Brig 
Galley 
Cargohold 

Instances

Instances details
Arbitrary Component 
Instance details

Defined in Wire.API.MakesFederatedCall

FromJSON Component 
Instance details

Defined in Wire.API.MakesFederatedCall

ToJSON Component 
Instance details

Defined in Wire.API.MakesFederatedCall

Generic Component 
Instance details

Defined in Wire.API.MakesFederatedCall

Associated Types

type Rep Component :: Type -> Type #

Show Component 
Instance details

Defined in Wire.API.MakesFederatedCall

Eq Component 
Instance details

Defined in Wire.API.MakesFederatedCall

FromHttpApiData Component 
Instance details

Defined in Wire.API.MakesFederatedCall

ToHttpApiData Component 
Instance details

Defined in Wire.API.MakesFederatedCall

ToSchema Component 
Instance details

Defined in Wire.API.MakesFederatedCall

type Rep Component 
Instance details

Defined in Wire.API.MakesFederatedCall

type Rep Component = D1 ('MetaData "Component" "Wire.API.MakesFederatedCall" "wire-api-0.1.0-3915FetN8WgFcCGrbk6Vve" 'False) (C1 ('MetaCons "Brig" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Galley" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Cargohold" 'PrefixI 'False) (U1 :: Type -> Type)))