Small fixes

This commit is contained in:
Jasper Van der Jeugt 2012-11-24 10:24:54 +01:00
parent c54c7a05b1
commit bc192a127b
4 changed files with 14 additions and 13 deletions

View file

@ -120,7 +120,7 @@ Library
Hakyll.Web.Pandoc
Hakyll.Web.Pandoc.Biblio
Hakyll.Web.Pandoc.FileType
-- Hakyll.Web.Tags
Hakyll.Web.Tags
Hakyll.Web.Template
Hakyll.Web.Template.Context
Hakyll.Web.Template.List

View file

@ -68,6 +68,8 @@ import Data.Binary (Binary (..), getWord8, putWord8)
import Data.List (inits, isPrefixOf, tails)
import Data.Maybe (isJust)
import Data.Monoid (Monoid, mappend, mempty)
import Data.Set (Set)
import qualified Data.Set as S
--------------------------------------------------------------------------------
@ -108,7 +110,7 @@ data Pattern
| Complement Pattern
| And Pattern Pattern
| Glob [GlobComponent]
| List [Identifier] -- TODO Maybe use a set here
| List (Set Identifier)
| Regex String
| Version (Maybe String)
deriving (Show)
@ -162,7 +164,7 @@ fromGlob = Glob . parse'
--------------------------------------------------------------------------------
-- | Create a 'Pattern' from a list of 'Identifier's it should match
fromList :: [Identifier] -> Pattern
fromList = List
fromList = List . S.fromList
--------------------------------------------------------------------------------
@ -205,7 +207,7 @@ matches Everything _ = True
matches (Complement p) i = not $ matches p i
matches (And x y) i = matches x i && matches y i
matches (Glob p) i = isJust $ capture (Glob p) i
matches (List l) i = i `elem` l
matches (List l) i = i `S.member` l
matches (Regex r) i = toFilePath i =~ r
matches (Version v) i = identifierVersion i == v

View file

@ -66,6 +66,7 @@ import qualified Text.Blaze.Html5.Attributes as A
--------------------------------------------------------------------------------
import Hakyll.Core.Compiler
import Hakyll.Core.Identifier
import Hakyll.Core.Identifier.Pattern
import Hakyll.Core.Item
import Hakyll.Core.Metadata
import Hakyll.Core.Util.String
@ -102,10 +103,11 @@ getCategory = return . return . takeBaseName . takeDirectory . toFilePath
--------------------------------------------------------------------------------
-- | Higher-level function to read tags
-- | Higher-order function to read tags
buildTagsWith :: MonadMetadata m
=> (Identifier -> m [String]) -> [Identifier] -> m Tags
buildTagsWith f ids = do
=> (Identifier -> m [String]) -> Pattern -> m Tags
buildTagsWith f pattern = do
ids <- getMatches pattern
tagMap <- foldM addTags M.empty ids
return $ Tags $ M.toList tagMap
where
@ -117,15 +119,13 @@ buildTagsWith f ids = do
--------------------------------------------------------------------------------
-- | Read a tagmap using the @tags@ metadata field
-- TODO: Should use pattern
buildTags :: MonadMetadata m => [Identifier] -> m Tags
buildTags :: MonadMetadata m => Pattern -> m Tags
buildTags = buildTagsWith getTags
--------------------------------------------------------------------------------
-- | Read a tagmap using the @category@ metadata field
-- TODO: Should use pattern
buildCategory :: MonadMetadata m => [Identifier] -> m Tags
buildCategory :: MonadMetadata m => Pattern -> m Tags
buildCategory = buildTagsWith getCategory

View file

@ -28,8 +28,7 @@ import qualified Data.Map as M
import Data.Monoid (Monoid (..))
import Data.Time.Clock (UTCTime (..))
import Data.Time.Format (formatTime, parseTime)
import System.FilePath (takeBaseName, takeDirectory,
takeFileName)
import System.FilePath (takeBaseName, takeFileName)
import System.Locale (TimeLocale, defaultTimeLocale)