Revert "Track metadata dependencies"

This reverts commit 712ffa39b5.

Conflicts:
	src/Hakyll/Core/Metadata.hs
	src/Hakyll/Core/Rules/Default.hs
This commit is contained in:
Jasper Van der Jeugt 2014-03-26 11:30:08 +01:00
parent e5446fd401
commit 6552dd5bc0
5 changed files with 14 additions and 47 deletions

View File

@ -132,7 +132,6 @@ Library
Hakyll.Core.Provider.Metadata
Hakyll.Core.Provider.MetadataCache
Hakyll.Core.Rules.Internal
Hakyll.Core.Rules.Default
Hakyll.Core.Runtime
Hakyll.Core.Store
Hakyll.Core.Util.File

View File

@ -5,7 +5,6 @@ module Hakyll.Core.Metadata
, getMetadataField
, getMetadataField'
, makePatternDependency
, metadataFiles
) where
@ -13,7 +12,6 @@ module Hakyll.Core.Metadata
import Control.Monad (forM)
import Data.Map (Map)
import qualified Data.Map as M
import System.FilePath.Posix ((</>), takeDirectory)
--------------------------------------------------------------------------------
@ -63,12 +61,3 @@ makePatternDependency :: MonadMetadata m => Pattern -> m Dependency
makePatternDependency pattern = do
matches' <- getMatches pattern
return $ PatternDependency pattern matches'
--------------------------------------------------------------------------------
-- | Returns a list of all directory-wise metadata files, subdir first, global last
metadataFiles :: Identifier -> [Identifier]
metadataFiles identifier = local : go (takeDirectory $ toFilePath identifier) where
go "." = [fromFilePath "metadata"]
go dir = fromFilePath (dir </> "metadata") : go (takeDirectory dir)
local = fromFilePath $ toFilePath identifier ++ ".metadata"

View File

@ -44,7 +44,7 @@ loadMetadata p identifier = do
Nothing -> return M.empty
Just mi' -> loadMetadataFile $ resourceFilePath p mi'
gmd <- loadGlobalMetadata p identifier
gmd <- loadGlobalMetadata p $ toFilePath identifier
return (M.unions [md, gmd], body)
where
@ -141,17 +141,21 @@ page = do
--------------------------------------------------------------------------------
-- | Load directory-wise metadata
loadGlobalMetadata :: Provider -> Identifier -> IO Metadata
loadGlobalMetadata p fp = liftM M.fromList $ loadgm fp where
loadgm :: Identifier -> IO [(String, String)]
loadgm = liftM concat . mapM loadOne . reverse . filter (resourceExists p) . metadataFiles
loadOne mfp =
loadGlobalMetadata :: Provider -> FilePath -> IO (M.Map String String)
loadGlobalMetadata p fp = liftM M.fromList $ loadgm $ takeDirectory fp where
loadgm :: FilePath -> IO [(String, String)]
loadgm dir | dir == "." = return []
| otherwise = do
let mfp = fromFilePath $ combine dir "metadata"
md <- if resourceExists p mfp then loadOne mfp dir else return []
others <- loadgm (takeDirectory dir)
return $ others ++ md
loadOne mfp dir =
let path = resourceFilePath p mfp
dir = takeDirectory $ toFilePath mfp
-- TODO: It might be better to print warning and continue
in either (error.show) (findMetadata dir) . P.parse namedMetadata path <$> readFile path
findMetadata dir =
concatMap snd . filter (flip matches fp . fromGlob . combine dir . fst)
concatMap snd . filter (flip matches (fromFilePath fp) . fromGlob . combine dir . fst)
namedMetadata :: Parser [(String, [(String, String)])]
namedMetadata = liftA2 (:) (namedMetadataBlock False) $ P.many $ namedMetadataBlock True

View File

@ -1,24 +0,0 @@
{-# LANGUAGE OverloadedStrings #-}
module Hakyll.Core.Rules.Default
( internalRules
, addMetadataDependencies
)
where
import Hakyll.Core.Rules
import Hakyll.Core.Compiler
import Hakyll.Core.Compiler.Internal (compilerTellDependencies)
import Hakyll.Core.Metadata (getMatches, metadataFiles)
import Hakyll.Core.Identifier.Pattern(fromList)
internalRules :: Rules ()
internalRules = do
match "metadata" $ compile $ makeItem ()
match "**/metadata" $ compile $ makeItem ()
match "**.metadata" $ compile $ makeItem ()
--------------------------------------------------------------------------------
addMetadataDependencies :: Compiler ()
addMetadataDependencies =
compilerTellDependencies . map IdentifierDependency =<< getMatches . fromList =<< fmap metadataFiles getUnderlying

View File

@ -35,7 +35,6 @@ import qualified Hakyll.Core.Logger as Logger
import Hakyll.Core.Provider
import Hakyll.Core.Routes
import Hakyll.Core.Rules.Internal
import Hakyll.Core.Rules.Default
import Hakyll.Core.Store (Store)
import qualified Hakyll.Core.Store as Store
import Hakyll.Core.Util.File
@ -54,7 +53,7 @@ run config verbosity rules = do
provider <- newProvider store (shouldIgnoreFile config) $
providerDirectory config
Logger.message logger "Running rules..."
ruleSet <- runRules (internalRules >> rules) provider
ruleSet <- runRules rules provider
-- Get old facts
mOldFacts <- Store.get store factsKey
@ -187,7 +186,7 @@ chase trail id'
config <- runtimeConfiguration <$> ask
Logger.debug logger $ "Processing " ++ show id'
let compiler = addMetadataDependencies >> todo M.! id'
let compiler = todo M.! id'
read' = CompilerRead
{ compilerConfig = config
, compilerUnderlying = id'