{-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE TypeSynonymInstances #-} {-# LANGUAGE Rank2Types #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE CPP #-} module Yesod.Content ( -- * Content Content (..) , emptyContent , ToContent (..) -- * Mime types -- ** Data type , ContentType , typeHtml , typePlain , typeJson , typeXml , typeAtom , typeRss , typeJpeg , typePng , typeGif , typeSvg , typeJavascript , typeCss , typeFlv , typeOgv , typeOctet -- * Utilities , simpleContentType -- * Evaluation strategy , DontFullyEvaluate (..) -- * Representations , ChooseRep , HasReps (..) , defChooseRep -- ** Specific content types , RepHtml (..) , RepJson (..) , RepHtmlJson (..) , RepPlain (..) , RepXml (..) -- * Utilities , formatW3 , formatRFC1123 , formatRFC822 ) where import Data.Maybe (mapMaybe) 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.Time import System.Locale import qualified Data.Text.Encoding import qualified Data.Text.Lazy.Encoding import Blaze.ByteString.Builder (Builder, fromByteString, fromLazyByteString) import Data.Monoid (mempty) import Text.Hamlet (Html) import Text.Blaze.Html.Renderer.Utf8 (renderHtmlBuilder) import Data.Conduit (Source, ResourceT, Flush (Chunk), ResumableSource, mapOutput) import Data.Conduit.Internal (ResumableSource (ResumableSource)) import qualified Data.Aeson as J import Data.Aeson.Encode (fromValue) import qualified Blaze.ByteString.Builder.Char.Utf8 as Blaze import Data.Text.Lazy.Builder (toLazyText) import Yesod.Core.Types -- | Zero-length enumerator. emptyContent :: Content emptyContent = ContentBuilder mempty $ Just 0 -- | Anything which can be converted into 'Content'. Most of the time, you will -- want to use the 'ContentBuilder' constructor. An easier approach will be to use -- a pre-defined 'toContent' function, such as converting your data into a lazy -- bytestring and then calling 'toContent' on that. -- -- Please note that the built-in instances for lazy data structures ('String', -- lazy 'L.ByteString', lazy 'Text' and 'Html') will not automatically include -- the content length for the 'ContentBuilder' constructor. class ToContent a where toContent :: a -> Content instance ToContent Builder where toContent = flip ContentBuilder Nothing instance ToContent B.ByteString where toContent bs = ContentBuilder (fromByteString bs) $ Just $ B.length bs instance ToContent L.ByteString where toContent = flip ContentBuilder Nothing . fromLazyByteString instance ToContent T.Text where toContent = toContent . Data.Text.Encoding.encodeUtf8 instance ToContent Text where toContent = toContent . Data.Text.Lazy.Encoding.encodeUtf8 instance ToContent String where toContent = toContent . pack instance ToContent Html where toContent bs = ContentBuilder (renderHtmlBuilder bs) Nothing instance ToFlushBuilder builder => ToContent (Source (ResourceT IO) builder) where toContent src = ContentSource $ mapOutput toFlushBuilder src instance ToFlushBuilder builder => ToContent (ResumableSource (ResourceT IO) builder) where toContent (ResumableSource src _) = toContent src class ToFlushBuilder a where toFlushBuilder :: a -> Flush Builder instance ToFlushBuilder (Flush Builder) where toFlushBuilder = id instance ToFlushBuilder Builder where toFlushBuilder = Chunk instance ToFlushBuilder (Flush B.ByteString) where toFlushBuilder = fmap fromByteString instance ToFlushBuilder B.ByteString where toFlushBuilder = Chunk . fromByteString -- | Any type which can be converted to representations. class HasReps a where chooseRep :: a -> ChooseRep -- | A helper method for generating 'HasReps' instances. -- -- This function should be given a list of pairs of content type and conversion -- functions. If none of the content types match, the first pair is used. defChooseRep :: [(ContentType, a -> IO Content)] -> a -> ChooseRep defChooseRep reps a ts = do let (ct, c) = case mapMaybe helper ts of (x:_) -> x [] -> case reps of [] -> error "Empty reps to defChooseRep" (x:_) -> x c' <- c a return (ct, c') where helper ct = do c <- lookup ct reps return (ct, c) instance HasReps ChooseRep where chooseRep = id instance HasReps () where chooseRep = defChooseRep [(typePlain, const $ return $ toContent B.empty)] instance HasReps (ContentType, Content) where chooseRep = const . return instance HasReps [(ContentType, Content)] where chooseRep a cts = return $ case filter (\(ct, _) -> go ct `elem` map go cts) a of ((ct, c):_) -> (ct, c) _ -> case a of (x:_) -> x _ -> error "chooseRep [(ContentType, Content)] of empty" where go = simpleContentType instance HasReps RepHtml where chooseRep (RepHtml c) _ = return (typeHtml, c) instance HasReps RepJson where chooseRep (RepJson c) _ = return (typeJson, c) instance HasReps RepHtmlJson where chooseRep (RepHtmlJson html json) = chooseRep [ (typeHtml, html) , (typeJson, json) ] instance HasReps RepPlain where chooseRep (RepPlain c) _ = return (typePlain, c) instance HasReps RepXml where chooseRep (RepXml c) _ = return (typeXml, c) typeHtml :: ContentType typeHtml = "text/html; charset=utf-8" typePlain :: ContentType typePlain = "text/plain; charset=utf-8" typeJson :: ContentType typeJson = "application/json; charset=utf-8" typeXml :: ContentType typeXml = "text/xml" typeAtom :: ContentType typeAtom = "application/atom+xml" typeRss :: ContentType typeRss = "application/rss+xml" typeJpeg :: ContentType typeJpeg = "image/jpeg" typePng :: ContentType typePng = "image/png" typeGif :: ContentType typeGif = "image/gif" typeSvg :: ContentType typeSvg = "image/svg+xml" typeJavascript :: ContentType typeJavascript = "text/javascript; charset=utf-8" typeCss :: ContentType typeCss = "text/css; charset=utf-8" typeFlv :: ContentType typeFlv = "video/x-flv" typeOgv :: ContentType typeOgv = "video/ogg" typeOctet :: ContentType typeOctet = "application/octet-stream" -- | Removes \"extra\" information at the end of a content type string. In -- particular, removes everything after the semicolon, if present. -- -- For example, \"text/html; charset=utf-8\" is commonly used to specify the -- character encoding for HTML data. This function would return \"text/html\". simpleContentType :: ContentType -> ContentType simpleContentType = fst . B.breakByte 59 -- 59 == ; -- | Format a 'UTCTime' in W3 format. formatW3 :: UTCTime -> T.Text formatW3 = T.pack . formatTime defaultTimeLocale "%FT%X-00:00" -- | Format as per RFC 1123. formatRFC1123 :: UTCTime -> T.Text formatRFC1123 = T.pack . formatTime defaultTimeLocale "%a, %d %b %Y %X %Z" -- | Format as per RFC 822. formatRFC822 :: UTCTime -> T.Text formatRFC822 = T.pack . formatTime defaultTimeLocale "%a, %d %b %Y %H:%M:%S %z" instance HasReps a => HasReps (DontFullyEvaluate a) where chooseRep (DontFullyEvaluate a) = fmap (fmap (fmap ContentDontEvaluate)) $ chooseRep a instance ToContent a => ToContent (DontFullyEvaluate a) where toContent (DontFullyEvaluate a) = ContentDontEvaluate $ toContent a instance ToContent J.Value where toContent = flip ContentBuilder Nothing . Blaze.fromLazyText . toLazyText . fromValue