summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--hakyll.cabal1
-rw-r--r--src/Hakyll.hs2
-rw-r--r--src/Hakyll/Core/Writable.hs12
-rw-r--r--src/Hakyll/Web/Blaze.hs34
4 files changed, 47 insertions, 2 deletions
diff --git a/hakyll.cabal b/hakyll.cabal
index f954f16..6e8cc64 100644
--- a/hakyll.cabal
+++ b/hakyll.cabal
@@ -65,6 +65,7 @@ library
strict-concurrency >= 0.2
exposed-modules: Hakyll
Hakyll.Main
+ Hakyll.Web.Blaze
Hakyll.Web.Util.Url
Hakyll.Web.Preview.Server
Hakyll.Web.Preview.Poll
diff --git a/src/Hakyll.hs b/src/Hakyll.hs
index dbc67f3..49410a6 100644
--- a/src/Hakyll.hs
+++ b/src/Hakyll.hs
@@ -16,6 +16,7 @@ module Hakyll
, module Hakyll.Core.Writable.CopyFile
, module Hakyll.Core.Writable.WritableTuple
, module Hakyll.Main
+ , module Hakyll.Web.Blaze
, module Hakyll.Web.CompressCss
, module Hakyll.Web.Feed
, module Hakyll.Web.FileType
@@ -44,6 +45,7 @@ import Hakyll.Core.Writable
import Hakyll.Core.Writable.CopyFile
import Hakyll.Core.Writable.WritableTuple
import Hakyll.Main
+import Hakyll.Web.Blaze
import Hakyll.Web.CompressCss
import Hakyll.Web.Feed
import Hakyll.Web.FileType
diff --git a/src/Hakyll/Core/Writable.hs b/src/Hakyll/Core/Writable.hs
index a3fd421..1253e19 100644
--- a/src/Hakyll/Core/Writable.hs
+++ b/src/Hakyll/Core/Writable.hs
@@ -1,6 +1,6 @@
-- | Describes writable items; items that can be saved to the disk
--
-{-# LANGUAGE FlexibleInstances #-}
+{-# LANGUAGE FlexibleInstances, TypeSynonymInstances #-}
module Hakyll.Core.Writable
( Writable (..)
) where
@@ -8,6 +8,8 @@ module Hakyll.Core.Writable
import Data.Word (Word8)
import qualified Data.ByteString as SB
+import Text.Blaze (Html)
+import Text.Blaze.Renderer.String (renderHtml)
-- | Describes an item that can be saved to the disk
--
@@ -18,5 +20,11 @@ class Writable a where
instance Writable [Char] where
write = writeFile
+instance Writable SB.ByteString where
+ write p = SB.writeFile p
+
instance Writable [Word8] where
- write p = SB.writeFile p . SB.pack
+ write p = write p . SB.pack
+
+instance Writable Html where
+ write p html = write p $ renderHtml html
diff --git a/src/Hakyll/Web/Blaze.hs b/src/Hakyll/Web/Blaze.hs
new file mode 100644
index 0000000..e83b340
--- /dev/null
+++ b/src/Hakyll/Web/Blaze.hs
@@ -0,0 +1,34 @@
+-- | Module providing BlazeHtml support for hakyll
+--
+module Hakyll.Web.Blaze
+ ( getFieldHtml
+ , getFieldHtml'
+ , getBodyHtml
+ , getBodyHtml'
+ ) where
+
+import Text.Blaze (Html, toHtml, preEscapedString)
+
+import Hakyll.Web.Page
+import Hakyll.Web.Page.Metadata
+
+-- | Get a field from a page and convert it to HTML. This version does escape
+-- the given HTML
+--
+getFieldHtml :: String -> Page a -> Html
+getFieldHtml key = preEscapedString . getField key
+
+-- | Version of 'getFieldHtml' that escapes the HTML content
+--
+getFieldHtml' :: String -> Page a -> Html
+getFieldHtml' key = toHtml . getField key
+
+-- | Get the body as HTML
+--
+getBodyHtml :: Page String -> Html
+getBodyHtml = preEscapedString . pageBody
+
+-- | Version of 'getBodyHtml' that escapes the HTML content
+--
+getBodyHtml' :: Page String -> Html
+getBodyHtml' = toHtml . pageBody