Rename require to load, thanks @ddfreyne

This commit is contained in:
Jasper Van der Jeugt 2012-12-13 22:25:28 +01:00
parent 089670629b
commit cfac1bbca6
6 changed files with 58 additions and 50 deletions

View file

@ -18,9 +18,17 @@ main = hakyll $ do
match (fromList ["about.rst", "contact.markdown"]) $ do
route $ setExtension "html"
compile $ do
defaultTpl <- loadBody "templates/default.html"
pageCompiler
>>= applyTemplate defaultTpl defaultContext
>>= relativizeUrls
{-
compile $ pageCompiler
>>= requireApplyTemplate "templates/default.html" defaultContext
>>= loadAndApplyTemplate "templates/default.html" defaultContext
>>= relativizeUrls
-}
match "posts/*" $ do
route $ setExtension "html"
@ -28,8 +36,8 @@ main = hakyll $ do
post <- pageCompiler
saveSnapshot "content" post
return post
>>= requireApplyTemplate "templates/post.html" postCtx
>>= requireApplyTemplate "templates/default.html" postCtx
>>= loadAndApplyTemplate "templates/post.html" postCtx
>>= loadAndApplyTemplate "templates/default.html" postCtx
>>= relativizeUrls
match "archive.html" $ do
@ -41,8 +49,8 @@ main = hakyll $ do
defaultContext
makeItem ""
>>= requireApplyTemplate "templates/archive.html" archiveCtx
>>= requireApplyTemplate "templates/default.html" archiveCtx
>>= loadAndApplyTemplate "templates/archive.html" archiveCtx
>>= loadAndApplyTemplate "templates/default.html" archiveCtx
>>= relativizeUrls
@ -52,8 +60,8 @@ main = hakyll $ do
let indexCtx = field "posts" $ \_ -> postList (take 3 . recentFirst)
getResourceBody
>>= applySelf indexCtx
>>= requireApplyTemplate "templates/default.html" postCtx
>>= applyAsTemplate indexCtx
>>= loadAndApplyTemplate "templates/default.html" postCtx
>>= relativizeUrls
match "templates/*" $ compile templateCompiler
@ -69,7 +77,7 @@ postCtx =
--------------------------------------------------------------------------------
postList :: ([Item String] -> [Item String]) -> Compiler String
postList preprocess = do
posts <- preprocess <$> requireAll "posts/*"
itemTpl <- requireBody "templates/post-item.html"
posts <- preprocess <$> loadAll "posts/*"
itemTpl <- loadBody "templates/post-item.html"
list <- applyTemplateList itemTpl postCtx posts
return list

View file

@ -13,12 +13,12 @@ module Hakyll.Core.Compiler
, Internal.Snapshot
, saveSnapshot
, Internal.require
, Internal.requireSnapshot
, Internal.requireBody
, Internal.requireSnapshotBody
, Internal.requireAll
, Internal.requireAllSnapshots
, Internal.load
, Internal.loadSnapshot
, Internal.loadBody
, Internal.loadSnapshotBody
, Internal.loadAll
, Internal.loadAllSnapshots
, cached
, unsafeCompiler

View file

@ -3,12 +3,12 @@ module Hakyll.Core.Compiler.Require
( Snapshot
, save
, saveSnapshot
, require
, requireSnapshot
, requireBody
, requireSnapshotBody
, requireAll
, requireAllSnapshots
, load
, loadSnapshot
, loadBody
, loadSnapshotBody
, loadAll
, loadAllSnapshots
) where
@ -44,7 +44,7 @@ save store item = saveSnapshot store final item
--------------------------------------------------------------------------------
-- | Save a specific snapshot of an item, so you can load it later using
-- 'requireSnapshot'.
-- 'loadSnapshot'.
saveSnapshot :: (Binary a, Typeable a)
=> Store -> Snapshot -> Item a -> IO ()
saveSnapshot store snapshot item =
@ -54,15 +54,15 @@ saveSnapshot store snapshot item =
--------------------------------------------------------------------------------
-- | Load an item compiled elsewhere. If the required item is not yet compiled,
-- the build system will take care of that automatically.
require :: (Binary a, Typeable a) => Identifier -> Compiler (Item a)
require id' = requireSnapshot id' final
load :: (Binary a, Typeable a) => Identifier -> Compiler (Item a)
load id' = loadSnapshot id' final
--------------------------------------------------------------------------------
-- | Require a specific snapshot of an item.
requireSnapshot :: (Binary a, Typeable a)
=> Identifier -> Snapshot -> Compiler (Item a)
requireSnapshot id' snapshot = do
loadSnapshot :: (Binary a, Typeable a)
=> Identifier -> Snapshot -> Compiler (Item a)
loadSnapshot id' snapshot = do
store <- compilerStore <$> compilerAsk
universe <- compilerUniverse <$> compilerAsk
@ -78,12 +78,12 @@ requireSnapshot id' snapshot = do
Store.Found x -> return $ Item id' x
where
notFound =
"Hakyll.Core.Compiler.Require.require: " ++ show id' ++
"Hakyll.Core.Compiler.Require.load: " ++ show id' ++
" (snapshot " ++ snapshot ++ ") was not found in the cache, " ++
"the cache might be corrupted or " ++
"the item you are referring to might not exist"
wrongType e r =
"Hakyll.Core.Compiler.Require.require: " ++ show id' ++
"Hakyll.Core.Compiler.Require.load: " ++ show id' ++
" (snapshot " ++ snapshot ++ ") was found in the cache, " ++
"but does not have the right type: expected " ++ show e ++
" but got " ++ show r
@ -92,29 +92,29 @@ requireSnapshot id' snapshot = do
--------------------------------------------------------------------------------
-- | A shortcut for only requiring the body of an item.
--
-- > requireBody = fmap itemBody . require
requireBody :: (Binary a, Typeable a) => Identifier -> Compiler a
requireBody id' = requireSnapshotBody id' final
-- > loadBody = fmap itemBody . load
loadBody :: (Binary a, Typeable a) => Identifier -> Compiler a
loadBody id' = loadSnapshotBody id' final
--------------------------------------------------------------------------------
requireSnapshotBody :: (Binary a, Typeable a)
=> Identifier -> Snapshot -> Compiler a
requireSnapshotBody id' snapshot = fmap itemBody $ requireSnapshot id' snapshot
loadSnapshotBody :: (Binary a, Typeable a)
=> Identifier -> Snapshot -> Compiler a
loadSnapshotBody id' snapshot = fmap itemBody $ loadSnapshot id' snapshot
--------------------------------------------------------------------------------
-- | This function allows you to 'require' a dynamic list of items
requireAll :: (Binary a, Typeable a) => Pattern -> Compiler [Item a]
requireAll pattern = requireAllSnapshots pattern final
-- | This function allows you to 'load' a dynamic list of items
loadAll :: (Binary a, Typeable a) => Pattern -> Compiler [Item a]
loadAll pattern = loadAllSnapshots pattern final
--------------------------------------------------------------------------------
requireAllSnapshots :: (Binary a, Typeable a)
=> Pattern -> Snapshot -> Compiler [Item a]
requireAllSnapshots pattern snapshot = do
loadAllSnapshots :: (Binary a, Typeable a)
=> Pattern -> Snapshot -> Compiler [Item a]
loadAllSnapshots pattern snapshot = do
matching <- getMatches pattern
mapM (\i -> requireSnapshot i snapshot) matching
mapM (\i -> loadSnapshot i snapshot) matching
--------------------------------------------------------------------------------

View file

@ -212,7 +212,7 @@ chase trail id'
liftIO $ write path item
Logger.debug logger $ "Routed to " ++ path
-- Save! (For require)
-- Save! (For load)
liftIO $ save store item
-- Update state

View file

@ -40,7 +40,7 @@ module Hakyll.Web.Template
( Template
, templateCompiler
, applyTemplate
, requireApplyTemplate
, loadAndApplyTemplate
, applyAsTemplate
, applyTemplateWith
) where
@ -82,20 +82,20 @@ applyTemplate tpl context item = do
--------------------------------------------------------------------------------
-- | The following pattern is so common:
--
-- > tpl <- requireBody "templates/foo.html"
-- > tpl <- loadBody "templates/foo.html"
-- > someCompiler
-- > >>= applyTemplate tpl context
--
-- That we have a single function which does this:
--
-- > someCompiler
-- > >>= requireApplyTemplate "templates/foo.html" context
requireApplyTemplate :: Identifier -- ^ Template identifier
-- > >>= loadAndApplyTemplate "templates/foo.html" context
loadAndApplyTemplate :: Identifier -- ^ Template identifier
-> Context a -- ^ Context
-> Item a -- ^ Page
-> Compiler (Item String) -- ^ Resulting item
requireApplyTemplate identifier context item = do
tpl <- requireBody identifier
loadAndApplyTemplate identifier context item = do
tpl <- loadBody identifier
applyTemplate tpl context item

View file

@ -36,7 +36,7 @@ case01 = withTestConfiguration $ \config -> do
match "bodies.txt" $ do
route idRoute
compile $ do
items <- requireAllSnapshots "*.md" "raw"
items <- loadAllSnapshots "*.md" "raw"
makeItem $ concat $ map itemBody (items :: [Item String])
example <- readFile $ destinationDirectory config </> "example.html"