roboservant-0.1.0.0: Automatic session-aware servant testing

Safe HaskellNone
LanguageHaskell2010

Roboservant.StateMachine

Synopsis

Documentation

data State v Source #

Constructors

State 

class FlattenServer api where Source #

Methods

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

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

Defined in Roboservant.StateMachine

Methods

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

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

Defined in Roboservant.StateMachine

Methods

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

(HasServer (Verb method statusCode contentTypes responseType) ([] :: [Type]), Endpoints (Verb method statusCode contentTypes responseType) ~ (Verb method statusCode contentTypes responseType ': ([] :: [Type]))) => FlattenServer (Verb method statusCode contentTypes responseType) Source # 
Instance details

Defined in Roboservant.StateMachine

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
ToReifiedApi ([] :: [Type]) Source # 
Instance details

Defined in Roboservant.StateMachine

(Typeable (Normal (ServerT endpoint Handler)), NormalizeFunction (ServerT endpoint Handler), ToReifiedEndpoint endpoint, ToReifiedApi endpoints, Typeable (ServerT endpoint Handler)) => ToReifiedApi (endpoint ': endpoints) Source # 
Instance details

Defined in Roboservant.StateMachine

Methods

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

class ToReifiedEndpoint (endpoint :: *) where Source #

Instances
(Typeable requestType, ToReifiedEndpoint endpoint) => ToReifiedEndpoint (ReqBody contentTypes requestType :> endpoint) Source # 
Instance details

Defined in Roboservant.StateMachine

Methods

toReifiedEndpoint :: Dynamic -> Proxy (ReqBody contentTypes requestType :> endpoint) -> ReifiedEndpoint Source #

(Typeable requestType, ToReifiedEndpoint endpoint) => ToReifiedEndpoint (Capture name requestType :> endpoint) Source # 
Instance details

Defined in Roboservant.StateMachine

Methods

toReifiedEndpoint :: Dynamic -> Proxy (Capture name requestType :> endpoint) -> ReifiedEndpoint Source #

ToReifiedEndpoint endpoint => ToReifiedEndpoint (x :> endpoint) Source # 
Instance details

Defined in Roboservant.StateMachine

Typeable responseType => ToReifiedEndpoint (Verb method statusCode contentTypes responseType) Source # 
Instance details

Defined in Roboservant.StateMachine

Methods

toReifiedEndpoint :: Dynamic -> Proxy (Verb method statusCode contentTypes responseType) -> ReifiedEndpoint Source #

class NormalizeFunction m where Source #

Associated Types

type Normal m Source #

Methods

normalize :: m -> Normal m Source #

Instances
Typeable x => NormalizeFunction (Handler x) Source # 
Instance details

Defined in Roboservant.StateMachine

Associated Types

type Normal (Handler x) :: Type Source #

Methods

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

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

Defined in Roboservant.StateMachine

Associated Types

type Normal (r -> x) :: Type Source #

Methods

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

data Op (v :: * -> *) Source #

we need to specify an offset because it's entirely possible to have two functions with the same arguments that do different things.

Constructors

Op ApiOffset [(TypeRep, Var (Opaque (IORef Dynamic)) v)] 
Instances
HTraversable Op Source # 
Instance details

Defined in Roboservant.StateMachine

Methods

htraverse :: Applicative f => (forall a. g a -> f (h a)) -> Op g -> f (Op h) #

Show (Op Symbolic) Source # 
Instance details

Defined in Roboservant.StateMachine