hakyll-dhall-0.2.1.0: Dhall compiler for Hakyll

Copyright(c) Justin Le 2018
LicenseBSD3
Maintainerjustin@jle.im
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Hakyll.Web.Dhall

Contents

Description

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:

  1. dExprCompiler, loadDhall, and dhallCompiler, for loading underlying Dhall files, saving them into the Hakyll cache and later interpreting them as values.
  2. parseDhall and parseDhallExpr, for parsing Dhall expressions provided as strings, and resolving them while tracking dependencies.
  3. dhallPrettyCompiler, for processing and re-formatting Dhall files and presenting them as-is as a "final end-point".
Synopsis

Configuration and Options

data DhallCompilerOptions a Source #

Options for loading Dhall files.

Constructors

DCO 

Fields

  • _dcoResolver :: DhallResolver a

    Method to resolve imports encountered in files. See documentation of DhallResolver for more details.

  • _dcoMinimize :: Bool

    Strictly for usage with dhallPrettyCompiler and family: should the result be "minimized" (all in one line) or pretty-printed for human readability?

    Can be useful for saving bandwidth.

    Default: False

  • _dcoNormalize :: Bool

    If True, reduce expressions to normal form before using them. Otherwise, attempts to do no normalization and presents the file as-is (stripping out comments and annotations)

    Default: True

Instances
Generic (DhallCompilerOptions a) Source # 
Instance details

Defined in Hakyll.Web.Dhall

Associated Types

type Rep (DhallCompilerOptions a) :: * -> * #

DefaultDhallResolver a => Default (DhallCompilerOptions a) Source #
def = defaultDhallCompilerOptions
Instance details

Defined in Hakyll.Web.Dhall

type Rep (DhallCompilerOptions a) Source # 
Instance details

Defined in Hakyll.Web.Dhall

type Rep (DhallCompilerOptions a) = D1 (MetaData "DhallCompilerOptions" "Hakyll.Web.Dhall" "hakyll-dhall-0.2.1.0-2LsKbWFzCQoAzPAIYHYVC1" False) (C1 (MetaCons "DCO" PrefixI True) (S1 (MetaSel (Just "_dcoResolver") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (DhallResolver a)) :*: (S1 (MetaSel (Just "_dcoMinimize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool) :*: S1 (MetaSel (Just "_dcoNormalize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool))))

data DhallCompilerTrust Source #

Types of external imports that a Dhall file may have.

Constructors

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
Eq DhallCompilerTrust Source # 
Instance details

Defined in Hakyll.Web.Dhall

Ord DhallCompilerTrust Source # 
Instance details

Defined in Hakyll.Web.Dhall

Show DhallCompilerTrust Source # 
Instance details

Defined in Hakyll.Web.Dhall

Generic DhallCompilerTrust Source # 
Instance details

Defined in Hakyll.Web.Dhall

Associated Types

type Rep DhallCompilerTrust :: * -> * #

type Rep DhallCompilerTrust Source # 
Instance details

Defined in Hakyll.Web.Dhall

type Rep DhallCompilerTrust = D1 (MetaData "DhallCompilerTrust" "Hakyll.Web.Dhall" "hakyll-dhall-0.2.1.0-2LsKbWFzCQoAzPAIYHYVC1" False) (C1 (MetaCons "DCTLocal" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "DCTRemote" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "DCTEnv" PrefixI False) (U1 :: * -> *)))

defaultDhallCompilerOptions :: DefaultDhallResolver a => DhallCompilerOptions a Source #

Default DhallCompilerOptions. If the type variable is not inferrable, it can be helpful to use TypeApplications syntax:

defaultCompilerOptions @Import         -- do not resolve imports
defaultCompilerOptions @X              -- resolve imports

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).

Constructors

DRRaw :: {..} -> DhallResolver Import

Leave imports as imports, but optionally remap the destinations.

Fields

  • _drRemap :: Import -> Compiler (Expr Src Import)

    Optionally remap the destinations.

    Important: _drRemap is not applied recursively; it is only applied once. Any imports in the resulting 'Expr Src Import' are not re-expanded.

    Default: leave imports unchanged

DRFull :: {..} -> DhallResolver X

Completely resolve all imports in IO. All imports within Hakyll project are tracked, and changes to dependencies will trigger rebuilds upstream.

Fields

  • _drTrust :: Set DhallCompilerTrust

    Set of "trusted" import behaviors. Files with external references or imports that aren't described in this set are always rebuilt every time.

    Default: singleton DCTRemote

    That is, do not trust any dependencies on the local disk outside of the project directory, but trust that any URL imports remain unchanged.

class DefaultDhallResolver a where Source #

Helper typeclass to allow functions to be polymorphic over different DhallResolver types.

Provides default behavior for each resolver type.

Minimal complete definition

defaultDhallResolver

Instances
DefaultDhallResolver X Source #

Only trust remote imports remain unchanged. Rebuild every time if any absolute, home-directory-based, or environment variable imports are in file.

Instance details

Defined in Hakyll.Web.Dhall

DefaultDhallResolver Import Source #

Leave all imports unchanged

Instance details

Defined in Hakyll.Web.Dhall

Import and Load Dhall Files

As Dhall expressions

newtype DExpr a Source #

Newtype wrapper over Expr Src a (A Dhall expression) with an appropriate Binary instance, meant to be usable as a compilable Hakyll result that can be saved with saveSnapshot, load, etc.

Constructors

DExpr 

Fields

Instances
Generic (DExpr a) Source # 
Instance details

Defined in Hakyll.Web.Dhall

Associated Types

type Rep (DExpr a) :: * -> * #

Methods

from :: DExpr a -> Rep (DExpr a) x #

to :: Rep (DExpr a) x -> DExpr a #

(DefaultDhallResolver a, Pretty a) => Binary (DExpr a) Source # 
Instance details

Defined in Hakyll.Web.Dhall

Methods

put :: DExpr a -> Put #

get :: Get (DExpr a) #

putList :: [DExpr a] -> Put #

Pretty a => Writable (DExpr a) Source #

Automatically "pretty prints" in multi-line form

Instance details

Defined in Hakyll.Web.Dhall

Methods

write :: FilePath -> Item (DExpr a) -> IO () #

type Rep (DExpr a) Source # 
Instance details

Defined in Hakyll.Web.Dhall

type Rep (DExpr a) = D1 (MetaData "DExpr" "Hakyll.Web.Dhall" "hakyll-dhall-0.2.1.0-2LsKbWFzCQoAzPAIYHYVC1" True) (C1 (MetaCons "DExpr" PrefixI True) (S1 (MetaSel (Just "getDExpr") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Expr Src a))))

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 DExpr a is an Expr Src a, but wrapped so that it has a Binary instance that is usable by the Hakyll cache.

For example, here is a rule to parse and cache all configuration files:

match "config/**.dhall" $ do
    route mempty
    compile $ dExprCompiler @X

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"

Note that 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 that 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 also that 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.

From Hakyll cache

loadDhall :: Type 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 DExpr X (possibly using dExprCompiler @X)

loadDhallSnapshot :: Type 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 DExpr X (possibly using dExprCompiler @X)

As Haskell types

dhallCompiler :: Type 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.

Parse Dhall

As Haskell types

parseDhall Source #

Arguments

:: Maybe FilePath

Override directory root

-> Type a 
-> Text 
-> Compiler (Item a) 

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.

parseDhallWith Source #

Arguments

:: DhallCompilerOptions X 
-> Maybe FilePath

Override directory root

-> Type a 
-> Text 
-> Compiler (Item a) 

Version of parseDhall taking custom DhallCompilerOptions.

As Dhall Expressions

parseDhallExpr Source #

Arguments

:: DefaultDhallResolver a 
=> Maybe FilePath

Override directory root

-> Text 
-> Compiler (Expr Src a) 

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.

parseDhallExprWith Source #

Arguments

:: DhallCompilerOptions a 
-> Maybe FilePath

Override directory root

-> Text 
-> Compiler (Expr Src a) 

Version of parseDhallExpr taking custom DhallCompilerOptions.

Compile (prettify, normalize, re-map) Dhall text files

dhallPrettyCompiler :: forall a. (DefaultDhallResolver a, Pretty 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 @X

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.

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.

resolveDhallImports Source #

Arguments

:: DhallCompilerOptions X 
-> Maybe FilePath

Override directory root

-> Expr Src Import 
-> Compiler (Expr Src X) 

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.