Fix tag dependency issue, slightly improve caching

This commit is contained in:
Jasper Van der Jeugt 2014-04-11 21:12:01 +02:00
parent 889e6f59f7
commit 8229765cbd
6 changed files with 17 additions and 11 deletions

View file

@ -248,5 +248,6 @@ compilerGetMatches :: Pattern -> Compiler [Identifier]
compilerGetMatches pattern = do
universe <- compilerUniverse <$> compilerAsk
let matching = filterMatches pattern $ S.toList universe
compilerTellDependencies [PatternDependency pattern matching]
set' = S.fromList matching
compilerTellDependencies [PatternDependency pattern set']
return matching

View file

@ -32,7 +32,7 @@ import Hakyll.Core.Identifier.Pattern
--------------------------------------------------------------------------------
data Dependency
= PatternDependency Pattern [Identifier]
= PatternDependency Pattern (Set Identifier)
| IdentifierDependency Identifier
deriving (Show, Typeable)
@ -91,7 +91,7 @@ dependenciesFor id' = do
return $ concatMap dependenciesFor' $ fromMaybe [] $ M.lookup id' facts
where
dependenciesFor' (IdentifierDependency i) = [i]
dependenciesFor' (PatternDependency _ is) = is
dependenciesFor' (PatternDependency _ is) = S.toList is
--------------------------------------------------------------------------------
@ -116,7 +116,7 @@ checkChangedPatterns = do
go _ ds (IdentifierDependency i) = return $ IdentifierDependency i : ds
go id' ds (PatternDependency p ls) = do
universe <- ask
let ls' = filterMatches p universe
let ls' = S.fromList $ filterMatches p universe
if ls == ls'
then return $ PatternDependency p ls : ds
else do

View file

@ -12,6 +12,7 @@ module Hakyll.Core.Metadata
import Control.Monad (forM)
import Data.Map (Map)
import qualified Data.Map as M
import qualified Data.Set as S
--------------------------------------------------------------------------------
@ -60,4 +61,4 @@ getMetadataField' identifier key = do
makePatternDependency :: MonadMetadata m => Pattern -> m Dependency
makePatternDependency pattern = do
matches' <- getMatches pattern
return $ PatternDependency pattern matches'
return $ PatternDependency pattern (S.fromList matches')

View file

@ -15,6 +15,7 @@ import Control.Monad (forM_)
import Data.List (unfoldr)
import qualified Data.Map as M
import Data.Monoid (mconcat)
import qualified Data.Set as S
import Text.Printf (printf)
@ -58,7 +59,7 @@ buildPaginate pattern = do
"invalid page number: " ++ show pn
return $ Paginate pagPages pagPlaces makeId
(PatternDependency pattern idents)
(PatternDependency pattern (S.fromList idents))
--------------------------------------------------------------------------------
@ -81,7 +82,7 @@ buildPaginateWith n makeId pattern = do
[(makeId i, i) | i <- [1 .. nPages]]
return $ Paginate (M.fromList paginatePages') (M.fromList pagPlaces') makeId
(PatternDependency pattern idents)
(PatternDependency pattern (S.fromList idents))
--------------------------------------------------------------------------------

View file

@ -71,6 +71,7 @@ import qualified Data.Map as M
import Data.Maybe (catMaybes, fromMaybe)
import Data.Monoid (mconcat)
import Data.Ord (comparing)
import qualified Data.Set as S
import System.FilePath (takeBaseName, takeDirectory)
import Text.Blaze.Html (toHtml, toValue, (!))
import Text.Blaze.Html.Renderer.String (renderHtml)
@ -124,7 +125,8 @@ buildTagsWith :: MonadMetadata m
buildTagsWith f pattern makeId = do
ids <- getMatches pattern
tagMap <- foldM addTags M.empty ids
return $ Tags (M.toList tagMap) makeId (PatternDependency pattern ids)
let set' = S.fromList ids
return $ Tags (M.toList tagMap) makeId (PatternDependency pattern set')
where
-- Create a tag map for one page
addTags tagMap id' = do
@ -148,8 +150,8 @@ buildCategories = buildTagsWith getCategory
tagsRules :: Tags -> (String -> Pattern -> Rules ()) -> Rules ()
tagsRules tags rules =
forM_ (tagsMap tags) $ \(tag, identifiers) ->
create [tagsMakeId tags tag] $
rulesExtraDependencies [tagsDependency tags] $
rulesExtraDependencies [tagsDependency tags] $
create [tagsMakeId tags tag] $
rules tag $ fromList identifiers

View file

@ -38,7 +38,8 @@ oldFacts = M.fromList
, ("posts/02.md",
[])
, ("index.md",
[ PatternDependency "posts/*" ["posts/01.md", "posts/02.md"]
[ PatternDependency "posts/*"
(S.fromList ["posts/01.md", "posts/02.md"])
, IdentifierDependency "posts/01.md"
, IdentifierDependency "posts/02.md"
])