diff options
-rw-r--r-- | src/Text/Hakyll/Paginate.hs | 5 | ||||
-rw-r--r-- | src/Text/Hakyll/Render.hs | 8 | ||||
-rw-r--r-- | src/Text/Hakyll/RenderAction.hs | 3 | ||||
-rw-r--r-- | src/Text/Hakyll/Renderables.hs | 28 | ||||
-rw-r--r-- | src/Text/Hakyll/Tags.hs | 36 |
5 files changed, 45 insertions, 35 deletions
diff --git a/src/Text/Hakyll/Paginate.hs b/src/Text/Hakyll/Paginate.hs index 4a0782a..349360a 100644 --- a/src/Text/Hakyll/Paginate.hs +++ b/src/Text/Hakyll/Paginate.hs @@ -7,7 +7,6 @@ module Text.Hakyll.Paginate import Control.Applicative ((<$>)) -import Text.Hakyll.Context import Text.Hakyll.Renderables import Text.Hakyll.RenderAction import Text.Hakyll.Util (link) @@ -50,8 +49,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 - -> [RenderAction () Context] - -> [RenderAction () Context] + -> [Renderable] + -> [Renderable] 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 3c62fe2..9a95374 100644 --- a/src/Text/Hakyll/Render.hs +++ b/src/Text/Hakyll/Render.hs @@ -56,7 +56,7 @@ renderWith manipulation templatePath = RenderAction -- * Concatenates the result. -- renderAndConcat :: [FilePath] -- ^ Templates to apply on every renderable. - -> [RenderAction () Context] -- ^ Renderables to render. + -> [Renderable] -- ^ Renderables to render. -> RenderAction () String renderAndConcat = renderAndConcatWith id @@ -65,7 +65,7 @@ renderAndConcat = renderAndConcatWith id -- apply on every @Renderable@. renderAndConcatWith :: ContextManipulation -> [FilePath] - -> [RenderAction () Context] + -> [Renderable] -> RenderAction () String renderAndConcatWith manipulation templatePaths renderables = RenderAction { actionDependencies = renders >>= actionDependencies @@ -91,14 +91,14 @@ renderAndConcatWith manipulation templatePaths renderables = RenderAction -- -- This code will first render @warning.html@ using @templates/notice.html@, -- and will then render the result with @templates/default.html@. -renderChain :: [FilePath] -> RenderAction () Context -> Hakyll () +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] - -> RenderAction () Context + -> Renderable -> Hakyll () renderChainWith manipulation templatePaths initial = runRenderActionIfNeeded renderChainWith' diff --git a/src/Text/Hakyll/RenderAction.hs b/src/Text/Hakyll/RenderAction.hs index b84a3c5..0038c9e 100644 --- a/src/Text/Hakyll/RenderAction.hs +++ b/src/Text/Hakyll/RenderAction.hs @@ -7,6 +7,7 @@ module Text.Hakyll.RenderAction , chain , runRenderAction , runRenderActionIfNeeded + , Renderable ) where import Control.Category @@ -69,3 +70,5 @@ runRenderActionIfNeeded action = do valid <- isFileMoreRecent destination $ actionDependencies action unless valid $ do liftIO $ hPutStrLn stderr $ "Rendering " ++ destination runRenderAction action + +type Renderable = RenderAction () Context diff --git a/src/Text/Hakyll/Renderables.hs b/src/Text/Hakyll/Renderables.hs index 00e11ca..f918c86 100644 --- a/src/Text/Hakyll/Renderables.hs +++ b/src/Text/Hakyll/Renderables.hs @@ -12,7 +12,6 @@ import Control.Arrow (second) import Control.Monad (liftM2, mplus) import Control.Applicative ((<$>)) - import Text.Hakyll.File import Text.Hakyll.Context import Text.Hakyll.RenderAction @@ -29,9 +28,9 @@ import Text.Hakyll.Internal.Page createCustomPage :: String -> [FilePath] -> [(String, Either String (RenderAction () String))] - -> RenderAction () Context + -> Renderable createCustomPage url dependencies association = RenderAction - { actionDependencies = dependencies + { actionDependencies = dependencies ++ dataDependencies , actionUrl = Just $ return url , actionFunction = \_ -> M.fromList <$> assoc' } @@ -39,6 +38,9 @@ createCustomPage url dependencies association = RenderAction mtuple (a, b) = b >>= \b' -> return (a, b') toHakyllString = second (either return runRenderAction) assoc' = mapM (mtuple . toHakyllString) $ ("url", Left url) : association + dataDependencies = (map snd association) >>= getDependencies + getDependencies (Left _) = [] + getDependencies (Right x) = actionDependencies x -- | A @createCustomPage@ function specialized in creating listings. -- @@ -55,9 +57,9 @@ createCustomPage url dependencies association = RenderAction -- > [("title", "Home")] -- ^ Additional context createListing :: String -- ^ Destination of the page. -> FilePath -- ^ Template to render all items with. - -> [RenderAction () Context] -- ^ Renderables in the list. + -> [Renderable] -- ^ Renderables in the list. -> [(String, String)] -- ^ Additional context. - -> RenderAction () Context + -> Renderable createListing = createListingWith id -- | A @createCustomPage@ function specialized in creating listings. @@ -67,9 +69,9 @@ createListing = createListingWith id createListingWith :: ContextManipulation -- ^ Manipulation for the renderables. -> String -- ^ Destination of the page. -> FilePath -- ^ Template to render all items with. - -> [RenderAction () Context] -- ^ Renderables in the list. + -> [Renderable] -- ^ Renderables in the list. -> [(String, String)] -- ^ Additional context. - -> RenderAction () Context + -> Renderable createListingWith manipulation url template renderables additional = createCustomPage url dependencies context where @@ -79,7 +81,7 @@ createListingWith manipulation url template renderables additional = additional' = map (second Left) additional -- | Create a PagePath from a FilePath. -createPagePath :: FilePath -> RenderAction () Context +createPagePath :: FilePath -> Renderable createPagePath path = RenderAction { actionDependencies = [path] , actionUrl = Just $ toUrl path @@ -92,8 +94,8 @@ createPagePath path = RenderAction -- -- Since renderables are always more or less key-value maps, you can see -- this as a @union@ between two maps. -combine :: RenderAction () Context -> RenderAction () Context - -> RenderAction () Context +combine :: Renderable -> Renderable + -> Renderable combine x y = RenderAction { actionDependencies = actionDependencies x ++ actionDependencies y , actionUrl = actionUrl x `mplus` actionUrl y @@ -104,9 +106,9 @@ combine x y = RenderAction -- | 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 - -> RenderAction () Context - -> RenderAction () Context - -> RenderAction () Context + -> Renderable + -> Renderable + -> Renderable 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 10be45c..cc69930 100644 --- a/src/Text/Hakyll/Tags.hs +++ b/src/Text/Hakyll/Tags.hs @@ -45,11 +45,11 @@ import Control.Arrow (second) import Control.Applicative ((<$>)) import System.FilePath -import Text.Hakyll.Hakyll import Text.Hakyll.Context +import Text.Hakyll.Hakyll import Text.Hakyll.Regex -import Text.Hakyll.Renderable import Text.Hakyll.Renderables +import Text.Hakyll.RenderAction import Text.Hakyll.Util import Text.Hakyll.Internal.Cache import Text.Hakyll.Internal.Template @@ -59,42 +59,48 @@ 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 [PagePath] +type TagMap = M.Map String [Renderable] -- | Read a tag map. This is a internally used function that can be used for -- tags as well as for categories. readMap :: (Context -> [String]) -- ^ Function to get tags from a context. -> String -- ^ Unique identifier for the tagmap. - -> [PagePath] - -> Hakyll TagMap -readMap getTagsFunction identifier paths = do - isCacheMoreRecent' <- isCacheMoreRecent fileName (getDependencies =<< paths) - if isCacheMoreRecent' then M.fromAscList <$> getFromCache fileName - else do tagMap <- readTagMap' - storeInCache (M.toAscList tagMap) fileName - return tagMap + -> [FilePath] + -> RenderAction () TagMap +readMap getTagsFunction identifier paths = RenderAction + { actionDependencies = paths + , actionUrl = Nothing + , actionFunction = actionFunction' + } where fileName = "tagmaps" </> identifier + actionFunction' _ = do + isCacheMoreRecent' <- isCacheMoreRecent fileName paths + if isCacheMoreRecent' then M.fromAscList <$> getFromCache fileName + else do tagMap <- readTagMap' + storeInCache (M.toAscList tagMap) fileName + return tagMap + readTagMap' = foldM addPaths M.empty paths addPaths current path = do - context <- toContext path + createPagePath path >>> let tags = getTagsFunction context addPaths' = flip (M.insertWith (++)) [path] return $ foldr addPaths' current tags -- | Read a @TagMap@, using the @tags@ metadata field. readTagMap :: String -- ^ Unique identifier for the map. - -> [PagePath] -- ^ Paths to get tags from. + -> [FilePath] -- ^ Paths to get tags from. -> Hakyll TagMap -readTagMap = readMap getTagsFunction +readTagMap = readMap getTagsFunction where getTagsFunction = map trim . splitRegex "," . fromMaybe [] . M.lookup "tags" -- | Read a @TagMap@, using the subdirectories the pages are placed in. readCategoryMap :: String -- ^ Unique identifier for the map. - -> [PagePath] -- ^ Paths to get tags from. + -> [FilePath] -- ^ Paths to get tags from. -> Hakyll TagMap readCategoryMap = readMap $ maybeToList . M.lookup "category" |