summaryrefslogtreecommitdiff
path: root/src/Hakyll/Web/Tags.hs
blob: cf0d9a53fa1874aca1d787ae9472e76eabff1e81 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
{-# LANGUAGE DeriveDataTypeable #-}
module Hakyll.Web.Tags
    ( Tags (..)
    , readTagsWith
    , readTags
    , readCategories
    ) where

import Control.Applicative ((<$>))
import Data.Map (Map)
import qualified Data.Map as M

import Data.Typeable (Typeable)
import Data.Binary (Binary, get, put)

import Hakyll.Web.Page
import Hakyll.Web.Util.String
import Hakyll.Core.Writable

-- | Data about tags
--
data Tags a = Tags
    { tagsMap :: Map String [Page a]
    } deriving (Show, Typeable)

instance Binary a => Binary (Tags a) where
    get = Tags <$> get
    put (Tags m) = put m

instance Writable (Tags a) where
    write _ _ = return ()

-- | Higher-level function to read tags
--
readTagsWith :: (Page a -> [String])  -- ^ Function extracting tags from a page
             -> [Page a]              -- ^ Pages
             -> Tags a                -- ^ Resulting tags
readTagsWith f pages = Tags
    { tagsMap = foldl (M.unionWith (++)) M.empty (map readTagsWith' pages)
    }
  where
    -- Create a tag map for one page
    readTagsWith' page =
        let tags = f page
        in M.fromList $ zip tags $ repeat [page]

-- | Read a tagmap using the @tags@ metadata field
--
readTags :: [Page a] -> Tags a
readTags = readTagsWith $ map trim . splitAll "," . getField "tags"

-- | Read a tagmap using the @category@ metadata field
--
readCategories :: [Page a] -> Tags a
readCategories = readTagsWith $ return . getField "category"