diff options
author | Jasper Van der Jeugt <jaspervdj@gmail.com> | 2010-03-10 16:02:17 +0100 |
---|---|---|
committer | Jasper Van der Jeugt <jaspervdj@gmail.com> | 2010-03-10 16:02:17 +0100 |
commit | 23f9d1e0cfb82260b73ce8799756fa6d3a838a70 (patch) | |
tree | 6dca9f11bfefafa5aeaeb27465236194abf3364d /src/Text/Hakyll | |
parent | fa28eac8a395da7e524dc50d910d10dc1fa76a12 (diff) | |
download | hakyll-23f9d1e0cfb82260b73ce8799756fa6d3a838a70.tar.gz |
Removed xxxWith functions, they can be implemented more elegant using Arrows anyway.
Diffstat (limited to 'src/Text/Hakyll')
-rw-r--r-- | src/Text/Hakyll/Context.hs | 34 | ||||
-rw-r--r-- | src/Text/Hakyll/Feed.hs | 98 | ||||
-rw-r--r-- | src/Text/Hakyll/Hakyll.hs | 7 | ||||
-rw-r--r-- | src/Text/Hakyll/HakyllAction.hs | 12 | ||||
-rw-r--r-- | src/Text/Hakyll/Internal/Render.hs | 17 | ||||
-rw-r--r-- | src/Text/Hakyll/Paginate.hs | 5 | ||||
-rw-r--r-- | src/Text/Hakyll/Render.hs | 54 | ||||
-rw-r--r-- | src/Text/Hakyll/Renderables.hs | 43 | ||||
-rw-r--r-- | src/Text/Hakyll/Tags.hs | 6 |
9 files changed, 95 insertions, 181 deletions
diff --git a/src/Text/Hakyll/Context.hs b/src/Text/Hakyll/Context.hs index 3058946..285ccd0 100644 --- a/src/Text/Hakyll/Context.hs +++ b/src/Text/Hakyll/Context.hs @@ -9,18 +9,17 @@ module Text.Hakyll.Context , changeExtension ) where -import qualified Data.Map as M -import Data.Map (Map) +import Control.Arrow (arr) import System.Locale (defaultTimeLocale) import System.FilePath (takeFileName, addExtension, dropExtension) import Data.Time.Format (parseTime, formatTime) import Data.Time.Clock (UTCTime) import Data.Maybe (fromMaybe) +import qualified Data.Map as M import Text.Hakyll.Regex (substituteRegex) - --- | Type for a context. -type Context = Map String String +import Text.Hakyll.HakyllAction (HakyllAction) +import Text.Hakyll.Hakyll (Context) -- | Type for context manipulating functions. type ContextManipulation = Context -> Context @@ -31,10 +30,11 @@ type ContextManipulation = Context -> Context renderValue :: String -- ^ Key of which the value should be copied. -> String -- ^ Key the value should be copied to. -> (String -> String) -- ^ Function to apply on the value. - -> ContextManipulation -renderValue source destination f context = case M.lookup source context of - Nothing -> context - (Just value) -> M.insert destination (f value) context + -> HakyllAction Context Context +renderValue source destination f = arr $ \context -> + case M.lookup source context of + Nothing -> context + (Just value) -> M.insert destination (f value) context -- | Change a value in a @Context@. -- @@ -44,13 +44,13 @@ renderValue source destination f context = case M.lookup source context of -- Will put the title in UPPERCASE. changeValue :: String -- ^ Key to change. -> (String -> String) -- ^ Function to apply on the value. - -> ContextManipulation + -> HakyllAction Context Context changeValue key = renderValue key key -- | Copy a value from one key to another in a @Context@. copyValue :: String -- ^ Source key. -> String -- ^ Destination key. - -> ContextManipulation + -> HakyllAction Context Context copyValue source destination = renderValue source destination id -- | When the context has a key called @path@ in a @yyyy-mm-dd-title.extension@ @@ -61,13 +61,11 @@ copyValue source destination = renderValue source destination id -- Will render something like @January 32, 2010@. renderDate :: String -- ^ Key in which the rendered date should be placed. -> String -- ^ Format to use on the date. - -> String -- ^ Default value when the date cannot be parsed. - -> ContextManipulation -renderDate key format defaultValue context = M.insert key value context + -> String -- ^ Default key, in case the date cannot be parsed. + -> HakyllAction Context Context +renderDate key format defaultValue = renderValue "path" key renderDate' where - value = fromMaybe defaultValue pretty - pretty = do - filePath <- M.lookup "path" context + renderDate' filePath = fromMaybe defaultValue $ do let dateString = substituteRegex "^([0-9]*-[0-9]*-[0-9]*).*" "\\1" (takeFileName filePath) time <- parseTime defaultTimeLocale @@ -84,7 +82,7 @@ renderDate key format defaultValue context = M.insert key value context -- -- Will render to @test.php@ instead of @test.html@. changeExtension :: String -- ^ Extension to change to. - -> ContextManipulation + -> HakyllAction Context Context changeExtension extension = changeValue "url" changeExtension' where changeExtension' = flip addExtension extension . dropExtension diff --git a/src/Text/Hakyll/Feed.hs b/src/Text/Hakyll/Feed.hs index 64443a5..db275f6 100644 --- a/src/Text/Hakyll/Feed.hs +++ b/src/Text/Hakyll/Feed.hs @@ -20,9 +20,7 @@ module Text.Hakyll.Feed ( FeedConfiguration (..) , renderRss - , renderRssWith , renderAtom - , renderAtomWith ) where import Control.Arrow ((>>>), second) @@ -31,9 +29,9 @@ import Data.Maybe (fromMaybe) import qualified Data.Map as M import Text.Hakyll.Context (ContextManipulation, renderDate) -import Text.Hakyll.Hakyll (Hakyll) +import Text.Hakyll.Hakyll (Hakyll, Context) import Text.Hakyll.Render (render, renderChain) -import Text.Hakyll.Renderables (createListingWith) +import Text.Hakyll.Renderables (createListing) import Text.Hakyll.HakyllAction import Paths_hakyll @@ -52,17 +50,16 @@ data FeedConfiguration = FeedConfiguration -- | This is an auxiliary function to create a listing that is, in fact, a feed. -- The items should be sorted on date. -createFeedWith :: ContextManipulation -- ^ Manipulation to apply on the items. - -> FeedConfiguration -- ^ Feed configuration. - -> [Renderable] -- ^ Items to include. - -> FilePath -- ^ Feed template. - -> FilePath -- ^ Item template. - -> Renderable -createFeedWith manipulation configuration renderables template itemTemplate = +createFeed :: FeedConfiguration -- ^ Feed configuration. + -> [HakyllAction () Context] -- ^ Items to include. + -> FilePath -- ^ Feed template. + -> FilePath -- ^ Item template. + -> HakyllAction () Context +createFeed configuration renderables template itemTemplate = listing >>> render template where - listing = createListingWith manipulation (feedUrl configuration) - [itemTemplate] renderables additional + listing = createListing (feedUrl configuration) + [itemTemplate] renderables additional additional = map (second $ Left . ($ configuration)) [ ("title", feedTitle) @@ -73,68 +70,41 @@ createFeedWith manipulation configuration renderables template itemTemplate = -- Take the first timestamp, which should be the most recent. updated = let action = createHakyllAction $ return . fromMaybe "foo" . M.lookup "timestamp" - manip = createManipulationAction manipulation - toTuple r = ("timestamp", Right $ r >>> manip >>> action) + toTuple r = ("timestamp", Right $ r >>> action) in map toTuple $ take 1 renderables -- | Abstract function to render any feed. -renderFeedWith :: ContextManipulation -- ^ Manipulation to apply on the items. - -> FeedConfiguration -- ^ Feed configuration. - -> [Renderable] -- ^ Items to include in the feed. - -> FilePath -- ^ Feed template. - -> FilePath -- ^ Item template. - -> Hakyll () -renderFeedWith manipulation configuration renderables template itemTemplate = do +renderFeed :: FeedConfiguration -- ^ Feed configuration. + -> [HakyllAction () Context] -- ^ Items to include in the feed. + -> FilePath -- ^ Feed template. + -> FilePath -- ^ Item template. + -> Hakyll () +renderFeed configuration renderables template itemTemplate = do template' <- liftIO $ getDataFileName template itemTemplate' <- liftIO $ getDataFileName itemTemplate - let renderFeedWith' = createFeedWith manipulation configuration - renderables template' itemTemplate' - renderChain [] renderFeedWith' + let renderFeed' = createFeed configuration renderables + template' itemTemplate' + renderChain [] renderFeed' -- | Render an RSS feed with a number of items. -renderRss :: FeedConfiguration -- ^ Feed configuration. - -> [Renderable] -- ^ Items to include in the RSS feed. +renderRss :: FeedConfiguration -- ^ Feed configuration. + -> [HakyllAction () Context] -- ^ Items to include in the feed. -> Hakyll () -renderRss = renderRssWith id - --- | Render an RSS feed with a number of items. This function allows you to --- specify a @ContextManipulation@ which will be applied on every --- @Renderable@. Note that the given @Renderable@s should be sorted so the --- most recent one is first. -renderRssWith :: ContextManipulation -- ^ Manipulation to apply on the items. - -> FeedConfiguration -- ^ Feed configuration. - -> [Renderable] -- ^ Items to include in the feed. - -> Hakyll () -renderRssWith manipulation configuration renderables = - renderFeedWith manipulation' configuration renderables - "templates/rss.xml" "templates/rss-item.xml" +renderRss configuration renderables = + renderFeed configuration (map (>>> renderRssDate) renderables) + "templates/rss.xml" "templates/rss-item.xml" where - manipulation' = manipulation . renderRssDate - --- | @ContextManipulation@ that renders a date to RSS format. -renderRssDate :: ContextManipulation -renderRssDate = renderDate "timestamp" "%a, %d %b %Y %H:%M:%S UT" - "No date found." + renderRssDate = renderDate "timestamp" "%a, %d %b %Y %H:%M:%S UT" + "No date found." -- | Render an Atom feed with a number of items. -renderAtom :: FeedConfiguration - -> [Renderable] +renderAtom :: FeedConfiguration -- ^ Feed configuration. + -> [HakyllAction () Context] -- ^ Items to include in the feed. -> Hakyll () -renderAtom = renderAtomWith id - --- | A version of @renderAtom@ that allows you to specify a manipulation to --- apply on the @Renderable@s. -renderAtomWith :: ContextManipulation -- ^ Manipulation to apply on the items. - -> FeedConfiguration -- ^ Feed configuration. - -> [Renderable] -- ^ Items to include in the feed. - -> Hakyll () -renderAtomWith manipulation configuration renderables = - renderFeedWith manipulation' configuration renderables - "templates/atom.xml" "templates/atom-item.xml" +renderAtom configuration renderables = + renderFeed configuration (map (>>> renderAtomDate) renderables) + "templates/atom.xml" "templates/atom-item.xml" where - manipulation' = manipulation . renderAtomDate - --- | Render a date to Atom format. -renderAtomDate :: ContextManipulation -renderAtomDate = renderDate "timestamp" "%Y-%m-%dT%H:%M:%SZ" "No date found." + renderAtomDate = renderDate "timestamp" "%Y-%m-%dT%H:%M:%SZ" + "No date found." diff --git a/src/Text/Hakyll/Hakyll.hs b/src/Text/Hakyll/Hakyll.hs index fab0be6..bff57d0 100644 --- a/src/Text/Hakyll/Hakyll.hs +++ b/src/Text/Hakyll/Hakyll.hs @@ -1,6 +1,7 @@ -- | Module describing the Hakyll monad stack. module Text.Hakyll.Hakyll - ( HakyllConfiguration (..) + ( Context + , HakyllConfiguration (..) , Hakyll , askHakyll , getAdditionalContext @@ -8,9 +9,11 @@ module Text.Hakyll.Hakyll import Control.Monad.Reader (ReaderT, ask) import Control.Monad (liftM) +import Data.Map (Map) import qualified Data.Map as M -import Text.Hakyll.Context (Context) +-- | Type for a context. +type Context = Map String String -- | Hakyll global configuration type. data HakyllConfiguration = HakyllConfiguration diff --git a/src/Text/Hakyll/HakyllAction.hs b/src/Text/Hakyll/HakyllAction.hs index ef8284d..8902edb 100644 --- a/src/Text/Hakyll/HakyllAction.hs +++ b/src/Text/Hakyll/HakyllAction.hs @@ -4,11 +4,9 @@ module Text.Hakyll.HakyllAction , createHakyllAction , createSimpleHakyllAction , createFileHakyllAction - , createManipulationAction , chain , runHakyllAction , runHakyllActionIfNeeded - , Renderable ) where import Control.Arrow @@ -18,7 +16,6 @@ import Control.Monad.Reader (liftIO) import Prelude hiding ((.), id) import System.IO (hPutStrLn, stderr) -import Text.Hakyll.Context import Text.Hakyll.File (toDestination, isFileMoreRecent) import Text.Hakyll.Hakyll @@ -52,11 +49,6 @@ createFileHakyllAction path action = HakyllAction , actionFunction = const action } --- | Create a @HakyllAction@ from a @ContextManipulation@. -createManipulationAction :: ContextManipulation -- ^ Manipulation to apply. - -> HakyllAction Context Context -createManipulationAction = createHakyllAction . (return .) - -- | Run a @HakyllAction@ now. runHakyllAction :: HakyllAction () a -- ^ Render action to run. -> Hakyll a -- ^ Result of the action. @@ -81,10 +73,6 @@ chain :: [HakyllAction a a] -- ^ Actions to chain. chain [] = id chain list@(_:_) = foldl1 (>>>) list --- | This is a specialized version of @HakyllAction@, a @Context@ that can be --- rendered. -type Renderable = HakyllAction () Context - instance Category HakyllAction where id = HakyllAction { actionDependencies = [] diff --git a/src/Text/Hakyll/Internal/Render.hs b/src/Text/Hakyll/Internal/Render.hs index 178e6ff..a771556 100644 --- a/src/Text/Hakyll/Internal/Render.hs +++ b/src/Text/Hakyll/Internal/Render.hs @@ -1,9 +1,6 @@ -- | Internal module do some low-level rendering. module Text.Hakyll.Internal.Render - ( substitute - , regularSubstitute - , finalSubstitute - , pureRenderWith + ( pureRender , writePage ) where @@ -11,21 +8,19 @@ import qualified Data.Map as M import Control.Monad.Reader (liftIO) import Data.Maybe (fromMaybe) -import Text.Hakyll.Context (Context, ContextManipulation) import Text.Hakyll.File import Text.Hakyll.Hakyll import Text.Hakyll.HakyllAction import Text.Hakyll.Internal.Template -- | A pure render function. -pureRenderWith :: ContextManipulation -- ^ Manipulation to apply on the context. - -> Template -- ^ Template to use for rendering. - -> Context -- ^ Renderable object to render with given template. - -> Context -- ^ The body of the result will contain the render. -pureRenderWith manipulation template context = +pureRender :: Template -- ^ Template to use for rendering. + -> Context -- ^ Renderable object to render with given template. + -> Context -- ^ The body of the result will contain the render. +pureRender template context = -- Ignore $root when substituting here. We will only replace that in the -- final render (just before writing). - let contextIgnoringRoot = M.insert "root" "$root" (manipulation context) + let contextIgnoringRoot = M.insert "root" "$root" context body = regularSubstitute template contextIgnoringRoot in M.insert "body" body context diff --git a/src/Text/Hakyll/Paginate.hs b/src/Text/Hakyll/Paginate.hs index 1de62b3..159a3a4 100644 --- a/src/Text/Hakyll/Paginate.hs +++ b/src/Text/Hakyll/Paginate.hs @@ -7,6 +7,7 @@ module Text.Hakyll.Paginate import Control.Applicative ((<$>)) +import Text.Hakyll.Hakyll (Context) import Text.Hakyll.Renderables import Text.Hakyll.HakyllAction import Text.Hakyll.Util (link) @@ -54,8 +55,8 @@ defaultPaginateConfiguration = PaginateConfiguration -- without a link. The same goes for when we are on the first or last page for -- @$first@ and @$last@. paginate :: PaginateConfiguration - -> [Renderable] - -> [Renderable] + -> [HakyllAction () Context] + -> [HakyllAction () Context] paginate configuration renderables = paginate' Nothing renderables (1 :: Int) where -- Create a link with a given label, taken from the configuration. diff --git a/src/Text/Hakyll/Render.hs b/src/Text/Hakyll/Render.hs index d945f94..96d2ffb 100644 --- a/src/Text/Hakyll/Render.hs +++ b/src/Text/Hakyll/Render.hs @@ -2,11 +2,8 @@ -- render files to the @_site@ directory. module Text.Hakyll.Render ( render - , renderWith , renderAndConcat - , renderAndConcatWith , renderChain - , renderChainWith , static , css ) where @@ -17,8 +14,7 @@ import System.Directory (copyFile) import Data.Maybe (fromMaybe) import qualified Data.Map as M -import Text.Hakyll.Hakyll (Hakyll) -import Text.Hakyll.Context (ContextManipulation, Context) +import Text.Hakyll.Hakyll (Hakyll, Context) import Text.Hakyll.File import Text.Hakyll.HakyllAction import Text.Hakyll.Internal.CompressCss @@ -28,14 +24,7 @@ import Text.Hakyll.Internal.Template (readTemplate) -- | Render to a Page. render :: FilePath -- ^ Template to use for rendering. -> HakyllAction Context Context -- ^ The render computation. -render = renderWith id - --- | Render to a Page. This function allows you to manipulate the context --- first. -renderWith :: ContextManipulation -- ^ Manipulation to apply first. - -> FilePath -- ^ Template to use for rendering. - -> HakyllAction Context Context -- ^ The render computation. -renderWith manipulation templatePath = HakyllAction +render templatePath = HakyllAction { actionDependencies = [templatePath] , actionUrl = Nothing , actionFunction = actionFunction' @@ -43,7 +32,7 @@ renderWith manipulation templatePath = HakyllAction where actionFunction' context = do template <- readTemplate templatePath - return $ pureRenderWith manipulation template context + return $ pureRender template context -- | Render each renderable with the given templates, then concatenate the -- result. So, basically this function: @@ -55,27 +44,17 @@ renderWith manipulation templatePath = HakyllAction -- -- * Concatenates the result. -- -renderAndConcat :: [FilePath] -- ^ Templates to apply on every renderable. - -> [Renderable] -- ^ Renderables to render. +renderAndConcat :: [FilePath] + -> [HakyllAction () Context] -> HakyllAction () String -renderAndConcat = renderAndConcatWith id - --- | Render each renderable with the given templates, then concatenate the --- result. This function allows you to specify a @ContextManipulation@ to --- apply on every @Renderable@. -renderAndConcatWith :: ContextManipulation - -> [FilePath] - -> [Renderable] - -> HakyllAction () String -renderAndConcatWith manipulation templatePaths renderables = HakyllAction +renderAndConcat templatePaths renderables = HakyllAction { actionDependencies = renders >>= actionDependencies - , actionUrl = Nothing + , actionUrl = Nothing , actionFunction = actionFunction' } where render' = chain (map render templatePaths) - renders = map (>>> manipulationAction >>> render') renderables - manipulationAction = createManipulationAction manipulation + renders = map (>>> render') renderables actionFunction' _ = do contexts <- mapM runHakyllAction renders @@ -91,23 +70,16 @@ renderAndConcatWith manipulation templatePaths renderables = HakyllAction -- -- This code will first render @warning.html@ using @templates/notice.html@, -- and will then render the result with @templates/default.html@. -renderChain :: [FilePath] -> Renderable -> Hakyll () -renderChain = renderChainWith id - --- | A more custom render chain that allows you to specify a --- @ContextManipulation@ which to apply on the context when it is read first. -renderChainWith :: ContextManipulation - -> [FilePath] - -> Renderable - -> Hakyll () -renderChainWith manipulation templatePaths initial = +renderChain :: [FilePath] + -> HakyllAction () Context + -> Hakyll () +renderChain templatePaths initial = runHakyllActionIfNeeded renderChainWith' where renderChainWith' :: HakyllAction () () - renderChainWith' = initial >>> manipulationAction >>> chain' >>> writePage + renderChainWith' = initial >>> chain' >>> writePage chain' = chain (map render templatePaths) - manipulationAction = createManipulationAction manipulation -- | Mark a certain file as static, so it will just be copied when the site is diff --git a/src/Text/Hakyll/Renderables.hs b/src/Text/Hakyll/Renderables.hs index 7fc658d..53530c6 100644 --- a/src/Text/Hakyll/Renderables.hs +++ b/src/Text/Hakyll/Renderables.hs @@ -1,7 +1,6 @@ module Text.Hakyll.Renderables ( createCustomPage , createListing - , createListingWith , createPagePath , combine , combineWithUrl @@ -27,7 +26,7 @@ import Text.Hakyll.Internal.Page -- cases. createCustomPage :: String -> [(String, Either String (HakyllAction () String))] - -> Renderable + -> HakyllAction () Context createCustomPage url association = HakyllAction { actionDependencies = dataDependencies , actionUrl = Just $ return url @@ -43,42 +42,30 @@ createCustomPage url association = HakyllAction -- | A @createCustomPage@ function specialized in creating listings. -- --- This function creates a listing of a certain list of @Renderable@s. Every +-- This function creates a listing of a certain list of renderables. Every -- item in the list is created by applying the given template to every -- renderable. You can also specify additional context to be included in the -- @CustomPage@. -- --- > let customPage = createListingWith +-- > let customPage = createListing -- > "index.html" -- Destination of the page. -- > ["templates/postitem.html"] -- Paths to templates to render the -- > -- items with. -- > posts -- Renderables to create the list with. -- > [("title", Left "Home")] -- Additional context -createListing :: String -- ^ Destination of the page. - -> [FilePath] -- ^ Templates to render all items with. - -> [Renderable] -- ^ Renderables in the list. +createListing :: String -- ^ Destination of the page. + -> [FilePath] -- ^ Templates to render items with. + -> [HakyllAction () Context] -- ^ Renderables in the list. -> [(String, Either String (HakyllAction () String))] - -> Renderable -createListing = createListingWith id - --- | A @createCustomPage@ function specialized in creating listings. --- --- In addition to @createListing@, this function allows you to specify an --- extra @ContextManipulation@ for all @Renderable@s given. -createListingWith :: ContextManipulation -- ^ Manipulation for the renderables. - -> String -- ^ Destination of the page. - -> [FilePath] -- ^ Templates to render all items with. - -> [Renderable] -- ^ Renderables in the list. - -> [(String, Either String (HakyllAction () String))] - -> Renderable -createListingWith manipulation url templates renderables additional = + -> HakyllAction () Context +createListing url templates renderables additional = createCustomPage url context where context = ("body", Right concatenation) : additional - concatenation = renderAndConcatWith manipulation templates renderables + concatenation = renderAndConcat templates renderables -- | Create a PagePath from a FilePath. -createPagePath :: FilePath -> Renderable +createPagePath :: FilePath -> HakyllAction () Context createPagePath path = HakyllAction { actionDependencies = [path] , actionUrl = Just $ toUrl path @@ -91,8 +78,8 @@ createPagePath path = HakyllAction -- -- Since renderables are always more or less key-value maps, you can see -- this as a @union@ between two maps. -combine :: Renderable -> Renderable - -> Renderable +combine :: HakyllAction () Context -> HakyllAction () Context + -> HakyllAction () Context combine x y = HakyllAction { actionDependencies = actionDependencies x ++ actionDependencies y , actionUrl = actionUrl x `mplus` actionUrl y @@ -103,9 +90,9 @@ combine x y = HakyllAction -- | Combine two renderables and set a custom URL. This behaves like @combine@, -- except that for the @url@ field, the given URL is always chosen. combineWithUrl :: FilePath - -> Renderable - -> Renderable - -> Renderable + -> HakyllAction () Context + -> HakyllAction () Context + -> HakyllAction () Context combineWithUrl url x y = combine' { actionUrl = Just $ return url , actionFunction = \_ -> diff --git a/src/Text/Hakyll/Tags.hs b/src/Text/Hakyll/Tags.hs index c469328..f4193eb 100644 --- a/src/Text/Hakyll/Tags.hs +++ b/src/Text/Hakyll/Tags.hs @@ -58,7 +58,7 @@ import Text.Hakyll.Internal.Template -- This is a map associating tags or categories to the appropriate pages -- using that tag or category. In the case of categories, each path will only -- appear under one category - this is not the case with tags. -type TagMap = M.Map String [Renderable] +type TagMap = M.Map String [HakyllAction () Context] -- | Read a tag map. This is a internally used function that can be used for -- tags as well as for categories. @@ -106,7 +106,7 @@ readCategoryMap :: String -- ^ Unique identifier for the map. readCategoryMap = readMap $ maybeToList . M.lookup "category" withTagMap :: HakyllAction () TagMap - -> (String -> [Renderable] -> Hakyll ()) + -> (String -> [HakyllAction () Context] -> Hakyll ()) -> Hakyll () withTagMap tagMap function = runHakyllAction (tagMap >>> action) where @@ -154,7 +154,7 @@ renderTagCloud urlFunction minSize maxSize = createHakyllAction renderTagCloud' -- Note that it is your own responsibility to ensure a page with such an url -- exists. renderTagLinks :: (String -> String) -- ^ Function to produce an url for a tag. - -> ContextManipulation + -> HakyllAction Context Context renderTagLinks urlFunction = changeValue "tags" renderTagLinks' where renderTagLinks' = intercalate ", " |