{-# LANGUAGE DuplicateRecordFields #-}
module PostgREST.ContentType
( ContentType(..)
, toHeader
, toMime
, decodeContentType
) where
import qualified Data.ByteString as BS
import qualified Data.ByteString.Internal as BS (c2w)
import Network.HTTP.Types.Header (Header, hContentType)
import Protolude
data ContentType
= CTApplicationJSON
| CTSingularJSON
| CTTextCSV
| CTTextPlain
| CTOpenAPI
| CTUrlEncoded
| CTOctetStream
| CTAny
| CTOther ByteString
deriving (ContentType -> ContentType -> Bool
(ContentType -> ContentType -> Bool)
-> (ContentType -> ContentType -> Bool) -> Eq ContentType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ContentType -> ContentType -> Bool
$c/= :: ContentType -> ContentType -> Bool
== :: ContentType -> ContentType -> Bool
$c== :: ContentType -> ContentType -> Bool
Eq)
toHeader :: ContentType -> Header
ContentType
ct = (HeaderName
hContentType, ContentType -> ByteString
toMime ContentType
ct ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
charset)
where
charset :: ByteString
charset = case ContentType
ct of
ContentType
CTOctetStream -> ByteString
forall a. Monoid a => a
mempty
CTOther ByteString
_ -> ByteString
forall a. Monoid a => a
mempty
ContentType
_ -> ByteString
"; charset=utf-8"
toMime :: ContentType -> ByteString
toMime :: ContentType -> ByteString
toMime ContentType
CTApplicationJSON = ByteString
"application/json"
toMime ContentType
CTTextCSV = ByteString
"text/csv"
toMime ContentType
CTTextPlain = ByteString
"text/plain"
toMime ContentType
CTOpenAPI = ByteString
"application/openapi+json"
toMime ContentType
CTSingularJSON = ByteString
"application/vnd.pgrst.object+json"
toMime ContentType
CTUrlEncoded = ByteString
"application/x-www-form-urlencoded"
toMime ContentType
CTOctetStream = ByteString
"application/octet-stream"
toMime ContentType
CTAny = ByteString
"*/*"
toMime (CTOther ByteString
ct) = ByteString
ct
decodeContentType :: BS.ByteString -> ContentType
decodeContentType :: ByteString -> ContentType
decodeContentType ByteString
ct =
case (Word8 -> Bool) -> ByteString -> ByteString
BS.takeWhile (Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
/= Char -> Word8
BS.c2w Char
';') ByteString
ct of
ByteString
"application/json" -> ContentType
CTApplicationJSON
ByteString
"text/csv" -> ContentType
CTTextCSV
ByteString
"text/plain" -> ContentType
CTTextPlain
ByteString
"application/openapi+json" -> ContentType
CTOpenAPI
ByteString
"application/vnd.pgrst.object+json" -> ContentType
CTSingularJSON
ByteString
"application/vnd.pgrst.object" -> ContentType
CTSingularJSON
ByteString
"application/x-www-form-urlencoded" -> ContentType
CTUrlEncoded
ByteString
"application/octet-stream" -> ContentType
CTOctetStream
ByteString
"*/*" -> ContentType
CTAny
ByteString
ct' -> ByteString -> ContentType
CTOther ByteString
ct'