{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
module Servant.HTML.Blaze where
import Data.Typeable (Typeable)
import qualified Network.HTTP.Media as M
import Servant.API (Accept (..), MimeRender (..))
import Text.Blaze.Html (Html, ToMarkup, toHtml)
import Text.Blaze.Html.Renderer.Utf8 (renderHtml)
import qualified Data.List.NonEmpty as NE
data HTML deriving Typeable
instance Accept HTML where
contentTypes :: Proxy HTML -> NonEmpty MediaType
contentTypes Proxy HTML
_ =
ByteString
"text" ByteString -> ByteString -> MediaType
M.// ByteString
"html" MediaType -> (ByteString, ByteString) -> MediaType
M./: (ByteString
"charset", ByteString
"utf-8") MediaType -> [MediaType] -> NonEmpty MediaType
forall a. a -> [a] -> NonEmpty a
NE.:|
[ByteString
"text" ByteString -> ByteString -> MediaType
M.// ByteString
"html"]
instance ToMarkup a => MimeRender HTML a where
mimeRender :: Proxy HTML -> a -> ByteString
mimeRender Proxy HTML
_ = Html -> ByteString
renderHtml (Html -> ByteString) -> (a -> Html) -> a -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Html
forall a. ToMarkup a => a -> Html
toHtml