Change dhall freeze to only freeze Remote imports (#808)

The motivation behind this change is so that users can freeze remote imports
(like the Prelude) but ignore local imports so that subsequent runs of the
interpreter reflect changes to local files and environment variables.

The reasoning behind this is that there are two primary benefits of integrity
checks:

* Improved security
* Caching

... and one downside which is that updates to those imports are not pulled in
until the integrity check is updated or removed.

However, environment variables and local file paths do not benefit from
improved security or caching, so there is only a downside to freezing them.

Specifically:

* Environment variables and local file paths are both cheap to resolve

  ... so they don't really benefit from caching.

  To be precise, they *could* benefit from caching if the cache expression is
  cheaper to parse and normalize compared to the original file.  For those
  cases there is still an `--all` flag to freeze all imports.

* Environment variables and local file paths are trusted

  For example, when a user runs the `dhall` executable they are implicitly
  trusting their filesystem which provides that executable.  Similarly, when
  they run `dhall` without an absolute path they are implicitly trusting that
  their `PATH` environment variable has not been compromised to point to a
  malicious executable.

  Up until now, Dhall's threat model has always been that local imports are
  trusted but remote imports are not, so this is consistent with that threat
  model.

... so as far as environment variables and local files are concerned there are
only downsides to freezing them and no up-side.  This is why this change
no longer freezes them.

This also renames `hashImport` to `freezeImport` for more terminology
consistency.
This commit is contained in:
Gabriel Gonzalez 2019-02-01 07:46:03 -08:00 committed by GitHub
parent b2514ff8bf
commit 15d0b8d063
No known key found for this signature in database
GPG Key ID: 4AEE18F83AFDEB23
2 changed files with 39 additions and 11 deletions

View File

@ -5,7 +5,8 @@
module Dhall.Freeze
( -- * Freeze
freeze
, hashImport
, freezeImport
, freezeRemoteImport
) where
import Control.Exception (SomeException)
@ -13,7 +14,7 @@ import Data.Monoid ((<>))
import Data.Maybe (fromMaybe)
import Data.Text
import Dhall.Binary (StandardVersion(..))
import Dhall.Core (Expr(..), Import(..), ImportHashed(..))
import Dhall.Core (Expr(..), Import(..), ImportHashed(..), ImportType(..))
import Dhall.Import (standardVersion)
import Dhall.Parser (exprAndHeaderFromText, Src)
import Dhall.Pretty (annToAnsiStyle, layoutOpts)
@ -33,13 +34,13 @@ import qualified System.FilePath
import qualified System.IO
-- | Retrieve an `Import` and update the hash to match the latest contents
hashImport
freezeImport
:: FilePath
-- ^ Current working directory
-> StandardVersion
-> Import
-> IO Import
hashImport directory _standardVersion import_ = do
freezeImport directory _standardVersion import_ = do
let unprotectedImport =
import_
{ importHashed =
@ -47,7 +48,11 @@ hashImport directory _standardVersion import_ = do
{ hash = Nothing
}
}
let status = set standardVersion _standardVersion (Dhall.Import.emptyStatus directory)
let status =
set standardVersion
_standardVersion
(Dhall.Import.emptyStatus directory)
let download =
State.evalStateT (Dhall.Import.loadWith (Embed import_)) status
@ -77,6 +82,18 @@ hashImport directory _standardVersion import_ = do
return newImport
-- | Freeze an import only if the import is a `Remote` import
freezeRemoteImport
:: FilePath
-- ^ Current working directory
-> StandardVersion
-> Import
-> IO Import
freezeRemoteImport directory _standardVersion import_ = do
case importType (importHashed import_) of
Remote {} -> freezeImport directory _standardVersion import_
_ -> return import_
parseExpr :: String -> Text -> IO (Text, Expr Src Import)
parseExpr src txt =
case exprAndHeaderFromText src txt of
@ -107,9 +124,11 @@ freeze
:: Maybe FilePath
-- ^ Modify file in-place if present, otherwise read from @stdin@ and write
-- to @stdout@
-> Bool
-- ^ If `True` then freeze all imports, otherwise freeze only remote imports
-> StandardVersion
-> IO ()
freeze inplace _standardVersion = do
freeze inplace everything _standardVersion = do
(text, directory) <- case inplace of
Nothing -> do
text <- Data.Text.IO.getContents
@ -122,7 +141,10 @@ freeze inplace _standardVersion = do
return (text, System.FilePath.takeDirectory file)
(header, parsedExpression) <- parseExpr srcInfo text
frozenExpression <- traverse (hashImport directory _standardVersion) parsedExpression
let freezeFunction = if everything then freezeImport else freezeRemoteImport
frozenExpression <- traverse (freezeFunction directory _standardVersion) parsedExpression
writeExpr inplace (header, frozenExpression)
where
srcInfo = fromMaybe "(stdin)" inplace

View File

@ -90,7 +90,7 @@ data Mode
| Normalize
| Repl
| Format { inplace :: Maybe FilePath }
| Freeze { inplace :: Maybe FilePath }
| Freeze { inplace :: Maybe FilePath, all_ :: Bool }
| Hash
| Diff { expr1 :: Text, expr2 :: Text }
| Lint { inplace :: Maybe FilePath }
@ -172,8 +172,8 @@ parseMode =
(Format <$> optional parseInplace)
<|> subcommand
"freeze"
"Add hashes to all import statements of an expression"
(Freeze <$> optional parseInplace)
"Add integrity checks to remote import statements of an expression"
(Freeze <$> optional parseInplace <*> parseAllFlag)
<|> subcommand
"encode"
"Encode a Dhall expression to binary"
@ -226,6 +226,12 @@ parseMode =
<> Options.Applicative.help "Use JSON representation of CBOR"
)
parseAllFlag =
Options.Applicative.switch
( Options.Applicative.long "all"
<> Options.Applicative.help "Add integrity checks to all imports (not just remote imports)"
)
throws :: Exception e => Either e a -> IO a
throws (Left e) = Control.Exception.throwIO e
throws (Right a) = return a
@ -403,7 +409,7 @@ command (Options {..}) = do
Dhall.Format.format characterSet inplace
Freeze {..} -> do
Dhall.Freeze.freeze inplace standardVersion
Dhall.Freeze.freeze inplace all_ standardVersion
Hash -> do
Dhall.Hash.hash standardVersion