summaryrefslogtreecommitdiff
path: root/src
diff options
context:
space:
mode:
authorJasper Van der Jeugt <jaspervdj@gmail.com>2011-01-03 23:24:22 +0100
committerJasper Van der Jeugt <jaspervdj@gmail.com>2011-01-03 23:24:22 +0100
commite395b0af9a969b8a1d93ad0d9f0554841beb9298 (patch)
treee91c16f909105c60dae66734ceac9e7c29b27f58 /src
parent2ceb5f59d0728c380ad7b4f319a9282741e715b9 (diff)
downloadhakyll-e395b0af9a969b8a1d93ad0d9f0554841beb9298.tar.gz
Store result automatically using runCompiler
Diffstat (limited to 'src')
-rw-r--r--src/Hakyll/Core/Compiler.hs27
-rw-r--r--src/Hakyll/Core/Compiler/Internal.hs1
-rw-r--r--src/Hakyll/Core/Run.hs7
3 files changed, 22 insertions, 13 deletions
diff --git a/src/Hakyll/Core/Compiler.hs b/src/Hakyll/Core/Compiler.hs
index df1caeb..57a6d07 100644
--- a/src/Hakyll/Core/Compiler.hs
+++ b/src/Hakyll/Core/Compiler.hs
@@ -3,10 +3,10 @@
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Hakyll.Core.Compiler
( Compiler
+ , runCompiler
, getIdentifier
, getRoute
, getResourceString
- , storeResult
, require
, requireAll
, cached
@@ -31,6 +31,23 @@ import Hakyll.Core.ResourceProvider
import Hakyll.Core.Compiler.Internal
import Hakyll.Core.Store
+-- | Run a compiler, yielding the resulting target and it's dependencies. This
+-- version of 'runCompilerJob' also stores the result
+--
+runCompiler :: Compiler () CompiledItem -- ^ Compiler to run
+ -> Identifier -- ^ Target identifier
+ -> ResourceProvider -- ^ Resource provider
+ -> DependencyLookup -- ^ Dependency lookup table
+ -> Maybe FilePath -- ^ Route
+ -> Store -- ^ Store
+ -> Bool -- ^ Was the resource modified?
+ -> IO CompiledItem -- ^ Resulting item
+runCompiler compiler identifier provider lookup' route store modified = do
+ CompiledItem result <- runCompilerJob
+ compiler identifier provider lookup' route store modified
+ storeSet store "Hakyll.Core.Compiler.runCompiler" identifier result
+ return $ CompiledItem result
+
-- | Get the identifier of the item that is currently being compiled
--
getIdentifier :: Compiler a Identifier
@@ -50,12 +67,6 @@ getResourceString = getIdentifier >>> getResourceString'
provider <- compilerResourceProvider <$> ask
liftIO $ resourceString provider id'
--- | Store a finished item in the cache
---
-storeResult :: Store -> Identifier -> CompiledItem -> IO ()
-storeResult store identifier (CompiledItem x) =
- storeSet store "Hakyll.Core.Compiler.storeResult" identifier x
-
-- | Auxiliary: get a dependency
--
getDependencyOrResult :: (Binary a, Writable a, Typeable a)
@@ -68,7 +79,7 @@ getDependencyOrResult identifier = CompilerM $ do
Just r -> return $ unCompiledItem r
-- Not found here, try the main cache
Nothing -> fmap (fromMaybe error') $ liftIO $
- storeGet store "Hakyll.Core.Compiler.storeResult" identifier
+ storeGet store "Hakyll.Core.Compiler.runCompiler" identifier
where
error' = error "Hakyll.Core.Compiler.getDependency: Not found"
diff --git a/src/Hakyll/Core/Compiler/Internal.hs b/src/Hakyll/Core/Compiler/Internal.hs
index 262cda0..1796565 100644
--- a/src/Hakyll/Core/Compiler/Internal.hs
+++ b/src/Hakyll/Core/Compiler/Internal.hs
@@ -3,6 +3,7 @@
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Hakyll.Core.Compiler.Internal
( Dependencies
+ , DependencyLookup
, CompilerEnvironment (..)
, CompilerM (..)
, Compiler (..)
diff --git a/src/Hakyll/Core/Run.hs b/src/Hakyll/Core/Run.hs
index e9ec47e..c5e6489 100644
--- a/src/Hakyll/Core/Run.hs
+++ b/src/Hakyll/Core/Run.hs
@@ -91,8 +91,8 @@ hakyllWith rules provider store = do
let isModified = id' `S.member` modified'
-- Run the compiler
- compiled <- runCompilerJob comp id' provider (dependencyLookup map')
- url store isModified
+ compiled <- runCompiler comp id' provider (dependencyLookup map')
+ url store isModified
putStrLn $ "Generated target: " ++ show id'
case url of
@@ -103,9 +103,6 @@ hakyllWith rules provider store = do
makeDirectories path
write path compiled
- -- Store it in the cache
- storeResult store id' compiled
-
putStrLn ""
return $ M.insert id' compiled map'