servant-0.19.1: A family of combinators for defining webservices APIs
Safe Haskell None
Language Haskell2010

Servant.Links

Description

Type safe generation of internal links.

Given an API with a few endpoints:

>>> :set -XDataKinds -XTypeFamilies -XTypeOperators
>>> import Servant.API
>>> import Servant.Links
>>> import Web.HttpApiData (toUrlPiece)
>>> import Data.Proxy
>>> 
>>> type Hello = "hello" :> Get '[JSON] Int
>>> type Bye   = "bye"   :> QueryParam "name" String :> Delete '[JSON] NoContent
>>> type API   = Hello :<|> Bye
>>> let api = Proxy :: Proxy API

It is possible to generate links that are guaranteed to be within API with safeLink . The first argument to safeLink is a type representing the API you would like to restrict links to. The second argument is the destination endpoint you would like the link to point to, this will need to end with a verb like GET or POST. Further arguments may be required depending on the type of the endpoint. If everything lines up you will get a Link out the other end.

You may omit QueryParam s and the like should you not want to provide them, but types which form part of the URL path like Capture must be included. The reason you may want to omit QueryParam s is that safeLink is a bit magical: if parameters are included that could take input it will return a function that accepts that input and generates a link. This is best shown with an example. Here, a link is generated with no parameters:

>>> let hello = Proxy :: Proxy ("hello" :> Get '[JSON] Int)
>>> toUrlPiece (safeLink api hello :: Link)
"hello"

If the API has an endpoint with parameters then we can generate links with or without those:

>>> let with = Proxy :: Proxy ("bye" :> QueryParam "name" String :> Delete '[JSON] NoContent)
>>> toUrlPiece $ safeLink api with (Just "Hubert")
"bye?name=Hubert"
>>> let without = Proxy :: Proxy ("bye" :> Delete '[JSON] NoContent)
>>> toUrlPiece $ safeLink api without
"bye"

If you would like to create a helper for generating links only within that API, you can partially apply safeLink if you specify a correct type signature like so:

>>> :set -XConstraintKinds
>>> :{
>>> let apiLink :: (IsElem endpoint API, HasLink endpoint)
>>> => Proxy endpoint -> MkLink endpoint Link
>>> apiLink = safeLink api
>>> :}

safeLink ` allows you to specialise the output:

>>> safeLink' toUrlPiece api without
"bye"
>>> :{
>>> let apiTextLink :: (IsElem endpoint API, HasLink endpoint)
>>> => Proxy endpoint -> MkLink endpoint Text
>>> apiTextLink = safeLink' toUrlPiece api
>>> :}
>>> apiTextLink without
"bye"

Attempting to construct a link to an endpoint that does not exist in api will result in a type error like this:

>>> let bad_link = Proxy :: Proxy ("hello" :> Delete '[JSON] NoContent)
>>> safeLink api bad_link
...
...Could not ...
...

This error is essentially saying that the type family couldn't find bad_link under api after trying the open (but empty) type family IsElem ` as a last resort.

Since: 0.14.1

Synopsis

Documentation

Building and using safe links

Note that URI is from the Network.URI module in the network-uri package.

safeLink Source #

Arguments

:: forall endpoint api. ( IsElem endpoint api, HasLink endpoint)
=> Proxy api

The whole API that this endpoint is a part of

-> Proxy endpoint

The API endpoint you would like to point to

-> MkLink endpoint Link

Create a valid (by construction) relative URI with query params.

This function will only typecheck if endpoint is part of the API api

safeLink' Source #

Arguments

:: forall endpoint api a. ( IsElem endpoint api, HasLink endpoint)
=> ( Link -> a)
-> Proxy api

The whole API that this endpoint is a part of

-> Proxy endpoint

The API endpoint you would like to point to

-> MkLink endpoint a

More general safeLink .

allLinks :: forall api. HasLink api => Proxy api -> MkLink api Link Source #

Create all links in an API.

Note that the api type must be restricted to the endpoints that have valid links to them.

>>> type API = "foo" :> Capture "name" Text :> Get '[JSON] Text :<|> "bar" :> Capture "name" Int :> Get '[JSON] Double
>>> let fooLink :<|> barLink = allLinks (Proxy :: Proxy API)
>>> :t fooLink
fooLink :: Text -> Link
>>> :t barLink
barLink :: Int -> Link

Note: nested APIs don't work well with this approach

>>> :kind! MkLink (Capture "nest" Char :> (Capture "x" Int :> Get '[JSON] Int :<|> Capture "y" Double :> Get '[JSON] Double)) Link
MkLink (Capture "nest" Char :> (Capture "x" Int :> Get '[JSON] Int :<|> Capture "y" Double :> Get '[JSON] Double)) Link :: *
= Char -> (Int -> Link) :<|> (Double -> Link)

allLinks' :: forall api a. HasLink api => ( Link -> a) -> Proxy api -> MkLink api a Source #

More general allLinks . See safeLink `.

data URI Source #

Represents a general universal resource identifier using its component parts.

For example, for the URI

  foo://anonymous@www.haskell.org:42/ghc?query#frag

the components are:

Constructors

URI

Instances

Instances details
Eq URI
Instance details

Defined in Network.URI

Data URI
Instance details

Defined in Network.URI

Methods

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

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

toConstr :: URI -> Constr Source #

dataTypeOf :: URI -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Ord URI
Instance details

Defined in Network.URI

Show URI
Instance details

Defined in Network.URI

Generic URI
Instance details

Defined in Network.URI

Associated Types

type Rep URI :: Type -> Type Source #

NFData URI
Instance details

Defined in Network.URI

Methods

rnf :: URI -> () Source #

Lift URI
Instance details

Defined in Network.URI

type Rep URI
Instance details

Defined in Network.URI

Generics

data AsLink (a :: *) Source #

A type that specifies that an API record contains a set of links.

Since: 0.14.1

Instances

fieldLink :: ( IsElem endpoint ( ToServantApi routes), HasLink endpoint, GenericServant routes AsApi ) => (routes AsApi -> endpoint) -> MkLink endpoint Link Source #

Given an API record field, create a link for that route. Only the field's type is used.

data Record route = Record
    { _get :: route :- Capture "id" Int :> Get '[JSON] String
    , _put :: route :- ReqBody '[JSON] Int :> Put '[JSON] Bool
    }
  deriving (Generic)

getLink :: Int -> Link
getLink = fieldLink _get

Since: 0.14.1

fieldLink' :: forall routes endpoint a. ( IsElem endpoint ( ToServantApi routes), HasLink endpoint, GenericServant routes AsApi ) => ( Link -> a) -> (routes AsApi -> endpoint) -> MkLink endpoint a Source #

More general version of fieldLink

Since: 0.14.1

allFieldLinks' :: forall routes a. ( HasLink ( ToServantApi routes), GenericServant routes ( AsLink a), ToServant routes ( AsLink a) ~ MkLink ( ToServantApi routes) a) => ( Link -> a) -> routes ( AsLink a) Source #

More general version of allFieldLinks .

Since: 0.14.1

Adding custom types

class HasLink endpoint where Source #

Construct a toLink for an endpoint.

Associated Types

type MkLink endpoint (a :: *) Source #

Methods

toLink Source #

Arguments

:: ( Link -> a)
-> Proxy endpoint

The API endpoint you would like to point to

-> Link
-> MkLink endpoint a

Instances

linkURI :: Link -> URI Source #

Transform Link into URI .

>>> type API = "something" :> Get '[JSON] Int
>>> linkURI $ safeLink (Proxy :: Proxy API) (Proxy :: Proxy API)
something
>>> type API = "sum" :> QueryParams "x" Int :> Get '[JSON] Int
>>> linkURI $ safeLink (Proxy :: Proxy API) (Proxy :: Proxy API) [1, 2, 3]
sum?x[]=1&x[]=2&x[]=3
>>> type API = "foo/bar" :> Get '[JSON] Int
>>> linkURI $ safeLink (Proxy :: Proxy API) (Proxy :: Proxy API)
foo%2Fbar
>>> type SomeRoute = "abc" :> Capture "email" String :> Put '[JSON] ()
>>> let someRoute = Proxy :: Proxy SomeRoute
>>> safeLink someRoute someRoute "test@example.com"
Link {_segments = ["abc","test%40example.com"], _queryParams = [], _fragment = Nothing}
>>> linkURI $ safeLink someRoute someRoute "test@example.com"
abc/test%40example.com

linkURI' :: LinkArrayElementStyle -> Link -> URI Source #

Configurable linkURI .

>>> type API = "sum" :> QueryParams "x" Int :> Get '[JSON] Int
>>> linkURI' LinkArrayElementBracket $ safeLink (Proxy :: Proxy API) (Proxy :: Proxy API) [1, 2, 3]
sum?x[]=1&x[]=2&x[]=3
>>> linkURI' LinkArrayElementPlain $ safeLink (Proxy :: Proxy API) (Proxy :: Proxy API) [1, 2, 3]
sum?x=1&x=2&x=3

data LinkArrayElementStyle Source #

How to encode array query elements.

Constructors

LinkArrayElementBracket
foo[]=1&foo[]=2
LinkArrayElementPlain
foo=1&foo=2

Instances

Instances details
Bounded LinkArrayElementStyle Source #
Instance details

Defined in Servant.Links

Enum LinkArrayElementStyle Source #
Instance details

Defined in Servant.Links

Eq LinkArrayElementStyle Source #
Instance details

Defined in Servant.Links

Ord LinkArrayElementStyle Source #
Instance details

Defined in Servant.Links

Show LinkArrayElementStyle Source #
Instance details

Defined in Servant.Links

Link accessors