{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeSynonymInstances #-}
{-# LANGUAGE Rank2Types #-}
{-# LANGUAGE OverloadedStrings #-}
module Yesod.Core.Content
    ( 
      Content (..)
    , emptyContent
    , ToContent (..)
    , ToFlushBuilder (..)
      
      
    , ContentType
    , typeHtml
    , typePlain
    , typeJson
    , typeXml
    , typeAtom
    , typeRss
    , typeJpeg
    , typePng
    , typeGif
    , typeSvg
    , typeJavascript
    , typeCss
    , typeFlv
    , typeOgv
    , typeOctet
      
    , simpleContentType
    , contentTypeTypes
      
    , DontFullyEvaluate (..)
      
    , TypedContent (..)
    , ToTypedContent (..)
    , HasContentType (..)
      
    , RepHtml
    , RepJson (..)
    , RepPlain (..)
    , RepXml (..)
      
    , repJson
    , repPlain
    , repXml
    ) where
import qualified Data.ByteString as B
import qualified Data.ByteString.Lazy as L
import Data.Text.Lazy (Text, pack)
import qualified Data.Text as T
import Data.Text.Encoding (encodeUtf8Builder)
import qualified Data.Text.Lazy as TL
import Data.ByteString.Builder (Builder, byteString, lazyByteString, stringUtf8)
import Text.Hamlet (Html)
import Text.Blaze.Html.Renderer.Utf8 (renderHtmlBuilder)
import Data.Conduit (Flush (Chunk), SealedConduitT, mapOutput)
import Control.Monad (liftM)
import Control.Monad.Trans.Resource (ResourceT)
import qualified Data.Conduit.Internal as CI
import qualified Data.Aeson as J
import Data.Text.Lazy.Builder (toLazyText)
import Yesod.Core.Types
import Text.Lucius (Css, renderCss)
import Text.Julius (Javascript, unJavascript)
import Data.Word8 (_semicolon, _slash)
import Control.Arrow (second)
emptyContent :: Content
emptyContent :: Content
emptyContent = Builder -> Maybe Int -> Content
ContentBuilder Builder
forall a. Monoid a => a
mempty (Maybe Int -> Content) -> Maybe Int -> Content
forall a b. (a -> b) -> a -> b
$ Int -> Maybe Int
forall a. a -> Maybe a
Just Int
0
class ToContent a where
    toContent :: a -> Content
instance ToContent Content where
    toContent :: Content -> Content
toContent = Content -> Content
forall a. a -> a
id
instance ToContent Builder where
    toContent :: Builder -> Content
toContent = (Builder -> Maybe Int -> Content)
-> Maybe Int -> Builder -> Content
forall a b c. (a -> b -> c) -> b -> a -> c
flip Builder -> Maybe Int -> Content
ContentBuilder Maybe Int
forall a. Maybe a
Nothing
instance ToContent B.ByteString where
    toContent :: ByteString -> Content
toContent ByteString
bs = Builder -> Maybe Int -> Content
ContentBuilder (ByteString -> Builder
byteString ByteString
bs) (Maybe Int -> Content) -> Maybe Int -> Content
forall a b. (a -> b) -> a -> b
$ Int -> Maybe Int
forall a. a -> Maybe a
Just (Int -> Maybe Int) -> Int -> Maybe Int
forall a b. (a -> b) -> a -> b
$ ByteString -> Int
B.length ByteString
bs
instance ToContent L.ByteString where
    toContent :: ByteString -> Content
toContent = (Builder -> Maybe Int -> Content)
-> Maybe Int -> Builder -> Content
forall a b c. (a -> b -> c) -> b -> a -> c
flip Builder -> Maybe Int -> Content
ContentBuilder Maybe Int
forall a. Maybe a
Nothing (Builder -> Content)
-> (ByteString -> Builder) -> ByteString -> Content
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Builder
lazyByteString
instance ToContent T.Text where
    toContent :: Text -> Content
toContent = Builder -> Content
forall a. ToContent a => a -> Content
toContent (Builder -> Content) -> (Text -> Builder) -> Text -> Content
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Builder
encodeUtf8Builder
instance ToContent Text where
    toContent :: Text -> Content
toContent = Builder -> Content
forall a. ToContent a => a -> Content
toContent (Builder -> Content) -> (Text -> Builder) -> Text -> Content
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> Builder) -> [Text] -> Builder
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap Text -> Builder
encodeUtf8Builder ([Text] -> Builder) -> (Text -> [Text]) -> Text -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [Text]
TL.toChunks
instance ToContent String where
    toContent :: String -> Content
toContent = Builder -> Content
forall a. ToContent a => a -> Content
toContent (Builder -> Content) -> (String -> Builder) -> String -> Content
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Builder
stringUtf8
instance ToContent Html where
    toContent :: Html -> Content
toContent Html
bs = Builder -> Maybe Int -> Content
ContentBuilder (Html -> Builder
renderHtmlBuilder Html
bs) Maybe Int
forall a. Maybe a
Nothing
instance ToContent () where
    toContent :: () -> Content
toContent () = ByteString -> Content
forall a. ToContent a => a -> Content
toContent ByteString
B.empty
instance ToContent (ContentType, Content) where
    toContent :: (ByteString, Content) -> Content
toContent = (ByteString, Content) -> Content
forall a b. (a, b) -> b
snd
instance ToContent TypedContent where
    toContent :: TypedContent -> Content
toContent (TypedContent ByteString
_ Content
c) = Content
c
instance ToContent (JSONResponse a) where
    toContent :: JSONResponse a -> Content
toContent (JSONResponse a
a) = Encoding -> Content
forall a. ToContent a => a -> Content
toContent (Encoding -> Content) -> Encoding -> Content
forall a b. (a -> b) -> a -> b
$ a -> Encoding
forall a. ToJSON a => a -> Encoding
J.toEncoding a
a
instance ToContent Css where
    toContent :: Css -> Content
toContent = Text -> Content
forall a. ToContent a => a -> Content
toContent (Text -> Content) -> (Css -> Text) -> Css -> Content
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Css -> Text
renderCss
instance ToContent Javascript where
    toContent :: Javascript -> Content
toContent = Text -> Content
forall a. ToContent a => a -> Content
toContent (Text -> Content) -> (Javascript -> Text) -> Javascript -> Content
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Builder -> Text
toLazyText (Builder -> Text) -> (Javascript -> Builder) -> Javascript -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Javascript -> Builder
unJavascript
instance ToFlushBuilder builder => ToContent (CI.Pipe () () builder () (ResourceT IO) ()) where
    toContent :: Pipe () () builder () (ResourceT IO) () -> Content
toContent Pipe () () builder () (ResourceT IO) ()
src = ConduitT () (Flush Builder) (ResourceT IO) () -> Content
ContentSource (ConduitT () (Flush Builder) (ResourceT IO) () -> Content)
-> ConduitT () (Flush Builder) (ResourceT IO) () -> Content
forall a b. (a -> b) -> a -> b
$ (forall b.
 (() -> Pipe () () (Flush Builder) () (ResourceT IO) b)
 -> Pipe () () (Flush Builder) () (ResourceT IO) b)
-> ConduitT () (Flush Builder) (ResourceT IO) ()
forall i o (m :: * -> *) r.
(forall b. (r -> Pipe i i o () m b) -> Pipe i i o () m b)
-> ConduitT i o m r
CI.ConduitT ((builder -> Flush Builder)
-> Pipe () () builder () (ResourceT IO) ()
-> Pipe () () (Flush Builder) () (ResourceT IO) ()
forall (m :: * -> *) o1 o2 l i u r.
Monad m =>
(o1 -> o2) -> Pipe l i o1 u m r -> Pipe l i o2 u m r
CI.mapOutput builder -> Flush Builder
forall a. ToFlushBuilder a => a -> Flush Builder
toFlushBuilder Pipe () () builder () (ResourceT IO) ()
src Pipe () () (Flush Builder) () (ResourceT IO) ()
-> (() -> Pipe () () (Flush Builder) () (ResourceT IO) b)
-> Pipe () () (Flush Builder) () (ResourceT IO) b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=)
instance ToFlushBuilder builder => ToContent (CI.ConduitT () builder (ResourceT IO) ()) where
    toContent :: ConduitT () builder (ResourceT IO) () -> Content
toContent ConduitT () builder (ResourceT IO) ()
src = ConduitT () (Flush Builder) (ResourceT IO) () -> Content
ContentSource (ConduitT () (Flush Builder) (ResourceT IO) () -> Content)
-> ConduitT () (Flush Builder) (ResourceT IO) () -> Content
forall a b. (a -> b) -> a -> b
$ (builder -> Flush Builder)
-> ConduitT () builder (ResourceT IO) ()
-> ConduitT () (Flush Builder) (ResourceT IO) ()
forall (m :: * -> *) o1 o2 i r.
Monad m =>
(o1 -> o2) -> ConduitT i o1 m r -> ConduitT i o2 m r
mapOutput builder -> Flush Builder
forall a. ToFlushBuilder a => a -> Flush Builder
toFlushBuilder ConduitT () builder (ResourceT IO) ()
src
instance ToFlushBuilder builder => ToContent (SealedConduitT () builder (ResourceT IO) ()) where
    toContent :: SealedConduitT () builder (ResourceT IO) () -> Content
toContent (CI.SealedConduitT Pipe () () builder () (ResourceT IO) ()
src) = Pipe () () builder () (ResourceT IO) () -> Content
forall a. ToContent a => a -> Content
toContent Pipe () () builder () (ResourceT IO) ()
src
class ToFlushBuilder a where toFlushBuilder :: a -> Flush Builder
instance ToFlushBuilder (Flush Builder) where toFlushBuilder :: Flush Builder -> Flush Builder
toFlushBuilder = Flush Builder -> Flush Builder
forall a. a -> a
id
instance ToFlushBuilder Builder where toFlushBuilder :: Builder -> Flush Builder
toFlushBuilder = Builder -> Flush Builder
forall a. a -> Flush a
Chunk
instance ToFlushBuilder (Flush B.ByteString) where toFlushBuilder :: Flush ByteString -> Flush Builder
toFlushBuilder = (ByteString -> Builder) -> Flush ByteString -> Flush Builder
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ByteString -> Builder
byteString
instance ToFlushBuilder B.ByteString where toFlushBuilder :: ByteString -> Flush Builder
toFlushBuilder = Builder -> Flush Builder
forall a. a -> Flush a
Chunk (Builder -> Flush Builder)
-> (ByteString -> Builder) -> ByteString -> Flush Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Builder
byteString
instance ToFlushBuilder (Flush L.ByteString) where toFlushBuilder :: Flush ByteString -> Flush Builder
toFlushBuilder = (ByteString -> Builder) -> Flush ByteString -> Flush Builder
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ByteString -> Builder
lazyByteString
instance ToFlushBuilder L.ByteString where toFlushBuilder :: ByteString -> Flush Builder
toFlushBuilder = Builder -> Flush Builder
forall a. a -> Flush a
Chunk (Builder -> Flush Builder)
-> (ByteString -> Builder) -> ByteString -> Flush Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Builder
lazyByteString
instance ToFlushBuilder (Flush Text) where toFlushBuilder :: Flush Text -> Flush Builder
toFlushBuilder = (Text -> Builder) -> Flush Text -> Flush Builder
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Text -> Builder) -> [Text] -> Builder
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap Text -> Builder
encodeUtf8Builder ([Text] -> Builder) -> (Text -> [Text]) -> Text -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [Text]
TL.toChunks)
instance ToFlushBuilder Text where toFlushBuilder :: Text -> Flush Builder
toFlushBuilder = Builder -> Flush Builder
forall a. a -> Flush a
Chunk (Builder -> Flush Builder)
-> (Text -> Builder) -> Text -> Flush Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> Builder) -> [Text] -> Builder
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap Text -> Builder
encodeUtf8Builder ([Text] -> Builder) -> (Text -> [Text]) -> Text -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [Text]
TL.toChunks
instance ToFlushBuilder (Flush T.Text) where toFlushBuilder :: Flush Text -> Flush Builder
toFlushBuilder = (Text -> Builder) -> Flush Text -> Flush Builder
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> Builder
encodeUtf8Builder
instance ToFlushBuilder T.Text where toFlushBuilder :: Text -> Flush Builder
toFlushBuilder = Builder -> Flush Builder
forall a. a -> Flush a
Chunk (Builder -> Flush Builder)
-> (Text -> Builder) -> Text -> Flush Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Builder
encodeUtf8Builder
instance ToFlushBuilder (Flush String) where toFlushBuilder :: Flush String -> Flush Builder
toFlushBuilder = (String -> Builder) -> Flush String -> Flush Builder
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap String -> Builder
stringUtf8
instance ToFlushBuilder String where toFlushBuilder :: String -> Flush Builder
toFlushBuilder = Builder -> Flush Builder
forall a. a -> Flush a
Chunk (Builder -> Flush Builder)
-> (String -> Builder) -> String -> Flush Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Builder
stringUtf8
instance ToFlushBuilder (Flush Html) where toFlushBuilder :: Flush Html -> Flush Builder
toFlushBuilder = (Html -> Builder) -> Flush Html -> Flush Builder
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Html -> Builder
renderHtmlBuilder
instance ToFlushBuilder Html where toFlushBuilder :: Html -> Flush Builder
toFlushBuilder = Builder -> Flush Builder
forall a. a -> Flush a
Chunk (Builder -> Flush Builder)
-> (Html -> Builder) -> Html -> Flush Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Html -> Builder
renderHtmlBuilder
repJson :: ToContent a => a -> RepJson
repJson :: a -> RepJson
repJson = Content -> RepJson
RepJson (Content -> RepJson) -> (a -> Content) -> a -> RepJson
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Content
forall a. ToContent a => a -> Content
toContent
repPlain :: ToContent a => a -> RepPlain
repPlain :: a -> RepPlain
repPlain = Content -> RepPlain
RepPlain (Content -> RepPlain) -> (a -> Content) -> a -> RepPlain
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Content
forall a. ToContent a => a -> Content
toContent
repXml :: ToContent a => a -> RepXml
repXml :: a -> RepXml
repXml = Content -> RepXml
RepXml (Content -> RepXml) -> (a -> Content) -> a -> RepXml
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Content
forall a. ToContent a => a -> Content
toContent
class ToTypedContent a => HasContentType a where
    getContentType :: Monad m => m a -> ContentType
instance HasContentType RepJson where
    getContentType :: m RepJson -> ByteString
getContentType m RepJson
_ = ByteString
typeJson
deriving instance ToContent RepJson
instance HasContentType RepPlain where
    getContentType :: m RepPlain -> ByteString
getContentType m RepPlain
_ = ByteString
typePlain
deriving instance ToContent RepPlain
instance HasContentType (JSONResponse a) where
    getContentType :: m (JSONResponse a) -> ByteString
getContentType m (JSONResponse a)
_ = ByteString
typeJson
instance HasContentType RepXml where
    getContentType :: m RepXml -> ByteString
getContentType m RepXml
_ = ByteString
typeXml
deriving instance ToContent RepXml
typeHtml :: ContentType
typeHtml :: ByteString
typeHtml = ByteString
"text/html; charset=utf-8"
typePlain :: ContentType
typePlain :: ByteString
typePlain = ByteString
"text/plain; charset=utf-8"
typeJson :: ContentType
typeJson :: ByteString
typeJson = ByteString
"application/json; charset=utf-8"
typeXml :: ContentType
typeXml :: ByteString
typeXml = ByteString
"text/xml"
typeAtom :: ContentType
typeAtom :: ByteString
typeAtom = ByteString
"application/atom+xml"
typeRss :: ContentType
 = ByteString
"application/rss+xml"
typeJpeg :: ContentType
typeJpeg :: ByteString
typeJpeg = ByteString
"image/jpeg"
typePng :: ContentType
typePng :: ByteString
typePng = ByteString
"image/png"
typeGif :: ContentType
typeGif :: ByteString
typeGif = ByteString
"image/gif"
typeSvg :: ContentType
typeSvg :: ByteString
typeSvg = ByteString
"image/svg+xml"
typeJavascript :: ContentType
typeJavascript :: ByteString
typeJavascript = ByteString
"text/javascript; charset=utf-8"
typeCss :: ContentType
typeCss :: ByteString
typeCss = ByteString
"text/css; charset=utf-8"
typeFlv :: ContentType
typeFlv :: ByteString
typeFlv = ByteString
"video/x-flv"
typeOgv :: ContentType
typeOgv :: ByteString
typeOgv = ByteString
"video/ogg"
typeOctet :: ContentType
typeOctet :: ByteString
typeOctet = ByteString
"application/octet-stream"
simpleContentType :: ContentType -> ContentType
simpleContentType :: ByteString -> ByteString
simpleContentType = (ByteString, ByteString) -> ByteString
forall a b. (a, b) -> a
fst ((ByteString, ByteString) -> ByteString)
-> (ByteString -> (ByteString, ByteString))
-> ByteString
-> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Word8 -> Bool) -> ByteString -> (ByteString, ByteString)
B.break (Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
_semicolon)
contentTypeTypes :: ContentType -> (B.ByteString, B.ByteString)
contentTypeTypes :: ByteString -> (ByteString, ByteString)
contentTypeTypes = (ByteString -> ByteString)
-> (ByteString, ByteString) -> (ByteString, ByteString)
forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (d, b) (d, c)
second ByteString -> ByteString
tailEmpty ((ByteString, ByteString) -> (ByteString, ByteString))
-> (ByteString -> (ByteString, ByteString))
-> ByteString
-> (ByteString, ByteString)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Word8 -> Bool) -> ByteString -> (ByteString, ByteString)
B.break (Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
_slash) (ByteString -> (ByteString, ByteString))
-> (ByteString -> ByteString)
-> ByteString
-> (ByteString, ByteString)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ByteString
simpleContentType
  where
    tailEmpty :: ByteString -> ByteString
tailEmpty ByteString
x = if ByteString -> Bool
B.null ByteString
x then ByteString
"" else ByteString -> ByteString
B.tail ByteString
x
instance HasContentType a => HasContentType (DontFullyEvaluate a) where
    getContentType :: m (DontFullyEvaluate a) -> ByteString
getContentType = m a -> ByteString
forall a (m :: * -> *).
(HasContentType a, Monad m) =>
m a -> ByteString
getContentType (m a -> ByteString)
-> (m (DontFullyEvaluate a) -> m a)
-> m (DontFullyEvaluate a)
-> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (DontFullyEvaluate a -> a) -> m (DontFullyEvaluate a) -> m a
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM DontFullyEvaluate a -> a
forall a. DontFullyEvaluate a -> a
unDontFullyEvaluate
instance ToContent a => ToContent (DontFullyEvaluate a) where
    toContent :: DontFullyEvaluate a -> Content
toContent (DontFullyEvaluate a
a) = Content -> Content
ContentDontEvaluate (Content -> Content) -> Content -> Content
forall a b. (a -> b) -> a -> b
$ a -> Content
forall a. ToContent a => a -> Content
toContent a
a
instance ToContent J.Value where
    toContent :: Value -> Content
toContent = (Builder -> Maybe Int -> Content)
-> Maybe Int -> Builder -> Content
forall a b c. (a -> b -> c) -> b -> a -> c
flip Builder -> Maybe Int -> Content
ContentBuilder Maybe Int
forall a. Maybe a
Nothing
              (Builder -> Content) -> (Value -> Builder) -> Value -> Content
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Encoding -> Builder
forall tag. Encoding' tag -> Builder
J.fromEncoding
              (Encoding -> Builder) -> (Value -> Encoding) -> Value -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Value -> Encoding
forall a. ToJSON a => a -> Encoding
J.toEncoding
instance ToContent J.Encoding where
    toContent :: Encoding -> Content
toContent = (Builder -> Maybe Int -> Content)
-> Maybe Int -> Builder -> Content
forall a b c. (a -> b -> c) -> b -> a -> c
flip Builder -> Maybe Int -> Content
ContentBuilder Maybe Int
forall a. Maybe a
Nothing (Builder -> Content)
-> (Encoding -> Builder) -> Encoding -> Content
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Encoding -> Builder
forall tag. Encoding' tag -> Builder
J.fromEncoding
instance HasContentType J.Value where
    getContentType :: m Value -> ByteString
getContentType m Value
_ = ByteString
typeJson
instance HasContentType J.Encoding where
    getContentType :: m Encoding -> ByteString
getContentType m Encoding
_ = ByteString
typeJson
instance HasContentType Html where
    getContentType :: m Html -> ByteString
getContentType m Html
_ = ByteString
typeHtml
instance HasContentType Text where
    getContentType :: m Text -> ByteString
getContentType m Text
_ = ByteString
typePlain
instance HasContentType T.Text where
    getContentType :: m Text -> ByteString
getContentType m Text
_ = ByteString
typePlain
instance HasContentType Css where
    getContentType :: m Css -> ByteString
getContentType m Css
_ = ByteString
typeCss
instance HasContentType Javascript where
    getContentType :: m Javascript -> ByteString
getContentType m Javascript
_ = ByteString
typeJavascript
class ToContent a => ToTypedContent a where
    toTypedContent :: a -> TypedContent
instance ToTypedContent TypedContent where
    toTypedContent :: TypedContent -> TypedContent
toTypedContent = TypedContent -> TypedContent
forall a. a -> a
id
instance ToTypedContent () where
    toTypedContent :: () -> TypedContent
toTypedContent () = ByteString -> Content -> TypedContent
TypedContent ByteString
typePlain (() -> Content
forall a. ToContent a => a -> Content
toContent ())
instance ToTypedContent (ContentType, Content) where
    toTypedContent :: (ByteString, Content) -> TypedContent
toTypedContent (ByteString
ct, Content
content) = ByteString -> Content -> TypedContent
TypedContent ByteString
ct Content
content
instance ToTypedContent RepJson where
    toTypedContent :: RepJson -> TypedContent
toTypedContent (RepJson Content
c) = ByteString -> Content -> TypedContent
TypedContent ByteString
typeJson Content
c
instance ToTypedContent RepPlain where
    toTypedContent :: RepPlain -> TypedContent
toTypedContent (RepPlain Content
c) = ByteString -> Content -> TypedContent
TypedContent ByteString
typePlain Content
c
instance ToTypedContent RepXml where
    toTypedContent :: RepXml -> TypedContent
toTypedContent (RepXml Content
c) = ByteString -> Content -> TypedContent
TypedContent ByteString
typeXml Content
c
instance ToTypedContent J.Value where
    toTypedContent :: Value -> TypedContent
toTypedContent Value
v = ByteString -> Content -> TypedContent
TypedContent ByteString
typeJson (Value -> Content
forall a. ToContent a => a -> Content
toContent Value
v)
instance ToTypedContent J.Encoding where
    toTypedContent :: Encoding -> TypedContent
toTypedContent Encoding
e = ByteString -> Content -> TypedContent
TypedContent ByteString
typeJson (Encoding -> Content
forall a. ToContent a => a -> Content
toContent Encoding
e)
instance ToTypedContent Html where
    toTypedContent :: Html -> TypedContent
toTypedContent Html
h = ByteString -> Content -> TypedContent
TypedContent ByteString
typeHtml (Html -> Content
forall a. ToContent a => a -> Content
toContent Html
h)
instance ToTypedContent T.Text where
    toTypedContent :: Text -> TypedContent
toTypedContent Text
t = ByteString -> Content -> TypedContent
TypedContent ByteString
typePlain (Text -> Content
forall a. ToContent a => a -> Content
toContent Text
t)
instance ToTypedContent [Char] where
    toTypedContent :: String -> TypedContent
toTypedContent = Text -> TypedContent
forall a. ToTypedContent a => a -> TypedContent
toTypedContent (Text -> TypedContent)
-> (String -> Text) -> String -> TypedContent
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
pack
instance ToTypedContent Text where
    toTypedContent :: Text -> TypedContent
toTypedContent Text
t = ByteString -> Content -> TypedContent
TypedContent ByteString
typePlain (Text -> Content
forall a. ToContent a => a -> Content
toContent Text
t)
instance ToTypedContent (JSONResponse a) where
    toTypedContent :: JSONResponse a -> TypedContent
toTypedContent JSONResponse a
c = ByteString -> Content -> TypedContent
TypedContent ByteString
typeJson (JSONResponse a -> Content
forall a. ToContent a => a -> Content
toContent JSONResponse a
c)
instance ToTypedContent a => ToTypedContent (DontFullyEvaluate a) where
    toTypedContent :: DontFullyEvaluate a -> TypedContent
toTypedContent (DontFullyEvaluate a
a) =
        let TypedContent ByteString
ct Content
c = a -> TypedContent
forall a. ToTypedContent a => a -> TypedContent
toTypedContent a
a
         in ByteString -> Content -> TypedContent
TypedContent ByteString
ct (Content -> Content
ContentDontEvaluate Content
c)
instance ToTypedContent Css where
    toTypedContent :: Css -> TypedContent
toTypedContent = ByteString -> Content -> TypedContent
TypedContent ByteString
typeCss (Content -> TypedContent)
-> (Css -> Content) -> Css -> TypedContent
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Css -> Content
forall a. ToContent a => a -> Content
toContent
instance ToTypedContent Javascript where
    toTypedContent :: Javascript -> TypedContent
toTypedContent = ByteString -> Content -> TypedContent
TypedContent ByteString
typeJavascript (Content -> TypedContent)
-> (Javascript -> Content) -> Javascript -> TypedContent
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Javascript -> Content
forall a. ToContent a => a -> Content
toContent