Safe Haskell | None |
---|---|
Language | Haskell2010 |
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:
- 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.
- data JSON
- data PlainText
- data FormUrlEncoded
- data OctetStream
- class Accept ctype where
- class Accept ctype => MimeRender ctype a where
- class Accept ctype => MimeUnrender ctype a where
- data NoContent = NoContent
- newtype AcceptHeader = AcceptHeader ByteString
- class AllMime list => AllCTRender list a where
- class AllCTUnrender list a where
- class AllMime list where
- class AllMime list => AllMimeRender list a where
- class AllMime list => AllMimeUnrender list a where
- eitherDecodeLenient :: FromJSON a => ByteString -> Either String a
- canHandleAcceptH :: AllMime list => Proxy list -> AcceptHeader -> Bool
Provided Content-Types
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 # | |
data FormUrlEncoded Source #
Accept * FormUrlEncoded Source # | application/x-www-form-urlencoded |
FromForm a => MimeUnrender * FormUrlEncoded a Source # |
|
ToForm a => MimeRender * FormUrlEncoded a Source # |
|
data OctetStream Source #
Accept * OctetStream Source # | application/octet-stream |
MimeUnrender * OctetStream ByteString Source # | Right . toStrict |
MimeUnrender * OctetStream ByteString Source # | Right . id |
MimeRender * OctetStream ByteString Source # | |
MimeRender * OctetStream ByteString Source # | id |
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") :}
contentType :: Proxy ctype -> MediaType Source #
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
mimeRender :: Proxy ctype -> a -> ByteString Source #
MimeRender * OctetStream ByteString Source # | |
MimeRender * OctetStream ByteString Source # | id |
ToForm a => MimeRender * FormUrlEncoded a Source # |
|
MimeRender * PlainText String Source # | BC.pack |
MimeRender * PlainText Text Source # | fromStrict . TextS.encodeUtf8 |
MimeRender * PlainText Text Source # | |
ToJSON a => MimeRender * JSON a Source # | |
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
mimeUnrender :: Proxy ctype -> ByteString -> Either String a Source #
mimeUnrenderWithType :: Proxy ctype -> MediaType -> ByteString -> Either String a Source #
MimeUnrender * OctetStream ByteString Source # | Right . toStrict |
MimeUnrender * OctetStream ByteString Source # | Right . id |
FromForm a => MimeUnrender * FormUrlEncoded a Source # |
|
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 # |
|
NoContent
A type for responses without content-body.
Eq NoContent Source # | |
Read NoContent Source # | |
Show NoContent Source # | |
Generic NoContent Source # | |
AllMime ((:) * ctyp ((:) * ctyp' ctyps)) => AllMimeRender ((:) * ctyp ((:) * ctyp' ctyps)) NoContent Source # | |
Accept * ctyp => AllMimeRender ((:) * ctyp ([] *)) NoContent Source # | |
type Rep NoContent Source # | |
Internal
newtype AcceptHeader Source #
class AllMime list => AllCTRender list a where Source #
handleAcceptH :: Proxy list -> AcceptHeader -> a -> Maybe (ByteString, ByteString) Source #
TypeError Constraint (Text "No instance for (), use NoContent instead.") => AllCTRender ([] *) () Source # | |
(Accept * ct, AllMime cts, AllMimeRender ((:) * ct cts) a) => AllCTRender ((:) * ct cts) a Source # | |
class AllCTUnrender list a where Source #
canHandleCTypeH :: Proxy list -> ByteString -> Maybe (ByteString -> Either String a) Source #
handleCTypeH :: Proxy list -> ByteString -> ByteString -> Maybe (Either String a) Source #
AllMimeUnrender ctyps a => AllCTUnrender ctyps a Source # | |
class AllMime list => AllMimeRender list a where Source #
allMimeRender :: Proxy list -> a -> [(MediaType, ByteString)] Source #
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 #
allMimeUnrender :: Proxy list -> [(MediaType, ByteString -> Either String a)] Source #
AllMimeUnrender ([] *) a Source # | |
(MimeUnrender * ctyp a, AllMimeUnrender ctyps a) => AllMimeUnrender ((:) * ctyp ctyps) 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"
canHandleAcceptH :: AllMime list => Proxy list -> AcceptHeader -> Bool Source #