Add freeze command (#486)

Implement the freeze command (#437)

Takes input from stdin or file and updates all imports with hashes
This commit is contained in:
Tobias Pflug 2018-06-26 19:30:54 +02:00 committed by GitHub
parent da8b540883
commit dba035e220
No known key found for this signature in database
GPG Key ID: 4AEE18F83AFDEB23
4 changed files with 107 additions and 1 deletions

View File

@ -209,6 +209,7 @@ Library
Dhall.Core,
Dhall.Diff,
Dhall.Format,
Dhall.Freeze,
Dhall.Hash,
Dhall.Import,
Dhall.Lint,

76
src/Dhall/Freeze.hs Normal file
View File

@ -0,0 +1,76 @@
{-# LANGUAGE OverloadedStrings #-}
module Dhall.Freeze (
freeze
, hashImport
) where
import Dhall.Core
import Dhall.Import (load, hashExpression)
import Dhall.Parser (exprAndHeaderFromText, Src)
import Dhall.Pretty (annToAnsiStyle)
import System.Console.ANSI (hSupportsANSI)
import Data.Monoid ((<>))
import Data.Maybe (fromMaybe)
import Data.Text
import qualified Data.Text.Prettyprint.Doc as Pretty
import qualified Data.Text.Prettyprint.Doc.Render.Terminal as Pretty
import qualified Control.Exception
import qualified Data.Text.IO
import qualified System.IO
opts :: Pretty.LayoutOptions
opts =
Pretty.defaultLayoutOptions
{ Pretty.layoutPageWidth = Pretty.AvailablePerLine 80 1.0 }
readInput :: Maybe FilePath -> IO Text
readInput = maybe fromStdin Data.Text.IO.readFile
where
fromStdin = System.IO.hSetEncoding System.IO.stdin System.IO.utf8 >> Data.Text.IO.getContents
hashImport :: Import -> IO Import
hashImport import_ = do
expression <- Dhall.Import.load (Embed import_)
let expressionHash = Just (Dhall.Import.hashExpression expression)
let newImportHashed = (importHashed import_) { hash = expressionHash }
return $ import_ { importHashed = newImportHashed }
parseExpr :: String -> Text -> IO (Text, Expr Src Import)
parseExpr src txt =
case exprAndHeaderFromText src txt of
Left err -> Control.Exception.throwIO err
Right x -> return x
freezeExpr :: (Text, Expr s Import) -> IO (Text, Expr s Import)
freezeExpr (t, e) = do
e' <- traverse hashImport e
return (t, e')
writeExpr :: Maybe FilePath -> (Text, Expr s Import) -> IO ()
writeExpr inplace (header, expr) = do
let doc = Pretty.pretty header <> Pretty.pretty expr
let layoutOptions = opts
let stream = Pretty.layoutSmart layoutOptions doc
case inplace of
Just f ->
System.IO.withFile f System.IO.WriteMode (\h ->
Pretty.renderIO h (annToAnsiStyle <$> stream))
Nothing -> do
supportsANSI <- System.Console.ANSI.hSupportsANSI System.IO.stdout
if supportsANSI
then
Pretty.renderIO System.IO.stdout (annToAnsiStyle <$> Pretty.layoutSmart opts doc)
else
Pretty.renderIO System.IO.stdout (Pretty.layoutSmart opts (Pretty.unAnnotate doc))
freeze :: Maybe FilePath -> IO ()
freeze inplace = do
expr <- readInput inplace
parseExpr srcInfo expr >>= freezeExpr >>= writeExpr inplace
where
srcInfo = fromMaybe "(stdin)" inplace

View File

@ -36,6 +36,7 @@ import qualified Dhall
import qualified Dhall.Core
import qualified Dhall.Diff
import qualified Dhall.Format
import qualified Dhall.Freeze
import qualified Dhall.Hash
import qualified Dhall.Lint
import qualified Dhall.Parser
@ -59,6 +60,7 @@ data Mode
| Normalize
| Repl
| Format (Maybe FilePath)
| Freeze (Maybe FilePath)
| Hash
| Diff Text Text
| Lint (Maybe FilePath)
@ -98,6 +100,7 @@ parseMode =
<|> subcommand "hash" "Compute semantic hashes for Dhall expressions" (pure Hash)
<|> subcommand "lint" "Improve Dhall code" parseLint
<|> formatSubcommand
<|> freezeSubcommand
<|> pure Default
where
subcommand name description modeParser =
@ -139,6 +142,10 @@ parseMode =
parserWithHelper = Options.Applicative.helper <*> parser
parser = Format <$> optional parseInplace
freezeSubcommand = subcommand "freeze" "Add hashes to all import statements of an expression" parseFreeze
where
parseFreeze = Freeze <$> optional parseInplace
opts :: Pretty.LayoutOptions
opts =
Pretty.defaultLayoutOptions
@ -279,6 +286,9 @@ command (Options {..}) = do
Format inplace -> do
Dhall.Format.format inplace
Freeze inplace -> do
Dhall.Freeze.freeze inplace
Hash -> do
Dhall.Hash.hash

View File

@ -1551,7 +1551,26 @@ import Dhall
-- behavior-preserving. This provides an easy way to detect refactoring errors
-- that you might accidentally introduce. The hash not only protects you
-- from attackers, but also protects against human error, too!
--
-- If you have a file which either doesn't already use hashed imports,
-- or you changed some of the imports and want to update the hashes you can use the
-- freeze command to either add or update hashes:
--
-- > cat foo.dhall
-- ''
-- let replicate =
-- https://raw.githubusercontent.com/dhall-lang/Prelude/c79c2bc3c46f129cc5b6d594ce298a381bcae92c/List/replicate
--
-- in replicate 5
-- ''
-- > dhall freeze --inplace ./foo.dhall
-- > cat ./foo.dhall
-- ''
-- let replicate =
-- https://raw.githubusercontent.com/dhall-lang/Prelude/c79c2bc3c46f129cc5b6d594ce298a381bcae92c/List/replicate sha256:b0e3ec1797b32c80c0bcb7e8254b08c7e9e35e75e6b410c7ac21477ab90167ad
-- in replicate 5
-- ''
--
-- $rawText
--
-- Sometimes you want to import the contents of a raw text file as a Dhall