servant-0.16.2: 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 PlainText Source #

Instances
Accept PlainText Source #
text/plain;charset=utf-8
Instance details

Defined in Servant.API.ContentTypes

MimeUnrender PlainText String Source #
Right . BC.unpack
Instance details

Defined in Servant.API.ContentTypes

MimeUnrender PlainText Text Source #
left show . TextS.decodeUtf8' . toStrict
Instance details

Defined in Servant.API.ContentTypes

MimeUnrender PlainText Text Source #
left show . TextL.decodeUtf8'
Instance details

Defined in Servant.API.ContentTypes

MimeRender PlainText String Source #
BC.pack
Instance details

Defined in Servant.API.ContentTypes

MimeRender PlainText Text Source #
fromStrict . TextS.encodeUtf8
Instance details

Defined in Servant.API.ContentTypes

MimeRender PlainText Text Source #

encodeUtf8

Instance details

Defined in Servant.API.ContentTypes

data FormUrlEncoded Source #

Instances
Accept FormUrlEncoded Source #
application/x-www-form-urlencoded
Instance details

Defined in Servant.API.ContentTypes

FromForm a => MimeUnrender FormUrlEncoded a Source #

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

Instance details

Defined in Servant.API.ContentTypes

ToForm a => MimeRender FormUrlEncoded a Source #

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

Instance details

Defined in Servant.API.ContentTypes

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")
:}

Minimal complete definition

contentType | contentTypes

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 a 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

Instance details

Defined in Servant.API.ContentTypes

MimeRender OctetStream ByteString Source #
id
Instance details

Defined in Servant.API.ContentTypes

ToForm a => MimeRender FormUrlEncoded a Source #

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

Instance details

Defined in Servant.API.ContentTypes

MimeRender PlainText String Source #
BC.pack
Instance details

Defined in Servant.API.ContentTypes

MimeRender PlainText Text Source #
fromStrict . TextS.encodeUtf8
Instance details

Defined in Servant.API.ContentTypes

MimeRender PlainText Text Source #

encodeUtf8

Instance details

Defined in Servant.API.ContentTypes

ToJSON a => MimeRender JSON a Source #

encode

Instance details

Defined in Servant.API.ContentTypes

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

Minimal complete definition

mimeUnrender | mimeUnrenderWithType

Methods

mimeUnrender :: Proxy ctype -> ByteString -> Either String a Source #

mimeUnrenderWithType :: Proxy ctype -> MediaType -> ByteString -> Either String a Source #

Variant which is given the actual MediaType provided by the other party.

In the most cases you don't want to branch based on the MediaType. See pr552 for a motivating example.

Instances
MimeUnrender OctetStream ByteString Source #
Right . toStrict
Instance details

Defined in Servant.API.ContentTypes

MimeUnrender OctetStream ByteString Source #
Right . id
Instance details

Defined in Servant.API.ContentTypes

FromForm a => MimeUnrender FormUrlEncoded a Source #

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

Instance details

Defined in Servant.API.ContentTypes

MimeUnrender PlainText String Source #
Right . BC.unpack
Instance details

Defined in Servant.API.ContentTypes

MimeUnrender PlainText Text Source #
left show . TextS.decodeUtf8' . toStrict
Instance details

Defined in Servant.API.ContentTypes

MimeUnrender PlainText Text Source #
left show . TextL.decodeUtf8'
Instance details

Defined in Servant.API.ContentTypes

FromJSON a => MimeUnrender JSON a Source #

eitherDecode

Instance details

Defined in Servant.API.ContentTypes

NoContent

data NoContent Source #

A type for responses without content-body.

Constructors

NoContent 
Instances
Eq NoContent Source # 
Instance details

Defined in Servant.API.ContentTypes

Read NoContent Source # 
Instance details

Defined in Servant.API.ContentTypes

Show NoContent Source # 
Instance details

Defined in Servant.API.ContentTypes

Generic NoContent Source # 
Instance details

Defined in Servant.API.ContentTypes

Associated Types

type Rep NoContent :: Type -> Type #

NFData NoContent Source # 
Instance details

Defined in Servant.API.ContentTypes

Methods

rnf :: NoContent -> () #

AllMime (ctyp ': (ctyp' ': ctyps)) => AllMimeRender (ctyp ': (ctyp' ': ctyps)) NoContent Source # 
Instance details

Defined in Servant.API.ContentTypes

Methods

allMimeRender :: Proxy (ctyp ': (ctyp' ': ctyps)) -> NoContent -> [(MediaType, ByteString)] Source #

Accept ctyp => AllMimeRender (ctyp ': ([] :: [Type])) NoContent Source # 
Instance details

Defined in Servant.API.ContentTypes

Methods

allMimeRender :: Proxy (ctyp ': []) -> NoContent -> [(MediaType, ByteString)] Source #

type Rep NoContent Source # 
Instance details

Defined in Servant.API.ContentTypes

type Rep NoContent = D1 (MetaData "NoContent" "Servant.API.ContentTypes" "servant-0.16.2-1OAYwP8NEHm2UuKAfDx1wh" False) (C1 (MetaCons "NoContent" PrefixI False) (U1 :: Type -> Type))

Internal

newtype AcceptHeader Source #

Constructors

AcceptHeader ByteString 
Instances
Eq AcceptHeader Source # 
Instance details

Defined in Servant.API.ContentTypes

Read AcceptHeader Source # 
Instance details

Defined in Servant.API.ContentTypes

Show AcceptHeader Source # 
Instance details

Defined in Servant.API.ContentTypes

Generic AcceptHeader Source # 
Instance details

Defined in Servant.API.ContentTypes

Associated Types

type Rep AcceptHeader :: Type -> Type #

type Rep AcceptHeader Source # 
Instance details

Defined in Servant.API.ContentTypes

type Rep AcceptHeader = D1 (MetaData "AcceptHeader" "Servant.API.ContentTypes" "servant-0.16.2-1OAYwP8NEHm2UuKAfDx1wh" True) (C1 (MetaCons "AcceptHeader" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ByteString)))

class AllMime list => AllCTRender (list :: [*]) a where Source #

Instances
(TypeError (Text "No instance for (), use NoContent instead.") :: Constraint) => AllCTRender ([] :: [Type]) () Source # 
Instance details

Defined in Servant.API.ContentTypes

(Accept ct, AllMime cts, AllMimeRender (ct ': cts) a) => AllCTRender (ct ': cts) a Source # 
Instance details

Defined in Servant.API.ContentTypes

Methods

handleAcceptH :: Proxy (ct ': cts) -> AcceptHeader -> a -> Maybe (ByteString, ByteString) Source #

class AllCTUnrender (list :: [*]) a where Source #

Minimal complete definition

canHandleCTypeH

Instances
AllMimeUnrender ctyps a => AllCTUnrender ctyps a Source # 
Instance details

Defined in Servant.API.ContentTypes

class AllMime (list :: [*]) where Source #

Methods

allMime :: Proxy list -> [MediaType] Source #

Instances
AllMime ([] :: [Type]) Source # 
Instance details

Defined in Servant.API.ContentTypes

Methods

allMime :: Proxy [] -> [MediaType] Source #

(Accept ctyp, AllMime ctyps) => AllMime (ctyp ': ctyps) Source # 
Instance details

Defined in Servant.API.ContentTypes

Methods

allMime :: Proxy (ctyp ': ctyps) -> [MediaType] 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 # 
Instance details

Defined in Servant.API.ContentTypes

Methods

allMimeRender :: Proxy (ctyp ': (ctyp' ': ctyps)) -> NoContent -> [(MediaType, ByteString)] Source #

Accept ctyp => AllMimeRender (ctyp ': ([] :: [Type])) NoContent Source # 
Instance details

Defined in Servant.API.ContentTypes

Methods

allMimeRender :: Proxy (ctyp ': []) -> NoContent -> [(MediaType, ByteString)] Source #

(MimeRender ctyp a, AllMimeRender (ctyp' ': ctyps) a) => AllMimeRender (ctyp ': (ctyp' ': ctyps)) a Source # 
Instance details

Defined in Servant.API.ContentTypes

Methods

allMimeRender :: Proxy (ctyp ': (ctyp' ': ctyps)) -> a -> [(MediaType, ByteString)] Source #

MimeRender ctyp a => AllMimeRender (ctyp ': ([] :: [Type])) a Source # 
Instance details

Defined in Servant.API.ContentTypes

Methods

allMimeRender :: Proxy (ctyp ': []) -> a -> [(MediaType, ByteString)] Source #

class AllMime list => AllMimeUnrender (list :: [*]) a where Source #

Instances
AllMimeUnrender ([] :: [Type]) a Source # 
Instance details

Defined in Servant.API.ContentTypes

(MimeUnrender ctyp a, AllMimeUnrender ctyps a) => AllMimeUnrender (ctyp ': ctyps) a Source # 
Instance details

Defined in Servant.API.ContentTypes

Methods

allMimeUnrender :: Proxy (ctyp ': ctyps) -> [(MediaType, ByteString -> Either String a)] 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"