Safe Haskell | None |
---|---|
Language | Haskell2010 |
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
- load :: Expr Src Import -> IO (Expr Src Void)
- loadWithManager :: IO Manager -> Expr Src Import -> IO (Expr Src Void)
- loadRelativeTo :: FilePath -> SemanticCacheMode -> Expr Src Import -> IO (Expr Src Void)
- loadWithStatus :: Status -> SemanticCacheMode -> Expr Src Import -> IO (Expr Src Void)
- loadWith :: Expr Src Import -> StateT Status IO (Expr Src Void)
- localToPath :: MonadIO io => FilePrefix -> File -> io FilePath
- hashExpression :: Expr Void Void -> SHA256Digest
- hashExpressionToCode :: Expr Void Void -> Text
- writeExpressionToSemanticCache :: Expr Void Void -> IO ()
- assertNoImports :: MonadIO io => Expr Src Import -> io (Expr Src Void)
- type Manager = Manager
- defaultNewManager :: IO Manager
- data CacheWarning
- data Status = Status {
- _stack :: NonEmpty Chained
- _graph :: [Depends]
- _cache :: Map Chained ImportSemantics
- _newManager :: IO Manager
- _manager :: Maybe Manager
- _loadOriginHeaders :: StateT Status IO OriginHeaders
- _remote :: URL -> StateT Status IO Text
- _substitutions :: Substitutions Src Void
- _normalizer :: Maybe (ReifiedNormalizer Void)
- _startingContext :: Context (Expr Src Void)
- _semanticCacheMode :: SemanticCacheMode
- _cacheWarning :: CacheWarning
- data SemanticCacheMode
- data Chained
- chainedImport :: Chained -> Import
- chainedFromLocalHere :: FilePrefix -> File -> ImportMode -> Chained
- chainedChangeMode :: ImportMode -> Chained -> Chained
- emptyStatus :: FilePath -> Status
- emptyStatusWithManager :: IO Manager -> FilePath -> Status
- envOriginHeaders :: Expr Src Import
- makeEmptyStatus :: IO Manager -> IO (Expr Src Import) -> FilePath -> Status
- remoteStatus :: URL -> Status
- remoteStatusWithManager :: IO Manager -> URL -> Status
- fetchRemote :: URL -> StateT Status IO Text
- stack :: Functor f => LensLike' f Status (NonEmpty Chained)
- cache :: Functor f => LensLike' f Status (Map Chained ImportSemantics)
- data Depends = Depends {}
- graph :: Functor f => LensLike' f Status [Depends]
- remote :: Functor f => LensLike' f Status (URL -> StateT Status IO Text)
- toHeaders :: Expr s a -> [HTTPHeader]
- substitutions :: Functor f => LensLike' f Status (Substitutions Src Void)
- normalizer :: Functor f => LensLike' f Status (Maybe (ReifiedNormalizer Void))
- startingContext :: Functor f => LensLike' f Status (Context (Expr Src Void))
- chainImport :: Chained -> Import -> StateT Status IO Chained
- dependencyToFile :: Status -> Import -> IO (Maybe FilePath)
- data ImportSemantics
- type HTTPHeader = (CI ByteString, ByteString)
- newtype Cycle = Cycle {}
- newtype ReferentiallyOpaque = ReferentiallyOpaque {}
- data Imported e = Imported {
- importStack :: NonEmpty Chained
- nested :: e
- data ImportResolutionDisabled = ImportResolutionDisabled
- data PrettyHttpException = PrettyHttpException String Dynamic
- newtype MissingFile = MissingFile FilePath
- newtype MissingEnvironmentVariable = MissingEnvironmentVariable {}
- newtype MissingImports = MissingImports [SomeException]
- data HashMismatch = HashMismatch {}
Import
loadRelativeTo :: FilePath -> SemanticCacheMode -> Expr Src Import -> IO (Expr Src Void) Source #
Resolve all imports within an expression, importing relative to the given directory.
loadWithStatus :: Status -> SemanticCacheMode -> Expr Src Import -> IO (Expr Src Void) Source #
See loadRelativeTo
.
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.
assertNoImports :: MonadIO io => Expr Src Import -> io (Expr Src Void) Source #
Assert than an expression is import-free
data CacheWarning Source #
Used internally to track whether or not we've already warned the user about caching issues
State threaded throughout the import process
Status | |
|
data SemanticCacheMode Source #
This enables or disables the semantic cache for imports protected by integrity checks
Instances
Eq SemanticCacheMode Source # | |
Defined in Dhall.Import.Types (==) :: SemanticCacheMode -> SemanticCacheMode -> Bool # (/=) :: SemanticCacheMode -> SemanticCacheMode -> Bool # |
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
.
chainedImport :: Chained -> Import Source #
The underlying import
chainedFromLocalHere :: FilePrefix -> File -> ImportMode -> Chained Source #
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.
emptyStatusWithManager :: IO Manager -> FilePath -> Status Source #
See emptyStatus
makeEmptyStatus :: IO Manager -> IO (Expr Src Import) -> FilePath -> Status Source #
See emptyStatus
.
remoteStatusWithManager :: IO Manager -> URL -> Status Source #
See remoteStatus
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.
substitutions :: Functor f => LensLike' f Status (Substitutions Src Void) Source #
Lens from a Status
to its _substitutions
field
normalizer :: Functor f => LensLike' f Status (Maybe (ReifiedNormalizer Void)) Source #
Lens from a Status
to its _normalizer
field
startingContext :: Functor f => LensLike' f Status (Context (Expr Src Void)) Source #
Lens from a Status
to its _startingContext
field
chainImport :: Chained -> Import -> StateT Status IO Chained Source #
Chain imports, also typecheck and normalize headers if applicable.
dependencyToFile :: Status -> Import -> IO (Maybe FilePath) Source #
This function is used by the --transitive
option of the
dhall {freeze,format,lint}
subcommands to determine which dependencies
to descend into
>>>
dependencyToFile (emptyStatus ".") Import{ importHashed = ImportHashed{ hash = Nothing, importType = Local Here (File (Directory []) "foo") }, importMode = Code }
Just "./foo"
>>>
dependencyToFile (emptyStatus "./foo") Import{ importHashed = ImportHashed{ hash = Nothing, importType = Local Here (File (Directory []) "bar") }, importMode = Code }
Just "./foo/bar"
>>>
dependencyToFile (emptyStatus "./foo") Import{ importHashed = ImportHashed{ hash = Nothing, importType = Remote (URL HTTPS "example.com" (File (Directory []) "") Nothing Nothing) }, importMode = Code }
Nothing
>>>
dependencyToFile (emptyStatus ".") Import{ importHashed = ImportHashed{ hash = Nothing, importType = Env "foo" }, importMode = Code }
Nothing
data ImportSemantics Source #
An import that has been fully interpeted
type HTTPHeader = (CI ByteString, ByteString) Source #
HTTP headers
An import failed because of a cycle in the import graph
Cycle | |
|
Instances
Show Cycle Source # | |
Exception Cycle Source # | |
Defined in Dhall.Import toException :: Cycle -> SomeException # fromException :: SomeException -> Maybe Cycle # displayException :: Cycle -> String # |
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
or127.0.0.1
All other imports are defined to be non-local
ReferentiallyOpaque | |
|
Instances
Show ReferentiallyOpaque Source # | |
Defined in Dhall.Import showsPrec :: Int -> ReferentiallyOpaque -> ShowS # show :: ReferentiallyOpaque -> String # showList :: [ReferentiallyOpaque] -> ShowS # | |
Exception ReferentiallyOpaque Source # | |
Defined in Dhall.Import |
Extend another exception with the current import stack
Imported | |
|
Instances
Show e => Show (Imported e) Source # | |
Exception e => Exception (Imported e) Source # | |
Defined in Dhall.Import toException :: Imported e -> SomeException # fromException :: SomeException -> Maybe (Imported e) # displayException :: Imported e -> String # |
data ImportResolutionDisabled Source #
A call to assertNoImports
failed because there was at least one import
Instances
Show ImportResolutionDisabled Source # | |
Defined in Dhall.Import showsPrec :: Int -> ImportResolutionDisabled -> ShowS # show :: ImportResolutionDisabled -> String # showList :: [ImportResolutionDisabled] -> ShowS # | |
Exception ImportResolutionDisabled Source # | |
data PrettyHttpException Source #
Wrapper around HttpException
s 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
HttpException
is stored in a Dynamic
Instances
Show PrettyHttpException Source # | |
Defined in Dhall.Import.Types showsPrec :: Int -> PrettyHttpException -> ShowS # show :: PrettyHttpException -> String # showList :: [PrettyHttpException] -> ShowS # | |
Exception PrettyHttpException Source # | |
Defined in Dhall.Import.Types |
newtype MissingFile Source #
Exception thrown when an imported file is missing
Instances
Show MissingFile Source # | |
Defined in Dhall.Import showsPrec :: Int -> MissingFile -> ShowS # show :: MissingFile -> String # showList :: [MissingFile] -> ShowS # | |
Exception MissingFile Source # | |
Defined in Dhall.Import |
newtype MissingEnvironmentVariable Source #
Exception thrown when an environment variable is missing
Instances
Show MissingEnvironmentVariable Source # | |
Defined in Dhall.Import showsPrec :: Int -> MissingEnvironmentVariable -> ShowS # show :: MissingEnvironmentVariable -> String # showList :: [MissingEnvironmentVariable] -> ShowS # | |
Exception MissingEnvironmentVariable Source # | |
newtype MissingImports Source #
List of Exceptions we encounter while resolving Import Alternatives
Instances
Show MissingImports Source # | |
Defined in Dhall.Import showsPrec :: Int -> MissingImports -> ShowS # show :: MissingImports -> String # showList :: [MissingImports] -> ShowS # | |
Exception MissingImports Source # | |
Defined in Dhall.Import |
data HashMismatch Source #
Exception thrown when an integrity check fails
Instances
Show HashMismatch Source # | |
Defined in Dhall.Import showsPrec :: Int -> HashMismatch -> ShowS # show :: HashMismatch -> String # showList :: [HashMismatch] -> ShowS # | |
Exception HashMismatch Source # | |
Defined in Dhall.Import |