servant-hateoas-0.3.4: HATEOAS extension for servant
Safe HaskellSafe-Inferred
LanguageGHC2021

Servant.Hateoas.Layer.Type

Synopsis

Type

data Layer Source #

Data-kind for a layer in an API.

Example

Expand
'Layer '[Sym "api", Sym "user"] '[Capture "id" Int, Sym "vip"] GetIntermediate

Represents the API

"api" :> "user" :> GetIntermediate

with children

"api" :> "user" :> Capture "id" Int :> GetIntermediate

and

"api" :> "user" :> "vip" :> GetIntermediate

Constructors

Layer 

Fields

Instances

Instances details
(api ~ LayerApi l, rApi ~ Resourcify api ct, ServerT (Resourcify l ct) m ~ ResourcifyServer (ServerT l m) ct m, rServer ~ ResourcifyServer (ServerT l m) ct m, res ~ MkResource ct, buildFun ~ ReplaceHandler rServer [(String, RelationLink)], Resource res, BuildLayerLinks (Resourcify l ct) m, PolyvariadicComp buildFun (IsFun buildFun), Return buildFun (IsFun buildFun) ~ [(String, RelationLink)], Replace buildFun (m (res Intermediate)) (IsFun buildFun) ~ rServer) => HasResourceServer (l :: Layer) m ct Source # 
Instance details

Defined in Servant.Hateoas.ResourceServer

Methods

getResourceServer :: Proxy m -> Proxy ct -> Proxy l -> ServerT (Resourcify l ct) m Source #

HasServer (MkPrefix apiCs verb) context => HasServer ('Layer apiCs cs verb :: Layer) context Source # 
Instance details

Defined in Servant.Hateoas.Layer.Type

Associated Types

type ServerT ('Layer apiCs cs verb) m #

Methods

route :: Proxy ('Layer apiCs cs verb) -> Context context -> Delayed env (Server ('Layer apiCs cs verb)) -> Router env #

hoistServerWithContext :: Proxy ('Layer apiCs cs verb) -> Proxy context -> (forall x. m x -> n x) -> ServerT ('Layer apiCs cs verb) m -> ServerT ('Layer apiCs cs verb) n #

HasServer ('[] :: [Layer]) context Source # 
Instance details

Defined in Servant.Hateoas.Layer.Type

Associated Types

type ServerT '[] m #

Methods

route :: Proxy '[] -> Context context -> Delayed env (Server '[]) -> Router env #

hoistServerWithContext :: Proxy '[] -> Proxy context -> (forall x. m x -> n x) -> ServerT '[] m -> ServerT '[] n #

HasResourceServer ('[] :: [Layer]) m ct Source # 
Instance details

Defined in Servant.Hateoas.ResourceServer

Methods

getResourceServer :: Proxy m -> Proxy ct -> Proxy '[] -> ServerT (Resourcify '[] ct) m Source #

(HasServer l context, HasServer ls context) => HasServer (l ': ls :: [Layer]) context Source # 
Instance details

Defined in Servant.Hateoas.Layer.Type

Associated Types

type ServerT (l ': ls) m #

Methods

route :: Proxy (l ': ls) -> Context context -> Delayed env (Server (l ': ls)) -> Router env #

hoistServerWithContext :: Proxy (l ': ls) -> Proxy context -> (forall x. m x -> n x) -> ServerT (l ': ls) m -> ServerT (l ': ls) n #

(MonadIO m, HasResourceServer ls m ct, HasResourceServer l m ct, BuildLayerLinks (Resourcify l ct) m) => HasResourceServer (l ': ls :: [Layer]) m ct Source # 
Instance details

Defined in Servant.Hateoas.ResourceServer

Methods

getResourceServer :: Proxy m -> Proxy ct -> Proxy (l ': ls) -> ServerT (Resourcify (l ': ls) ct) m Source #

type ServerT ('Layer apiCs cs verb :: Layer) m Source # 
Instance details

Defined in Servant.Hateoas.Layer.Type

type ServerT ('Layer apiCs cs verb :: Layer) m = ServerT (MkPrefix apiCs verb) m
type ServerT ('[] :: [Layer]) m Source # 
Instance details

Defined in Servant.Hateoas.Layer.Type

type ServerT ('[] :: [Layer]) m = ServerT EmptyAPI m
type ServerT (l ': ls :: [Layer]) m Source # 
Instance details

Defined in Servant.Hateoas.Layer.Type

type ServerT (l ': ls :: [Layer]) m = ServerT l m :<|> ServerT ls m

Getter

type family LayerApiCs (a :: Layer) where ... Source #

Type-level getter for the API of a Layer.

Equations

LayerApiCs ('Layer api _ _) = api 

type family RelativeChildren (a :: Layer) where ... Source #

Type-level getter for the children of a Layer.

Equations

RelativeChildren ('Layer _ children _) = children 

type family LayerVerb (a :: Layer) where ... Source #

Type-level getter for the verb of a Layer.

Equations

LayerVerb ('Layer _ _ verb) = verb 

API-construction

type family LayerApi (a :: Layer) where ... Source #

Constructs the actual API of a Layer.

Equations

LayerApi ('Layer api _ verb) = MkPrefix api verb 

type family MkPrefix prefix api where ... Source #

Folds a list of path segments into an API by intercalating (:>).

Example

Expand
MkPrefix '[Sym "api", Sym "user"] GetIntermediate

resolves to

Sym "api" :> Sym "user" :> GetIntermediate

Equations

MkPrefix (Sym x ': xs) api = x :> MkPrefix xs api 
MkPrefix (x ': xs) api = x :> MkPrefix xs api 
MkPrefix '[] api = api 

type (++) xs ys = AppendList xs ys Source #

Convenience alias for AppendList.

Intermediate