| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Servant.API.ContentTypes
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 :> Put '[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:
- Declare a new data type with no constructors (e.g. data HTML).
- Make an instance of it for Accept.
- If you want to be able to serialize data *into* that
      Content-Type, make an instance of it for MimeRender.
- 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
- data JSON
- data PlainText
- data FormUrlEncoded
- data OctetStream
- data EventStream
- class Accept (ctype :: k) where- contentType :: Proxy ctype -> MediaType
- contentTypes :: Proxy ctype -> NonEmpty MediaType
 
- class Accept ctype => MimeRender (ctype :: k) a where- mimeRender :: Proxy ctype -> a -> ByteString
 
- class Accept ctype => MimeUnrender (ctype :: k) a where- mimeUnrender :: Proxy ctype -> ByteString -> Either String a
- mimeUnrenderWithType :: Proxy ctype -> MediaType -> ByteString -> Either String a
 
- data NoContent = NoContent
- newtype AcceptHeader = AcceptHeader ByteString
- class AllMime list => AllCTRender (list :: [Type]) a where- handleAcceptH :: Proxy list -> AcceptHeader -> a -> Maybe (ByteString, ByteString)
 
- class AllCTUnrender (list :: [Type]) a where- canHandleCTypeH :: Proxy list -> ByteString -> Maybe (ByteString -> Either String a)
- handleCTypeH :: Proxy list -> ByteString -> ByteString -> Maybe (Either String a)
 
- class AllMime (list :: [Type]) where
- class AllMime list => AllMimeRender (list :: [Type]) a where- allMimeRender :: Proxy list -> a -> [(MediaType, ByteString)]
 
- class AllMime list => AllMimeUnrender (list :: [Type]) a where- allMimeUnrender :: Proxy list -> [(MediaType, ByteString -> Either String a)]
 
- eitherDecodeLenient :: FromJSON a => ByteString -> Either String a
- canHandleAcceptH :: forall (list :: [Type]). AllMime list => Proxy list -> AcceptHeader -> Bool
- newtype EventStreamChunk = EventStreamChunk {}
Provided Content-Types
Instances
| Accept JSON Source # | application/json | 
| Defined in Servant.API.ContentTypes | |
| ToJSON a => MimeRender JSON a Source # | |
| Defined in Servant.API.ContentTypes Methods mimeRender :: Proxy JSON -> a -> ByteString Source # | |
| FromJSON a => MimeUnrender JSON a Source # | |
| Defined in Servant.API.ContentTypes Methods mimeUnrender :: Proxy JSON -> ByteString -> Either String a Source # mimeUnrenderWithType :: Proxy JSON -> MediaType -> ByteString -> Either String a Source # | |
| MimeRender JSON a => MimeRender JSON (WithStatus _status a) Source # | |
| Defined in Servant.API.UVerb Methods mimeRender :: Proxy JSON -> WithStatus _status a -> ByteString Source # | |
| MimeUnrender JSON a => MimeUnrender JSON (WithStatus _status a) Source # | |
| Defined in Servant.API.UVerb Methods mimeUnrender :: Proxy JSON -> ByteString -> Either String (WithStatus _status a) Source # mimeUnrenderWithType :: Proxy JSON -> MediaType -> ByteString -> Either String (WithStatus _status a) Source # | |
Instances
data FormUrlEncoded Source #
Instances
data OctetStream Source #
Instances
data EventStream Source #
Instances
| Accept EventStream Source # | text/event-stream | 
| Defined in Servant.API.ContentTypes Methods contentType :: Proxy EventStream -> MediaType Source # contentTypes :: Proxy EventStream -> NonEmpty MediaType Source # | |
| MimeUnrender EventStream EventStreamChunk Source # | |
| Defined in Servant.API.ContentTypes Methods mimeUnrender :: Proxy EventStream -> ByteString -> Either String EventStreamChunk Source # mimeUnrenderWithType :: Proxy EventStream -> MediaType -> ByteString -> Either String EventStreamChunk Source # | |
Building your own Content-Type
class Accept (ctype :: k) 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
Methods
contentType :: Proxy ctype -> MediaType Source #
Instances
| Accept EventStream Source # | text/event-stream | 
| Defined in Servant.API.ContentTypes Methods contentType :: Proxy EventStream -> MediaType Source # contentTypes :: Proxy EventStream -> NonEmpty MediaType Source # | |
| Accept FormUrlEncoded Source # | application/x-www-form-urlencoded | 
| Defined in Servant.API.ContentTypes Methods contentType :: Proxy FormUrlEncoded -> MediaType Source # contentTypes :: Proxy FormUrlEncoded -> NonEmpty MediaType Source # | |
| Accept JSON Source # | application/json | 
| Defined in Servant.API.ContentTypes | |
| Accept OctetStream Source # | application/octet-stream | 
| Defined in Servant.API.ContentTypes Methods contentType :: Proxy OctetStream -> MediaType Source # contentTypes :: Proxy OctetStream -> NonEmpty MediaType Source # | |
| Accept PlainText Source # | text/plain;charset=utf-8 | 
| Defined in Servant.API.ContentTypes | |
class Accept ctype => MimeRender (ctype :: k) 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] IntMethods
mimeRender :: Proxy ctype -> a -> ByteString Source #
Instances
class Accept ctype => MimeUnrender (ctype :: k) 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
Methods
mimeUnrender :: Proxy ctype -> ByteString -> Either String a Source #
mimeUnrenderWithType :: Proxy ctype -> MediaType -> ByteString -> Either String a Source #
Instances
NoContent
A type for responses without content-body.
Constructors
| NoContent | 
Instances
| Generic NoContent Source # | |||||
| Defined in Servant.API.ContentTypes | |||||
| Read NoContent Source # | |||||
| Show NoContent Source # | |||||
| NFData NoContent Source # | |||||
| Defined in Servant.API.ContentTypes | |||||
| Eq NoContent Source # | |||||
| HasStatus NoContent Source # | If an API can respond with  | ||||
| Defined in Servant.API.UVerb Associated Types 
 | |||||
| AllMime (ctyp ': (ctyp' ': ctyps)) => AllMimeRender (ctyp ': (ctyp' ': ctyps)) NoContent Source # | |||||
| Defined in Servant.API.ContentTypes Methods allMimeRender :: Proxy (ctyp ': (ctyp' ': ctyps)) -> NoContent -> [(MediaType, ByteString)] Source # | |||||
| Accept ctyp => AllMimeRender '[ctyp] NoContent Source # | |||||
| Defined in Servant.API.ContentTypes Methods allMimeRender :: Proxy '[ctyp] -> NoContent -> [(MediaType, ByteString)] Source # | |||||
| type Rep NoContent Source # | |||||
| type StatusOf NoContent Source # | |||||
| Defined in Servant.API.UVerb | |||||
Internal
newtype AcceptHeader Source #
Constructors
| AcceptHeader ByteString | 
Instances
class AllMime list => AllCTRender (list :: [Type]) a where Source #
Methods
handleAcceptH :: Proxy list -> AcceptHeader -> a -> Maybe (ByteString, ByteString) Source #
Instances
| (TypeError ('Text "No instance for (), use NoContent instead.") :: Constraint) => AllCTRender ('[] :: [Type]) () Source # | |
| Defined in Servant.API.ContentTypes Methods handleAcceptH :: Proxy ('[] :: [Type]) -> AcceptHeader -> () -> Maybe (ByteString, ByteString) Source # | |
| (Accept ct, AllMime cts, AllMimeRender (ct ': cts) a) => AllCTRender (ct ': cts) a Source # | |
| Defined in Servant.API.ContentTypes Methods handleAcceptH :: Proxy (ct ': cts) -> AcceptHeader -> a -> Maybe (ByteString, ByteString) Source # | |
class AllCTUnrender (list :: [Type]) a where Source #
Minimal complete definition
Methods
canHandleCTypeH :: Proxy list -> ByteString -> Maybe (ByteString -> Either String a) Source #
handleCTypeH :: Proxy list -> ByteString -> ByteString -> Maybe (Either String a) Source #
Instances
| AllMimeUnrender ctyps a => AllCTUnrender ctyps a Source # | |
| Defined in Servant.API.ContentTypes Methods canHandleCTypeH :: Proxy ctyps -> ByteString -> Maybe (ByteString -> Either String a) Source # handleCTypeH :: Proxy ctyps -> ByteString -> ByteString -> Maybe (Either String a) Source # | |
class AllMime list => AllMimeRender (list :: [Type]) a where Source #
Methods
allMimeRender :: Proxy list -> a -> [(MediaType, ByteString)] Source #
Instances
| AllMime (ctyp ': (ctyp' ': ctyps)) => AllMimeRender (ctyp ': (ctyp' ': ctyps)) NoContent Source # | |
| Defined in Servant.API.ContentTypes Methods allMimeRender :: Proxy (ctyp ': (ctyp' ': ctyps)) -> NoContent -> [(MediaType, ByteString)] Source # | |
| (MimeRender ctyp a, AllMimeRender (ctyp' ': ctyps) a) => AllMimeRender (ctyp ': (ctyp' ': ctyps)) a Source # | |
| Defined in Servant.API.ContentTypes Methods allMimeRender :: Proxy (ctyp ': (ctyp' ': ctyps)) -> a -> [(MediaType, ByteString)] Source # | |
| Accept ctyp => AllMimeRender '[ctyp] NoContent Source # | |
| Defined in Servant.API.ContentTypes Methods allMimeRender :: Proxy '[ctyp] -> NoContent -> [(MediaType, ByteString)] Source # | |
| MimeRender ctyp a => AllMimeRender '[ctyp] a Source # | |
| Defined in Servant.API.ContentTypes Methods allMimeRender :: Proxy '[ctyp] -> a -> [(MediaType, ByteString)] Source # | |
class AllMime list => AllMimeUnrender (list :: [Type]) a where Source #
Methods
allMimeUnrender :: Proxy list -> [(MediaType, ByteString -> Either String a)] Source #
Instances
| AllMimeUnrender ('[] :: [Type]) a Source # | |
| Defined in Servant.API.ContentTypes Methods allMimeUnrender :: Proxy ('[] :: [Type]) -> [(MediaType, ByteString -> Either String a)] Source # | |
| (MimeUnrender ctyp a, AllMimeUnrender ctyps a) => AllMimeUnrender (ctyp ': ctyps) a Source # | |
| Defined in Servant.API.ContentTypes Methods allMimeUnrender :: Proxy (ctyp ': ctyps) -> [(MediaType, ByteString -> Either String a)] Source # | |
eitherDecodeLenient :: FromJSON a => ByteString -> Either String a Source #
Deprecated: use eitherDecode instead
Deprecated: since aeson version 0.9 eitherDecode has lenient behavior.
canHandleAcceptH :: forall (list :: [Type]). AllMime list => Proxy list -> AcceptHeader -> Bool Source #
newtype EventStreamChunk Source #
Chunk of an event stream
Constructors
| EventStreamChunk | |
| Fields | |
Instances
| MimeUnrender EventStream EventStreamChunk Source # | |
| Defined in Servant.API.ContentTypes Methods mimeUnrender :: Proxy EventStream -> ByteString -> Either String EventStreamChunk Source # mimeUnrenderWithType :: Proxy EventStream -> MediaType -> ByteString -> Either String EventStreamChunk Source # | |