summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--README.markdown2
-rw-r--r--hakyll.cabal27
-rw-r--r--src/Hakyll.hs2
-rw-r--r--src/Hakyll/Core/Provider/Internal.hs4
-rw-r--r--src/Hakyll/Core/Routes.hs18
-rw-r--r--src/Hakyll/Web/Feed.hs1
-rw-r--r--src/Hakyll/Web/Template.hs85
-rw-r--r--src/Hakyll/Web/Template/Context.hs35
-rw-r--r--src/Hakyll/Web/Template/Internal.hs99
-rw-r--r--src/Hakyll/Web/Template/Read.hs93
-rw-r--r--tests/Hakyll/Core/Routes/Tests.hs12
-rw-r--r--tests/data/example.md.metadata1
-rw-r--r--web/css/syntax.css26
-rw-r--r--web/examples.markdown14
-rw-r--r--web/releases.markdown9
-rw-r--r--web/templates/tutorials.html6
-rw-r--r--web/tutorials/hakyll-3-to-hakyll4-migration-guide.markdown2
17 files changed, 288 insertions, 148 deletions
diff --git a/README.markdown b/README.markdown
index ea89626..87e5564 100644
--- a/README.markdown
+++ b/README.markdown
@@ -3,7 +3,7 @@
[![Build Status](https://secure.travis-ci.org/jaspervdj/hakyll.png?branch=master)](http://travis-ci.org/jaspervdj/hakyll)
Hakyll is a static site generator library in Haskell. More information
-(including and a tutorial) can be found on
+(including a tutorial) can be found on
[the hakyll homepage](http://jaspervdj.be/hakyll).
You can install this library using cabal:
diff --git a/hakyll.cabal b/hakyll.cabal
index 7af36b6..9173bac 100644
--- a/hakyll.cabal
+++ b/hakyll.cabal
@@ -1,5 +1,5 @@
Name: hakyll
-Version: 4.4.1.0
+Version: 4.4.3.2
Synopsis: A static website compiler library
Description:
@@ -119,7 +119,6 @@ Library
Hakyll.Web.Template
Hakyll.Web.Template.Context
Hakyll.Web.Template.List
- Hakyll.Web.Template.Read
Other-Modules:
Hakyll.Check
@@ -149,7 +148,7 @@ Library
bytestring >= 0.9 && < 0.11,
cmdargs >= 0.10 && < 0.11,
containers >= 0.3 && < 0.6,
- cryptohash >= 0.7 && < 0.11,
+ cryptohash >= 0.7 && < 0.12,
data-default >= 0.4 && < 0.6,
deepseq >= 1.3 && < 1.4,
directory >= 1.0 && < 1.3,
@@ -160,14 +159,14 @@ Library
old-locale >= 1.0 && < 1.1,
old-time >= 1.0 && < 1.2,
pandoc >= 1.12 && < 1.13,
- pandoc-citeproc >= 0.1 && < 0.2,
+ pandoc-citeproc >= 0.1 && < 0.3,
parsec >= 3.0 && < 3.2,
- process >= 1.0 && < 1.2,
+ process >= 1.0 && < 1.3,
random >= 1.0 && < 1.1,
regex-base >= 0.93 && < 0.94,
regex-tdfa >= 1.1 && < 1.2,
- tagsoup >= 0.12.6 && < 0.13,
- text >= 0.11 && < 1.12,
+ tagsoup >= 0.13.1 && < 0.14,
+ text >= 0.11 && < 1.2,
time >= 1.1 && < 1.5
If flag(previewServer)
@@ -193,7 +192,7 @@ Library
If flag(checkExternal)
Build-depends:
- http-conduit >= 1.8 && < 1.10,
+ http-conduit >= 1.8 && < 2.1,
http-types >= 0.7 && < 0.9
Cpp-options:
-DCHECK_EXTERNAL
@@ -235,7 +234,7 @@ Test-suite hakyll-tests
bytestring >= 0.9 && < 0.11,
cmdargs >= 0.10 && < 0.11,
containers >= 0.3 && < 0.6,
- cryptohash >= 0.7 && < 0.11,
+ cryptohash >= 0.7 && < 0.12,
data-default >= 0.4 && < 0.6,
deepseq >= 1.3 && < 1.4,
directory >= 1.0 && < 1.3,
@@ -246,14 +245,14 @@ Test-suite hakyll-tests
old-locale >= 1.0 && < 1.1,
old-time >= 1.0 && < 1.2,
pandoc >= 1.12 && < 1.13,
- pandoc-citeproc >= 0.1 && < 0.2,
+ pandoc-citeproc >= 0.1 && < 0.3,
parsec >= 3.0 && < 3.2,
- process >= 1.0 && < 1.2,
+ process >= 1.0 && < 1.3,
random >= 1.0 && < 1.1,
regex-base >= 0.93 && < 0.94,
regex-tdfa >= 1.1 && < 1.2,
- tagsoup >= 0.12.6 && < 0.13,
- text >= 0.11 && < 1.12,
+ tagsoup >= 0.13.1 && < 0.14,
+ text >= 0.11 && < 1.2,
time >= 1.1 && < 1.5
If flag(previewServer)
@@ -279,7 +278,7 @@ Test-suite hakyll-tests
If flag(checkExternal)
Build-depends:
- http-conduit >= 1.8 && < 1.10,
+ http-conduit >= 1.8 && < 2.1,
http-types >= 0.7 && < 0.9
Cpp-options:
-DCHECK_EXTERNAL
diff --git a/src/Hakyll.hs b/src/Hakyll.hs
index f7113cd..edc79a0 100644
--- a/src/Hakyll.hs
+++ b/src/Hakyll.hs
@@ -28,7 +28,6 @@ module Hakyll
, module Hakyll.Web.Template
, module Hakyll.Web.Template.Context
, module Hakyll.Web.Template.List
- , module Hakyll.Web.Template.Read
) where
@@ -59,4 +58,3 @@ import Hakyll.Web.Tags
import Hakyll.Web.Template
import Hakyll.Web.Template.Context
import Hakyll.Web.Template.List
-import Hakyll.Web.Template.Read
diff --git a/src/Hakyll/Core/Provider/Internal.hs b/src/Hakyll/Core/Provider/Internal.hs
index d566f3a..fdf1342 100644
--- a/src/Hakyll/Core/Provider/Internal.hs
+++ b/src/Hakyll/Core/Provider/Internal.hs
@@ -174,7 +174,9 @@ resourceModified :: Provider -> Identifier -> Bool
resourceModified p r = case (ri, oldRi) of
(Nothing, _) -> False
(Just _, Nothing) -> True
- (Just n, Just o) -> resourceInfoModified n > resourceInfoModified o
+ (Just n, Just o) ->
+ resourceInfoModified n > resourceInfoModified o ||
+ resourceInfoMetadata n /= resourceInfoMetadata o
where
normal = setVersion Nothing r
ri = M.lookup normal (providerFiles p)
diff --git a/src/Hakyll/Core/Routes.hs b/src/Hakyll/Core/Routes.hs
index 34a613d..470d727 100644
--- a/src/Hakyll/Core/Routes.hs
+++ b/src/Hakyll/Core/Routes.hs
@@ -61,9 +61,16 @@ type UsedMetadata = Bool
--------------------------------------------------------------------------------
+data RoutesRead = RoutesRead
+ { routesProvider :: Provider
+ , routesUnderlying :: Identifier
+ }
+
+
+--------------------------------------------------------------------------------
-- | Type used for a route
newtype Routes = Routes
- { unRoutes :: Provider -> Identifier -> IO (Maybe FilePath, UsedMetadata)
+ { unRoutes :: RoutesRead -> Identifier -> IO (Maybe FilePath, UsedMetadata)
}
@@ -81,7 +88,8 @@ instance Monoid Routes where
-- | Apply a route to an identifier
runRoutes :: Routes -> Provider -> Identifier
-> IO (Maybe FilePath, UsedMetadata)
-runRoutes = unRoutes
+runRoutes routes provider identifier =
+ unRoutes routes (RoutesRead provider identifier) identifier
--------------------------------------------------------------------------------
@@ -156,9 +164,9 @@ gsubRoute pattern replacement = customRoute $
--------------------------------------------------------------------------------
-- | Get access to the metadata in order to determine the route
metadataRoute :: (Metadata -> Routes) -> Routes
-metadataRoute f = Routes $ \p i -> do
- metadata <- resourceMetadata p i
- unRoutes (f metadata) p i
+metadataRoute f = Routes $ \r i -> do
+ metadata <- resourceMetadata (routesProvider r) (routesUnderlying r)
+ unRoutes (f metadata) r i
--------------------------------------------------------------------------------
diff --git a/src/Hakyll/Web/Feed.hs b/src/Hakyll/Web/Feed.hs
index d394243..8c68a75 100644
--- a/src/Hakyll/Web/Feed.hs
+++ b/src/Hakyll/Web/Feed.hs
@@ -35,7 +35,6 @@ import Hakyll.Core.Item
import Hakyll.Web.Template
import Hakyll.Web.Template.Context
import Hakyll.Web.Template.List
-import Hakyll.Web.Template.Read
--------------------------------------------------------------------------------
diff --git a/src/Hakyll/Web/Template.hs b/src/Hakyll/Web/Template.hs
index 76911e0..086e9b2 100644
--- a/src/Hakyll/Web/Template.hs
+++ b/src/Hakyll/Web/Template.hs
@@ -33,12 +33,96 @@
--
-- Because of it's simplicity, these templates can be used for more than HTML:
-- you could make, for example, CSS or JS templates as well.
+--
+-- Apart from interpolating @$key$@s from the 'Context' you can also
+-- use the following macros:
+--
+-- * @$if(key)$@
+--
+-- > $if(key)$
+-- > <b> Defined </b>
+-- > $else$
+-- > <b> Non-defined </b>
+-- > $endif$
+--
+-- This example will print @Defined@ if @key@ is defined in the
+-- context and @Non-defined@ otherwise. The @$else$@ clause is
+-- optional.
+--
+-- * @$for(key)$@
+--
+-- The @for@ macro is used for enumerating 'Context' elements that are
+-- lists, i.e. constructed using the 'listField' function. Assume that
+-- in a context we have an element @listField \"key\" c itms@. Then
+-- the snippet
+--
+-- > $for(key)$
+-- > $x$
+-- > $sep$,
+-- > $endfor$
+--
+-- would, for each item @i@ in 'itms', lookup @$x$@ in the context @c@
+-- with item @i@, interpolate it, and join the resulting list with
+-- @,@.
+--
+-- Another concrete example one may consider is the following. Given the
+-- context
+--
+-- > listField "things" (field "thing" (return . itemBody))
+-- > (sequence [makeItem "fruits", makeItem "vegetables"])
+--
+-- and a template
+--
+-- > I like
+-- > $for(things)$
+-- > fresh $thing$$sep$, and
+-- > $endfor$
+--
+-- the resulting page would look like
+--
+-- > <p>
+-- > I like
+-- >
+-- > fresh fruits, and
+-- >
+-- > fresh vegetables
+-- > </p>
+--
+-- The @$sep$@ part can be omitted. Usually, you can get by using the
+-- 'applyListTemplate' and 'applyJoinListTemplate' functions.
+--
+-- * @$partial(path)$@
+--
+-- Loads a template located in a separate file and interpolates it
+-- under the current context.
+--
+-- Assuming that the file @test.html@ contains
+--
+-- > <b>$key$</b>
+--
+-- The result of rendering
+--
+-- > <p>
+-- > $partial("test.html")$
+-- > </p>
+--
+-- is the same as the result of rendering
+--
+-- > <p>
+-- > <b>$key$</b>
+-- > </p>
+--
+-- That is, calling @$partial$@ is equivalent to just copying and pasting
+-- template code.
+--
+
module Hakyll.Web.Template
( Template
, templateCompiler
, applyTemplate
, loadAndApplyTemplate
, applyAsTemplate
+ , readTemplate
) where
@@ -56,7 +140,6 @@ import Hakyll.Core.Identifier
import Hakyll.Core.Item
import Hakyll.Web.Template.Context
import Hakyll.Web.Template.Internal
-import Hakyll.Web.Template.Read
--------------------------------------------------------------------------------
diff --git a/src/Hakyll/Web/Template/Context.hs b/src/Hakyll/Web/Template/Context.hs
index cd52eb0..a741272 100644
--- a/src/Hakyll/Web/Template/Context.hs
+++ b/src/Hakyll/Web/Template/Context.hs
@@ -56,6 +56,20 @@ data ContextField
--------------------------------------------------------------------------------
+-- | The 'Context' monoid. Please note that the order in which you
+-- compose the items is important. For example in
+--
+-- > field "A" f1 <> field "A" f2
+--
+-- the first context will overwrite the second. This is especially
+-- important when something is being composed with
+-- 'metadataField' (or 'defaultContext'). If you want your context to be
+-- overwritten by the metadata fields, compose it from the right:
+--
+-- @
+-- 'metadataField' \<\> field \"date\" fDate
+-- @
+--
newtype Context a = Context
{ unContext :: String -> Item a -> Compiler ContextField
}
@@ -73,11 +87,16 @@ field' key value = Context $ \k i -> if k == key then value i else empty
--------------------------------------------------------------------------------
-field :: String -> (Item a -> Compiler String) -> Context a
+-- | Constructs a new field in the 'Context.'
+field :: String -- ^ Key
+ -> (Item a -> Compiler String) -- ^ Function that constructs a
+ -- value based on the item
+ -> Context a
field key value = field' key (fmap StringField . value)
--------------------------------------------------------------------------------
+-- | Creates a 'field' that does not depend on the 'Item'
constField :: String -> String -> Context a
constField key = field key . const . return
@@ -108,6 +127,17 @@ mapContext f (Context c) = Context $ \k i -> do
--------------------------------------------------------------------------------
+-- | A context that contains (in that order)
+--
+-- 1. A @$body$@ field
+--
+-- 2. Metadata fields
+--
+-- 3. A @$url$@ 'urlField'
+--
+-- 4. A @$path$@ 'pathField'
+--
+-- 5. A @$title$@ 'titleField'
defaultContext :: Context String
defaultContext =
bodyField "body" `mappend`
@@ -124,6 +154,7 @@ teaserSeparator = "<!--more-->"
--------------------------------------------------------------------------------
+-- | Constructs a 'field' that contains the body of the item.
bodyField :: String -> Context String
bodyField key = field key $ return . itemBody
@@ -150,7 +181,7 @@ pathField key = field key $ return . toFilePath . itemIdentifier
--------------------------------------------------------------------------------
--- | This title field takes the basename of the underlying file by default
+-- | This title 'field' takes the basename of the underlying file by default
titleField :: String -> Context a
titleField = mapContext takeBaseName . pathField
diff --git a/src/Hakyll/Web/Template/Internal.hs b/src/Hakyll/Web/Template/Internal.hs
index 138010e..4450a19 100644
--- a/src/Hakyll/Web/Template/Internal.hs
+++ b/src/Hakyll/Web/Template/Internal.hs
@@ -5,16 +5,22 @@
module Hakyll.Web.Template.Internal
( Template (..)
, TemplateElement (..)
+ , readTemplate
) where
--------------------------------------------------------------------------------
-import Control.Applicative (pure, (<$>), (<*>))
-import Data.Binary (Binary, get, getWord8, put, putWord8)
-import Data.Typeable (Typeable)
+import Control.Applicative (pure, (<$), (<$>), (<*>), (<|>))
+import Control.Monad (void)
+import Data.Binary (Binary, get, getWord8, put, putWord8)
+import Data.Typeable (Typeable)
+import GHC.Exts (IsString (..))
+import qualified Text.Parsec as P
+import qualified Text.Parsec.String as P
--------------------------------------------------------------------------------
+import Hakyll.Core.Util.Parser
import Hakyll.Core.Writable
@@ -46,10 +52,10 @@ data TemplateElement
--------------------------------------------------------------------------------
instance Binary TemplateElement where
put (Chunk string) = putWord8 0 >> put string
- put (Key key) = putWord8 1 >> put key
+ put (Key k) = putWord8 1 >> put k
put (Escaped) = putWord8 2
- put (If key t f) = putWord8 3 >> put key >> put t >> put f
- put (For key b s) = putWord8 4 >> put key >> put b >> put s
+ put (If k t f ) = putWord8 3 >> put k >> put t >> put f
+ put (For k b s) = putWord8 4 >> put k >> put b >> put s
put (Partial p) = putWord8 5 >> put p
get = getWord8 >>= \tag -> case tag of
@@ -61,3 +67,84 @@ instance Binary TemplateElement where
5 -> Partial <$> get
_ -> error $
"Hakyll.Web.Template.Internal: Error reading cached template"
+
+
+--------------------------------------------------------------------------------
+instance IsString Template where
+ fromString = readTemplate
+
+
+--------------------------------------------------------------------------------
+readTemplate :: String -> Template
+readTemplate input = case P.parse template "" input of
+ Left err -> error $ "Cannot parse template: " ++ show err
+ Right t -> t
+
+
+--------------------------------------------------------------------------------
+template :: P.Parser Template
+template = Template <$>
+ (P.many1 $ chunk <|> escaped <|> conditional <|> for <|> partial <|> key)
+
+
+--------------------------------------------------------------------------------
+chunk :: P.Parser TemplateElement
+chunk = Chunk <$> (P.many1 $ P.noneOf "$")
+
+
+--------------------------------------------------------------------------------
+escaped :: P.Parser TemplateElement
+escaped = Escaped <$ (P.try $ P.string "$$")
+
+
+--------------------------------------------------------------------------------
+conditional :: P.Parser TemplateElement
+conditional = P.try $ do
+ void $ P.string "$if("
+ i <- metadataKey
+ void $ P.string ")$"
+ thenBranch <- template
+ elseBranch <- P.optionMaybe $ P.try (P.string "$else$") >> template
+ void $ P.string "$endif$"
+ return $ If i thenBranch elseBranch
+
+
+--------------------------------------------------------------------------------
+for :: P.Parser TemplateElement
+for = P.try $ do
+ void $ P.string "$for("
+ i <- metadataKey
+ void $ P.string ")$"
+ body <- template
+ sep <- P.optionMaybe $ P.try (P.string "$sep$") >> template
+ void $ P.string "$endfor$"
+ return $ For i body sep
+
+
+--------------------------------------------------------------------------------
+partial :: P.Parser TemplateElement
+partial = P.try $ do
+ void $ P.string "$partial("
+ i <- stringLiteral
+ void $ P.string ")$"
+ return $ Partial i
+
+
+--------------------------------------------------------------------------------
+key :: P.Parser TemplateElement
+key = P.try $ do
+ void $ P.char '$'
+ k <- metadataKey
+ void $ P.char '$'
+ return $ Key k
+
+
+--------------------------------------------------------------------------------
+stringLiteral :: P.Parser String
+stringLiteral = do
+ void $ P.char '\"'
+ str <- P.many $ do
+ x <- P.noneOf "\""
+ if x == '\\' then P.anyChar else return x
+ void $ P.char '\"'
+ return str
diff --git a/src/Hakyll/Web/Template/Read.hs b/src/Hakyll/Web/Template/Read.hs
deleted file mode 100644
index 2421b2d..0000000
--- a/src/Hakyll/Web/Template/Read.hs
+++ /dev/null
@@ -1,93 +0,0 @@
---------------------------------------------------------------------------------
--- | Read templates in Hakyll's native format
-module Hakyll.Web.Template.Read
- ( readTemplate
- ) where
-
-
---------------------------------------------------------------------------------
-import Control.Applicative ((<$), (<$>))
-import Control.Monad (void)
-import Text.Parsec
-import Text.Parsec.String
-
-
---------------------------------------------------------------------------------
-import Hakyll.Core.Util.Parser
-import Hakyll.Web.Template.Internal
-
-
---------------------------------------------------------------------------------
-readTemplate :: String -> Template
-readTemplate input = case parse template "" input of
- Left err -> error $ "Cannot parse template: " ++ show err
- Right t -> t
-
-
---------------------------------------------------------------------------------
-template :: Parser Template
-template = Template <$>
- (many1 $ chunk <|> escaped <|> conditional <|> for <|> partial <|> key)
-
-
---------------------------------------------------------------------------------
-chunk :: Parser TemplateElement
-chunk = Chunk <$> (many1 $ noneOf "$")
-
-
---------------------------------------------------------------------------------
-escaped :: Parser TemplateElement
-escaped = Escaped <$ (try $ string "$$")
-
-
---------------------------------------------------------------------------------
-conditional :: Parser TemplateElement
-conditional = try $ do
- void $ string "$if("
- i <- metadataKey
- void $ string ")$"
- thenBranch <- template
- elseBranch <- optionMaybe $ try (string "$else$") >> template
- void $ string "$endif$"
- return $ If i thenBranch elseBranch
-
-
---------------------------------------------------------------------------------
-for :: Parser TemplateElement
-for = try $ do
- void $ string "$for("
- i <- metadataKey
- void $ string ")$"
- body <- template
- sep <- optionMaybe $ try (string "$sep$") >> template
- void $ string "$endfor$"
- return $ For i body sep
-
-
---------------------------------------------------------------------------------
-partial :: Parser TemplateElement
-partial = try $ do
- void $ string "$partial("
- i <- stringLiteral
- void $ string ")$"
- return $ Partial i
-
-
---------------------------------------------------------------------------------
-key :: Parser TemplateElement
-key = try $ do
- void $ char '$'
- k <- metadataKey
- void $ char '$'
- return $ Key k
-
-
---------------------------------------------------------------------------------
-stringLiteral :: Parser String
-stringLiteral = do
- void $ char '\"'
- str <- many $ do
- x <- noneOf "\""
- if x == '\\' then anyChar else return x
- void $ char '\"'
- return str
diff --git a/tests/Hakyll/Core/Routes/Tests.hs b/tests/Hakyll/Core/Routes/Tests.hs
index c681c99..4f975ae 100644
--- a/tests/Hakyll/Core/Routes/Tests.hs
+++ b/tests/Hakyll/Core/Routes/Tests.hs
@@ -6,6 +6,8 @@ module Hakyll.Core.Routes.Tests
--------------------------------------------------------------------------------
+import qualified Data.Map as M
+import System.FilePath ((</>))
import Test.Framework (Test, testGroup)
import Test.HUnit (Assertion, (@=?))
@@ -33,12 +35,18 @@ tests = testGroup "Hakyll.Core.Routes.Tests" $ fromAssertions "runRoutes"
, testRoutes "tags/bar.xml"
(gsubRoute "rss/" (const "") `composeRoutes` setExtension "xml")
"tags/rss/bar"
+
+ , testRoutes "food/example.md" (metadataRoute $ \md -> customRoute $ \id' ->
+ M.findWithDefault "?" "subblog" md </> toFilePath id')
+ "example.md"
]
--------------------------------------------------------------------------------
testRoutes :: FilePath -> Routes -> Identifier -> Assertion
testRoutes expected r id' = do
- (route, _) <- runRoutes r
- (error "Hakyll.Core.Routes.Tests: no provider") id'
+ store <- newTestStore
+ provider <- newTestProvider store
+ (route, _) <- runRoutes r provider id'
Just expected @=? route
+ cleanTestEnv
diff --git a/tests/data/example.md.metadata b/tests/data/example.md.metadata
index 9685918..5d463ae 100644
--- a/tests/data/example.md.metadata
+++ b/tests/data/example.md.metadata
@@ -1,2 +1,3 @@
external: External data
date: 2012-10-22 14:35:24
+subblog: food
diff --git a/web/css/syntax.css b/web/css/syntax.css
index 75ead0a..57b31eb 100644
--- a/web/css/syntax.css
+++ b/web/css/syntax.css
@@ -3,16 +3,16 @@ table.sourceCode, tr.sourceCode, td.lineNumbers, td.sourceCode, table.sourceCode
{ margin: 0; padding: 0; border: 0; vertical-align: baseline; border: none; }
td.lineNumbers { border-right: 1px solid #AAAAAA; text-align: right; color: #AAAAAA; padding-right: 5px; padding-left: 5px; }
td.sourceCode { padding-left: 5px; }
-pre.sourceCode span.kw { color: #007020; font-weight: bold; }
-pre.sourceCode span.dt { color: #902000; }
-pre.sourceCode span.dv { color: #40a070; }
-pre.sourceCode span.bn { color: #40a070; }
-pre.sourceCode span.fl { color: #40a070; }
-pre.sourceCode span.ch { color: #4070a0; }
-pre.sourceCode span.st { color: #4070a0; }
-pre.sourceCode span.co { color: #60a0b0; font-style: italic; }
-pre.sourceCode span.ot { color: #007020; }
-pre.sourceCode span.al { color: red; font-weight: bold; }
-pre.sourceCode span.fu { color: #06287e; }
-pre.sourceCode span.re { }
-pre.sourceCode span.er { color: red; font-weight: bold; }
+.sourceCode span.kw { color: #007020; font-weight: bold; }
+.sourceCode span.dt { color: #902000; }
+.sourceCode span.dv { color: #40a070; }
+.sourceCode span.bn { color: #40a070; }
+.sourceCode span.fl { color: #40a070; }
+.sourceCode span.ch { color: #4070a0; }
+.sourceCode span.st { color: #4070a0; }
+.sourceCode span.co { color: #60a0b0; font-style: italic; }
+.sourceCode span.ot { color: #007020; }
+.sourceCode span.al { color: red; font-weight: bold; }
+.sourceCode span.fu { color: #06287e; }
+.sourceCode span.re { }
+.sourceCode span.er { color: red; font-weight: bold; }
diff --git a/web/examples.markdown b/web/examples.markdown
index e178902..113bd25 100644
--- a/web/examples.markdown
+++ b/web/examples.markdown
@@ -53,7 +53,7 @@ this list. This list has no particular ordering.
[source](https://github.com/blaenk/blaenk.github.io)
- <https://xinitrc.de/>,
[source](https://github.com/xinitrc/xinitrc.de)
-- <http://darkfox.us.to/>,
+- <http://blog.darkfox.id.au/>,
[source](http://hub.darcs.net/DarkFox/DarkFox-blog)
- <http://nickcharlton.net/>,
[source](https://github.com/nickcharlton/nickcharlton.net)
@@ -67,6 +67,16 @@ this list. This list has no particular ordering.
[source](https://github.com/piyush-kurur-pages/website)
- <http://web.engr.oregonstate.edu/~walkiner/>,
[source](https://github.com/walkie/WebPage)
+- <http://techblog.rosedu.org/>,
+ [source](https://github.com/rosedu/techblog)
+- <http://abizern.org>,
+ [source](https://github.com/Abizern/hblog)
+- <http://freizl.github.io>,
+ [source](https://github.com/freizl/freizl.github.com/tree/master/build)
+- <http://covariant.me>,
+ [source](http://hub.darcs.net/co-dan/website)
+- <http://www.gwern.net/>,
+ [source](https://github.com/gwern/gwern.net)
## Hakyll 3.X
@@ -82,8 +92,6 @@ this list. This list has no particular ordering.
[source](https://github.com/wunki/wunki.org)
- <http://rs.io>,
[source](https://github.com/robertseaton/rs.io/)
-- <http://www.gwern.net/>,
- source [on Patch-tag](https://patch-tag.com/r/gwern/Gwern/home)
- <http://blog.coldflake.com/>,
[source](https://github.com/marcmo/blog.coldflake)
- <http://deepak.jois.name>,
diff --git a/web/releases.markdown b/web/releases.markdown
index bc17298..7277ea9 100644
--- a/web/releases.markdown
+++ b/web/releases.markdown
@@ -4,6 +4,15 @@ title: Releases
# Releases
+## Hakyll 4.4.3.0
+
+- Fix issue when using `metadataRoute` after other custom routes
+
+## Hakyll 4.4.2.0
+
+- Fix issue where Hakyll would not detect a change if a `.metadata` file was
+ deleted
+
## Hakyll 4.4.1.0
- Use Pandoc 1.12 highlighting by default
diff --git a/web/templates/tutorials.html b/web/templates/tutorials.html
index af14097..36c808c 100644
--- a/web/templates/tutorials.html
+++ b/web/templates/tutorials.html
@@ -8,6 +8,6 @@
All these tutorials assume you are using the latest stable version of
Hakyll. If this is not the case, you might want to update using:
</p>
-<pre><code>$ ghc-pkg unregister hakyll
-$ cabal update
-$ cabal install hakyll</code></pre>
+<pre><code>$$ ghc-pkg unregister hakyll
+$$ cabal update
+$$ cabal install hakyll</code></pre>
diff --git a/web/tutorials/hakyll-3-to-hakyll4-migration-guide.markdown b/web/tutorials/hakyll-3-to-hakyll4-migration-guide.markdown
index 86e9412..929e909 100644
--- a/web/tutorials/hakyll-3-to-hakyll4-migration-guide.markdown
+++ b/web/tutorials/hakyll-3-to-hakyll4-migration-guide.markdown
@@ -37,7 +37,7 @@ The `Page` type in Hakyll 3.X has been removed and replaced by an `Item` type.
`pageCompiler` no longer exists -- where you previously used this, you probably
want to use `pandocCompiler` instead.
-`Page`s where manipulated using `setField`/`getField` functions in Hakyll 3.X.
+`Page`s were manipulated using `setField`/`getField` functions in Hakyll 3.X.
In Hakyll 4, all metadata is completely immutable, so these functions have been
removed. In order to format and add fields, use a `Context` -- see the next
section.