{-# OPTIONS_GHC -Wno-unrecognised-pragmas #-}
{-# HLINT ignore "Use list literal" #-}
module Web.Scim.ContentType
( SCIM,
)
where
import Data.Aeson
import Data.List.NonEmpty
import Data.Proxy
import Network.HTTP.Media hiding (Accept)
import Servant.API.ContentTypes
data SCIM
instance Accept SCIM where
contentTypes :: Proxy SCIM -> NonEmpty MediaType
contentTypes Proxy SCIM
_ =
(ByteString
"application" ByteString -> ByteString -> MediaType
// ByteString
"scim+json" MediaType -> (ByteString, ByteString) -> MediaType
/: (ByteString
"charset", ByteString
"utf-8"))
MediaType -> [MediaType] -> NonEmpty MediaType
forall a. a -> [a] -> NonEmpty a
:| [ ByteString
"application" ByteString -> ByteString -> MediaType
// ByteString
"scim+json",
ByteString
"application" ByteString -> ByteString -> MediaType
// ByteString
"json" MediaType -> (ByteString, ByteString) -> MediaType
/: (ByteString
"charset", ByteString
"utf-8"),
ByteString
"application" ByteString -> ByteString -> MediaType
// ByteString
"json"
]
instance (ToJSON a) => MimeRender SCIM a where
mimeRender :: Proxy SCIM -> a -> ByteString
mimeRender Proxy SCIM
_ = Proxy JSON -> a -> ByteString
forall {k} (ctype :: k) a.
MimeRender ctype a =>
Proxy ctype -> a -> ByteString
mimeRender (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @JSON)
instance (FromJSON a) => MimeUnrender SCIM a where
mimeUnrender :: Proxy SCIM -> ByteString -> Either String a
mimeUnrender Proxy SCIM
_ = Proxy JSON -> ByteString -> Either String a
forall {k} (ctype :: k) a.
MimeUnrender ctype a =>
Proxy ctype -> ByteString -> Either String a
mimeUnrender (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @JSON)