A Compiler manages targets and dependencies between targets
The most distinguishing property of a Compiler
is that it is an Arrow. A
compiler of the type Compiler a b
is simply a compilation phase which takes
an a
as input, and produces a b
as output.
Compilers are chained using the >>>
arrow operation. If we have a compiler
getResourceString :: Compiler Resource String
which reads the resource, and a compiler
readPage :: Compiler String (Page String)
we can chain these two compilers to get a
(getResourceString >>> readPage) :: Compiler Resource (Page String)
Most compilers can be created by combining smaller compilers using >>>
.
More advanced constructions are also possible using arrow, and sometimes these are needed. For a good introduction to arrow, you can refer to
http://en.wikibooks.org/wiki/Haskell/Understanding_arrows
A construction worth writing a few paragraphs about here are the require
functions. Different variants of this function are exported here, but they
all serve more or less the same goal.
When you use only >>>
to chain your compilers, you get a linear pipeline --
it is not possible to add extra items from other compilers along the way.
This is where the require
functions come in.
This function allows you to reference other items, which are then added to the pipeline. Let's look at this crappy ASCII illustration which represents a pretty common scenario:
read resource >>> pandoc render >>> layout >>> relativize URL's @templates/fancy.html@
We want to construct a pipeline of compilers to go from our resource to a
proper webpage. However, the layout
compiler takes more than just the
rendered page as input: it needs the templates/fancy.html
template as well.
This is an example of where we need the require
function. We can solve
this using a construction that looks like:
... >>> pandoc render >>> require >>> layout >>> ... | @templates/fancy.html@ ------/
This illustration can help us understand the type signature of require
.
require :: (Binary a, Typeable a, Writable a) => Identifier -> (b -> a -> c) -> Compiler b c
Let's look at it in detail:
(Binary a, Typeable a, Writable a)
These are constraints for the a
type. a
(the template) needs to have
certain properties for it to be required.
Identifier
This is simply templates/fancy.html
: the Identifier
of the item we want
to require
, in other words, the name of the item we want to add to the
pipeline somehow.
(b -> a -> c)
This is a function given by the user, specifying how the two items shall be
merged. b
is the output of the previous compiler, and a
is the item we
just required -- the template. This means c
will be the final output of the
require
combinator.
Compiler b c
Indeed, we have now constructed a compiler which takes a b
and produces a
c
. This means that we have a linear pipeline again, thanks to the require
function. So, the require
function actually helps to reduce to complexity
of Hakyll applications!
Note that require will fetch a previously compiled item: in our example of
the type a
. It is very important that the compiler which produced this
value, produced the right type as well!
- data Compiler a b
- runCompiler :: Compiler () CompileRule -> Identifier -> ResourceProvider -> [Identifier] -> Routes -> Store -> Bool -> Logger -> IO (Throwing CompileRule)
- getIdentifier :: Compiler a Identifier
- getResource :: Compiler a Resource
- getRoute :: Compiler a (Maybe FilePath)
- getRouteFor :: Compiler Identifier (Maybe FilePath)
- getResourceString :: Compiler Resource String
- getResourceLBS :: Compiler Resource ByteString
- fromDependency :: Identifier -> Compiler a a
- require_ :: (Binary a, Typeable a, Writable a) => Identifier -> Compiler b a
- require :: (Binary a, Typeable a, Writable a) => Identifier -> (b -> a -> c) -> Compiler b c
- requireA :: (Binary a, Typeable a, Writable a) => Identifier -> Compiler (b, a) c -> Compiler b c
- requireAll_ :: (Binary a, Typeable a, Writable a) => Pattern -> Compiler b [a]
- requireAll :: (Binary a, Typeable a, Writable a) => Pattern -> (b -> [a] -> c) -> Compiler b c
- requireAllA :: (Binary a, Typeable a, Writable a) => Pattern -> Compiler (b, [a]) c -> Compiler b c
- cached :: (Binary a, Typeable a, Writable a) => String -> Compiler Resource a -> Compiler Resource a
- unsafeCompiler :: (a -> IO b) -> Compiler a b
- traceShowCompiler :: Show a => Compiler a a
- mapCompiler :: Compiler a b -> Compiler [a] [b]
- timedCompiler :: String -> Compiler a b -> Compiler a b
- byExtension :: Compiler a b -> [(String, Compiler a b)] -> Compiler a b
Documentation
The compiler arrow
:: Compiler () CompileRule | Compiler to run |
-> Identifier | Target identifier |
-> ResourceProvider | Resource provider |
-> [Identifier] | Universe |
-> Routes | Route |
-> Store | Store |
-> Bool | Was the resource modified? |
-> Logger | Logger |
-> IO (Throwing CompileRule) | Resulting item |
Run a compiler, yielding the resulting target and it's dependencies. This
version of runCompilerJob
also stores the result
getIdentifier :: Compiler a IdentifierSource
Get the identifier of the item that is currently being compiled
getResource :: Compiler a ResourceSource
Get the resource that is currently being compiled
getRouteFor :: Compiler Identifier (Maybe FilePath)Source
Get the route for a specified item
getResourceString :: Compiler Resource StringSource
Get the resource we are compiling as a string
getResourceLBS :: Compiler Resource ByteStringSource
Get the resource we are compiling as a lazy bytestring
fromDependency :: Identifier -> Compiler a aSource
Wait until another compiler has finished before running this compiler
require_ :: (Binary a, Typeable a, Writable a) => Identifier -> Compiler b aSource
Variant of require
which drops the current value
require :: (Binary a, Typeable a, Writable a) => Identifier -> (b -> a -> c) -> Compiler b cSource
Require another target. Using this function ensures automatic handling of dependencies
requireA :: (Binary a, Typeable a, Writable a) => Identifier -> Compiler (b, a) c -> Compiler b cSource
Arrow-based variant of require
requireAll_ :: (Binary a, Typeable a, Writable a) => Pattern -> Compiler b [a]Source
Variant of requireAll
which drops the current value
requireAll :: (Binary a, Typeable a, Writable a) => Pattern -> (b -> [a] -> c) -> Compiler b cSource
Require a number of targets. Using this function ensures automatic handling of dependencies
requireAllA :: (Binary a, Typeable a, Writable a) => Pattern -> Compiler (b, [a]) c -> Compiler b cSource
Arrow-based variant of requireAll
cached :: (Binary a, Typeable a, Writable a) => String -> Compiler Resource a -> Compiler Resource aSource
Create an unsafe compiler from a function in IO
traceShowCompiler :: Show a => Compiler a aSource
Compiler for debugging purposes
mapCompiler :: Compiler a b -> Compiler [a] [b]Source
Map over a compiler
Log and time a compiler
:: Compiler a b | Default compiler |
-> [(String, Compiler a b)] | Choices |
-> Compiler a b | Resulting compiler |
Choose a compiler by extension
Example:
route "css/*" $ setExtension "css" compile "css/*" $ byExtension (error "Not a (S)CSS file") [ (".css", compressCssCompiler) , (".scss", sass) ]
This piece of code will select the compressCssCompiler
for .css
files,
and the sass
compiler (defined elsewhere) for .scss
files.