Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
Servant.Hateoas.RelationLink
Synopsis
- data RelationLink = RelationLink {}
- data RelationParam = RelationParam {}
- fromLink :: [MediaType] -> StdMethod -> Link -> RelationLink
- fromURI :: [MediaType] -> StdMethod -> URI -> RelationLink
- (<<<) :: RelationLink -> RelationLink -> RelationLink
- getHref :: RelationLink -> Text
- getPath :: RelationLink -> Text
- getParams :: RelationLink -> Text
- prependSeg :: Text -> RelationLink -> RelationLink
- prependSegs :: [Text] -> RelationLink -> RelationLink
- addParam :: RelationParam -> RelationLink -> RelationLink
- addParams :: [RelationParam] -> RelationLink -> RelationLink
- mkPlaceHolder :: Text -> Text
- class HasTemplatedLink endpoint where
- toTemplatedLink :: Proxy endpoint -> RelationLink
- class HasLink endpoint => HasRelationLink endpoint where
- toRelationLink :: Proxy endpoint -> MkLink endpoint RelationLink
- type RightLink b = (HasRelationLink b, PolyvariadicComp (MkLink b RelationLink) (IsFun (MkLink b RelationLink)), Return (MkLink b RelationLink) (IsFun (MkLink b RelationLink)) ~ RelationLink, Replace (MkLink b RelationLink) RelationLink (IsFun (MkLink b RelationLink)) ~ MkLink b RelationLink)
- reflectStdMethod :: ReflectMethod method => Proxy method -> StdMethod
RelationLink
Type
data RelationLink Source #
Link data-type for hypermedia-links in HATEOAS with potentially templated URIs.
Constructors
RelationLink | |
Instances
ToJSON RelationLink Source # | |
Defined in Servant.Hateoas.RelationLink Methods toJSON :: RelationLink -> Value # toEncoding :: RelationLink -> Encoding # toJSONList :: [RelationLink] -> Value # toEncodingList :: [RelationLink] -> Encoding # omitField :: RelationLink -> Bool # | |
Show RelationLink Source # | |
Defined in Servant.Hateoas.RelationLink Methods showsPrec :: Int -> RelationLink -> ShowS # show :: RelationLink -> String # showList :: [RelationLink] -> ShowS # | |
Eq RelationLink Source # | |
Defined in Servant.Hateoas.RelationLink |
data RelationParam Source #
Parameter data-type for hypermedia-links in HATEOAS.
Instances
Show RelationParam Source # | |
Defined in Servant.Hateoas.RelationLink Methods showsPrec :: Int -> RelationParam -> ShowS # show :: RelationParam -> String # showList :: [RelationParam] -> ShowS # | |
Eq RelationParam Source # | |
Defined in Servant.Hateoas.RelationLink Methods (==) :: RelationParam -> RelationParam -> Bool # (/=) :: RelationParam -> RelationParam -> Bool # |
Creation
fromLink :: [MediaType] -> StdMethod -> Link -> RelationLink Source #
Creates a RelationLink
from a Link
.
fromURI :: [MediaType] -> StdMethod -> URI -> RelationLink Source #
Creates a RelationLink
from an URI
.
Operations
(<<<) :: RelationLink -> RelationLink -> RelationLink Source #
Shifting append-operator for RelationLink
.
This operator can be seen as a monoidal append for RelationLink
with a right-bias for meta information
e.g. _method
, _contentTypes
, _summary
and _description
.
getHref :: RelationLink -> Text Source #
Get the hypermedia-reference of a RelationLink
.
getPath :: RelationLink -> Text Source #
Get the path of a RelationLink
as in getHref
.
getParams :: RelationLink -> Text Source #
Get the parameters of a RelationLink
as in getHref
.
prependSeg :: Text -> RelationLink -> RelationLink Source #
Prepend a path segment to a RelationLink
.
Takes care of potential templating.
prependSegs :: [Text] -> RelationLink -> RelationLink Source #
Prepend path segments to a RelationLink
.
Takes care of potential templating.
addParam :: RelationParam -> RelationLink -> RelationLink Source #
Add a parameter to a RelationLink
.
Takes care of potential templating.
addParams :: [RelationParam] -> RelationLink -> RelationLink Source #
Add parameters to a RelationLink
.
Takes care of potential templating.
mkPlaceHolder :: Text -> Text Source #
Create a placeholder for a template path segment.
Class
class HasTemplatedLink endpoint where Source #
Class for creating a templated RelationLink
to an endpoint.
Methods
toTemplatedLink :: Proxy endpoint -> RelationLink Source #
Instances
class HasLink endpoint => HasRelationLink endpoint where Source #
Class for creating a RelationLink
to an endpoint.
This is highly similar to HasLink
but it also gathers HATEOAS meta-information for the resource a link refers to.
Methods
toRelationLink :: Proxy endpoint -> MkLink endpoint RelationLink Source #
Instances
type RightLink b = (HasRelationLink b, PolyvariadicComp (MkLink b RelationLink) (IsFun (MkLink b RelationLink)), Return (MkLink b RelationLink) (IsFun (MkLink b RelationLink)) ~ RelationLink, Replace (MkLink b RelationLink) RelationLink (IsFun (MkLink b RelationLink)) ~ MkLink b RelationLink) Source #
Convenience alias-constraint for right-hand sides of a
where b is some function producing a :>
bRelationLink
.
Utility
ReflectStdMethod
reflectStdMethod :: ReflectMethod method => Proxy method -> StdMethod Source #
Like reflectMethod
but returns a StdMethod
.