servant-0.6: A family of combinators for defining webservices APIs

Safe HaskellNone
LanguageHaskell2010

Servant.Utils.Links

Contents

Description

Type safe generation of internal links.

Given an API with a few endpoints:

>>> :set -XDataKinds -XTypeFamilies -XTypeOperators
>>> import Servant.API
>>> import Servant.Utils.Links
>>> import Data.Proxy
>>> 
>>> 
>>> 
>>> type Hello = "hello" :> Get '[JSON] Int
>>> type Bye   = "bye"   :> QueryParam "name" String :> Delete '[JSON] ()
>>> 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 URI out the other end.

You may omit QueryParams 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 QueryParams 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)
>>> print (safeLink api hello :: URI)
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] ())
>>> print $ safeLink api with (Just "Hubert")
bye?name=Hubert
>>> let without = Proxy :: Proxy ("bye" :> Delete '[JSON] ())
>>> print $ safeLink api without
bye

If you would like 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
>>> apiLink = safeLink api
>>> :}

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] ())
>>> safeLink api bad_link
...
    Could not deduce (Or
                        (IsElem' (Verb 'DELETE 200 '[JSON] ()) (Verb 'GET 200 '[JSON] Int))
                        (IsElem'
                           ("hello" :> Delete '[JSON] ())
                           ("bye" :> (QueryParam "name" String :> Delete '[JSON] ()))))
      arising from a use of ‘safeLink’
    In the expression: safeLink api bad_link
    In an equation for ‘it’: it = safeLink api bad_link

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.

Synopsis

Building and using safe links

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

safeLink Source

Arguments

:: (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 

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

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

data URI :: *

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 

Fields

uriScheme :: String
foo:
uriAuthority :: Maybe URIAuth
//anonymous@www.haskell.org:42
uriPath :: String
/ghc
uriQuery :: String
?query
uriFragment :: String
#frag

Instances

Eq URI 
Data URI 
Ord URI 
Show URI 
Generic URI 
NFData URI 
type Rep URI = D1 D1URI (C1 C1_0URI ((:*:) ((:*:) (S1 S1_0_0URI (Rec0 String)) (S1 S1_0_1URI (Rec0 (Maybe URIAuth)))) ((:*:) (S1 S1_0_2URI (Rec0 String)) ((:*:) (S1 S1_0_3URI (Rec0 String)) (S1 S1_0_4URI (Rec0 String)))))) 

Adding custom types

class HasLink endpoint where Source

Construct a toLink for an endpoint.

Associated Types

type MkLink endpoint Source

Methods

toLink Source

Arguments

:: Proxy endpoint

The API endpoint you would like to point to

-> Link 
-> MkLink endpoint 

data Link Source

A safe link datatype. The only way of constructing a Link is using safeLink, which means any Link is guaranteed to be part of the mentioned API.

type family IsElem' a s :: Constraint Source

You may use this type family to tell the type checker that your custom type may be skipped as part of a link. This is useful for things like QueryParam that are optional in a URI and do not affect them if they are omitted.

>>> data CustomThing
>>> type instance IsElem' e (CustomThing :> s) = IsElem e s

Note that IsElem is called, which will mutually recurse back to IsElem' if it exhausts all other options again.

Once you have written a HasLink instance for CustomThing you are ready to go.

Illustrative exports

type family IsElem endpoint api :: Constraint Source

Closed type family, check if endpoint is within api

Equations

IsElem e (sa :<|> sb) = Or (IsElem e sa) (IsElem e sb) 
IsElem (e :> sa) (e :> sb) = IsElem sa sb 
IsElem sa (Header sym x :> sb) = IsElem sa sb 
IsElem sa (ReqBody y x :> sb) = IsElem sa sb 
IsElem (Capture z y :> sa) (Capture x y :> sb) = IsElem sa sb 
IsElem sa (QueryParam x y :> sb) = IsElem sa sb 
IsElem sa (QueryParams x y :> sb) = IsElem sa sb 
IsElem sa (QueryFlag x :> sb) = IsElem sa sb 
IsElem (Verb m s ct typ) (Verb m s ct' typ) = IsSubList ct ct' 
IsElem e e = () 
IsElem e a = IsElem' e a 

type family Or a b :: Constraint Source

If either a or b produce an empty constraint, produce an empty constraint.

Equations

Or () b = () 
Or a () = ()