Support import via environment variables

You can now use `env:NAME` to syntax to import an environment variable named
`NAME`
This commit is contained in:
Gabriel Gonzalez 2017-03-03 16:27:18 -08:00
parent 2f40a462e6
commit 11ceab1dfe
4 changed files with 76 additions and 1 deletions

View File

@ -88,7 +88,11 @@ instance Buildable Const where
-- | Path to an external resource
data Path
= File FilePath
-- ^ Local path
| URL Text
-- ^ Remote resource
| Env Text
-- ^ Environment variable
deriving (Eq, Ord, Show)
instance Buildable Path where
@ -102,6 +106,7 @@ instance Buildable Path where
where
txt = Text.fromStrict (either id id (Filesystem.toText file))
build (URL str ) = build str <> " "
build (Env env ) = "env:" <> build env
{-| Label for a bound variable

View File

@ -1,6 +1,7 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# OPTIONS_GHC -Wall #-}
{-| Dhall lets you import external expressions located either in local files or
@ -59,6 +60,18 @@
You can also reuse directory names as expressions. If you provide a path
to a local or remote directory then the compiler will look for a file named
@\@@ within that directory and use that file to represent the directory.
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 }
-}
module Dhall.Import (
@ -118,6 +131,7 @@ import qualified Filesystem.Path.CurrentOS
import qualified Network.HTTP.Client as HTTP
import qualified Network.HTTP.Client.TLS as HTTP
import qualified Filesystem.Path.CurrentOS as Filesystem
import qualified System.Environment
import qualified Text.Parser.Combinators
import qualified Text.Parser.Token
import qualified Text.Trifecta
@ -248,6 +262,19 @@ instance Show MissingFile where
"\n"
<> "\ESC[1;31mError\ESC[0m: Missing file\n"
-- | Exception thrown when an environment variable is missing
newtype MissingEnvironmentVariable = MissingEnvironmentVariable { name :: Text }
deriving (Typeable)
instance Exception MissingEnvironmentVariable
instance Show MissingEnvironmentVariable where
show (MissingEnvironmentVariable {..}) =
"\n"
<> "\ESC[1;31mError\ESC[0m: Missing environment variable\n"
<> "\n"
<> "" <> Text.unpack name
data Status = Status
{ _stack :: [Path]
, _cache :: Map Path (Expr Src X)
@ -310,6 +337,7 @@ canonicalize (File file0:paths0) =
else File (clean file0)
where
go currPath [] = File (clean currPath)
go currPath (Env _ :_ ) = File (clean currPath)
go currPath (URL url0:_ ) = combine prefix suffix
where
prefix = parentURL (removeAtFromURL url0)
@ -342,6 +370,7 @@ canonicalize (File file0:paths0) =
where
file' = Filesystem.parent (removeAtFromFile file) </> currPath
canonicalize (URL path:_) = URL path
canonicalize (Env env :_) = Env env
parentURL :: Text -> Text
parentURL = Text.dropWhileEnd (/= '/')
@ -452,6 +481,28 @@ exprFromURL m url = do
Text.Parser.Combinators.eof
return r )
-- | Parse an expression from an environment variable
exprFromEnv :: Text -> IO (Expr Src Path)
exprFromEnv env = do
m <- System.Environment.lookupEnv (Text.unpack env)
case m of
Just str -> do
let envBytes = Data.Text.Lazy.Encoding.encodeUtf8 env
let delta =
Directed (Data.ByteString.Lazy.toStrict envBytes) 0 0 0 0
case Text.Trifecta.parseString parser delta str of
Failure errInfo -> do
throwIO (ParseError (Text.Trifecta._errDoc errInfo))
Success expr -> do
return expr
Nothing -> throwIO (MissingEnvironmentVariable env)
where
parser = unParser (do
Text.Parser.Token.whiteSpace
r <- Dhall.Parser.expr
Text.Parser.Combinators.eof
return r )
{-| Load a `Path` as a \"dynamic\" expression (without resolving any imports)
This also returns the true final path (i.e. explicit "/@" at the end for
@ -469,6 +520,8 @@ loadDynamic p = do
URL url -> do
m <- needManager
liftIO (exprFromURL m url `catch` handler)
Env env -> do
liftIO (exprFromEnv env `catch` handler)
-- | Load a `Path` as a \"static\" expression (with all imports resolved)
loadStatic :: Path -> StateT Status IO (Expr Src X)
@ -482,6 +535,7 @@ loadStatic path = do
"localhost" -> True
_ -> False
local (File _) = True
local (Env _) = True
let parent = canonicalize paths
let here = canonicalize (path:paths)

View File

@ -721,7 +721,7 @@ listLit embedded = do
import_ :: Parser Path
import_ = do
a <- import0 <|> import1
a <- import0 <|> import1 <|> import2
Text.Parser.Token.whiteSpace
return a
where
@ -733,6 +733,10 @@ import_ = do
a <- url
return (URL a)
import2 = do
a <- env
return (Env a)
file :: Parser FilePath
file = try (token file0)
<|> token file1
@ -770,6 +774,12 @@ url = try url0
b <- many (Text.Parser.Char.satisfy (not . Data.Char.isSpace))
return (Data.Text.Lazy.pack (a <> b))
env :: Parser Text
env = do
_ <- Text.Parser.Char.string "env:"
a <- many (Text.Parser.Char.satisfy (not . Data.Char.isSpace))
return (Data.Text.Lazy.pack a)
-- | A parsing error
newtype ParseError = ParseError Doc deriving (Typeable)

View File

@ -417,6 +417,12 @@ import Dhall
-- Dhall expression anywhere that you can host UTF8-encoded text on the web, such
-- as Github, a pastebin, or your own web server.
--
-- You can also import Dhall expressions from environment variables, too:
--
-- > >>> System.Environment.setEnv "FOO" "1"
-- > >>> input auto "env:FOO" :: IO Integer
-- > 1
--
-- You can import types, too. For example, we can change our @./bar@ file to:
--
-- > $ echo "[3.0, 4.0, 5.0] : List ./type" > ./bar