summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--hakyll.cabal138
-rw-r--r--src/Hakyll/Commands.hs51
-rw-r--r--src/Hakyll/Core/Configuration.hs5
-rw-r--r--src/Hakyll/Core/Provider/Internal.hs2
-rw-r--r--src/Hakyll/Core/Provider/Metadata.hs5
-rw-r--r--src/Hakyll/Core/Store.hs5
-rw-r--r--src/Hakyll/Main.hs40
-rw-r--r--src/Hakyll/Web/Html.hs2
-rw-r--r--src/Hakyll/Web/Pandoc/Biblio.hs15
-rw-r--r--src/Hakyll/Web/Template/Context.hs26
-rw-r--r--src/Hakyll/Web/Template/Read.hs2
-rw-r--r--tests/Hakyll/Web/Template/Tests.hs1
-rw-r--r--tests/data/template.html2
-rw-r--r--tests/data/template.html.out2
-rw-r--r--web/examples.markdown12
15 files changed, 211 insertions, 97 deletions
diff --git a/hakyll.cabal b/hakyll.cabal
index ced01c6..6ec6ab8 100644
--- a/hakyll.cabal
+++ b/hakyll.cabal
@@ -1,5 +1,5 @@
Name: hakyll
-Version: 4.3.1.0
+Version: 4.3.3.0
Synopsis: A static website compiler library
Description:
@@ -78,6 +78,10 @@ Flag previewServer
Description: Include the preview server
Default: True
+Flag watchServer
+ Description: Include the watch server
+ Default: True
+
Flag checkExternal
Description: Include external link checking
Default: True
@@ -137,33 +141,33 @@ Library
Paths_hakyll
Build-Depends:
- base >= 4 && < 5,
- binary >= 0.5 && < 0.8,
- blaze-html >= 0.5 && < 0.7,
- blaze-markup >= 0.5.1 && < 0.6,
- bytestring >= 0.9 && < 0.11,
- citeproc-hs >= 0.3.2 && < 0.4,
- cmdargs >= 0.10 && < 0.11,
- containers >= 0.3 && < 0.6,
- cryptohash >= 0.7 && < 0.10,
- data-default >= 0.4 && < 0.6,
- deepseq >= 1.3 && < 1.4,
- directory >= 1.0 && < 1.3,
- filepath >= 1.0 && < 1.4,
- lrucache >= 1.1.1 && < 1.2,
- mtl >= 1 && < 2.2,
- network >= 2.4 && < 2.5,
- old-locale >= 1.0 && < 1.1,
- old-time >= 1.0 && < 1.2,
- pandoc >= 1.10 && < 1.12,
- parsec >= 3.0 && < 3.2,
- process >= 1.0 && < 1.2,
- 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,
- time >= 1.1 && < 1.5
+ base >= 4 && < 5,
+ binary >= 0.5 && < 0.8,
+ blaze-html >= 0.5 && < 0.7,
+ blaze-markup >= 0.5.1 && < 0.6,
+ bytestring >= 0.9 && < 0.11,
+ cmdargs >= 0.10 && < 0.11,
+ containers >= 0.3 && < 0.6,
+ cryptohash >= 0.7 && < 0.11,
+ data-default >= 0.4 && < 0.6,
+ deepseq >= 1.3 && < 1.4,
+ directory >= 1.0 && < 1.3,
+ filepath >= 1.0 && < 1.4,
+ lrucache >= 1.1.1 && < 1.2,
+ mtl >= 1 && < 2.2,
+ network >= 2.4 && < 2.5,
+ old-locale >= 1.0 && < 1.1,
+ old-time >= 1.0 && < 1.2,
+ pandoc >= 1.12 && < 1.13,
+ pandoc-citeproc >= 0.1 && < 0.2,
+ parsec >= 3.0 && < 3.2,
+ process >= 1.0 && < 1.2,
+ 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,
+ time >= 1.1 && < 1.5
If flag(previewServer)
Build-depends:
@@ -177,6 +181,15 @@ Library
Hakyll.Preview.Poll
Hakyll.Preview.Server
+ If flag(watchServer)
+ Build-depends:
+ fsnotify >= 0.0.6 && < 0.1,
+ system-filepath >= 0.4.6 && <= 0.5
+ Cpp-options:
+ -DWATCH_SERVER
+ Other-modules:
+ Hakyll.Preview.Poll
+
If flag(checkExternal)
Build-depends:
http-conduit >= 1.8 && < 1.10,
@@ -209,38 +222,38 @@ Test-suite hakyll-tests
Build-Depends:
HUnit >= 1.2 && < 1.3,
- QuickCheck >= 2.4 && < 2.6,
+ QuickCheck >= 2.4 && < 2.7,
test-framework >= 0.4 && < 0.9,
- test-framework-hunit >= 0.2 && < 0.4,
- test-framework-quickcheck2 >= 0.2 && < 0.4,
+ test-framework-hunit >= 0.3 && < 0.4,
+ test-framework-quickcheck2 >= 0.3 && < 0.4,
-- Copy pasted from hakyll dependencies:
- base >= 4 && < 5,
- binary >= 0.5 && < 0.8,
- blaze-html >= 0.5 && < 0.7,
- blaze-markup >= 0.5.1 && < 0.6,
- bytestring >= 0.9 && < 0.11,
- citeproc-hs >= 0.3.2 && < 0.4,
- cmdargs >= 0.10 && < 0.11,
- containers >= 0.3 && < 0.6,
- cryptohash >= 0.7 && < 0.10,
- data-default >= 0.4 && < 0.6,
- deepseq >= 1.3 && < 1.4,
- directory >= 1.0 && < 1.3,
- filepath >= 1.0 && < 1.4,
- lrucache >= 1.1.1 && < 1.2,
- mtl >= 1 && < 2.2,
- network >= 2.4 && < 2.5,
- old-locale >= 1.0 && < 1.1,
- old-time >= 1.0 && < 1.2,
- pandoc >= 1.10 && < 1.12,
- parsec >= 3.0 && < 3.2,
- process >= 1.0 && < 1.2,
- 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,
- time >= 1.1 && < 1.5
+ base >= 4 && < 5,
+ binary >= 0.5 && < 0.8,
+ blaze-html >= 0.5 && < 0.7,
+ blaze-markup >= 0.5.1 && < 0.6,
+ bytestring >= 0.9 && < 0.11,
+ cmdargs >= 0.10 && < 0.11,
+ containers >= 0.3 && < 0.6,
+ cryptohash >= 0.7 && < 0.11,
+ data-default >= 0.4 && < 0.6,
+ deepseq >= 1.3 && < 1.4,
+ directory >= 1.0 && < 1.3,
+ filepath >= 1.0 && < 1.4,
+ lrucache >= 1.1.1 && < 1.2,
+ mtl >= 1 && < 2.2,
+ network >= 2.4 && < 2.5,
+ old-locale >= 1.0 && < 1.1,
+ old-time >= 1.0 && < 1.2,
+ pandoc >= 1.12 && < 1.13,
+ pandoc-citeproc >= 0.1 && < 0.2,
+ parsec >= 3.0 && < 3.2,
+ process >= 1.0 && < 1.2,
+ 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,
+ time >= 1.1 && < 1.5
If flag(previewServer)
Build-depends:
@@ -254,6 +267,15 @@ Test-suite hakyll-tests
Hakyll.Preview.Poll
Hakyll.Preview.Server
+ If flag(watchServer)
+ Build-depends:
+ fsnotify >= 0.0.6 && < 0.1,
+ system-filepath >= 0.4.6 && <= 0.5
+ Cpp-options:
+ -DWATCH_SERVER
+ Other-modules:
+ Hakyll.Preview.Poll
+
If flag(checkExternal)
Build-depends:
http-conduit >= 1.8 && < 1.10,
diff --git a/src/Hakyll/Commands.hs b/src/Hakyll/Commands.hs
index d86fd5c..7951f4e 100644
--- a/src/Hakyll/Commands.hs
+++ b/src/Hakyll/Commands.hs
@@ -1,4 +1,4 @@
---------------------------------------------------------------------------------
+ --------------------------------------------------------------------------------
-- | Implementation of Hakyll commands: build, preview...
{-# LANGUAGE CPP #-}
module Hakyll.Commands
@@ -9,12 +9,14 @@ module Hakyll.Commands
, rebuild
, server
, deploy
+ , watch
) where
--------------------------------------------------------------------------------
import System.Exit (exitWith, ExitCode)
import Control.Applicative
+import Control.Concurrent
--------------------------------------------------------------------------------
import qualified Hakyll.Check as Check
@@ -26,8 +28,11 @@ import Hakyll.Core.Runtime
import Hakyll.Core.Util.File
--------------------------------------------------------------------------------
+#ifdef WATCH_SERVER
+import Hakyll.Preview.Poll (watchUpdates)
+#endif
+
#ifdef PREVIEW_SERVER
-import Hakyll.Preview.Poll
import Hakyll.Preview.Server
#endif
@@ -60,18 +65,39 @@ clean conf = do
-- | Preview the site
preview :: Configuration -> Verbosity -> Rules a -> Int -> IO ()
#ifdef PREVIEW_SERVER
-preview conf verbosity rules port = do
+preview conf verbosity rules port = do
+ deprecatedMessage
+ watch conf verbosity port True rules
+ where
+ deprecatedMessage = mapM_ putStrLn [ "The preview command has been deprecated."
+ , "Use the watch command for recompilation and serving."
+ ]
+#else
+preview _ _ _ _ = previewServerDisabled
+#endif
+
+
+--------------------------------------------------------------------------------
+-- | Watch and recompile for changes
+
+watch :: Configuration -> Verbosity -> Int -> Bool -> Rules a -> IO ()
+#ifdef WATCH_SERVER
+watch conf verbosity port runServer rules = do
watchUpdates conf update
- server conf port
+ _ <- forkIO (server')
+ loop
where
update = do
(_, ruleSet) <- run conf verbosity rules
return $ rulesPattern ruleSet
+
+ loop = threadDelay 100000 >> loop
+
+ server' = if runServer then server conf port else return ()
#else
-preview _ _ _ _ = previewServerDisabled
+watch _ _ _ _ _ = watchServerDisabled
#endif
-
--------------------------------------------------------------------------------
-- | Rebuild the site
rebuild :: Configuration -> Verbosity -> Rules a -> IO ExitCode
@@ -111,3 +137,16 @@ previewServerDisabled =
, "Alternatively, use an external tool to serve your site directory."
]
#endif
+
+#ifndef WATCH_SERVER
+watchServerDisabled :: IO ()
+watchServerDisabled =
+ mapM_ putStrLn
+ [ "WATCH SERVER"
+ , ""
+ , "The watch server is not enabled in the version of Hakyll. To"
+ , "enable it, set the flag to True and recompile Hakyll."
+ , "Alternatively, use an external tool to serve your site directory."
+ ]
+#endif
+
diff --git a/src/Hakyll/Core/Configuration.hs b/src/Hakyll/Core/Configuration.hs
index a4bc90b..f9927de 100644
--- a/src/Hakyll/Core/Configuration.hs
+++ b/src/Hakyll/Core/Configuration.hs
@@ -69,6 +69,10 @@ data Configuration = Configuration
, -- | Use an in-memory cache for items. This is faster but uses more
-- memory.
inMemoryCache :: Bool
+ , -- | Override default port for preview server. Default is 8000.
+ -- One can also override the port as a command line argument:
+ -- ./site preview -p 1234
+ previewPort :: Int
}
--------------------------------------------------------------------------------
@@ -87,6 +91,7 @@ defaultConfiguration = Configuration
, deployCommand = "echo 'No deploy command specified' && exit 1"
, deploySite = system . deployCommand
, inMemoryCache = True
+ , previewPort = 8000
}
where
ignoreFile' path
diff --git a/src/Hakyll/Core/Provider/Internal.hs b/src/Hakyll/Core/Provider/Internal.hs
index 583c665..d566f3a 100644
--- a/src/Hakyll/Core/Provider/Internal.hs
+++ b/src/Hakyll/Core/Provider/Internal.hs
@@ -98,7 +98,7 @@ data Provider = Provider
providerOldFiles :: Map Identifier ResourceInfo
, -- | Underlying persistent store for caching
providerStore :: Store
- }
+ } deriving (Show)
--------------------------------------------------------------------------------
diff --git a/src/Hakyll/Core/Provider/Metadata.hs b/src/Hakyll/Core/Provider/Metadata.hs
index fe2857a..7e4d7ed 100644
--- a/src/Hakyll/Core/Provider/Metadata.hs
+++ b/src/Hakyll/Core/Provider/Metadata.hs
@@ -44,8 +44,9 @@ loadMetadata p identifier = do
return (M.union md emd, body)
where
- fp = resourceFilePath p identifier
- mi = M.lookup identifier (providerFiles p) >>= resourceInfoMetadata
+ normal = setVersion Nothing identifier
+ fp = resourceFilePath p identifier
+ mi = M.lookup normal (providerFiles p) >>= resourceInfoMetadata
--------------------------------------------------------------------------------
diff --git a/src/Hakyll/Core/Store.hs b/src/Hakyll/Core/Store.hs
index 74d9d2f..5c3667d 100644
--- a/src/Hakyll/Core/Store.hs
+++ b/src/Hakyll/Core/Store.hs
@@ -50,6 +50,11 @@ data Store = Store
--------------------------------------------------------------------------------
+instance Show Store where
+ show _ = "<Store>"
+
+
+--------------------------------------------------------------------------------
-- | Result of a store query
data Result a
= Found a -- ^ Found, result
diff --git a/src/Hakyll/Main.hs b/src/Hakyll/Main.hs
index 7e50418..86516cb 100644
--- a/src/Hakyll/Main.hs
+++ b/src/Hakyll/Main.hs
@@ -34,27 +34,28 @@ hakyll = hakyllWith Config.defaultConfiguration
-- configuration
hakyllWith :: Config.Configuration -> Rules a -> IO ()
hakyllWith conf rules = do
- args' <- cmdArgs hakyllArgs
+ args' <- cmdArgs (hakyllArgs conf)
let verbosity' = if verbose args' then Logger.Debug else Logger.Message
check' =
if internal_links args' then Check.InternalLinks else Check.All
case args' of
- Build _ -> Commands.build conf verbosity' rules >>= exitWith
- Check _ _ -> Commands.check conf verbosity' check'
- Clean _ -> Commands.clean conf
- Deploy _ -> Commands.deploy conf >>= exitWith
- Help _ -> showHelp
- Preview _ p -> Commands.preview conf verbosity' rules p
- Rebuild _ -> Commands.rebuild conf verbosity' rules >>= exitWith
- Server _ _ -> Commands.server conf (port args')
+ Build _ -> Commands.build conf verbosity' rules >>= exitWith
+ Check _ _ -> Commands.check conf verbosity' check'
+ Clean _ -> Commands.clean conf
+ Deploy _ -> Commands.deploy conf >>= exitWith
+ Help _ -> showHelp
+ Preview _ p -> Commands.preview conf verbosity' rules p
+ Rebuild _ -> Commands.rebuild conf verbosity' rules >>= exitWith
+ Server _ _ -> Commands.server conf (port args')
+ Watch _ p s -> Commands.watch conf verbosity' p (not s) rules
--------------------------------------------------------------------------------
-- | Show usage information.
showHelp :: IO ()
-showHelp = print $ CA.helpText [] CA.HelpFormatOne $ cmdArgsMode hakyllArgs
+showHelp = print $ CA.helpText [] CA.HelpFormatOne $ cmdArgsMode (hakyllArgs Config.defaultConfiguration)
--------------------------------------------------------------------------------
@@ -67,24 +68,28 @@ data HakyllArgs
| Preview {verbose :: Bool, port :: Int}
| Rebuild {verbose :: Bool}
| Server {verbose :: Bool, port :: Int}
+ | Watch {verbose :: Bool, port :: Int, no_server :: Bool }
deriving (Data, Typeable, Show)
--------------------------------------------------------------------------------
-hakyllArgs :: HakyllArgs
-hakyllArgs = modes
+hakyllArgs :: Config.Configuration -> HakyllArgs
+hakyllArgs conf = modes
[ (Build $ verboseFlag def) &= help "Generate the site"
, (Check (verboseFlag def) (False &= help "Check internal links only")) &=
help "Validate the site output"
, (Clean $ verboseFlag def) &= help "Clean up and remove cache"
, (Deploy $ verboseFlag def) &= help "Upload/deploy your site"
, (Help $ verboseFlag def) &= help "Show this message" &= auto
- , (Preview (verboseFlag def) (portFlag 8000)) &=
- help "Start a preview server and autocompile on changes"
+ , (Preview (verboseFlag def) (portFlag defaultPort)) &=
+ help "[Deprecated] Please use the watch command"
, (Rebuild $ verboseFlag def) &= help "Clean and build again"
- , (Server (verboseFlag def) (portFlag 8000)) &=
+ , (Server (verboseFlag def) (portFlag defaultPort)) &=
help "Start a preview server"
+ , (Watch (verboseFlag def) (portFlag defaultPort) (noServerFlag False) &=
+ help "Autocompile on changes and start a preview server. You can watch and recompile without running a server with --no-server.")
] &= help "Hakyll static site compiler" &= program progName
+ where defaultPort = Config.previewPort conf
--------------------------------------------------------------------------------
@@ -94,6 +99,11 @@ verboseFlag x = x &= help "Run in verbose mode"
--------------------------------------------------------------------------------
+noServerFlag :: Data a => a -> a
+noServerFlag x = x &= help "Disable the built-in web server"
+{-# INLINE noServerFlag #-}
+
+--------------------------------------------------------------------------------
portFlag :: Data a => a -> a
portFlag x = x &= help "Port to listen on"
{-# INLINE portFlag #-}
diff --git a/src/Hakyll/Web/Html.hs b/src/Hakyll/Web/Html.hs
index 3a0aa3b..f5a7ccc 100644
--- a/src/Hakyll/Web/Html.hs
+++ b/src/Hakyll/Web/Html.hs
@@ -25,7 +25,7 @@ import Data.Char (digitToInt, intToDigit,
isDigit, toLower)
import Data.List (isPrefixOf)
import qualified Data.Set as S
-import System.FilePath (joinPath, splitPath,
+import System.FilePath.Posix (joinPath, splitPath,
takeDirectory)
import Text.Blaze.Html (toHtml)
import Text.Blaze.Html.Renderer.String (renderHtml)
diff --git a/src/Hakyll/Web/Pandoc/Biblio.hs b/src/Hakyll/Web/Pandoc/Biblio.hs
index 9c4b0bf..db022bc 100644
--- a/src/Hakyll/Web/Pandoc/Biblio.hs
+++ b/src/Hakyll/Web/Pandoc/Biblio.hs
@@ -22,12 +22,10 @@ module Hakyll.Web.Pandoc.Biblio
--------------------------------------------------------------------------------
import Control.Applicative ((<$>))
import Data.Binary (Binary (..))
-import Data.Traversable (traverse)
import Data.Typeable (Typeable)
import qualified Text.CSL as CSL
+import Text.CSL.Pandoc (processCites)
import Text.Pandoc (Pandoc, ReaderOptions (..))
-import Text.Pandoc.Biblio (processBiblio)
-
--------------------------------------------------------------------------------
import Hakyll.Core.Compiler
@@ -86,21 +84,20 @@ biblioCompiler = do
--------------------------------------------------------------------------------
readPandocBiblio :: ReaderOptions
- -> Maybe (Item CSL)
+ -> Item CSL
-> Item Biblio
-> (Item String)
-> Compiler (Item Pandoc)
readPandocBiblio ropt csl biblio item = do
-- Parse CSL file, if given
- style <- unsafeCompiler $
- traverse (CSL.readCSLFile . toFilePath . itemIdentifier) csl
+ style <- unsafeCompiler $ CSL.readCSLFile . toFilePath . itemIdentifier $ csl
-- We need to know the citation keys, add then *before* actually parsing the
-- actual page. If we don't do this, pandoc won't even consider them
-- citations!
let Biblio refs = itemBody biblio
- ropt' = ropt {readerReferences = readerReferences ropt ++ refs}
- pandoc = itemBody $ readPandocWith ropt' item
- pandoc' = processBiblio style refs pandoc
+ pandoc = itemBody $ readPandocWith ropt item
+ pandoc' = processCites style refs pandoc
return $ fmap (const pandoc') item
+
diff --git a/src/Hakyll/Web/Template/Context.hs b/src/Hakyll/Web/Template/Context.hs
index ecf769d..cd52eb0 100644
--- a/src/Hakyll/Web/Template/Context.hs
+++ b/src/Hakyll/Web/Template/Context.hs
@@ -6,6 +6,8 @@ module Hakyll.Web.Template.Context
, field
, constField
, listField
+ , functionField
+ , mapContext
, defaultContext
, bodyField
@@ -86,6 +88,26 @@ listField key c xs = field' key $ \_ -> fmap (ListField c) xs
--------------------------------------------------------------------------------
+functionField :: String -> ([String] -> Item a -> Compiler String) -> Context a
+functionField name value = Context $ \k i -> case words k of
+ [] -> empty
+ (n : args)
+ | n == name -> StringField <$> value args i
+ | otherwise -> empty
+
+
+--------------------------------------------------------------------------------
+mapContext :: (String -> String) -> Context a -> Context a
+mapContext f (Context c) = Context $ \k i -> do
+ fld <- c k i
+ case fld of
+ StringField str -> return $ StringField (f str)
+ ListField _ _ -> fail $
+ "Hakyll.Web.Template.Context.mapContext: " ++
+ "can't map over a ListField!"
+
+
+--------------------------------------------------------------------------------
defaultContext :: Context String
defaultContext =
bodyField "body" `mappend`
@@ -108,7 +130,7 @@ bodyField key = field key $ return . itemBody
--------------------------------------------------------------------------------
-- | Map any field to its metadata value, if present
-metadataField :: Context String
+metadataField :: Context a
metadataField = Context $ \k i -> do
value <- getMetadataField (itemIdentifier i) k
maybe empty (return . StringField) value
@@ -130,7 +152,7 @@ pathField key = field key $ return . toFilePath . itemIdentifier
--------------------------------------------------------------------------------
-- | This title field takes the basename of the underlying file by default
titleField :: String -> Context a
-titleField key = field key $ return . takeBaseName . toFilePath . itemIdentifier
+titleField = mapContext takeBaseName . pathField
--------------------------------------------------------------------------------
diff --git a/src/Hakyll/Web/Template/Read.hs b/src/Hakyll/Web/Template/Read.hs
index bb5c8c2..2421b2d 100644
--- a/src/Hakyll/Web/Template/Read.hs
+++ b/src/Hakyll/Web/Template/Read.hs
@@ -21,7 +21,7 @@ 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
+ Right t -> t
--------------------------------------------------------------------------------
diff --git a/tests/Hakyll/Web/Template/Tests.hs b/tests/Hakyll/Web/Template/Tests.hs
index 1d80a06..8763147 100644
--- a/tests/Hakyll/Web/Template/Tests.hs
+++ b/tests/Hakyll/Web/Template/Tests.hs
@@ -58,6 +58,7 @@ testContext = mconcat
n1 <- makeItem "Jan"
n2 <- makeItem "Piet"
return [n1, n2]
+ , functionField "rev" $ \args _ -> return $ unwords $ map reverse args
]
where
diff --git a/tests/data/template.html b/tests/data/template.html
index 22e5ddd..26f9e8a 100644
--- a/tests/data/template.html
+++ b/tests/data/template.html
@@ -1,6 +1,8 @@
<div>
I'm so rich I have $$3.
+ $rev foo$
+
$if(body)$
I have body
$else$
diff --git a/tests/data/template.html.out b/tests/data/template.html.out
index 8047b0d..0b17d31 100644
--- a/tests/data/template.html.out
+++ b/tests/data/template.html.out
@@ -1,6 +1,8 @@
<div>
I'm so rich I have $3.
+ oof
+
I have body
diff --git a/web/examples.markdown b/web/examples.markdown
index 16ebf96..96817ac 100644
--- a/web/examples.markdown
+++ b/web/examples.markdown
@@ -55,7 +55,15 @@ this list. This list has no particular ordering.
[source](https://github.com/xinitrc/xinitrc.de)
- <http://darkfox.us.to/>,
[source](http://hub.darcs.net/DarkFox/DarkFox-blog)
-- <http://cse.iitk.ac.in/users/ppk>
+- <http://nickcharlton.net/>,
+ [source](https://github.com/nickcharlton/nickcharlton.net)
+- <http://scr.stunts.hu/>,
+ [literate source](http://scr.stunts.hu/hakyll.html)
+- <http://www.eanalytica.com/>,
+ [literate source](http://www.eanalytica.com/site/)
+- <http://dikmax.name/>,
+ [source](https://github.com/dikmax/dikmax.name)
+- <http://cse.iitk.ac.in/users/ppk>,
[source](https://github.com/piyush-kurur-pages/website)
## Hakyll 3.X
@@ -73,7 +81,7 @@ this list. This list has no particular ordering.
- <http://rs.io>,
[source](https://github.com/robertseaton/rs.io/)
- <http://www.gwern.net/>,
- source: `darcs get 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>,