Safe Haskell | None |
---|---|
Language | Haskell2010 |
Once a target is compiled, the user usually wants to save it to the disk.
This is where the Routes
type comes in; it determines where a certain
target should be written.
Suppose we have an item foo/bar.markdown
. We can render this to
foo/bar.html
using:
route "foo/bar.markdown" (setExtension ".html")
If we do not want to change the extension, we can use idRoute
, the simplest
route available:
route "foo/bar.markdown" idRoute
That will route foo/bar.markdown
to foo/bar.markdown
.
Note that the extension says nothing about the content! If you set the
extension to .html
, it is your own responsibility to ensure that the
content is indeed HTML.
Finally, some special cases:
- If there is no route for an item, this item will not be routed, so it will not appear in your site directory.
- If an item matches multiple routes, the first rule will be chosen.
Synopsis
- type UsedMetadata = Bool
- data Routes
- 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
A route that uses the identifier as filepath. For example, the target with
ID foo/bar
will be written to the file foo/bar
.
setExtension :: String -> Routes Source #
Set (or replace) the extension of a route.
Example:
runRoutes (setExtension "html") "foo/bar"
Result:
Just "foo/bar.html"
Example:
runRoutes (setExtension "html") "posts/the-art-of-trolling.markdown"
Result:
Just "posts/the-art-of-trolling.html"
matchRoute :: Pattern -> Routes -> Routes Source #
Apply the route if the identifier matches the given pattern, fail otherwise
customRoute :: (Identifier -> FilePath) -> Routes Source #
Create a custom route. This should almost always be used with
matchRoute
constRoute :: FilePath -> Routes Source #
A route that always gives the same result. Obviously, you should only use this for a single compilation rule.
Create a gsub route
Example:
runRoutes (gsubRoute "rss/" (const "")) "tags/rss/bar.xml"
Result:
Just "tags/bar.xml"
metadataRoute :: (Metadata -> Routes) -> Routes Source #
Get access to the metadata in order to determine the route
Compose routes so that f `composeRoutes` g
is more or less equivalent
with g . f
.
Example:
let routes = gsubRoute "rss/" (const "") `composeRoutes` setExtension "xml" in runRoutes routes "tags/rss/bar"
Result:
Just "tags/bar.xml"
If the first route given fails, Hakyll will not apply the second route.