Hakyll.Core.Rules
Description
This module provides a declarative DSL in which the user can specify the different rules used to run the compilers.
The convention is to just list all items in the RulesM
monad, routes and
compilation rules.
A typical usage example would be:
main = hakyll $ do match "posts/*" $ do route (setExtension "html") compile someCompiler match "css/*" $ do route idRoute compile compressCssCompiler
- data RulesM a
- type Rules = RulesM ()
- match :: Pattern a -> RulesM b -> RulesM b
- group :: String -> RulesM a -> RulesM a
- compile :: (Binary a, Typeable a, Writable a) => Compiler Resource a -> RulesM (Pattern a)
- create :: (Binary a, Typeable a, Writable a) => Identifier a -> Compiler () a -> RulesM (Identifier a)
- route :: Routes -> Rules
- resources :: RulesM [Identifier a]
- metaCompile :: (Binary a, Typeable a, Writable a) => Compiler () [(Identifier a, Compiler () a)] -> Rules
- metaCompileWith :: (Binary a, Typeable a, Writable a) => Identifier () -> Compiler () [(Identifier a, Compiler () a)] -> Rules
Documentation
The monad used to compose rules
Simplification of the RulesM type; usually, it will not return any result.
match :: Pattern a -> RulesM b -> RulesM bSource
Only compile/route items satisfying the given predicate
group :: String -> RulesM a -> RulesM aSource
Greate a group of compilers
Imagine you have a page that you want to render, but you also want the raw content available on your site.
match "test.markdown" $ do route $ setExtension "html" compile pageCompiler match "test.markdown" $ do route idRoute compile copyPageCompiler
Will of course conflict! In this case, Hakyll will pick the first matching
compiler (pageCompiler
in this case).
In case you want to have them both, you can use the group
function to
create a new group. For example,
match "test.markdown" $ do route $ setExtension "html" compile pageCompiler group "raw" $ do match "test.markdown" $ do route idRoute compile copyPageCompiler
This will put the compiler for the raw content in a separate group
("raw"
), which causes it to be compiled as well.
compile :: (Binary a, Typeable a, Writable a) => Compiler Resource a -> RulesM (Pattern a)Source
Add a compilation rule to the rules.
This instructs all resources to be compiled using the given compiler. When
no resources match the current selection, nothing will happen. In this case,
you might want to have a look at create
.
create :: (Binary a, Typeable a, Writable a) => Identifier a -> Compiler () a -> RulesM (Identifier a)Source
Add a compilation rule
This sets a compiler for the given identifier. No resource is needed, since we are creating the item from scratch. This is useful if you want to create a page on your site that just takes content from other items -- but has no actual content itself.
route :: Routes -> RulesSource
Add a route.
This adds a route for all items matching the current pattern.
resources :: RulesM [Identifier a]Source
Get a list of resources matching the current pattern. This will also set the correct group to the identifiers.
Arguments
:: (Binary a, Typeable a, Writable a) | |
=> Compiler () [(Identifier a, Compiler () a)] | Compiler generating the other compilers |
-> Rules | Resulting rules |
Apart from regular compilers, one is also able to specify metacompilers. Metacompilers are a special class of compilers: they are compilers which produce other compilers.
This is needed when the list of compilers depends on something we cannot know before actually running other compilers. The most typical example is if we have a blogpost using tags.
Every post has a collection of tags. For example,
post1: code, haskell post2: code, random
Now, we want to create a list of posts for every tag. We cannot write this
down in our Rules
DSL directly, since we don't know what tags the different
posts will have -- we depend on information that will only be available when
we are actually compiling the pages.
The solution is simple, using metaCompile
, we can add a compiler that will
parse the pages and produce the compilers needed for the different tag pages.
And indeed, we can see that the first argument to metaCompile
is a
Compiler
which produces a list of (Identifier
, Compiler
) pairs. The
idea is simple: metaCompile
produces a list of compilers, and the
corresponding identifiers.
For simple hakyll systems, it is no need for this construction. More formally, it is only needed when the content of one or more items determines which items must be rendered.
Arguments
:: (Binary a, Typeable a, Writable a) | |
=> Identifier () | Identifier for this compiler |
-> Compiler () [(Identifier a, Compiler () a)] | Compiler generating the other compilers |
-> Rules | Resulting rules |
Version of metaCompile
that allows you to specify a custom identifier for
the metacompiler.