summaryrefslogtreecommitdiff
path: root/src
diff options
context:
space:
mode:
Diffstat (limited to 'src')
-rw-r--r--src/Hakyll/Check.hs13
-rw-r--r--src/Hakyll/Commands.hs55
-rw-r--r--src/Hakyll/Core/Runtime.hs7
-rw-r--r--src/Hakyll/Core/Util/String.hs1
-rw-r--r--src/Hakyll/Init.hs2
-rw-r--r--src/Hakyll/Main.hs30
-rw-r--r--src/Hakyll/Preview/Server.hs20
-rw-r--r--src/Hakyll/Web/Feed.hs2
-rw-r--r--src/Hakyll/Web/Pandoc.hs33
-rw-r--r--src/Hakyll/Web/Pandoc/Biblio.hs4
-rw-r--r--src/Hakyll/Web/Pandoc/FileType.hs43
-rw-r--r--src/Hakyll/Web/Template/Context.hs33
-rw-r--r--src/Hakyll/Web/Template/List.hs2
13 files changed, 152 insertions, 93 deletions
diff --git a/src/Hakyll/Check.hs b/src/Hakyll/Check.hs
index cfd30e4..8e808ba 100644
--- a/src/Hakyll/Check.hs
+++ b/src/Hakyll/Check.hs
@@ -42,7 +42,7 @@ import qualified Paths_hakyll as Paths_hakyll
--------------------------------------------------------------------------------
import Hakyll.Core.Configuration
-import Hakyll.Core.Logger (Logger, Verbosity)
+import Hakyll.Core.Logger (Logger)
import qualified Hakyll.Core.Logger as Logger
import Hakyll.Core.Util.File
import Hakyll.Web.Html
@@ -54,9 +54,9 @@ data Check = All | InternalLinks
--------------------------------------------------------------------------------
-check :: Configuration -> Verbosity -> Check -> IO ExitCode
-check config verbosity check' = do
- ((), write) <- runChecker checkDestination config verbosity check'
+check :: Configuration -> Logger -> Check -> IO ExitCode
+check config logger check' = do
+ ((), write) <- runChecker checkDestination config logger check'
return $ if checkerFaulty write > 0 then ExitFailure 1 else ExitSuccess
@@ -91,10 +91,9 @@ type Checker a = RWST CheckerRead CheckerWrite CheckerState IO a
--------------------------------------------------------------------------------
-runChecker :: Checker a -> Configuration -> Verbosity -> Check
+runChecker :: Checker a -> Configuration -> Logger -> Check
-> IO (a, CheckerWrite)
-runChecker checker config verbosity check' = do
- logger <- Logger.new verbosity
+runChecker checker config logger check' = do
let read' = CheckerRead
{ checkerConfig = config
, checkerLogger = logger
diff --git a/src/Hakyll/Commands.hs b/src/Hakyll/Commands.hs
index 8db889c..6f81080 100644
--- a/src/Hakyll/Commands.hs
+++ b/src/Hakyll/Commands.hs
@@ -14,16 +14,17 @@ module Hakyll.Commands
--------------------------------------------------------------------------------
-import System.Exit (exitWith, ExitCode)
-import System.IO.Error (catchIOError)
import Control.Applicative
-import Control.Monad (void)
import Control.Concurrent
+import Control.Monad (void)
+import System.Exit (ExitCode, exitWith)
+import System.IO.Error (catchIOError)
--------------------------------------------------------------------------------
import qualified Hakyll.Check as Check
import Hakyll.Core.Configuration
-import Hakyll.Core.Logger (Verbosity)
+import Hakyll.Core.Logger (Logger)
+import qualified Hakyll.Core.Logger as Logger
import Hakyll.Core.Rules
import Hakyll.Core.Rules.Internal
import Hakyll.Core.Runtime
@@ -31,7 +32,7 @@ import Hakyll.Core.Util.File
--------------------------------------------------------------------------------
#ifdef WATCH_SERVER
-import Hakyll.Preview.Poll (watchUpdates)
+import Hakyll.Preview.Poll (watchUpdates)
#endif
#ifdef PREVIEW_SERVER
@@ -41,35 +42,36 @@ import Hakyll.Preview.Server
--------------------------------------------------------------------------------
-- | Build the site
-build :: Configuration -> Verbosity -> Rules a -> IO ExitCode
-build conf verbosity rules = fst <$> run conf verbosity rules
+build :: Configuration -> Logger -> Rules a -> IO ExitCode
+build conf logger rules = fst <$> run conf logger rules
+
--------------------------------------------------------------------------------
-- | Run the checker and exit
-check :: Configuration -> Verbosity -> Check.Check -> IO ()
-check config verbosity check' = Check.check config verbosity check' >>= exitWith
+check :: Configuration -> Logger -> Check.Check -> IO ()
+check config logger check' = Check.check config logger check' >>= exitWith
--------------------------------------------------------------------------------
-- | Remove the output directories
-clean :: Configuration -> IO ()
-clean conf = do
+clean :: Configuration -> Logger -> IO ()
+clean conf logger = do
remove $ destinationDirectory conf
remove $ storeDirectory conf
remove $ tmpDirectory conf
where
remove dir = do
- putStrLn $ "Removing " ++ dir ++ "..."
+ Logger.header logger $ "Removing " ++ dir ++ "..."
removeDirectory dir
--------------------------------------------------------------------------------
-- | Preview the site
-preview :: Configuration -> Verbosity -> Rules a -> Int -> IO ()
+preview :: Configuration -> Logger -> Rules a -> Int -> IO ()
#ifdef PREVIEW_SERVER
-preview conf verbosity rules port = do
+preview conf logger rules port = do
deprecatedMessage
- watch conf verbosity "0.0.0.0" port True rules
+ watch conf logger "0.0.0.0" port True rules
where
deprecatedMessage = mapM_ putStrLn [ "The preview command has been deprecated."
, "Use the watch command for recompilation and serving."
@@ -82,9 +84,9 @@ preview _ _ _ _ = previewServerDisabled
--------------------------------------------------------------------------------
-- | Watch and recompile for changes
-watch :: Configuration -> Verbosity -> String -> Int -> Bool -> Rules a -> IO ()
+watch :: Configuration -> Logger -> String -> Int -> Bool -> Rules a -> IO ()
#ifdef WATCH_SERVER
-watch conf verbosity host port runServer rules = do
+watch conf logger host port runServer rules = do
#ifndef mingw32_HOST_OS
_ <- forkIO $ watchUpdates conf update
#else
@@ -97,31 +99,31 @@ watch conf verbosity host port runServer rules = do
server'
where
update = do
- (_, ruleSet) <- run conf verbosity rules
+ (_, ruleSet) <- run conf logger rules
return $ rulesPattern ruleSet
loop = threadDelay 100000 >> loop
- server' = if runServer then server conf host port else loop
+ server' = if runServer then server conf logger host port else loop
#else
watch _ _ _ _ _ _ = watchServerDisabled
#endif
--------------------------------------------------------------------------------
-- | Rebuild the site
-rebuild :: Configuration -> Verbosity -> Rules a -> IO ExitCode
-rebuild conf verbosity rules =
- clean conf >> build conf verbosity rules
+rebuild :: Configuration -> Logger -> Rules a -> IO ExitCode
+rebuild conf logger rules =
+ clean conf logger >> build conf logger rules
--------------------------------------------------------------------------------
-- | Start a server
-server :: Configuration -> String -> Int -> IO ()
+server :: Configuration -> Logger -> String -> Int -> IO ()
#ifdef PREVIEW_SERVER
-server conf host port = do
+server conf logger host port = do
let destination = destinationDirectory conf
- staticServer destination preServeHook host port
+ staticServer logger destination preServeHook host port
where
preServeHook _ = return ()
#else
-server _ _ _ = previewServerDisabled
+server _ _ _ _ = previewServerDisabled
#endif
@@ -156,4 +158,3 @@ watchServerDisabled =
, "Alternatively, use an external tool to serve your site directory."
]
#endif
-
diff --git a/src/Hakyll/Core/Runtime.hs b/src/Hakyll/Core/Runtime.hs
index ea5f811..e85d60d 100644
--- a/src/Hakyll/Core/Runtime.hs
+++ b/src/Hakyll/Core/Runtime.hs
@@ -30,7 +30,7 @@ import Hakyll.Core.Dependencies
import Hakyll.Core.Identifier
import Hakyll.Core.Item
import Hakyll.Core.Item.SomeItem
-import Hakyll.Core.Logger (Logger, Verbosity)
+import Hakyll.Core.Logger (Logger)
import qualified Hakyll.Core.Logger as Logger
import Hakyll.Core.Provider
import Hakyll.Core.Routes
@@ -42,10 +42,9 @@ import Hakyll.Core.Writable
--------------------------------------------------------------------------------
-run :: Configuration -> Verbosity -> Rules a -> IO (ExitCode, RuleSet)
-run config verbosity rules = do
+run :: Configuration -> Logger -> Rules a -> IO (ExitCode, RuleSet)
+run config logger rules = do
-- Initialization
- logger <- Logger.new verbosity
Logger.header logger "Initialising..."
Logger.message logger "Creating store..."
store <- Store.new (inMemoryCache config) $ storeDirectory config
diff --git a/src/Hakyll/Core/Util/String.hs b/src/Hakyll/Core/Util/String.hs
index b46f7b8..23bdd39 100644
--- a/src/Hakyll/Core/Util/String.hs
+++ b/src/Hakyll/Core/Util/String.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE FlexibleContexts #-}
--------------------------------------------------------------------------------
-- | Miscellaneous string manipulation functions.
module Hakyll.Core.Util.String
diff --git a/src/Hakyll/Init.hs b/src/Hakyll/Init.hs
index 98b44ec..9d90f31 100644
--- a/src/Hakyll/Init.hs
+++ b/src/Hakyll/Init.hs
@@ -72,7 +72,7 @@ makeName dstDir = do
createCabal :: FilePath -> String -> IO ()
createCabal path name = do
- writeFile (path ++ ".cabal") $ unlines [
+ writeFile path $ unlines [
"name: " ++ name
, "version: 0.1.0.0"
, "build-type: Simple"
diff --git a/src/Hakyll/Main.hs b/src/Hakyll/Main.hs
index e0c8d4e..86c3245 100644
--- a/src/Hakyll/Main.hs
+++ b/src/Hakyll/Main.hs
@@ -5,6 +5,7 @@
module Hakyll.Main
( hakyll
, hakyllWith
+ , hakyllWithExitCode
) where
@@ -13,7 +14,7 @@ import System.Console.CmdArgs
import qualified System.Console.CmdArgs.Explicit as CA
import System.Environment (getProgName)
import System.IO.Unsafe (unsafePerformIO)
-import System.Exit (exitWith)
+import System.Exit (ExitCode(ExitSuccess), exitWith)
--------------------------------------------------------------------------------
import qualified Hakyll.Check as Check
@@ -28,28 +29,33 @@ import Hakyll.Core.Rules
hakyll :: Rules a -> IO ()
hakyll = hakyllWith Config.defaultConfiguration
-
--------------------------------------------------------------------------------
-- | A variant of 'hakyll' which allows the user to specify a custom
-- configuration
hakyllWith :: Config.Configuration -> Rules a -> IO ()
-hakyllWith conf rules = do
+hakyllWith conf rules = hakyllWithExitCode conf rules >>= exitWith
+
+hakyllWithExitCode :: Config.Configuration -> Rules a -> IO ExitCode
+hakyllWithExitCode conf rules = do
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
+ logger <- Logger.new verbosity'
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 (host args') (port args')
- Watch _ _ p s -> Commands.watch conf verbosity' (host args') p (not s) rules
+ Build _ -> Commands.build conf logger rules
+ Check _ _ -> Commands.check conf logger check' >> ok
+ Clean _ -> Commands.clean conf logger >> ok
+ Deploy _ -> Commands.deploy conf
+ Help _ -> showHelp >> ok
+ Preview _ p -> Commands.preview conf logger rules p >> ok
+ Rebuild _ -> Commands.rebuild conf logger rules
+ Server _ _ _ -> Commands.server conf logger (host args') (port args') >> ok
+ Watch _ _ p s -> Commands.watch conf logger (host args') p (not s) rules >> ok
+ where
+ ok = return ExitSuccess
--------------------------------------------------------------------------------
diff --git a/src/Hakyll/Preview/Server.hs b/src/Hakyll/Preview/Server.hs
index ef1c3c5..5de3d0c 100644
--- a/src/Hakyll/Preview/Server.hs
+++ b/src/Hakyll/Preview/Server.hs
@@ -7,11 +7,16 @@ module Hakyll.Preview.Server
--------------------------------------------------------------------------------
-import Control.Monad.Trans (liftIO)
+import Control.Monad.Trans (liftIO)
import qualified Data.ByteString.Char8 as B
-import qualified Snap.Core as Snap
-import qualified Snap.Http.Server as Snap
-import qualified Snap.Util.FileServe as Snap
+import qualified Snap.Core as Snap
+import qualified Snap.Http.Server as Snap
+import qualified Snap.Util.FileServe as Snap
+
+
+--------------------------------------------------------------------------------
+import Hakyll.Core.Logger (Logger)
+import qualified Hakyll.Core.Logger as Logger
--------------------------------------------------------------------------------
@@ -30,12 +35,14 @@ static directory preServe =
--------------------------------------------------------------------------------
-- | Main method, runs a static server in the given directory
-staticServer :: FilePath -- ^ Directory to serve
+staticServer :: Logger -- ^ Logger
+ -> FilePath -- ^ Directory to serve
-> (FilePath -> IO ()) -- ^ Pre-serve hook
-> String -- ^ Host to bind on
-> Int -- ^ Port to listen on
-> IO () -- ^ Blocks forever
-staticServer directory preServe host port =
+staticServer logger directory preServe host port = do
+ Logger.header logger $ "Listening on http://" ++ host ++ ":" ++ show port
Snap.httpServe config $ static directory preServe
where
-- Snap server config
@@ -43,4 +50,5 @@ staticServer directory preServe host port =
$ Snap.setPort port
$ Snap.setAccessLog Snap.ConfigNoLog
$ Snap.setErrorLog Snap.ConfigNoLog
+ $ Snap.setVerbose False
$ Snap.emptyConfig
diff --git a/src/Hakyll/Web/Feed.hs b/src/Hakyll/Web/Feed.hs
index 794ded5..c5f8e0b 100644
--- a/src/Hakyll/Web/Feed.hs
+++ b/src/Hakyll/Web/Feed.hs
@@ -77,6 +77,8 @@ renderFeed feedPath itemPath config itemContext items = do
itemContext' = mconcat
[ constField "root" (feedRoot config)
+ , constField "authorName" (feedAuthorName config)
+ , constField "authorEmail" (feedAuthorEmail config)
, itemContext
]
diff --git a/src/Hakyll/Web/Pandoc.hs b/src/Hakyll/Web/Pandoc.hs
index 78df1df..f6e9ff1 100644
--- a/src/Hakyll/Web/Pandoc.hs
+++ b/src/Hakyll/Web/Pandoc.hs
@@ -26,6 +26,7 @@ import Control.Applicative ((<$>))
import qualified Data.Set as S
import Data.Traversable (traverse)
import Text.Pandoc
+import Text.Pandoc.Error (PandocError (..))
--------------------------------------------------------------------------------
@@ -36,23 +37,33 @@ import Hakyll.Web.Pandoc.FileType
--------------------------------------------------------------------------------
-- | Read a string using pandoc, with the default options
-readPandoc :: Item String -- ^ String to read
- -> Item Pandoc -- ^ Resulting document
+readPandoc
+ :: Item String -- ^ String to read
+ -> Compiler (Item Pandoc) -- ^ Resulting document
readPandoc = readPandocWith defaultHakyllReaderOptions
--------------------------------------------------------------------------------
-- | Read a string using pandoc, with the supplied options
-readPandocWith :: ReaderOptions -- ^ Parser options
- -> Item String -- ^ String to read
- -> Item Pandoc -- ^ Resulting document
-readPandocWith ropt item = fmap (reader ropt (itemFileType item)) item
+readPandocWith
+ :: ReaderOptions -- ^ Parser options
+ -> Item String -- ^ String to read
+ -> Compiler (Item Pandoc) -- ^ Resulting document
+readPandocWith ropt item =
+ case traverse (reader ropt (itemFileType item)) item of
+ Left (ParseFailure err) -> fail $
+ "Hakyll.Web.Pandoc.readPandocWith: parse failed: " ++ err
+ Left (ParsecError _ err) -> fail $
+ "Hakyll.Web.Pandoc.readPandocWith: parse failed: " ++ show err
+ Right item' -> return item'
where
reader ro t = case t of
+ DocBook -> readDocBook ro
Html -> readHtml ro
LaTeX -> readLaTeX ro
LiterateHaskell t' -> reader (addExt ro Ext_literate_haskell) t'
Markdown -> readMarkdown ro
+ MediaWiki -> readMediaWiki ro
OrgMode -> readOrg ro
Rst -> readRST ro
Textile -> readTextile ro
@@ -80,15 +91,17 @@ writePandocWith wopt = fmap $ writeHtmlString wopt
--------------------------------------------------------------------------------
-- | Render the resource using pandoc
-renderPandoc :: Item String -> Item String
+renderPandoc :: Item String -> Compiler (Item String)
renderPandoc =
renderPandocWith defaultHakyllReaderOptions defaultHakyllWriterOptions
--------------------------------------------------------------------------------
-- | Render the resource using pandoc
-renderPandocWith :: ReaderOptions -> WriterOptions -> Item String -> Item String
-renderPandocWith ropt wopt = writePandocWith wopt . readPandocWith ropt
+renderPandocWith
+ :: ReaderOptions -> WriterOptions -> Item String -> Compiler (Item String)
+renderPandocWith ropt wopt item =
+ writePandocWith wopt <$> readPandocWith ropt item
--------------------------------------------------------------------------------
@@ -127,7 +140,7 @@ pandocCompilerWithTransformM :: ReaderOptions -> WriterOptions
-> Compiler (Item String)
pandocCompilerWithTransformM ropt wopt f =
writePandocWith wopt <$>
- (traverse f =<< readPandocWith ropt <$> getResourceBody)
+ (traverse f =<< readPandocWith ropt =<< getResourceBody)
--------------------------------------------------------------------------------
diff --git a/src/Hakyll/Web/Pandoc/Biblio.hs b/src/Hakyll/Web/Pandoc/Biblio.hs
index c85512f..53e3419 100644
--- a/src/Hakyll/Web/Pandoc/Biblio.hs
+++ b/src/Hakyll/Web/Pandoc/Biblio.hs
@@ -104,8 +104,8 @@ readPandocBiblio ropt csl biblio item = do
-- actual page. If we don't do this, pandoc won't even consider them
-- citations!
let Biblio refs = itemBody biblio
- pandoc = itemBody $ readPandocWith ropt item
- pandoc' = processCites style refs pandoc
+ pandoc <- itemBody <$> readPandocWith ropt item
+ let pandoc' = processCites style refs pandoc
return $ fmap (const pandoc') item
diff --git a/src/Hakyll/Web/Pandoc/FileType.hs b/src/Hakyll/Web/Pandoc/FileType.hs
index 46c8e24..3636e41 100644
--- a/src/Hakyll/Web/Pandoc/FileType.hs
+++ b/src/Hakyll/Web/Pandoc/FileType.hs
@@ -22,10 +22,12 @@ import Hakyll.Core.Item
data FileType
= Binary
| Css
+ | DocBook
| Html
| LaTeX
| LiterateHaskell FileType
| Markdown
+ | MediaWiki
| OrgMode
| PlainText
| Rst
@@ -38,29 +40,32 @@ data FileType
fileType :: FilePath -> FileType
fileType = uncurry fileType' . splitExtension
where
- fileType' _ ".css" = Css
- fileType' _ ".htm" = Html
- fileType' _ ".html" = Html
- fileType' f ".lhs" = LiterateHaskell $ case fileType f of
+ fileType' _ ".css" = Css
+ fileType' _ ".dbk" = DocBook
+ fileType' _ ".htm" = Html
+ fileType' _ ".html" = Html
+ fileType' f ".lhs" = LiterateHaskell $ case fileType f of
-- If no extension is given, default to Markdown + LiterateHaskell
Binary -> Markdown
-- Otherwise, LaTeX + LiterateHaskell or whatever the user specified
x -> x
- fileType' _ ".markdown" = Markdown
- fileType' _ ".md" = Markdown
- fileType' _ ".mdn" = Markdown
- fileType' _ ".mdown" = Markdown
- fileType' _ ".mdwn" = Markdown
- fileType' _ ".mkd" = Markdown
- fileType' _ ".mkdwn" = Markdown
- fileType' _ ".org" = OrgMode
- fileType' _ ".page" = Markdown
- fileType' _ ".rst" = Rst
- fileType' _ ".tex" = LaTeX
- fileType' _ ".text" = PlainText
- fileType' _ ".textile" = Textile
- fileType' _ ".txt" = PlainText
- fileType' _ _ = Binary -- Treat unknown files as binary
+ fileType' _ ".markdown" = Markdown
+ fileType' _ ".mediawiki" = MediaWiki
+ fileType' _ ".md" = Markdown
+ fileType' _ ".mdn" = Markdown
+ fileType' _ ".mdown" = Markdown
+ fileType' _ ".mdwn" = Markdown
+ fileType' _ ".mkd" = Markdown
+ fileType' _ ".mkdwn" = Markdown
+ fileType' _ ".org" = OrgMode
+ fileType' _ ".page" = Markdown
+ fileType' _ ".rst" = Rst
+ fileType' _ ".tex" = LaTeX
+ fileType' _ ".text" = PlainText
+ fileType' _ ".textile" = Textile
+ fileType' _ ".txt" = PlainText
+ fileType' _ ".wiki" = MediaWiki
+ fileType' _ _ = Binary -- Treat unknown files as binary
--------------------------------------------------------------------------------
diff --git a/src/Hakyll/Web/Template/Context.hs b/src/Hakyll/Web/Template/Context.hs
index 2da76d4..a0f2779 100644
--- a/src/Hakyll/Web/Template/Context.hs
+++ b/src/Hakyll/Web/Template/Context.hs
@@ -4,6 +4,7 @@ module Hakyll.Web.Template.Context
( ContextField (..)
, Context (..)
, field
+ , boolField
, constField
, listField
, listFieldWith
@@ -22,12 +23,13 @@ module Hakyll.Web.Template.Context
, modificationTimeField
, modificationTimeFieldWith
, teaserField
+ , teaserFieldWithSeparator
, missingField
) where
--------------------------------------------------------------------------------
-import Control.Applicative (Alternative (..), (<$>))
+import Control.Applicative (Alternative (..), (<$>), pure)
import Control.Monad (msum)
import Data.List (intercalate)
import qualified Data.Map as M
@@ -35,7 +37,7 @@ import Data.Monoid (Monoid (..))
import Data.Time.Clock (UTCTime (..))
import Data.Time.Format (formatTime, parseTime)
import System.FilePath (takeBaseName, splitDirectories)
-import System.Locale (TimeLocale, defaultTimeLocale)
+import Data.Time.Locale.Compat (TimeLocale, defaultTimeLocale)
--------------------------------------------------------------------------------
@@ -98,6 +100,17 @@ field key value = field' key (fmap StringField . value)
--------------------------------------------------------------------------------
+-- | Creates a 'field' to use with the @$if()$@ template macro.
+boolField
+ :: String
+ -> (Item a -> Bool)
+ -> Context a
+boolField name f = field name (\i -> if f i
+ then pure (error $ unwords ["no string value for bool field:",name])
+ else empty)
+
+
+--------------------------------------------------------------------------------
-- | Creates a 'field' that does not depend on the 'Item'
constField :: String -> String -> Context a
constField key = field key . const . return
@@ -306,9 +319,21 @@ modificationTimeFieldWith locale key fmt = field key $ \i -> do
teaserField :: String -- ^ Key to use
-> Snapshot -- ^ Snapshot to load
-> Context String -- ^ Resulting context
-teaserField key snapshot = field key $ \item -> do
+teaserField = teaserFieldWithSeparator teaserSeparator
+
+
+--------------------------------------------------------------------------------
+-- | A context with "teaser" key which contain a teaser of the item, defined as
+-- the snapshot content before the teaser separator. The item is loaded from the
+-- given snapshot (which should be saved in the user code before any templates
+-- are applied).
+teaserFieldWithSeparator :: String -- ^ Separator to use
+ -> String -- ^ Key to use
+ -> Snapshot -- ^ Snapshot to load
+ -> Context String -- ^ Resulting context
+teaserFieldWithSeparator separator key snapshot = field key $ \item -> do
body <- itemBody <$> loadSnapshot (itemIdentifier item) snapshot
- case needlePrefix teaserSeparator body of
+ case needlePrefix separator body of
Nothing -> fail $
"Hakyll.Web.Template.Context: no teaser defined for " ++
show (itemIdentifier item)
diff --git a/src/Hakyll/Web/Template/List.hs b/src/Hakyll/Web/Template/List.hs
index 1f2a570..4d769fc 100644
--- a/src/Hakyll/Web/Template/List.hs
+++ b/src/Hakyll/Web/Template/List.hs
@@ -22,7 +22,7 @@ module Hakyll.Web.Template.List
import Control.Monad (liftM)
import Data.List (intersperse, sortBy)
import Data.Ord (comparing)
-import System.Locale (defaultTimeLocale)
+import Data.Time.Locale.Compat (defaultTimeLocale)
--------------------------------------------------------------------------------