Safe Haskell | None |
---|---|
Language | Haskell2010 |
Internally used compiler module
Synopsis
- type Snapshot = String
- data CompilerRead = CompilerRead {}
- data CompilerWrite = CompilerWrite {}
- data CompilerErrors a
- = CompilationFailure (NonEmpty a)
- | CompilationNoResult [a]
- data CompilerResult a
- = CompilerDone a CompilerWrite
- | CompilerSnapshot Snapshot (Compiler a)
- | CompilerRequire [(Identifier, Snapshot)] (Compiler a)
- | CompilerError (CompilerErrors String)
- newtype Compiler a = Compiler {
- unCompiler :: CompilerRead -> IO (CompilerResult a)
- runCompiler :: Compiler a -> CompilerRead -> IO (CompilerResult a)
- compilerResult :: CompilerResult a -> Compiler a
- compilerTell :: CompilerWrite -> Compiler ()
- compilerAsk :: Compiler CompilerRead
- compilerUnsafeIO :: IO a -> Compiler a
- compilerThrow :: [String] -> Compiler a
- compilerNoResult :: [String] -> Compiler a
- compilerCatch :: Compiler a -> (CompilerErrors String -> Compiler a) -> Compiler a
- compilerTry :: Compiler a -> Compiler (Either (CompilerErrors String) a)
- compilerErrorMessages :: CompilerErrors a -> [a]
- compilerDebugEntries :: String -> [String] -> Compiler ()
- compilerTellDependencies :: [Dependency] -> Compiler ()
- compilerTellCacheHits :: Int -> Compiler ()
Types
type Snapshot = String Source #
Whilst compiling an item, it possible to save multiple snapshots of it, and not just the final result.
data CompilerRead Source #
Environment in which a compiler runs
CompilerRead | |
|
data CompilerWrite Source #
Instances
Show CompilerWrite Source # | |
Defined in Hakyll.Core.Compiler.Internal showsPrec :: Int -> CompilerWrite -> ShowS # show :: CompilerWrite -> String # showList :: [CompilerWrite] -> ShowS # | |
Semigroup CompilerWrite Source # | |
Defined in Hakyll.Core.Compiler.Internal (<>) :: CompilerWrite -> CompilerWrite -> CompilerWrite # sconcat :: NonEmpty CompilerWrite -> CompilerWrite # stimes :: Integral b => b -> CompilerWrite -> CompilerWrite # | |
Monoid CompilerWrite Source # | |
Defined in Hakyll.Core.Compiler.Internal mempty :: CompilerWrite # mappend :: CompilerWrite -> CompilerWrite -> CompilerWrite # mconcat :: [CompilerWrite] -> CompilerWrite # |
data CompilerErrors a Source #
Distinguishes reasons in a CompilerError
CompilationFailure (NonEmpty a) | One or more exceptions occured during compilation |
CompilationNoResult [a] | Absence of any result, most notably in template contexts. May still have error messages. |
Instances
Functor CompilerErrors Source # | |
Defined in Hakyll.Core.Compiler.Internal fmap :: (a -> b) -> CompilerErrors a -> CompilerErrors b # (<$) :: a -> CompilerErrors b -> CompilerErrors a # |
data CompilerResult a Source #
An intermediate result of a compilation step
A monad which lets you compile items and takes care of dependency tracking for you.
Compiler | |
|
Instances
Monad Compiler Source # | |
Functor Compiler Source # | |
MonadFail Compiler Source # | |
Defined in Hakyll.Core.Compiler.Internal | |
Applicative Compiler Source # | |
Alternative Compiler Source # | Trying alternative compilers if the first fails, regardless whether through
|
MonadMetadata Compiler Source # | Access provided metadata from anywhere |
Defined in Hakyll.Core.Compiler.Internal getMetadata :: Identifier -> Compiler Metadata Source # getMatches :: Pattern -> Compiler [Identifier] Source # getAllMetadata :: Pattern -> Compiler [(Identifier, Metadata)] Source # | |
MonadError [String] Compiler Source # | Compilation may fail with multiple error messages.
|
Defined in Hakyll.Core.Compiler.Internal throwError :: [String] -> Compiler a # catchError :: Compiler a -> ([String] -> Compiler a) -> Compiler a # |
runCompiler :: Compiler a -> CompilerRead -> IO (CompilerResult a) Source #
Like unCompiler
but treating IO exceptions as CompilerError
s
Core operations
compilerResult :: CompilerResult a -> Compiler a Source #
Put the result back in a compiler
compilerTell :: CompilerWrite -> Compiler () Source #
Put a CompilerWrite
compilerAsk :: Compiler CompilerRead Source #
Get the current environment
compilerUnsafeIO :: IO a -> Compiler a Source #
Run an IO computation without dependencies in a Compiler
Error operations
compilerThrow :: [String] -> Compiler a Source #
Throw errors in the Compiler
.
If no messages are given, this is considered a CompilationNoResult
error.
Otherwise, it is treated as a proper compilation failure.
compilerNoResult :: [String] -> Compiler a Source #
Put a CompilerError
with multiple messages as CompilationNoResult
compilerCatch :: Compiler a -> (CompilerErrors String -> Compiler a) -> Compiler a Source #
Allows you to recover from CompilerError
s.
Uses the same parameter order as catchError
so that it can be used infix.
c `compilerCatch` f = compilerTry c >>= either f return
compilerTry :: Compiler a -> Compiler (Either (CompilerErrors String) a) Source #
Allows to distinguish CompilerError
s and branch on them with Either
compilerTry = (`compilerCatch` return . Left) . fmap Right
compilerErrorMessages :: CompilerErrors a -> [a] Source #
Unwrap a CompilerErrors
Utilities
compilerDebugEntries :: String -> [String] -> Compiler () Source #
Pass a list of messages with a heading to the debug logger
compilerTellDependencies :: [Dependency] -> Compiler () Source #
compilerTellCacheHits :: Int -> Compiler () Source #