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

Safe HaskellNone
LanguageHaskell2010

Servant.Utils.Links

Contents

Description

Type safe internal links.

Provides the function mkLink:

  type API = Proxy ("hello" :> Get Int
               :| "bye" :> QueryParam "name" String :> Post Bool)

  api :: API
  api = proxy

  link1 :: Proxy ("hello" :> Get Int)
  link1 = proxy

  link2 :: Proxy ("hello" :> Delete)
  link2 = proxy

  mkLink link1 API  --  typechecks, returns 'Link "/hello"'

  mkLink link2  API  -- doesn't typecheck

That is, mkLink takes two arguments, a link proxy and a sitemap, and returns a Link, but only typechecks if the link proxy is a valid link, and part of the sitemap.

N.B.: mkLink assumes a capture matches any string (without slashes).

Synopsis

Link and mkLink

The only end-user utilities

data Link Source

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

Internal

These functions will likely only be of interest if you are writing more API combinators and would like to extend the behavior of mkLink

class ValidLinkIn f s where Source

The 'ValidLinkIn f s' constraint holds when s is an API that contains f, and f is a link.

Methods

mkLink Source

Arguments

:: f 
-> s 
-> Link

This function will only typecheck if f is an URI within s

Instances

((~) Bool (IsElem f s) True, (~) Bool (IsLink f) True, VLinkHelper * f) => ValidLinkIn f s 

class VLinkHelper f where Source

Methods

vlh :: forall proxy. proxy f -> String Source

Instances

type family IsElem a s Source

Equations

IsElem e (sa :<|> sb) = Or (IsElem e sa) (IsElem e sb) 
IsElem (e :> sa) (e :> sb) = IsElem sa sb 
IsElem (e :> sa) (Capture x y :> sb) = IsElem sa sb 
IsElem sa (ReqBody x :> sb) = IsElem sa sb 
IsElem sa (QueryParam x y :> sb) = IsElem sa sb 
IsElem e e = True 
IsElem e a = False 

type family IsLink e Source

Equations

IsLink (a :> b) = Or (And (IsLink' a) (IsLink'' b)) (IsLink'' (a :> b))