servant/servant.txt

653 lines
22 KiB
Plaintext

-- Hoogle documentation, generated by Haddock
-- See Hoogle, http://www.haskell.org/hoogle/
-- | A family of combinators for defining webservices APIs and serving them
--
@package servant
@version 0.2
module Servant.Common.Text
-- | For getting values from url captures and query string parameters
class FromText a
fromText :: FromText a => Text -> Maybe a
-- | For putting values in paths and query string parameters
class ToText a
toText :: ToText a => a -> Text
instance ToText Float
instance FromText Float
instance ToText Double
instance FromText Double
instance ToText Integer
instance FromText Integer
instance ToText Word64
instance FromText Word64
instance ToText Word32
instance FromText Word32
instance ToText Word16
instance FromText Word16
instance ToText Word8
instance FromText Word8
instance ToText Word
instance FromText Word
instance ToText Int64
instance FromText Int64
instance ToText Int32
instance FromText Int32
instance ToText Int16
instance FromText Int16
instance ToText Int8
instance FromText Int8
instance ToText Int
instance FromText Int
instance ToText Bool
instance FromText Bool
instance ToText String
instance FromText String
instance ToText Text
instance FromText Text
-- | This module lets you implement <a>Server</a>s for defined APIs. You'll
-- most likely just need <a>serve</a>.
module Servant.Server
-- | <a>serve</a> allows you to implement an API and produce a wai
-- <a>Application</a>.
--
-- Example:
--
-- <pre>
-- type MyApi = "books" :&gt; Get [Book] -- GET /books
-- :&lt;|&gt; "books" :&gt; ReqBody Book :&gt; Post Book -- POST /books
--
-- server :: Server MyApi
-- server = listAllBooks :&lt;|&gt; postBook
-- where listAllBooks = ...
-- postBook book = ...
--
-- app :: Application
-- app = serve myApi server
--
-- main :: IO ()
-- main = Network.Wai.Handler.Warp.run 8080 app
-- </pre>
serve :: HasServer layout => Proxy layout -> Server layout -> Application
toApplication :: RoutingApplication -> Application
data RouteMismatch
-- | the usual "not found" error
NotFound :: RouteMismatch
-- | a more informative "you just got the HTTP method wrong" error
WrongMethod :: RouteMismatch
-- | an even more informative "your json request body wasn't valid" error
InvalidBody :: RouteMismatch
-- | <pre>
-- &gt; mempty = NotFound
-- &gt;
-- &gt; NotFound <a>mappend</a> x = x
-- &gt; WrongMethod <a>mappend</a> InvalidBody = InvalidBody
-- &gt; WrongMethod <a>mappend</a> _ = WrongMethod
-- &gt; InvalidBody <a>mappend</a> _ = InvalidBody
-- </pre>
-- | A wrapper around <tt><a>Either</a> <a>RouteMismatch</a> a</tt>.
newtype RouteResult a
RR :: Either RouteMismatch a -> RouteResult a
routeResult :: RouteResult a -> Either RouteMismatch a
failWith :: RouteMismatch -> RouteResult a
succeedWith :: a -> RouteResult a
isMismatch :: RouteResult a -> Bool
-- | If we get a <a>Right</a>, it has precedence over everything else.
--
-- This in particular means that if we could get several <a>Right</a>s,
-- only the first we encounter would be taken into account.
type RoutingApplication = Request -> (RouteResult Response -> IO ResponseReceived) -> IO ResponseReceived
class HasServer layout where type family Server layout :: *
route :: HasServer layout => Proxy layout -> Server layout -> RoutingApplication
instance Eq RouteMismatch
instance Show RouteMismatch
instance Eq a => Eq (RouteResult a)
instance Show a => Show (RouteResult a)
instance Monoid (RouteResult a)
instance Monoid RouteMismatch
module Servant.API.Sub
-- | The contained API (second argument) can be found under <tt>("/" ++
-- path)</tt> (path being the first argument).
--
-- Example:
--
-- <pre>
-- -- GET /hello/world
-- -- returning a JSON encoded World value
-- type MyApi = "hello" :&gt; "world" :&gt; Get World
-- </pre>
data (:>) (path :: k) a
(:>) :: Proxy path -> a -> (:>) a
-- | Make sure the incoming request starts with <tt>"/path"</tt>, strip it
-- and pass the rest of the request path to <tt>sublayout</tt>.
instance (KnownSymbol path, HasServer sublayout) => HasServer (path :> sublayout)
module Servant.API.Alternative
-- | Union of two APIs, first takes precedence in case of overlap.
--
-- Example:
--
-- <pre>
-- type MyApi = "books" :&gt; Get [Book] -- GET /books
-- :&lt;|&gt; "books" :&gt; ReqBody Book :&gt; Post Book -- POST /books
-- </pre>
data (:<|>) a b
(:<|>) :: a -> b -> (:<|>) a b
-- | A server for <tt>a <a>:&lt;|&gt;</a> b</tt> first tries to match the
-- request again the route represented by <tt>a</tt> and if it fails
-- tries <tt>b</tt>. You must provide a request handler for each route.
--
-- <pre>
-- type MyApi = "books" :&gt; Get [Book] -- GET /books
-- :&lt;|&gt; "books" :&gt; ReqBody Book :&gt; Post Book -- POST /books
--
-- server :: Server MyApi
-- server = listAllBooks :&lt;|&gt; postBook
-- where listAllBooks = ...
-- postBook book = ...
-- </pre>
instance (HasServer a, HasServer b) => HasServer (a :<|> b)
module Servant.API.Capture
-- | Capture a value from the request path under a certain type <tt>a</tt>.
--
-- Example:
--
-- <pre>
-- -- GET /books/:isbn
-- type MyApi = "books" :&gt; Capture "isbn" Text :&gt; Get Book
-- </pre>
data Capture sym a
instance (KnownSymbol capture, FromText a, HasServer sublayout) => HasServer (Capture capture a :> sublayout)
module Servant.API.Header
-- | Extract the given header's value as a value of type <tt>a</tt>.
--
-- Example:
--
-- <pre>
-- newtype Referer = Referer Text
-- deriving (Eq, Show, FromText, ToText)
--
-- -- GET /view-my-referer
-- type MyApi = "view-my-referer" :&gt; Header "from" Referer :&gt; Get Referer
-- </pre>
data Header sym a
-- | If you use <a>Header</a> in one of the endpoints for your API, this
-- automatically requires your server-side handler to be a function that
-- takes an argument of the type specified by <a>Header</a>. This lets
-- servant worry about extracting it from the request and turning it into
-- a value of the type you specify.
--
-- All it asks is for a <a>FromText</a> instance.
--
-- Example:
--
-- <pre>
-- newtype Referer = Referer Text
-- deriving (Eq, Show, FromText, ToText)
--
-- -- GET /view-my-referer
-- type MyApi = "view-my-referer" :&gt; Header "Referer" Referer :&gt; Get Referer
--
-- server :: Server MyApi
-- server = viewReferer
-- where viewReferer :: Referer -&gt; EitherT (Int, String) IO referer
-- viewReferer referer = return referer
-- </pre>
instance (KnownSymbol sym, FromText a, HasServer sublayout) => HasServer (Header sym a :> sublayout)
module Servant.API.QueryParam
-- | Lookup the value associated to the <tt>sym</tt> query string parameter
-- and try to extract it as a value of type <tt>a</tt>.
--
-- Example:
--
-- <pre>
-- -- /books?author=&lt;author name&gt;
-- type MyApi = "books" :&gt; QueryParam "author" Text :&gt; Get [Book]
-- </pre>
data QueryParam sym a
-- | If you use <tt><a>QueryParam</a> "author" Text</tt> in one of the
-- endpoints for your API, this automatically requires your server-side
-- handler to be a function that takes an argument of type
-- <tt><a>Maybe</a> <tt>Text</tt></tt>.
--
-- This lets servant worry about looking it up in the query string and
-- turning it into a value of the type you specify, enclosed in
-- <a>Maybe</a>, because it may not be there and servant would then hand
-- you <a>Nothing</a>.
--
-- You can control how it'll be converted from <tt>Text</tt> to your type
-- by simply providing an instance of <a>FromText</a> for your type.
--
-- Example:
--
-- <pre>
-- type MyApi = "books" :&gt; QueryParam "author" Text :&gt; Get [Book]
--
-- server :: Server MyApi
-- server = getBooksBy
-- where getBooksBy :: Maybe Text -&gt; EitherT (Int, String) IO [Book]
-- getBooksBy Nothing = ...return all books...
-- getBooksBy (Just author) = ...return books by the given author...
-- </pre>
-- | Lookup the values associated to the <tt>sym</tt> query string
-- parameter and try to extract it as a value of type <tt>[a]</tt>. This
-- is typically meant to support query string parameters of the form
-- <tt>param[]=val1&amp;param[]=val2</tt> and so on. Note that servant
-- doesn't actually require the <tt>[]</tt>s and will fetch the values
-- just fine with <tt>param=val1&amp;param=val2</tt>, too.
--
-- Example:
--
-- <pre>
-- -- /books?authors[]=&lt;author1&gt;&amp;authors[]=&lt;author2&gt;&amp;...
-- type MyApi = "books" :&gt; QueryParams "authors" Text :&gt; Get [Book]
-- </pre>
data QueryParams sym a
-- | If you use <tt><a>QueryParams</a> "authors" Text</tt> in one of the
-- endpoints for your API, this automatically requires your server-side
-- handler to be a function that takes an argument of type
-- <tt>[<tt>Text</tt>]</tt>.
--
-- This lets servant worry about looking up 0 or more values in the query
-- string associated to <tt>authors</tt> and turning each of them into a
-- value of the type you specify.
--
-- You can control how the individual values are converted from
-- <tt>Text</tt> to your type by simply providing an instance of
-- <a>FromText</a> for your type.
--
-- Example:
--
-- <pre>
-- type MyApi = "books" :&gt; QueryParams "authors" Text :&gt; Get [Book]
--
-- server :: Server MyApi
-- server = getBooksBy
-- where getBooksBy :: [Text] -&gt; EitherT (Int, String) IO [Book]
-- getBooksBy authors = ...return all books by these authors...
-- </pre>
-- | Lookup a potentially value-less query string parameter with boolean
-- semantics. If the param <tt>sym</tt> is there without any value, or if
-- it's there with value "true" or "1", it's interpreted as <a>True</a>.
-- Otherwise, it's interpreted as <a>False</a>.
--
-- Example:
--
-- <pre>
-- -- /books?published
-- type MyApi = "books" :&gt; QueryFlag "published" :&gt; Get [Book]
-- </pre>
data QueryFlag sym
-- | If you use <tt><a>QueryFlag</a> "published"</tt> in one of the
-- endpoints for your API, this automatically requires your server-side
-- handler to be a function that takes an argument of type <a>Bool</a>.
--
-- Example:
--
-- <pre>
-- type MyApi = "books" :&gt; QueryFlag "published" :&gt; Get [Book]
--
-- server :: Server MyApi
-- server = getBooks
-- where getBooks :: Bool -&gt; EitherT (Int, String) IO [Book]
-- getBooks onlyPublished = ...return all books, or only the ones that are already published, depending on the argument...
-- </pre>
instance (KnownSymbol sym, HasServer sublayout) => HasServer (QueryFlag sym :> sublayout)
instance (KnownSymbol sym, FromText a, HasServer sublayout) => HasServer (QueryParams sym a :> sublayout)
instance (KnownSymbol sym, FromText a, HasServer sublayout) => HasServer (QueryParam sym a :> sublayout)
module Servant.API.ReqBody
-- | Extract the request body as a value of type <tt>a</tt>.
--
-- Example:
--
-- <pre>
-- -- POST /books
-- type MyApi = "books" :&gt; ReqBody Book :&gt; Post Book
-- </pre>
data ReqBody a
-- | If you use <a>ReqBody</a> in one of the endpoints for your API, this
-- automatically requires your server-side handler to be a function that
-- takes an argument of the type specified by <a>ReqBody</a>. This lets
-- servant worry about extracting it from the request and turning it into
-- a value of the type you specify.
--
-- All it asks is for a <a>FromJSON</a> instance.
--
-- Example:
--
-- <pre>
-- type MyApi = "books" :&gt; ReqBody Book :&gt; Post Book
--
-- server :: Server MyApi
-- server = postBook
-- where postBook :: Book -&gt; EitherT (Int, String) IO Book
-- postBook book = ...insert into your db...
-- </pre>
instance (FromJSON a, HasServer sublayout) => HasServer (ReqBody a :> sublayout)
module Servant.API.Get
-- | Endpoint for simple GET requests. Serves the result as JSON.
--
-- Example:
--
-- <pre>
-- type MyApi = "books" :&gt; Get [Book]
-- </pre>
data Get a
-- | When implementing the handler for a <a>Get</a> endpoint, just like for
-- <a>Delete</a>, <a>Post</a> and <a>Put</a>, the handler code runs in
-- the <tt>EitherT (Int, String) IO</tt> monad, where the <a>Int</a>
-- represents the status code and the <a>String</a> a message, returned
-- in case of failure. You can quite handily use <a>left</a> to quickly
-- fail if some conditions are not met.
--
-- If successfully returning a value, we just require that its type has a
-- <a>ToJSON</a> instance and servant takes care of encoding it for you,
-- yielding status code 200 along the way.
instance Typeable Get
instance ToJSON result => HasServer (Get result)
module Servant.API.Post
-- | Endpoint for POST requests. The type variable represents the type of
-- the response body (not the request body, use <a>RQBody</a> for that).
--
-- Example:
--
-- <pre>
-- -- POST /books
-- -- with a JSON encoded Book as the request body
-- -- returning the just-created Book
-- type MyApi = "books" :&gt; ReqBody Book :&gt; Post Book
-- </pre>
data Post a
-- | When implementing the handler for a <a>Post</a> endpoint, just like
-- for <a>Delete</a>, <a>Get</a> and <a>Put</a>, the handler code runs in
-- the <tt>EitherT (Int, String) IO</tt> monad, where the <a>Int</a>
-- represents the status code and the <a>String</a> a message, returned
-- in case of failure. You can quite handily use <a>left</a> to quickly
-- fail if some conditions are not met.
--
-- If successfully returning a value, we just require that its type has a
-- <a>ToJSON</a> instance and servant takes care of encoding it for you,
-- yielding status code 201 along the way.
instance Typeable Post
instance ToJSON a => HasServer (Post a)
module Servant.API.Delete
-- | Combinator for DELETE requests.
--
-- Example:
--
-- <pre>
-- -- DELETE /books/:isbn
-- type MyApi = "books" :&gt; Capture "isbn" Text :&gt; Delete
-- </pre>
data Delete
-- | If you have a <a>Delete</a> endpoint in your API, the handler for this
-- endpoint is meant to delete a resource.
--
-- The code of the handler will, just like for <a>Get</a>, <a>Post</a>
-- and <a>Put</a>, run in <tt>EitherT (Int, String) IO ()</tt>. The
-- <a>Int</a> represents the status code and the <a>String</a> a message
-- to be returned. You can use <a>left</a> to painlessly error out if the
-- conditions for a successful deletion are not met.
instance Typeable Delete
instance HasServer Delete
module Servant.API.Put
-- | Endpoint for PUT requests, usually used to update a ressource. The
-- type <tt>a</tt> is the type of the response body that's returned.
--
-- Example:
--
-- <pre>
-- -- PUT /books/:isbn
-- -- with a Book as request body, returning the updated Book
-- type MyApi = "books" :&gt; Capture "isbn" Text :&gt; ReqBody Book :&gt; Put Book
-- </pre>
data Put a
-- | When implementing the handler for a <a>Put</a> endpoint, just like for
-- <a>Delete</a>, <a>Get</a> and <a>Post</a>, the handler code runs in
-- the <tt>EitherT (Int, String) IO</tt> monad, where the <a>Int</a>
-- represents the status code and the <a>String</a> a message, returned
-- in case of failure. You can quite handily use <a>left</a> to quickly
-- fail if some conditions are not met.
--
-- If successfully returning a value, we just require that its type has a
-- <a>ToJSON</a> instance and servant takes care of encoding it for you,
-- yielding status code 200 along the way.
instance Typeable Put
instance ToJSON a => HasServer (Put a)
-- | QuasiQuoting utilities for API types.
--
-- <a>sitemap</a> allows you to write your type in a very natural way:
--
-- <pre>
-- [sitemap|
-- PUT hello String -&gt; ()
-- POST hello/p:Int String -&gt; ()
-- GET hello/?name:String Int
-- |]
-- </pre>
--
-- Will generate:
--
-- <pre>
-- "hello" :&gt; ReqBody String :&gt; Put ()
-- :&lt;|&gt; "hello" :&gt; Capture "p" Int :&gt; ReqBody String :&gt; Post ()
-- :&lt;|&gt; "hello" :&gt; QueryParam "name" String :&gt; Get Int
-- </pre>
--
-- Note the <tt>/</tt> before a <tt>QueryParam</tt>!
module Servant.QQ
-- | Finally-tagless encoding for our DSL. Keeping <tt>repr'</tt> and
-- <tt>repr</tt> distinct when writing functions with an <tt>ExpSYM</tt>
-- context ensures certain invariants (for instance, that there is only
-- one of <a>get</a>, <a>post</a>, <a>put</a>, and <a>delete</a> in a
-- value), but sometimes requires a little more work.
class ExpSYM repr' repr | repr -> repr', repr' -> repr
lit :: ExpSYM repr' repr => String -> repr' -> repr
capture :: ExpSYM repr' repr => String -> String -> repr -> repr
reqBody :: ExpSYM repr' repr => String -> repr -> repr
queryParam :: ExpSYM repr' repr => String -> String -> repr -> repr
conj :: ExpSYM repr' repr => repr' -> repr -> repr
get :: ExpSYM repr' repr => String -> repr
post :: ExpSYM repr' repr => String -> repr
put :: ExpSYM repr' repr => String -> repr
delete :: ExpSYM repr' repr => String -> repr
(>:) :: Type -> Type -> Type
parseMethod :: ExpSYM repr' repr => Parser (String -> repr)
parseUrlSegment :: ExpSYM repr repr => Parser (repr -> repr)
parseUrl :: ExpSYM repr repr => Parser (repr -> repr)
data Typ
Val :: String -> Typ
ReqArgVal :: String -> String -> Typ
parseTyp :: Parser Typ
parseEntry :: ExpSYM repr repr => Parser repr
blockComment :: Parser ()
inlineComment :: Parser ()
eol :: Parser String
eols :: Parser ()
parseAll :: Parser Type
-- | The sitemap QuasiQuoter.
--
-- <ul>
-- <li><tt>...<i><a>var</a>:<a>type</a></i>...</tt> becomes a
-- capture</li>
-- <li><tt>.../?<a>var</a>:<a>type</a></tt> becomes a query
-- parameter</li>
-- <li><tt><a>method</a> ... <a>typ</a></tt> becomes a method returning
-- <tt><a>typ</a></tt></li>
-- <li><tt><a>method</a> ... <a>typ1</a> -&gt; <a>typ2</a></tt> becomes a
-- method with request body of <tt><a>typ1</a></tt> and returning
-- <tt><a>typ2</a></tt></li>
-- </ul>
--
-- Comments are allowed, and have the standard Haskell format
--
-- <ul>
-- <li><tt>--</tt> for inline</li>
-- <li><tt>{- ... -}</tt> for block</li>
-- </ul>
sitemap :: QuasiQuoter
instance ExpSYM Type Type
-- | Type safe internal links.
--
-- Provides the function <a>mkLink</a>:
--
-- <pre>
-- type API = Proxy ("hello" :&gt; Get Int
-- :<a>|</a> "bye" :&gt; QueryParam "name" String :&gt; Post Bool)
--
-- api :: API
-- api = proxy
--
-- link1 :: Proxy ("hello" :&gt; Get Int)
-- link1 = proxy
--
-- link2 :: Proxy ("hello" :&gt; Delete)
-- link2 = proxy
--
-- mkLink link1 API -- typechecks, returns 'Link "/hello"'
--
-- mkLink link2 API -- doesn't typecheck
-- </pre>
--
-- That is, <a>mkLink</a> takes two arguments, a link proxy and a
-- sitemap, and returns a <a>Link</a>, but only typechecks if the link
-- proxy is a valid link, and part of the sitemap.
--
-- <b>N.B.:</b> <a>mkLink</a> assumes a capture matches any string
-- (without slashes).
module Servant.Utils.Links
-- | The 'ValidLinkIn f s' constraint holds when <tt>s</tt> is an API that
-- contains <tt>f</tt>, and <tt>f</tt> is a link.
class ValidLinkIn f s
mkLink :: ValidLinkIn f s => f -> s -> Link
data Link
Link :: String -> Link
class VLinkHelper f
vlh :: VLinkHelper f => proxy f -> String
instance Show Link
instance VLinkHelper (Post x)
instance VLinkHelper (Get x)
instance (KnownSymbol s, VLinkHelper e) => VLinkHelper (s :> e)
instance (IsElem f s ~ 'True, IsLink f ~ 'True, VLinkHelper f) => ValidLinkIn f s
module Servant.API.Raw
-- | Endpoint for plugging in your own Wai <a>Application</a>s.
--
-- The given <a>Application</a> will get the request as received by the
-- server, potentially with a modified (stripped) <a>pathInfo</a> if the
-- <a>Application</a> is being routed with <a>:&gt;</a>.
--
-- In addition to just letting you plug in your existing WAI
-- <a>Application</a>s, this can also be used with <a>serveDirectory</a>
-- to serve static files stored in a particular directory on your
-- filesystem, or to serve your API's documentation with
-- <a>serveDocumentation</a>.
data Raw
-- | Just pass the request to the underlying application and serve its
-- response.
--
-- Example:
--
-- <pre>
-- type MyApi = "images" :&gt; Raw
--
-- server :: Server MyApi
-- server = serveDirectory "/var/www/images"
-- </pre>
instance HasServer Raw
-- | This module defines a sever-side handler that lets you serve static
-- files.
--
-- <ul>
-- <li><a>serveDirectory</a> lets you serve anything that lives under a
-- particular directory on your filesystem.</li>
-- </ul>
module Servant.Utils.StaticFiles
-- | Serve anything under the specified directory as a <a>Raw</a> endpoint.
--
-- <pre>
-- type MyApi = "static" :&gt; Raw
--
-- server :: Server MyApi
-- server = serveDirectory "/var/www"
-- </pre>
--
-- would capture any request to <tt>/static/&lt;something&gt;</tt> and
-- look for <tt>&lt;something&gt;</tt> under <tt>/var/www</tt>.
--
-- It will do its best to guess the MIME type for that file, based on the
-- extension, and send an appropriate <i>Content-Type</i> header if
-- possible.
--
-- If your goal is to serve HTML, CSS and Javascript files that use the
-- rest of the API as a webapp backend, you will most likely not want the
-- static files to be hidden behind a <i>/static/</i> prefix. In that
-- case, remember to put the <a>serveDirectory</a> handler in the last
-- position, because <i>servant</i> will try to match the handlers in
-- order.
serveDirectory :: FilePath -> Server Raw
module Servant.API
module Servant
-- | A concrete, poly-kinded proxy type
data Proxy (t :: k) :: k -> *
Proxy :: Proxy