Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Routes
is part of the Rules
processing pipeline.
It determines if and where the compilation result of the underlying
Item
being processed is written out to
(relative to the destination directory as configured in
destinationDirectory
).
- If there is no route for an item, the compiled item won't be written out to a file and so won't appear in the destination (site) directory.
- If an item matches multiple routes, the first route will be chosen.
Examples
Suppose we have a markdown file posts/hakyll.md
. We can route its
compilation result to posts/hakyll.html
using setExtension
:
-- file on disk: '<project-directory>/posts/hakyll.md' match "posts/*" $ do -- compilation result is written to '<destination-directory>/posts/hakyll.html' route (setExtension "html") compile pandocCompiler
Hint: You can configure the destination directory with
destinationDirectory
.
If we do not want to change the extension, we can replace setExtension
with
idRoute
(the simplest route available):
-- compilation result is written to '<destination-directory>/posts/hakyll.md' route idRoute
That will route the file posts/hakyll.md
from the project directory to
posts/hakyll.md
in the destination directory.
Note:
The extension of the destination filepath says nothing about the content!
If you set the extension to .html
, you have to ensure that the
compilation result is indeed HTML (for example with the
pandocCompiler
to transform Markdown to HTML).
Take a look at the built-in routes here for detailed usage examples.
Synopsis
- data Routes
- type UsedMetadata = Bool
- runRoutes :: Routes -> Provider -> Identifier -> IO (Maybe FilePath, UsedMetadata)
- idRoute :: Routes
- setExtension :: String -> Routes
- matchRoute :: Pattern -> Routes -> Routes
- customRoute :: (Identifier -> FilePath) -> Routes
- constRoute :: FilePath -> Routes
- gsubRoute :: String -> (String -> String) -> Routes
- metadataRoute :: (Metadata -> Routes) -> Routes
- composeRoutes :: Routes -> Routes -> Routes
Documentation
type UsedMetadata = Bool Source #
When you ran a route, it's useful to know whether or not this used metadata. This allows us to do more granular dependency analysis.
runRoutes :: Routes -> Provider -> Identifier -> IO (Maybe FilePath, UsedMetadata) Source #
Apply a route to an identifier
An "identity" route that interprets the identifier (of the item being
processed) as the destination filepath. This identifier is normally the
filepath of the source file being processed.
See Identifier
for details.
Examples
Route when using match
-- e.g. file on disk: '<project-directory>/posts/hakyll.md' -- 'hakyll.md' source file implicitly gets filepath as identifier: -- 'posts/hakyll.md' match "posts/*" $ do -- compilation result is written to '<destination-directory>/posts/hakyll.md' route idRoute compile getResourceBody
setExtension :: String -> Routes Source #
Create a route like idRoute
that interprets the identifier (of the item
being processed) as the destination filepath but also sets (or replaces) the
extension suffix of that path. This identifier is normally the filepath of the
source file being processed.
See Identifier
for details.
Examples
Route with an existing extension
-- e.g. file on disk: '<project-directory>/posts/hakyll.md' -- 'hakyll.md' source file implicitly gets filepath as identifier: -- 'posts/hakyll.md' match "posts/*" $ do -- compilation result is written to '<destination-directory>/posts/hakyll.html' route (setExtension "html") compile pandocCompiler
Route without an existing extension
-- implicitly gets identifier: 'about' create ["about"] $ do -- compilation result is written to '<destination-directory>/about.html' route (setExtension "html") compile $ makeItem ("Hello world" :: String)
matchRoute :: Pattern -> Routes -> Routes Source #
Apply the route if the identifier matches the given pattern, fail otherwise
:: (Identifier -> FilePath) | Destination filepath construction function |
-> Routes | Resulting route |
Create a route where the destination filepath is built with the given
construction function. The provided identifier for that function is normally the
filepath of the source file being processed.
See Identifier
for details.
Examples
Route that appends a custom extension
-- e.g. file on disk: '<project-directory>/posts/hakyll.md' -- 'hakyll.md' source file implicitly gets filepath as identifier: -- 'posts/hakyll.md' match "posts/*" $ do -- compilation result is written to '<destination-directory>/posts/hakyll.md.html' route $ customRoute ((<> ".html") . toFilePath) compile pandocCompiler
Note that the last part of the destination filepath becomes .md.html
constRoute :: FilePath -> Routes Source #
Create a route that writes the compiled item to the given destination filepath (ignoring any identifier or other data about the item being processed). Warning: you should use a specific destination path only for a single file in a single compilation rule. Otherwise it's unclear which of the contents should be written to that route.
Examples
Route to a specific filepath
-- implicitly gets identifier: 'main' (ignored on next line) create ["main"] $ do -- compilation result is written to '<destination-directory>/index.html' route $ constRoute "index.html" compile $ makeItem ("<h1>Hello World</h1>" :: String)
:: String | Pattern to repeatedly match against in the underlying identifier |
-> (String -> String) | Replacement function to apply to the matched substrings |
-> Routes | Resulting route |
Create a "substituting" route that searches for substrings (in the
underlying identifier) that match the given pattern and transforms them
according to the given replacement function.
The identifier here is that of the underlying item being processed and is
interpreted as an destination filepath. It's normally the filepath of the
source file being processed.
See Identifier
for details.
Hint: The name "gsub" comes from a similar function in R and can be read as "globally substituting" (globally in the Unix sense of repeated, not just once).
Examples
Route that replaces part of the filepath
-- e.g. file on disk: '<project-directory>/posts/hakyll.md' -- 'hakyll.md' source file implicitly gets filepath as identifier: -- 'posts/hakyll.md' match "posts/*" $ do -- compilation result is written to '<destination-directory>/haskell/hakyll.md' route $ gsubRoute "posts/" (const "haskell/") compile getResourceBody
Note that "posts/" is replaced with "haskell/" in the destination filepath.
Route that removes part of the filepath
-- implicitly gets identifier: 'tags/rss/bar.xml' create ["tags/rss/bar.xml"] $ do -- compilation result is written to '<destination-directory>/tags/bar.xml' route $ gsubRoute "rss/" (const "") compile ...
Note that "rss/" is removed from the destination filepath.
Wrapper function around other route construction functions to get access to the metadata (of the underlying item being processed) and use that for the destination filepath construction. Warning: you have to ensure that the accessed metadata fields actually exist.
Examples
Route that uses a custom slug markdown metadata field
To create a search engine optimized yet human-readable url, we can introduce a slug metadata field to our files, e.g. like in the following Markdown file: 'posts/hakyll.md'
--- title: Hakyll Post slug: awesome-post ... --- In this blog post we learn about Hakyll ...
Then we can construct a route whose destination filepath is based on that field:
match "posts/*" $ do -- compilation result is written to '<destination-directory>/awesome-post.html' route $ metadataRoute $ \meta -> constRoute $ fromJust (lookupString "slug" meta) <> ".html" compile pandocCompiler
Note how we wrap metadataRoute
around the constRoute
function and how the
slug is looked up from the markdown field to construct the destination filepath.
You can use helper functions like lookupString
to access
a specific metadata field.
Compose two routes where the first route is applied before the second.
So f `composeRoutes` g
is more or less equivalent with g . f
.
Warning: If the first route fails (e.g. when using matchRoute
), Hakyll will
not apply the second route (if you need Hakyll to try the second route,
use <>
on Routes
instead).
Examples
Route that applies two transformations
-- e.g. file on disk: '<project-directory>/posts/hakyll.md' -- 'hakyll.md' source file implicitly gets filepath as identifier: -- 'posts/hakyll.md' match "posts/*" $ do -- compilation result is written to '<destination-directory>/hakyll.html' route $ gsubRoute "posts/" (const "") `composeRoutes` setExtension "html" compile pandocCompiler
The identifier here is that of the underlying item being processed and is
interpreted as an destination filepath.
See Identifier
for details.
Note how we first remove the "posts/" substring from that destination filepath
with gsubRoute
and then replace the extension with setExtension
.