roboservant-0.1.0.3: Automatic session-aware servant testing
Safe HaskellSafe-Inferred
LanguageHaskell2010

Roboservant.Types.ReifiedApi.Server

Documentation

class NormalizeFunction m where Source #

Associated Types

type Normal m Source #

Methods

normalize :: m -> Normal m Source #

Instances

Instances details
(Typeable x, Hashable x, Breakdown x) => NormalizeFunction (ClientM x) Source # 
Instance details

Defined in Roboservant.Client

Associated Types

type Normal (ClientM x) Source #

Methods

normalize :: ClientM x -> Normal (ClientM x) Source #

(Typeable x, Hashable x, Breakdown x) => NormalizeFunction (Handler x) Source # 
Instance details

Defined in Roboservant.Types.ReifiedApi.Server

Associated Types

type Normal (Handler x) Source #

Methods

normalize :: Handler x -> Normal (Handler x) Source #

NormalizeFunction x => NormalizeFunction (r -> x) Source # 
Instance details

Defined in Roboservant.Types.ReifiedApi.Server

Associated Types

type Normal (r -> x) Source #

Methods

normalize :: (r -> x) -> Normal (r -> x) Source #

class FlattenServer api where Source #

Methods

flattenServer :: Server api -> Bundled (Endpoints api) Source #

Instances

Instances details
(FlattenServer api, Endpoints endpoint ~ '[endpoint]) => FlattenServer (endpoint :<|> api) Source # 
Instance details

Defined in Roboservant.Types.ReifiedApi.Server

Methods

flattenServer :: Server (endpoint :<|> api) -> Bundled (Endpoints (endpoint :<|> api)) Source #

Endpoints api ~ '[api] => FlattenServer (x :> api) Source # 
Instance details

Defined in Roboservant.Types.ReifiedApi.Server

Methods

flattenServer :: Server (x :> api) -> Bundled (Endpoints (x :> api)) Source #

FlattenServer (Verb method statusCode contentTypes responseType) Source # 
Instance details

Defined in Roboservant.Types.ReifiedApi.Server

Methods

flattenServer :: Server (Verb method statusCode contentTypes responseType) -> Bundled (Endpoints (Verb method statusCode contentTypes responseType)) Source #

data Bundled endpoints where Source #

Constructors

AnEndpoint :: Server endpoint -> Bundled endpoints -> Bundled (endpoint ': endpoints) 
NoEndpoints :: Bundled '[] 

class ToReifiedApi endpoints where Source #

Methods

toReifiedApi :: Bundled endpoints -> Proxy endpoints -> ReifiedApi Source #

Instances

Instances details
ToReifiedApi ('[] :: [k]) Source # 
Instance details

Defined in Roboservant.Types.ReifiedApi.Server

Methods

toReifiedApi :: Bundled '[] -> Proxy '[] -> ReifiedApi Source #

(NormalizeFunction (ServerT endpoint Handler), Normal (ServerT endpoint Handler) ~ Curried (EndpointArgs endpoint) (IO (Either InteractionError (NonEmpty (Dynamic, Int)))), ToReifiedEndpoint endpoint, ToReifiedApi endpoints) => ToReifiedApi (endpoint ': endpoints :: [Type]) Source # 
Instance details

Defined in Roboservant.Types.ReifiedApi.Server

Methods

toReifiedApi :: Bundled (endpoint ': endpoints) -> Proxy (endpoint ': endpoints) -> ReifiedApi Source #