hakyll-4.13.4.1: A static website compiler library

Safe HaskellNone
LanguageHaskell2010

Hakyll.Core.Compiler

Synopsis

Documentation

data Compiler a Source #

A monad which lets you compile items and takes care of dependency tracking for you.

Instances
Monad Compiler Source # 
Instance details

Defined in Hakyll.Core.Compiler.Internal

Methods

(>>=) :: Compiler a -> (a -> Compiler b) -> Compiler b #

(>>) :: Compiler a -> Compiler b -> Compiler b #

return :: a -> Compiler a #

fail :: String -> Compiler a #

Functor Compiler Source # 
Instance details

Defined in Hakyll.Core.Compiler.Internal

Methods

fmap :: (a -> b) -> Compiler a -> Compiler b #

(<$) :: a -> Compiler b -> Compiler a #

MonadFail Compiler Source # 
Instance details

Defined in Hakyll.Core.Compiler.Internal

Methods

fail :: String -> Compiler a #

Applicative Compiler Source # 
Instance details

Defined in Hakyll.Core.Compiler.Internal

Methods

pure :: a -> Compiler a #

(<*>) :: Compiler (a -> b) -> Compiler a -> Compiler b #

liftA2 :: (a -> b -> c) -> Compiler a -> Compiler b -> Compiler c #

(*>) :: Compiler a -> Compiler b -> Compiler b #

(<*) :: Compiler a -> Compiler b -> Compiler a #

Alternative Compiler Source #

Trying alternative compilers if the first fails, regardless whether through fail, throwError or noResult. Aggregates error messages if all fail.

Instance details

Defined in Hakyll.Core.Compiler.Internal

Methods

empty :: Compiler a #

(<|>) :: Compiler a -> Compiler a -> Compiler a #

some :: Compiler a -> Compiler [a] #

many :: Compiler a -> Compiler [a] #

MonadMetadata Compiler Source #

Access provided metadata from anywhere

Instance details

Defined in Hakyll.Core.Compiler.Internal

MonadError [String] Compiler Source #

Compilation may fail with multiple error messages. catchError handles errors from throwError, fail and noResult

Instance details

Defined in Hakyll.Core.Compiler.Internal

Methods

throwError :: [String] -> Compiler a #

catchError :: Compiler a -> ([String] -> Compiler a) -> Compiler a #

getUnderlying :: Compiler Identifier Source #

Get the underlying identifier.

getUnderlyingExtension :: Compiler String Source #

Get the extension of the underlying identifier. Returns something like ".html"

makeItem :: a -> Compiler (Item a) Source #

Create an item from the underlying identifier and a given value.

getRoute :: Identifier -> Compiler (Maybe FilePath) Source #

Get the route for a specified item

getResourceBody :: Compiler (Item String) Source #

Get the full contents of the matched source file as a string, but without metadata preamble, if there was one.

getResourceString :: Compiler (Item String) Source #

Get the full contents of the matched source file as a string.

getResourceLBS :: Compiler (Item ByteString) Source #

Get the full contents of the matched source file as a lazy bytestring.

getResourceFilePath :: Compiler FilePath Source #

Get the file path of the resource we are compiling

type Snapshot = String Source #

Whilst compiling an item, it possible to save multiple snapshots of it, and not just the final result.

saveSnapshot :: (Binary a, Typeable a) => Snapshot -> Item a -> Compiler (Item a) Source #

Save a snapshot of the item. This function returns the same item, which convenient for building >>= chains.

load :: (Binary a, Typeable a) => Identifier -> Compiler (Item a) Source #

Load an item compiled elsewhere. If the required item is not yet compiled, the build system will take care of that automatically.

loadSnapshot :: (Binary a, Typeable a) => Identifier -> Snapshot -> Compiler (Item a) Source #

Require a specific snapshot of an item.

loadBody :: (Binary a, Typeable a) => Identifier -> Compiler a Source #

A shortcut for only requiring the body of an item.

loadBody = fmap itemBody . load

loadSnapshotBody :: (Binary a, Typeable a) => Identifier -> Snapshot -> Compiler a Source #

A shortcut for only requiring the body for a specific snapshot of an item

loadAll :: (Binary a, Typeable a) => Pattern -> Compiler [Item a] Source #

This function allows you to load a dynamic list of items

loadAllSnapshots :: (Binary a, Typeable a) => Pattern -> Snapshot -> Compiler [Item a] Source #

Load a specific snapshot for each of dynamic list of items

cached :: (Binary a, Typeable a) => String -> Compiler a -> Compiler a Source #

Turn on caching for a compilation value to avoid recomputing it on subsequent Hakyll runs. The storage key consists of the underlying identifier of the compiled ressource and the given name.

unsafeCompiler :: IO a -> Compiler a Source #

Run an IO computation without dependencies in a Compiler

debugCompiler :: String -> Compiler () Source #

Compiler for debugging purposes. Passes a message to the debug logger that is printed in verbose mode.

noResult :: String -> Compiler a Source #

Fail so that it is treated as non-defined in an $if()$ branching Hakyll.Web.Template macro, and alternative Contexts are tried

Since: 4.13.0

withErrorMessage :: String -> Compiler a -> Compiler a Source #

Prepend an error line to the error, if there is one. This allows you to add helpful context to error messages.

Since: 4.13.0