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

Safe HaskellNone
LanguageHaskell2010

Servant.API.ContentTypes

Contents

Description

A collection of basic Content-Types (also known as Internet Media Types, or MIME types). Additionally, this module provides classes that encapsulate how to serialize or deserialize values to or from a particular Content-Type.

Content-Types are used in ReqBody and the method combinators:

>>> type MyEndpoint = ReqBody '[JSON, PlainText] Book :> Get '[JSON, PlainText] Book

Meaning the endpoint accepts requests of Content-Type application/json or text/plain;charset-utf8, and returns data in either one of those formats (depending on the Accept header).

If you would like to support Content-Types beyond those provided here, then:

  1. Declare a new data type with no constructors (e.g. data HTML).
  2. Make an instance of it for Accept.
  3. If you want to be able to serialize data *into* that Content-Type, make an instance of it for MimeRender.
  4. If you want to be able to deserialize data *from* that Content-Type, make an instance of it for MimeUnrender.

Note that roles are reversed in servant-server and servant-client: to be able to serve (or even typecheck) a Get '[JSON, XML] MyData, you'll need to have the appropriate MimeRender instances in scope, whereas to query that endpoint with servant-client, you'll need a MimeUnrender instance in scope.

Synopsis

Provided Content-Types

data JSON Source

Instances

Accept * JSON Source
application/json
FromJSON a => MimeUnrender * JSON a Source

eitherDecode

ToJSON a => MimeRender * JSON a Source

encode

data PlainText Source

Instances

Accept * PlainText Source
text/plain;charset=utf-8
MimeUnrender * PlainText String Source
Right . BC.unpack
MimeUnrender * PlainText Text Source
left show . TextS.decodeUtf8' . toStrict
MimeUnrender * PlainText Text Source
left show . TextL.decodeUtf8'
MimeRender * PlainText String Source
BC.pack
MimeRender * PlainText Text Source
fromStrict . TextS.encodeUtf8
MimeRender * PlainText Text Source

encodeUtf8

data FormUrlEncoded Source

Instances

Accept * FormUrlEncoded Source
application/x-www-form-urlencoded
FromFormUrlEncoded a => MimeUnrender * FormUrlEncoded a Source

decodeFormUrlEncoded >=> fromFormUrlEncoded Note that the mimeUnrender p (mimeRender p x) == Right x law only holds if every element of x is non-null (i.e., not ("", ""))

ToFormUrlEncoded a => MimeRender * FormUrlEncoded a Source

encodeFormUrlEncoded . toFormUrlEncoded Note that the mimeUnrender p (mimeRender p x) == Right x law only holds if every element of x is non-null (i.e., not ("", ""))

Building your own Content-Type

class Accept ctype where Source

Instances of Accept represent mimetypes. They are used for matching against the Accept HTTP header of the request, and for setting the Content-Type header of the response

Example:

>>> import Network.HTTP.Media ((//), (/:))
>>> data HTML
>>> :{
instance Accept HTML where
   contentType _ = "text" // "html" /: ("charset", "utf-8")
:}

Methods

contentType :: Proxy ctype -> MediaType Source

Instances

Accept * OctetStream Source
application/octet-stream
Accept * FormUrlEncoded Source
application/x-www-form-urlencoded
Accept * PlainText Source
text/plain;charset=utf-8
Accept * JSON Source
application/json

class Accept ctype => MimeRender ctype a where Source

Instantiate this class to register a way of serializing a type based on the Accept header.

Example:

data MyContentType

instance Accept MyContentType where
   contentType _ = "example" // "prs.me.mine" /: ("charset", "utf-8")

instance Show a => MimeRender MyContentType where
   mimeRender _ val = pack ("This is MINE! " ++ show val)

type MyAPI = "path" :> Get '[MyContentType] Int

Methods

mimeRender :: Proxy ctype -> a -> ByteString Source

Instances

MimeRender * OctetStream ByteString Source

fromStrict

MimeRender * OctetStream ByteString Source
id
ToFormUrlEncoded a => MimeRender * FormUrlEncoded a Source

encodeFormUrlEncoded . toFormUrlEncoded Note that the mimeUnrender p (mimeRender p x) == Right x law only holds if every element of x is non-null (i.e., not ("", ""))

MimeRender * PlainText String Source
BC.pack
MimeRender * PlainText Text Source
fromStrict . TextS.encodeUtf8
MimeRender * PlainText Text Source

encodeUtf8

ToJSON a => MimeRender * JSON a Source

encode

class Accept ctype => MimeUnrender ctype a where Source

Instantiate this class to register a way of deserializing a type based on the request's Content-Type header.

>>> import Network.HTTP.Media hiding (Accept)
>>> import qualified Data.ByteString.Lazy.Char8 as BSC
>>> data MyContentType = MyContentType String
>>> :{
instance Accept MyContentType where
   contentType _ = "example" // "prs.me.mine" /: ("charset", "utf-8")
:}
>>> :{
instance Read a => MimeUnrender MyContentType a where
   mimeUnrender _ bs = case BSC.take 12 bs of
     "MyContentType" -> return . read . BSC.unpack $ BSC.drop 12 bs
     _ -> Left "didn't start with the magic incantation"
:}
>>> type MyAPI = "path" :> ReqBody '[MyContentType] Int :> Get '[JSON] Int

Instances

MimeUnrender * OctetStream ByteString Source
Right . toStrict
MimeUnrender * OctetStream ByteString Source
Right . id
FromFormUrlEncoded a => MimeUnrender * FormUrlEncoded a Source

decodeFormUrlEncoded >=> fromFormUrlEncoded Note that the mimeUnrender p (mimeRender p x) == Right x law only holds if every element of x is non-null (i.e., not ("", ""))

MimeUnrender * PlainText String Source
Right . BC.unpack
MimeUnrender * PlainText Text Source
left show . TextS.decodeUtf8' . toStrict
MimeUnrender * PlainText Text Source
left show . TextL.decodeUtf8'
FromJSON a => MimeUnrender * JSON a Source

eitherDecode

NoContent

data NoContent Source

A type for responses without content-body.

Constructors

NoContent 

Instances

Eq NoContent Source 
Read NoContent Source 
Show NoContent Source 
AllMime ((:) * ctyp ((:) * ctyp' ctyps)) => AllMimeRender ((:) * ctyp ((:) * ctyp' ctyps)) NoContent Source 
Accept * ctyp => AllMimeRender ((:) * ctyp ([] *)) NoContent Source 

Internal

class AllMime list => AllCTRender list a where Source

Instances

(Accept * ct, AllMime cts, AllMimeRender ((:) * ct cts) a) => AllCTRender ((:) * ct cts) a Source 

class AllCTUnrender list a where Source

Instances

AllMimeUnrender ctyps a => AllCTUnrender ctyps a Source 

class AllMime list where Source

Methods

allMime :: Proxy list -> [MediaType] Source

Instances

AllMime ([] *) Source 
(Accept * ctyp, AllMime ctyps) => AllMime ((:) * ctyp ctyps) Source 

class AllMime list => AllMimeRender list a where Source

Methods

allMimeRender :: Proxy list -> a -> [(MediaType, ByteString)] Source

Instances

AllMime ((:) * ctyp ((:) * ctyp' ctyps)) => AllMimeRender ((:) * ctyp ((:) * ctyp' ctyps)) NoContent Source 
Accept * ctyp => AllMimeRender ((:) * ctyp ([] *)) NoContent Source 
(MimeRender * ctyp a, AllMimeRender ((:) * ctyp' ctyps) a) => AllMimeRender ((:) * ctyp ((:) * ctyp' ctyps)) a Source 
MimeRender * ctyp a => AllMimeRender ((:) * ctyp ([] *)) a Source 

class AllMime list => AllMimeUnrender list a where Source

Instances

AllMimeUnrender ([] *) a Source 
(MimeUnrender * ctyp a, AllMimeUnrender ctyps a) => AllMimeUnrender ((:) * ctyp ctyps) a Source 

class FromFormUrlEncoded a where Source

A type that can be converted from application/x-www-form-urlencoded, with the possibility of failure.

class ToFormUrlEncoded a where Source

A type that can be converted to application/x-www-form-urlencoded

Methods

toFormUrlEncoded :: a -> [(Text, Text)] Source

eitherDecodeLenient :: FromJSON a => ByteString -> Either String a Source

Like eitherDecode but allows all JSON values instead of just objects and arrays.

Will handle trailing whitespace, but not trailing junk. ie.

>>> eitherDecodeLenient "1 " :: Either String Int
Right 1
>>> eitherDecodeLenient "1 junk" :: Either String Int
Left "trailing junk after valid JSON: endOfInput"