dhall-1.33.0: A configuration language guaranteed to terminate
Safe HaskellNone
LanguageHaskell2010

Dhall.Import

Contents

Description

Dhall lets you import external expressions located either in local files or hosted on network endpoints.

To import a local file as an expression, just insert the path to the file, prepending a ./ if the path is relative to the current directory. For example, if you create a file named id with the following contents:

$ cat id
λ(a : Type) → λ(x : a) → x

Then you can use the file directly within a dhall program just by referencing the file's path:

$ dhall
./id Bool True
<Ctrl-D>
Bool

True

Imported expressions may contain imports of their own, too, which will continue to be resolved. However, Dhall will prevent cyclic imports. For example, if you had these two files:

$ cat foo
./bar
$ cat bar
./foo

... Dhall would throw the following exception if you tried to import foo:

$ dhall
./foo
^D
↳ ./foo
  ↳ ./bar

Cyclic import: ./foo

You can also import expressions hosted on network endpoints. Just use the URL

http://host[:port]/path

The compiler expects the downloaded expressions to be in the same format as local files, specifically UTF8-encoded source code text.

For example, if our id expression were hosted at http://example.com/id, then we would embed the expression within our code using:

http://example.com/id

You can also import expressions stored within environment variables using env:NAME, where NAME is the name of the environment variable. For example:

$ export FOO=1
$ export BAR='"Hi"'
$ export BAZ='λ(x : Bool) → x == False'
$ dhall <<< "{ foo = env:FOO , bar = env:BAR , baz = env:BAZ }"
{ bar : Text, baz : ∀(x : Bool) → Bool, foo : Integer }

{ bar = "Hi", baz = λ(x : Bool) → x == False, foo = 1 }

If you wish to import the raw contents of an impoert as Text then add as Text to the end of the import:

$ dhall <<< "http://example.com as Text"
Text

"<!doctype html>\n<html>\n<head>\n    <title>Example Domain</title>\n\n    <meta
 charset=\"utf-8\" />\n    <meta http-equiv=\"Content-type\" content=\"text/html
; charset=utf-8\" />\n    <meta name=\"viewport\" content=\"width=device-width,
initial-scale=1\" />\n    <style type=\"text/css\">\n    body {\n        backgro
und-color: #f0f0f2;\n        margin: 0;\n        padding: 0;\n        font-famil
y: \"Open Sans\", \"Helvetica Neue\", Helvetica, Arial, sans-serif;\n        \n
   }\n    div {\n        width: 600px;\n        margin: 5em auto;\n        paddi
ng: 50px;\n        background-color: #fff;\n        border-radius: 1em;\n    }\n
    a:link, a:visited {\n        color: #38488f;\n        text-decoration: none;
\n    }\n    @media (max-width: 700px) {\n        body {\n            background
-color: #fff;\n        }\n        div {\n            width: auto;\n            m
argin: 0 auto;\n            border-radius: 0;\n            padding: 1em;\n
  }\n    }\n    </style>    \n</head>\n\n<body>\n<div>\n    <h1>Example Domain</
h1>\n    <p>This domain is established to be used for illustrative examples in d
ocuments. You may use this\n    domain in examples without prior coordination or
 asking for permission.</p>\n    <p><a href=\"http://www.iana.org/domains/exampl
e\">More information...</a></p>\n</div>\n</body>\n</html>\n"
Synopsis

Import

load :: Expr Src Import -> IO (Expr Src Void) Source #

Resolve all imports within an expression

loadRelativeTo :: FilePath -> SemanticCacheMode -> Expr Src Import -> IO (Expr Src Void) Source #

Resolve all imports within an expression, importing relative to the given directory.

loadWith :: Expr Src Import -> StateT Status IO (Expr Src Void) Source #

Generalized version of load

You can configure the desired behavior through the initial Status that you supply

localToPath :: MonadIO io => FilePrefix -> File -> io FilePath Source #

Construct the file path corresponding to a local import. If the import is _relative_ then the resulting path is also relative.

hashExpression :: Expr Void Void -> SHA256Digest Source #

Hash a fully resolved expression

hashExpressionToCode :: Expr Void Void -> Text Source #

Convenience utility to hash a fully resolved expression and return the base-16 encoded hash with the sha256: prefix

In other words, the output of this function can be pasted into Dhall source code to add an integrity check to an import

writeExpressionToSemanticCache :: Expr Void Void -> IO () Source #

Ensure that the given expression is present in the semantic cache. The given expression should be alpha-beta-normal.

warnAboutMissingCaches :: (MonadCatch m, Alternative m, MonadIO m) => m () Source #

Warn if no cache directory is available

assertNoImports :: MonadIO io => Expr Src Import -> io (Expr Src Void) Source #

Assert than an expression is import-free

data Status Source #

State threaded throughout the import process

Constructors

Status 

Fields

data SemanticCacheMode Source #

This enables or disables the semantic cache for imports protected by integrity checks

Instances

Instances details
Eq SemanticCacheMode Source # 
Instance details

Defined in Dhall.Import.Types

data Chained Source #

A fully chained import, i.e. if it contains a relative path that path is relative to the current directory. If it is a remote import with headers those are well-typed (either of type `List { header : Text, value Text}` or `List { mapKey : Text, mapValue Text})` and in normal form. These invariants are preserved by the API exposed by Dhall.Import.

Instances

Instances details
Eq Chained Source # 
Instance details

Defined in Dhall.Import.Types

Methods

(==) :: Chained -> Chained -> Bool #

(/=) :: Chained -> Chained -> Bool #

Ord Chained Source # 
Instance details

Defined in Dhall.Import.Types

Pretty Chained Source # 
Instance details

Defined in Dhall.Import.Types

Methods

pretty :: Chained -> Doc ann #

prettyList :: [Chained] -> Doc ann #

chainedImport :: Chained -> Import Source #

The underlying import

chainedFromLocalHere :: FilePrefix -> File -> ImportMode -> Chained Source #

Given a Local import construct the corresponding unhashed Chained import (interpreting relative path as relative to the current directory).

chainedChangeMode :: ImportMode -> Chained -> Chained Source #

Adjust the import mode of a chained import

emptyStatus :: FilePath -> Status Source #

Default starting Status, importing relative to the given directory.

stack :: Functor f => LensLike' f Status (NonEmpty Chained) Source #

Lens from a Status to its _stack field

data Depends Source #

parent imports (i.e. depends on) child

Constructors

Depends 

Fields

graph :: Functor f => LensLike' f Status [Depends] Source #

Lens from a Status to its _graph field

remote :: Functor f => LensLike' f Status (URL -> StateT Status IO Text) Source #

Lens from a Status to its _remote field

toHeaders :: Expr s a -> [HTTPHeader] Source #

Given a well-typed (of type `List { header : Text, value Text }` or `List { mapKey : Text, mapValue Text }`) headers expressions in normal form construct the corresponding binary http headers; otherwise return the empty list.

chainImport :: Chained -> Import -> StateT Status IO Chained Source #

Chain imports, also typecheck and normalize headers if applicable.

data ImportSemantics Source #

An import that has been fully interpeted

newtype Cycle Source #

An import failed because of a cycle in the import graph

Constructors

Cycle 

Fields

Instances

Instances details
Show Cycle Source # 
Instance details

Defined in Dhall.Import

Methods

showsPrec :: Int -> Cycle -> ShowS #

show :: Cycle -> String #

showList :: [Cycle] -> ShowS #

Exception Cycle Source # 
Instance details

Defined in Dhall.Import

newtype ReferentiallyOpaque Source #

Dhall tries to ensure that all expressions hosted on network endpoints are weakly referentially transparent, meaning roughly that any two clients will compile the exact same result given the same URL.

To be precise, a strong interpretaton of referential transparency means that if you compiled a URL you could replace the expression hosted at that URL with the compiled result. Let's call this "static linking". Dhall (very intentionally) does not satisfy this stronger interpretation of referential transparency since "statically linking" an expression (i.e. permanently resolving all imports) means that the expression will no longer update if its dependencies change.

In general, either interpretation of referential transparency is not enforceable in a networked context since one can easily violate referential transparency with a custom DNS, but Dhall can still try to guard against common unintentional violations. To do this, Dhall enforces that a non-local import may not reference a local import.

Local imports are defined as:

  • A file
  • A URL with a host of localhost or 127.0.0.1

All other imports are defined to be non-local

Constructors

ReferentiallyOpaque 

Fields

data Imported e Source #

Extend another exception with the current import stack

Constructors

Imported 

Fields

Instances

Instances details
Show e => Show (Imported e) Source # 
Instance details

Defined in Dhall.Import

Methods

showsPrec :: Int -> Imported e -> ShowS #

show :: Imported e -> String #

showList :: [Imported e] -> ShowS #

Exception e => Exception (Imported e) Source # 
Instance details

Defined in Dhall.Import

data PrettyHttpException Source #

Wrapper around HttpExceptions with a prettier Show instance.

In order to keep the library API constant even when the with-http Cabal flag is disabled the pretty error message is pre-rendered and the real HttpExcepion is stored in a Dynamic

newtype MissingFile Source #

Exception thrown when an imported file is missing

Constructors

MissingFile FilePath 

newtype MissingImports Source #

List of Exceptions we encounter while resolving Import Alternatives

data HashMismatch Source #

Exception thrown when an integrity check fails