yesod-core for blaze-html 0.5
This commit is contained in:
parent
e2c79f95bd
commit
4bb2c33bfe
@ -2,6 +2,7 @@
|
||||
{-# LANGUAGE TypeSynonymInstances #-}
|
||||
{-# LANGUAGE Rank2Types #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{-# LANGUAGE CPP #-}
|
||||
module Yesod.Content
|
||||
( -- * Content
|
||||
Content (..)
|
||||
@ -59,7 +60,11 @@ import Blaze.ByteString.Builder (Builder, fromByteString, fromLazyByteString)
|
||||
import Data.Monoid (mempty)
|
||||
|
||||
import Text.Hamlet (Html)
|
||||
#if MIN_VERSION_blaze_html(0, 5, 0)
|
||||
import Text.Blaze.Html.Renderer.Utf8 (renderHtmlBuilder)
|
||||
#else
|
||||
import Text.Blaze.Renderer.Utf8 (renderHtmlBuilder)
|
||||
#endif
|
||||
import Data.String (IsString (fromString))
|
||||
import Network.Wai (FilePart)
|
||||
import Data.Conduit (Source, ResourceT, Flush)
|
||||
|
||||
@ -138,7 +138,11 @@ import qualified Network.Wai as W
|
||||
import qualified Network.HTTP.Types as H
|
||||
|
||||
import Text.Hamlet
|
||||
import qualified Text.Blaze.Renderer.Text
|
||||
#if MIN_VERSION_blaze_html(0, 5, 0)
|
||||
import qualified Text.Blaze.Html.Renderer.Text as RenderText
|
||||
#else
|
||||
import qualified Text.Blaze.Renderer.Text as RenderText
|
||||
#endif
|
||||
import qualified Data.Text as T
|
||||
import Data.Text.Encoding (encodeUtf8, decodeUtf8With)
|
||||
import Data.Text.Encoding.Error (lenientDecode)
|
||||
@ -161,7 +165,12 @@ import Blaze.ByteString.Builder (toByteString)
|
||||
import Data.Text (Text)
|
||||
import Yesod.Message (RenderMessage (..))
|
||||
|
||||
#if MIN_VERSION_blaze_html(0, 5, 0)
|
||||
import Text.Blaze.Html (toHtml, preEscapedToMarkup)
|
||||
#define preEscapedText preEscapedToMarkup
|
||||
#else
|
||||
import Text.Blaze (toHtml, preEscapedText)
|
||||
#endif
|
||||
|
||||
import qualified Yesod.Internal.Cache as Cache
|
||||
import Yesod.Internal.Cache (mkCacheKey, CacheKey)
|
||||
@ -528,7 +537,7 @@ msgKey = "_MSG"
|
||||
--
|
||||
-- See 'getMessage'.
|
||||
setMessage :: Html -> GHandler sub master ()
|
||||
setMessage = setSession msgKey . T.concat . TL.toChunks . Text.Blaze.Renderer.Text.renderHtml
|
||||
setMessage = setSession msgKey . T.concat . TL.toChunks . RenderText.renderHtml
|
||||
|
||||
-- | Sets a message in the user's session.
|
||||
--
|
||||
|
||||
@ -84,7 +84,11 @@ import qualified Data.Text.Lazy as TL
|
||||
import qualified Data.Text.Lazy.IO
|
||||
import qualified Data.Text.Lazy.Builder as TB
|
||||
import Language.Haskell.TH.Syntax (Loc (..), Lift (..))
|
||||
#if MIN_VERSION_blaze_html(0, 5, 0)
|
||||
import Text.Blaze (preEscapedToMarkup)
|
||||
#else
|
||||
import Text.Blaze (preEscapedLazyText)
|
||||
#endif
|
||||
import Data.Aeson (Value (Array, String))
|
||||
import Data.Aeson.Encode (encode)
|
||||
import qualified Data.Vector as Vector
|
||||
@ -92,6 +96,11 @@ import Network.Wai.Middleware.Gzip (GzipSettings, def)
|
||||
import qualified Paths_yesod_core
|
||||
import Data.Version (showVersion)
|
||||
|
||||
#if MIN_VERSION_blaze_html(0, 5, 0)
|
||||
preEscapedLazyText :: TL.Text -> Html
|
||||
preEscapedLazyText = preEscapedToMarkup
|
||||
#endif
|
||||
|
||||
yesodVersion :: String
|
||||
yesodVersion = showVersion Paths_yesod_core.version
|
||||
|
||||
|
||||
@ -80,11 +80,21 @@ import Control.Monad.Trans.Control (MonadBaseControl (..))
|
||||
import Control.Exception (throwIO)
|
||||
import qualified Text.Hamlet as NP
|
||||
import Data.Text.Lazy.Builder (fromLazyText)
|
||||
#if MIN_VERSION_blaze_html(0, 5, 0)
|
||||
import Text.Blaze.Html (toHtml, preEscapedToMarkup)
|
||||
import qualified Data.Text.Lazy as TL
|
||||
#else
|
||||
import Text.Blaze (toHtml, preEscapedLazyText)
|
||||
#endif
|
||||
import Control.Monad.Base (MonadBase (liftBase))
|
||||
import Control.Arrow (first)
|
||||
import Control.Monad.Trans.Resource
|
||||
|
||||
#if MIN_VERSION_blaze_html(0, 5, 0)
|
||||
preEscapedLazyText :: TL.Text -> Html
|
||||
preEscapedLazyText = preEscapedToMarkup
|
||||
#endif
|
||||
|
||||
-- | A generic widget, allowing specification of both the subsite and master
|
||||
-- site datatypes. While this is simply a @WriterT@, we define a newtype for
|
||||
-- better error messages.
|
||||
|
||||
@ -1,5 +1,5 @@
|
||||
name: yesod-core
|
||||
version: 1.0.1
|
||||
version: 1.0.1.1
|
||||
license: MIT
|
||||
license-file: LICENSE
|
||||
author: Michael Snoyman <michael@snoyman.com>
|
||||
@ -40,6 +40,10 @@ flag test
|
||||
description: Build the executable to run unit tests
|
||||
default: False
|
||||
|
||||
flag blaze_html_0_5
|
||||
description: use blaze-html 0.5 and blaze-markup 0.5
|
||||
default: False
|
||||
|
||||
flag ghc7
|
||||
|
||||
library
|
||||
@ -78,7 +82,6 @@ library
|
||||
, monad-control >= 0.3 && < 0.4
|
||||
, transformers-base >= 0.4
|
||||
, cookie >= 0.4 && < 0.5
|
||||
, blaze-html >= 0.4.1.3 && < 0.5
|
||||
, http-types >= 0.6.5 && < 0.7
|
||||
, case-insensitive >= 0.2
|
||||
, parsec >= 2 && < 3.2
|
||||
@ -90,6 +93,15 @@ library
|
||||
, conduit >= 0.4 && < 0.5
|
||||
, resourcet >= 0.3 && < 0.4
|
||||
, lifted-base >= 0.1 && < 0.2
|
||||
|
||||
if flag(blaze_html_0_5)
|
||||
build-depends:
|
||||
blaze-html >= 0.5 && < 0.6
|
||||
, blaze-markup >= 0.5.1 && < 0.6
|
||||
else
|
||||
build-depends:
|
||||
blaze-html >= 0.4 && < 0.5
|
||||
|
||||
exposed-modules: Yesod.Content
|
||||
Yesod.Core
|
||||
Yesod.Dispatch
|
||||
|
||||
Loading…
Reference in New Issue
Block a user