Safe Haskell | None |
---|---|
Language | Haskell2010 |
Internally used compiler module
Synopsis
- type Snapshot = String
- data CompilerRead = CompilerRead {}
- data CompilerWrite = CompilerWrite {}
- data CompilerResult a where
- CompilerDone :: a -> CompilerWrite -> CompilerResult a
- CompilerSnapshot :: Snapshot -> Compiler a -> CompilerResult a
- CompilerError :: [String] -> CompilerResult a
- CompilerRequire :: (Identifier, Snapshot) -> Compiler a -> CompilerResult a
- newtype Compiler a = Compiler {
- unCompiler :: CompilerRead -> IO (CompilerResult a)
- runCompiler :: Compiler a -> CompilerRead -> IO (CompilerResult a)
- compilerTell :: CompilerWrite -> Compiler ()
- compilerAsk :: Compiler CompilerRead
- compilerThrow :: [String] -> Compiler a
- compilerCatch :: Compiler a -> ([String] -> Compiler a) -> Compiler a
- compilerResult :: CompilerResult a -> Compiler a
- compilerUnsafeIO :: IO a -> Compiler a
- 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 CompilerResult a where Source #
CompilerDone :: a -> CompilerWrite -> CompilerResult a | |
CompilerSnapshot :: Snapshot -> Compiler a -> CompilerResult a | |
CompilerError :: [String] -> CompilerResult a | |
CompilerRequire :: (Identifier, Snapshot) -> Compiler a -> CompilerResult a |
A monad which lets you compile items and takes care of dependency tracking for you.
Compiler | |
|
Instances
Monad Compiler Source # | |
Functor Compiler Source # | |
Applicative Compiler Source # | |
Alternative Compiler Source # | |
MonadMetadata Compiler Source # | |
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 # | |
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 #
Core operations
compilerTell :: CompilerWrite -> Compiler () Source #
compilerThrow :: [String] -> Compiler a Source #
compilerResult :: CompilerResult a -> Compiler a Source #
Put the result back in a compiler
compilerUnsafeIO :: IO a -> Compiler a Source #
Utilities
compilerTellDependencies :: [Dependency] -> Compiler () Source #
compilerTellCacheHits :: Int -> Compiler () Source #