Copyright | (c) Justin Le 2018 |
---|---|
License | BSD3 |
Maintainer | justin@jle.im |
Stability | experimental |
Portability | non-portable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Hakyll compiler and loader for Dhall files. Functions are intended to track all local dependencies within the project directory, so rebuilds are properly triggered on up-stream imports. Provides options for customizing rebuilding behavior for network, environment variable, and non-project local files.
There are three major workflows:
dExprCompiler
,loadDhall
, anddhallCompiler
, for loading underlying Dhall files, saving them into the Hakyll cache and later interpreting them as values.parseDhall
andparseDhallExpr
, for parsing Dhall expressions provided as strings, and resolving them while tracking dependencies.dhallPrettyCompiler
, for processing and re-formatting Dhall files and presenting them as-is as a "final end-point".
Synopsis
- newtype DExpr a = DExpr {}
- dExprCompiler :: DefaultDhallResolver a => Compiler (Item (DExpr a))
- dExprCompilerWith :: DhallCompilerOptions a -> Compiler (Item (DExpr a))
- loadDhall :: Decoder a -> Identifier -> Compiler (Item a)
- loadDhallSnapshot :: Decoder a -> Identifier -> Snapshot -> Compiler (Item a)
- dhallCompiler :: Decoder a -> Compiler (Item a)
- dhallCompilerWith :: DhallCompilerOptions Void -> Decoder a -> Compiler (Item a)
- parseDhall :: Maybe FilePath -> Decoder a -> Text -> Compiler (Item a)
- parseDhallWith :: DhallCompilerOptions Void -> Maybe FilePath -> Decoder a -> Text -> Compiler (Item a)
- parseDhallExpr :: DefaultDhallResolver a => Maybe FilePath -> Text -> Compiler (Expr Src a)
- parseDhallExprWith :: DhallCompilerOptions a -> Maybe FilePath -> Text -> Compiler (Expr Src a)
- dhallPrettyCompiler :: forall a. DefaultDhallResolver a => Compiler (Item String)
- dhallRawPrettyCompiler :: Compiler (Item String)
- dhallFullPrettyCompiler :: Compiler (Item String)
- dhallPrettyCompilerWith :: DhallCompilerOptions a -> Compiler (Item String)
- renderDhallExprWith :: DhallCompilerOptions a -> Expr Src a -> Text
- data DhallCompilerOptions a = DCO {}
- data DhallCompilerTrust
- defaultDhallCompilerOptions :: DefaultDhallResolver a => DhallCompilerOptions a
- dcoResolver :: forall a a. Lens (DhallCompilerOptions a) (DhallCompilerOptions a) (DhallResolver a) (DhallResolver a)
- dcoMinimize :: forall a. Lens' (DhallCompilerOptions a) Bool
- dcoNormalize :: forall a. Lens' (DhallCompilerOptions a) Bool
- data DhallResolver :: Type -> Type where
- DRRaw :: {..} -> DhallResolver Import
- DRFull :: {..} -> DhallResolver Void
- class DefaultDhallResolver a where
- drRemap :: Lens' (DhallResolver Import) (Import -> Compiler (Expr Src Import))
- drFull :: Lens' (DhallResolver Void) (Set DhallCompilerTrust)
- interpretDhallCompiler :: Decoder a -> Expr Src Void -> Compiler a
- parseRawDhallExprWith :: DhallCompilerOptions Import -> Text -> Compiler (Expr Src Import)
- resolveDhallImports :: DhallCompilerOptions Void -> Maybe FilePath -> Expr Src Import -> Compiler (Expr Src Void)
Import and Load Dhall Files
As Dhall expressions
Newtype wrapper over
(A Dhall expression) with an
appropriate Expr
Src
aBinary
instance, meant to be usable as a compilable
Hakyll result that can be saved with saveSnapshot
, load
, etc.
dExprCompiler :: DefaultDhallResolver a => Compiler (Item (DExpr a)) Source #
Compile the underlying text file as a Dhall expression, wrapped in
a DExpr
newtype. Mostly useful for pre-cacheing fully resolved Dhall
expressions into the Hakyll cache, which you can later interpret and
load with loadDhall
or loadDhallSnapshot
. A
is an
DExpr
a
, but wrapped so that it has a Expr
Src
aBinary
instance that
is usable by the Hakyll cache. Tracks all dependencies, so will trigger
rebuilds of items that depend on it if any downstream dhall files are
modified.
For example, here is a rule to parse and cache all Dhall files in the directory ./config:
match
"config/**.dhall" $ doroute
mempty
compile
$dExprCompiler
@Void
This will save all of the dhall files in the directory ./config in the
Hakyll cache. They can later be loaded and interpreted in the
Compiler
monad using:
loadDhall
auto
"config/my_config.dhall"
This is mostly useful for routes that match many different
files which will be interpreted as values of different types, or for
caching a single expression that you might want to interpret as
different types later. If you want to parse and immediately interpret,
see dhallCompiler
.
_Note:_ If the a
is not inferrable by type inference (like in the
situation above), you can specify the a
using type application syntax
(like above).
_Note:_ This isn't really meant to be a "final end-point", but if it is
used as such, a pretty-printed version will be rendered to the output
directory, based on the Writable
instance of DExpr
.
dExprCompilerWith :: DhallCompilerOptions a -> Compiler (Item (DExpr a)) Source #
dExprCompiler
, but with custom DhallCompilerOptions
.
From Hakyll cache
loadDhall :: Decoder a -> Identifier -> Compiler (Item a) Source #
Wrapper over load
and interpretDhallCompiler
. Pulls up a DExpr
compiled or saved into the Hakyll cache and interprets it as a value.
Expects item at identifier to be saved as
(possibly using
DExpr
Void
)dExprCompiler
@Void
Tracks dependencies properly, so any pages or routes that use the saved Dhall expression will re-build if any of the downstream Dhall files are edited.
loadDhallSnapshot :: Decoder a -> Identifier -> Snapshot -> Compiler (Item a) Source #
Wrapper over loadSnapshot
and interpretDhallCompiler
. Pulls up
a DExpr
saved into the Hakyll cache as a snapshot and interprets it as
a value.
Expects item at identifier to be saved as
(possibly using
DExpr
Void
)dExprCompiler
@Void
Tracks dependencies properly, so any pages or routes that use the saved Dhall expression will re-build if any of the downstream Dhall files are edited.
As Haskell types
dhallCompiler :: Decoder a -> Compiler (Item a) Source #
Parse the underlying text file as a Dhall expression and directly interpret it as a value of the given type. Tracks all dependencies, so will trigger rebuilds based on downstream changes.
dhallCompilerWith :: DhallCompilerOptions Void -> Decoder a -> Compiler (Item a) Source #
dhallCompiler
, but with custom DhallCompilerOptions
.
Parse Dhall
As Haskell types
Parse a Dhall source. Meant to be useful for patterns similar to
dhall-to-text
. If using examples from
https://github.com/dhall-lang/dhall-text, you can use:
parseDhallExpr
Nothing
"./make-items ./people"
Any local dependencies within the project directory (./make-items and ./people above, for example) are tracked by Hakyll, and so modifications to required files will also cause upstream files to be rebuilt.
To directly obtain a Dhall expression, see parseDhallExpr
.
:: DhallCompilerOptions Void | |
-> Maybe FilePath | Override directory root |
-> Decoder a | |
-> Text | |
-> Compiler (Item a) |
Version of parseDhall
taking custom DhallCompilerOptions
.
As Dhall Expressions
Version of parseDhall
that directly returns a Dhall expression,
instead of trying to interpret it into a custom Haskell type.
Any local dependencies within the project directory (./make-items and ./people above, for example) are tracked by Hakyll, and so modifications to required files will also cause upstream files to be rebuilt.
Version of parseDhallExpr
taking custom DhallCompilerOptions
.
Compile (prettify, normalize, re-map) Dhall text files
dhallPrettyCompiler :: forall a. DefaultDhallResolver a => Compiler (Item String) Source #
Essentially a Dhall pretty-printer, (optional) normalizer, and
re-formatter. Compile the Dhall file as text according to default
DhallCompilerOptions
. Note that this is polymorphic over both "raw"
and "fully resolved" versions; it must be called with
TypeApplications.
dhallRawPrettyCompiler
=dhallPrettyCompiler
@Import
dhallFullPrettyCompiler
=dhallPrettyCompiler
@Void
It might be more convenient to just use dhallRawCompiler
or
dhallFullCompiler
.
dhallRawPrettyCompiler :: Compiler (Item String) Source #
Compile the Dhall file as text according to default
DhallCompilerOptions
while leaving all imports unchanged and
unresolved. Essentially a Dhall pretty-printer, (optional) normalizer,
and re-formatter.
dhallFullPrettyCompiler :: Compiler (Item String) Source #
Compile the Dhall file as text according to default
DhallCompilerOptions
, resolving all imports in IO and tracking
dependencies. Essentially a Dhall pretty-printer, (optional)
normalizer, and re-formatter.
dhallPrettyCompilerWith :: DhallCompilerOptions a -> Compiler (Item String) Source #
dhallPrettyCompiler
, but with custom DhallCompilerOptions
.
renderDhallExprWith :: DhallCompilerOptions a -> Expr Src a -> Text Source #
Format and pretty-print an Expr
according to options in a given
DhallCompilerOptions
.
Configuration and Options
data DhallCompilerOptions a Source #
Options for loading Dhall files.
DCO | |
|
Instances
data DhallCompilerTrust Source #
Types of external imports that a Dhall file may have.
DCTLocal | File on local filesystem outside of project directory, and therefore not tracked by Hakyll |
DCTRemote | Link to remote resource over a network connection |
DCTEnv | Reference to environment variable on machine |
Instances
defaultDhallCompilerOptions :: DefaultDhallResolver a => DhallCompilerOptions a Source #
Default DhallCompilerOptions
. If the type variable is not
inferrable, it can be helpful to use TypeApplications syntax:
defaultDhallCompilerOptions
@Import
-- do not resolve importsdefaultDhallCompilerOptions
@Void
-- resolve imports
Default values are:
DCO
{_dcoResolver
=defaultDhallResolver
,_dcoMinimize
=False
,_dcoNormalize
=True
}
dcoResolver :: forall a a. Lens (DhallCompilerOptions a) (DhallCompilerOptions a) (DhallResolver a) (DhallResolver a) Source #
dcoMinimize :: forall a. Lens' (DhallCompilerOptions a) Bool Source #
dcoNormalize :: forall a. Lens' (DhallCompilerOptions a) Bool Source #
Resolver Behaviors
data DhallResolver :: Type -> Type where Source #
Method for resolving imports.
The choice will determine the type of expression that loadDhallExpr
and family will produce.
Note that at this moment, the only available options are "all or nothing" --- either resolve all types imports completely and fully, or none of them. Hopefully one day this library will offer the ability to resolve only certain types of imports (environment variables, absolute paths) and not others (remote network, local paths).
DRRaw | Leave imports as imports, but optionally remap the destinations. |
DRFull | Completely resolve all imports in IO. All imports within Hakyll project are tracked, and changes to dependencies will trigger rebuilds upstream. |
|
class DefaultDhallResolver a where Source #
Helper typeclass to allow functions to be polymorphic over different
DhallResolver
types.
Provides default behavior for each resolver type.
Instances
DefaultDhallResolver Void Source # | Only trust remote imports remain unchanged. Rebuild every time if any absolute, home-directory-based, or environment variable imports are in file. |
Defined in Hakyll.Web.Dhall | |
DefaultDhallResolver Import Source # | Leave all imports unchanged |
Defined in Hakyll.Web.Dhall |
drRemap :: Lens' (DhallResolver Import) (Import -> Compiler (Expr Src Import)) Source #
Lens for _drRemap
field of DhallResolver
.
drFull :: Lens' (DhallResolver Void) (Set DhallCompilerTrust) Source #
Lens for _drFull
field of DhallResolver
.
Internal Utilities
parseRawDhallExprWith :: DhallCompilerOptions Import -> Text -> Compiler (Expr Src Import) Source #
Version of parseDhallExprWith
that only acceps the DRRaw
resolver,
remapping the imports with the function in the DRRaw
. Does not
perform any normalization.
:: DhallCompilerOptions Void | |
-> Maybe FilePath | Override directory root |
-> Expr Src Import | |
-> Compiler (Expr Src Void) |
Resolve all imports in a parsed Dhall expression.
This implements the "magic" of dependency tracking: implemented so that any local dependencies within the project directory are tracked by Hakyll, and so modifications to required files will also cause upstream files to be rebuilt.