dhall-haskell/dhall/src/Dhall/Main.hs

775 lines
27 KiB
Haskell
Raw Normal View History

{-| This module contains the top-level entrypoint and options parsing for the
@dhall@ executable
-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
module Dhall.Main
( -- * Options
Options(..)
, Mode(..)
, parseOptions
, parserInfoOptions
-- * Execution
, command
, main
) where
import Control.Applicative (optional, (<|>))
import Control.Exception (Handler(..), SomeException)
import Control.Monad (when)
dhall-lsp-server: Fix cache to correctly invalidate transitive dependencies (#1069) * Move "Dot" import graph generation to Dhall.Main Previously `Dhall.Import` would generate the import graph in "dot" format while resolving imports. This change simplifies `Dhall.Import` to only keep track of the adjacency list representing the import graph, moving the logic for generating "dot" files to Dhall.Main. This change will allow us to implement proper cache invalidation for `dhall-lsp-server`. * Correctly invalidate transitive dependencies Fixes dhall-lsp-server`s caching behaviour to correctly invalidate cached imports that (possibly indirectly) depend on the changed file. Example: Suppose we have the following three files: {- In A.dhall -} 2 : ./B.dhall {- In B.dhall -} ./C.dhall {- In C.dhall -} Natural Previously, changing C.dhall to `Text` would not cause `A.dhall` to stop type-checking, since the old version of `B.dhall` (which evaluated to `Natural`) would still have been in the cache. This change fixes that behaviour. * Make edges of import graph self-documenting As suggested by @Gabriel439 * Don't cache expressions manually After computing the diagnostics for a given file we added its normal form to the cache, but forgot to add its dependencies to the dependency graph. This bug points out that keeping the import graph consistent manually is probably not a good idea. With this commit we never mess with the import cache manually; this means that files are only cached once they are depended upon by some other file, potentially causing us to duplicate work (but no more than once). * Fix left-overs from previous commit
2019-07-08 12:55:15 +02:00
import Data.List.NonEmpty (NonEmpty(..))
import Data.Monoid ((<>))
import Data.Text (Text)
import Data.Text.Prettyprint.Doc (Doc, Pretty)
import Data.Void (Void)
import Dhall.Core (Expr(Annot), Import, pretty)
import Dhall.Freeze (Intent(..), Scope(..))
import Dhall.Import (Imported(..), Depends(..), SemanticCacheMode(..), _semanticCacheMode)
import Dhall.Parser (Src)
import Dhall.Pretty (Ann, CharacterSet(..), annToAnsiStyle)
import Dhall.TypeCheck (Censored(..), DetailedTypeError(..), TypeError)
import Dhall.Util (Censor(..), Header (..), Input(..), Output(..))
import Dhall.Version (dhallVersionString)
import Options.Applicative (Parser, ParserInfo)
import System.Exit (ExitCode, exitFailure)
import System.IO (Handle)
dhall-lsp-server: Fix cache to correctly invalidate transitive dependencies (#1069) * Move "Dot" import graph generation to Dhall.Main Previously `Dhall.Import` would generate the import graph in "dot" format while resolving imports. This change simplifies `Dhall.Import` to only keep track of the adjacency list representing the import graph, moving the logic for generating "dot" files to Dhall.Main. This change will allow us to implement proper cache invalidation for `dhall-lsp-server`. * Correctly invalidate transitive dependencies Fixes dhall-lsp-server`s caching behaviour to correctly invalidate cached imports that (possibly indirectly) depend on the changed file. Example: Suppose we have the following three files: {- In A.dhall -} 2 : ./B.dhall {- In B.dhall -} ./C.dhall {- In C.dhall -} Natural Previously, changing C.dhall to `Text` would not cause `A.dhall` to stop type-checking, since the old version of `B.dhall` (which evaluated to `Natural`) would still have been in the cache. This change fixes that behaviour. * Make edges of import graph self-documenting As suggested by @Gabriel439 * Don't cache expressions manually After computing the diagnostics for a given file we added its normal form to the cache, but forgot to add its dependencies to the dependency graph. This bug points out that keeping the import graph consistent manually is probably not a good idea. With this commit we never mess with the import cache manually; this means that files are only cached once they are depended upon by some other file, potentially causing us to duplicate work (but no more than once). * Fix left-overs from previous commit
2019-07-08 12:55:15 +02:00
import Text.Dot ((.->.))
import qualified Codec.CBOR.JSON
import qualified Codec.CBOR.Read
import qualified Codec.CBOR.Write
import qualified Control.Exception
import qualified Control.Monad.Trans.State.Strict as State
import qualified Data.Aeson
import qualified Data.Aeson.Encode.Pretty
import qualified Data.ByteString.Lazy
import qualified Data.ByteString.Lazy.Char8
import qualified Data.Map
import qualified Data.Text
import qualified Data.Text.IO
import qualified Data.Text.Prettyprint.Doc as Pretty
import qualified Data.Text.Prettyprint.Doc.Render.Terminal as Pretty
import qualified Dhall
import qualified Dhall.Binary
import qualified Dhall.Core
import qualified Dhall.Diff
import qualified Dhall.Format
import qualified Dhall.Freeze
import qualified Dhall.Import
import qualified Dhall.Import.Types
import qualified Dhall.Lint
List dependencies in "post-order" (#1539) * List dependencies in "post-order" Related to https://github.com/dhall-lang/dhall-lang/issues/823 This lists dependencies starting from the leaves and concluding with the root import, same as how `nix-store --query --requisites` does Example output: ```bash $ dhall resolve --no-cache --transitive-dependencies <<< 'https://prelude.dhall-lang.org/package.dhall' https://prelude.dhall-lang.org/Bool/and https://prelude.dhall-lang.org/Bool/build https://prelude.dhall-lang.org/Bool/even https://prelude.dhall-lang.org/Bool/fold https://prelude.dhall-lang.org/Bool/not https://prelude.dhall-lang.org/Bool/odd https://prelude.dhall-lang.org/Bool/or https://prelude.dhall-lang.org/Bool/show https://prelude.dhall-lang.org/Bool/package.dhall https://prelude.dhall-lang.org/Double/show https://prelude.dhall-lang.org/Double/package.dhall https://prelude.dhall-lang.org/Function/compose https://prelude.dhall-lang.org/Function/package.dhall https://prelude.dhall-lang.org/Integer/show https://prelude.dhall-lang.org/Integer/toDouble https://prelude.dhall-lang.org/Integer/package.dhall https://prelude.dhall-lang.org/List/all https://prelude.dhall-lang.org/List/any https://prelude.dhall-lang.org/List/build https://prelude.dhall-lang.org/List/concat https://prelude.dhall-lang.org/List/concatMap https://prelude.dhall-lang.org/List/default https://prelude.dhall-lang.org/List/empty https://prelude.dhall-lang.org/List/filter https://prelude.dhall-lang.org/List/fold https://prelude.dhall-lang.org/List/generate https://prelude.dhall-lang.org/List/head https://prelude.dhall-lang.org/List/indexed https://prelude.dhall-lang.org/List/iterate https://prelude.dhall-lang.org/List/last https://prelude.dhall-lang.org/List/length https://prelude.dhall-lang.org/List/map https://prelude.dhall-lang.org/List/null https://prelude.dhall-lang.org/List/partition https://prelude.dhall-lang.org/List/replicate https://prelude.dhall-lang.org/List/reverse https://prelude.dhall-lang.org/List/shifted https://prelude.dhall-lang.org/List/unzip https://prelude.dhall-lang.org/List/package.dhall https://prelude.dhall-lang.org/Location/Type https://prelude.dhall-lang.org/Location/package.dhall https://prelude.dhall-lang.org/Map/Type https://prelude.dhall-lang.org/Map/Entry https://prelude.dhall-lang.org/Map/empty https://prelude.dhall-lang.org/Map/keyText https://prelude.dhall-lang.org/Map/keyValue https://prelude.dhall-lang.org/Map/keys https://prelude.dhall-lang.org/Map/map https://prelude.dhall-lang.org/Map/values https://prelude.dhall-lang.org/Map/package.dhall https://prelude.dhall-lang.org/Monoid https://prelude.dhall-lang.org/Natural/build https://prelude.dhall-lang.org/Natural/enumerate https://prelude.dhall-lang.org/Natural/even https://prelude.dhall-lang.org/Natural/fold https://prelude.dhall-lang.org/Natural/isZero https://prelude.dhall-lang.org/Natural/odd https://prelude.dhall-lang.org/Natural/product https://prelude.dhall-lang.org/Natural/sum https://prelude.dhall-lang.org/Natural/show https://prelude.dhall-lang.org/Natural/toDouble https://prelude.dhall-lang.org/Natural/toInteger https://prelude.dhall-lang.org/Natural/lessThanEqual https://prelude.dhall-lang.org/Natural/greaterThanEqual https://prelude.dhall-lang.org/Natural/lessThan https://prelude.dhall-lang.org/Natural/equal https://prelude.dhall-lang.org/Natural/greaterThan https://prelude.dhall-lang.org/Natural/min https://prelude.dhall-lang.org/Natural/max https://prelude.dhall-lang.org/Optional/map https://prelude.dhall-lang.org/Natural/listMin https://prelude.dhall-lang.org/Natural/listMax https://prelude.dhall-lang.org/Natural/sort https://prelude.dhall-lang.org/Natural/subtract https://prelude.dhall-lang.org/Natural/package.dhall https://prelude.dhall-lang.org/Optional/all https://prelude.dhall-lang.org/Optional/any https://prelude.dhall-lang.org/Optional/build https://prelude.dhall-lang.org/Optional/concat https://prelude.dhall-lang.org/Optional/default https://prelude.dhall-lang.org/Optional/filter https://prelude.dhall-lang.org/Optional/fold https://prelude.dhall-lang.org/Optional/head https://prelude.dhall-lang.org/Optional/last https://prelude.dhall-lang.org/Optional/length https://prelude.dhall-lang.org/Optional/null https://prelude.dhall-lang.org/Optional/toList https://prelude.dhall-lang.org/Optional/unzip https://prelude.dhall-lang.org/Optional/package.dhall https://prelude.dhall-lang.org/JSON/Type https://prelude.dhall-lang.org/JSON/Nesting https://prelude.dhall-lang.org/JSON/Tagged https://prelude.dhall-lang.org/JSON/keyText https://prelude.dhall-lang.org/JSON/keyValue https://prelude.dhall-lang.org/JSON/string https://prelude.dhall-lang.org/JSON/number https://prelude.dhall-lang.org/JSON/object https://prelude.dhall-lang.org/JSON/array https://prelude.dhall-lang.org/JSON/bool https://prelude.dhall-lang.org/JSON/null https://prelude.dhall-lang.org/Text/concatMapSep https://prelude.dhall-lang.org/JSON/render https://prelude.dhall-lang.org/JSON/package.dhall https://prelude.dhall-lang.org/Text/concat https://prelude.dhall-lang.org/Text/concatMap https://prelude.dhall-lang.org/Text/concatSep https://prelude.dhall-lang.org/Text/default https://prelude.dhall-lang.org/Text/defaultMap https://prelude.dhall-lang.org/Text/show https://prelude.dhall-lang.org/Text/package.dhall https://prelude.dhall-lang.org/XML/Type https://prelude.dhall-lang.org/XML/attribute https://prelude.dhall-lang.org/XML/render https://prelude.dhall-lang.org/XML/element https://prelude.dhall-lang.org/XML/leaf https://prelude.dhall-lang.org/XML/text https://prelude.dhall-lang.org/XML/emptyAttributes https://prelude.dhall-lang.org/XML/package.dhall https://prelude.dhall-lang.org/package.dhall ``` * Document order in `dhall resolve --help` output ... as suggested by @sjakobi * Fix dhall-lsp-server build
2019-11-21 17:20:48 +01:00
import qualified Dhall.Map
import qualified Dhall.Tags
import qualified Dhall.Pretty
import qualified Dhall.Repl
import qualified Dhall.TypeCheck
import qualified Dhall.Util
import qualified GHC.IO.Encoding
import qualified Options.Applicative
import qualified System.Console.ANSI
import qualified System.Exit as Exit
import qualified System.IO
import qualified System.FilePath
import qualified Text.Dot
import qualified Text.Pretty.Simple
-- | Top-level program options
data Options = Options
{ mode :: Mode
, explain :: Bool
, plain :: Bool
, ascii :: Bool
, censor :: Censor
}
ignoreSemanticCache :: Mode -> Bool
ignoreSemanticCache Default {..} = semanticCacheMode == IgnoreSemanticCache
ignoreSemanticCache Resolve {..} = semanticCacheMode == IgnoreSemanticCache
ignoreSemanticCache Type {..} = semanticCacheMode == IgnoreSemanticCache
ignoreSemanticCache _ = False
-- | The subcommands for the @dhall@ executable
data Mode
= Default
{ file :: Input
2019-10-07 11:51:30 +02:00
, output :: Output
, annotate :: Bool
, alpha :: Bool
, semanticCacheMode :: SemanticCacheMode
, version :: Bool
}
| Version
| Resolve
{ file :: Input
, resolveMode :: Maybe ResolveMode
, semanticCacheMode :: SemanticCacheMode
}
| Type
{ file :: Input
, quiet :: Bool
, semanticCacheMode :: SemanticCacheMode
}
| Normalize { file :: Input , alpha :: Bool }
| Repl
| Format { formatMode :: Dhall.Format.FormatMode }
| Freeze { inplace :: Input, all_ :: Bool, cache :: Bool }
| Hash { file :: Input }
| Diff { expr1 :: Text, expr2 :: Text }
| Lint { inplace :: Input }
| Tags
{ input :: Input
, output :: Output
, suffixes :: Maybe [Text]
, followSymlinks :: Bool
}
| Encode { file :: Input, json :: Bool }
| Decode { file :: Input, json :: Bool }
| Text { file :: Input }
| SyntaxTree { file :: Input }
data ResolveMode
= Dot
| ListTransitiveDependencies
| ListImmediateDependencies
-- | `Parser` for the `Options` type
parseOptions :: Parser Options
parseOptions =
Options
<$> parseMode
<*> switch "explain" "Explain error messages in more detail"
<*> switch "plain" "Disable syntax highlighting"
<*> switch "ascii" "Format code using only ASCII syntax"
<*> parseCensor
where
switch name description =
Options.Applicative.switch
( Options.Applicative.long name
<> Options.Applicative.help description
)
parseCensor = fmap f (switch "censor" "Hide source code in error messages")
where
f True = Censor
f False = NoCensor
subcommand' :: Bool -> String -> String -> Parser a -> Parser a
subcommand' internal name description parser =
Options.Applicative.hsubparser
( Options.Applicative.command name parserInfo
<> Options.Applicative.metavar name
<> if internal then Options.Applicative.internal else mempty
)
where
parserInfo =
Options.Applicative.info parser
( Options.Applicative.fullDesc
<> Options.Applicative.progDesc description
)
subcommand :: String -> String -> Parser a -> Parser a
subcommand = subcommand' False
internalSubcommand :: String -> String -> Parser a -> Parser a
internalSubcommand = subcommand' True
parseMode :: Parser Mode
parseMode =
subcommand
"version"
"Display version"
(pure Version)
<|> subcommand
"resolve"
"Resolve an expression's imports"
(Resolve <$> parseFile <*> parseResolveMode <*> parseSemanticCacheMode)
<|> subcommand
"type"
"Infer an expression's type"
(Type <$> parseFile <*> parseQuiet <*> parseSemanticCacheMode)
<|> subcommand
"normalize"
"Normalize an expression"
(Normalize <$> parseFile <*> parseAlpha)
<|> subcommand
"repl"
"Interpret expressions in a REPL"
(pure Repl)
<|> subcommand
"diff"
"Render the difference between the normal form of two expressions"
(Diff <$> argument "expr1" <*> argument "expr2")
<|> subcommand
"hash"
"Compute semantic hashes for Dhall expressions"
(Hash <$> parseFile)
<|> subcommand
"lint"
"Improve Dhall code by using newer language features and removing dead code"
(Lint <$> parseInplace)
<|> subcommand
"tags"
"Generate etags file"
(Tags <$> parseInput <*> parseTagsOutput <*> parseSuffixes <*> parseFollowSymlinks)
<|> subcommand
"format"
"Standard code formatter for the Dhall language"
(Format <$> parseFormatMode)
<|> subcommand
"freeze"
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.
2019-02-01 16:46:03 +01:00
"Add integrity checks to remote import statements of an expression"
(Freeze <$> parseInplace <*> parseAllFlag <*> parseCacheFlag)
<|> subcommand
"encode"
"Encode a Dhall expression to binary"
(Encode <$> parseFile <*> parseJSONFlag)
<|> subcommand
"decode"
"Decode a Dhall expression from binary"
(Decode <$> parseFile <*> parseJSONFlag)
<|> subcommand
"text"
"Render a Dhall expression that evaluates to a Text literal"
(Text <$> parseFile)
<|> internalSubcommand
"haskell-syntax-tree"
"Output the parsed syntax tree (for debugging)"
(SyntaxTree <$> parseFile)
<|> ( Default
<$> parseFile
2019-10-07 11:51:30 +02:00
<*> parseOutput
<*> parseAnnotate
<*> parseAlpha
<*> parseSemanticCacheMode
<*> parseVersion
)
where
argument =
fmap Data.Text.pack
. Options.Applicative.strArgument
. Options.Applicative.metavar
parseFile = fmap f (optional p)
where
f Nothing = StandardInput
f (Just file) = InputFile file
p = Options.Applicative.strOption
( Options.Applicative.long "file"
<> Options.Applicative.help "Read expression from a file instead of standard input"
<> Options.Applicative.metavar "FILE"
)
2019-10-07 11:51:30 +02:00
parseOutput = fmap f (optional p)
where
f Nothing = StandardOutput
f (Just file) = OutputFile file
p = Options.Applicative.strOption
( Options.Applicative.long "output"
<> Options.Applicative.help "Write result to a file instead of standard output"
<> Options.Applicative.metavar "FILE"
)
parseAlpha =
Options.Applicative.switch
( Options.Applicative.long "alpha"
<> Options.Applicative.help "α-normalize expression"
)
parseAnnotate =
Options.Applicative.switch
( Options.Applicative.long "annotate"
<> Options.Applicative.help "Add a type annotation to the output"
)
parseSemanticCacheMode =
Options.Applicative.flag
UseSemanticCache
IgnoreSemanticCache
( Options.Applicative.long "no-cache"
<> Options.Applicative.help
"Handle protected imports as if the cache was empty"
)
parseVersion =
Options.Applicative.switch
( Options.Applicative.long "version"
<> Options.Applicative.help "Display version"
)
parseResolveMode =
Options.Applicative.flag' (Just Dot)
( Options.Applicative.long "dot"
<> Options.Applicative.help
"Output import dependency graph in dot format"
)
<|>
Options.Applicative.flag' (Just ListImmediateDependencies)
( Options.Applicative.long "immediate-dependencies"
<> Options.Applicative.help
"List immediate import dependencies"
)
<|>
Options.Applicative.flag' (Just ListTransitiveDependencies)
( Options.Applicative.long "transitive-dependencies"
<> Options.Applicative.help
List dependencies in "post-order" (#1539) * List dependencies in "post-order" Related to https://github.com/dhall-lang/dhall-lang/issues/823 This lists dependencies starting from the leaves and concluding with the root import, same as how `nix-store --query --requisites` does Example output: ```bash $ dhall resolve --no-cache --transitive-dependencies <<< 'https://prelude.dhall-lang.org/package.dhall' https://prelude.dhall-lang.org/Bool/and https://prelude.dhall-lang.org/Bool/build https://prelude.dhall-lang.org/Bool/even https://prelude.dhall-lang.org/Bool/fold https://prelude.dhall-lang.org/Bool/not https://prelude.dhall-lang.org/Bool/odd https://prelude.dhall-lang.org/Bool/or https://prelude.dhall-lang.org/Bool/show https://prelude.dhall-lang.org/Bool/package.dhall https://prelude.dhall-lang.org/Double/show https://prelude.dhall-lang.org/Double/package.dhall https://prelude.dhall-lang.org/Function/compose https://prelude.dhall-lang.org/Function/package.dhall https://prelude.dhall-lang.org/Integer/show https://prelude.dhall-lang.org/Integer/toDouble https://prelude.dhall-lang.org/Integer/package.dhall https://prelude.dhall-lang.org/List/all https://prelude.dhall-lang.org/List/any https://prelude.dhall-lang.org/List/build https://prelude.dhall-lang.org/List/concat https://prelude.dhall-lang.org/List/concatMap https://prelude.dhall-lang.org/List/default https://prelude.dhall-lang.org/List/empty https://prelude.dhall-lang.org/List/filter https://prelude.dhall-lang.org/List/fold https://prelude.dhall-lang.org/List/generate https://prelude.dhall-lang.org/List/head https://prelude.dhall-lang.org/List/indexed https://prelude.dhall-lang.org/List/iterate https://prelude.dhall-lang.org/List/last https://prelude.dhall-lang.org/List/length https://prelude.dhall-lang.org/List/map https://prelude.dhall-lang.org/List/null https://prelude.dhall-lang.org/List/partition https://prelude.dhall-lang.org/List/replicate https://prelude.dhall-lang.org/List/reverse https://prelude.dhall-lang.org/List/shifted https://prelude.dhall-lang.org/List/unzip https://prelude.dhall-lang.org/List/package.dhall https://prelude.dhall-lang.org/Location/Type https://prelude.dhall-lang.org/Location/package.dhall https://prelude.dhall-lang.org/Map/Type https://prelude.dhall-lang.org/Map/Entry https://prelude.dhall-lang.org/Map/empty https://prelude.dhall-lang.org/Map/keyText https://prelude.dhall-lang.org/Map/keyValue https://prelude.dhall-lang.org/Map/keys https://prelude.dhall-lang.org/Map/map https://prelude.dhall-lang.org/Map/values https://prelude.dhall-lang.org/Map/package.dhall https://prelude.dhall-lang.org/Monoid https://prelude.dhall-lang.org/Natural/build https://prelude.dhall-lang.org/Natural/enumerate https://prelude.dhall-lang.org/Natural/even https://prelude.dhall-lang.org/Natural/fold https://prelude.dhall-lang.org/Natural/isZero https://prelude.dhall-lang.org/Natural/odd https://prelude.dhall-lang.org/Natural/product https://prelude.dhall-lang.org/Natural/sum https://prelude.dhall-lang.org/Natural/show https://prelude.dhall-lang.org/Natural/toDouble https://prelude.dhall-lang.org/Natural/toInteger https://prelude.dhall-lang.org/Natural/lessThanEqual https://prelude.dhall-lang.org/Natural/greaterThanEqual https://prelude.dhall-lang.org/Natural/lessThan https://prelude.dhall-lang.org/Natural/equal https://prelude.dhall-lang.org/Natural/greaterThan https://prelude.dhall-lang.org/Natural/min https://prelude.dhall-lang.org/Natural/max https://prelude.dhall-lang.org/Optional/map https://prelude.dhall-lang.org/Natural/listMin https://prelude.dhall-lang.org/Natural/listMax https://prelude.dhall-lang.org/Natural/sort https://prelude.dhall-lang.org/Natural/subtract https://prelude.dhall-lang.org/Natural/package.dhall https://prelude.dhall-lang.org/Optional/all https://prelude.dhall-lang.org/Optional/any https://prelude.dhall-lang.org/Optional/build https://prelude.dhall-lang.org/Optional/concat https://prelude.dhall-lang.org/Optional/default https://prelude.dhall-lang.org/Optional/filter https://prelude.dhall-lang.org/Optional/fold https://prelude.dhall-lang.org/Optional/head https://prelude.dhall-lang.org/Optional/last https://prelude.dhall-lang.org/Optional/length https://prelude.dhall-lang.org/Optional/null https://prelude.dhall-lang.org/Optional/toList https://prelude.dhall-lang.org/Optional/unzip https://prelude.dhall-lang.org/Optional/package.dhall https://prelude.dhall-lang.org/JSON/Type https://prelude.dhall-lang.org/JSON/Nesting https://prelude.dhall-lang.org/JSON/Tagged https://prelude.dhall-lang.org/JSON/keyText https://prelude.dhall-lang.org/JSON/keyValue https://prelude.dhall-lang.org/JSON/string https://prelude.dhall-lang.org/JSON/number https://prelude.dhall-lang.org/JSON/object https://prelude.dhall-lang.org/JSON/array https://prelude.dhall-lang.org/JSON/bool https://prelude.dhall-lang.org/JSON/null https://prelude.dhall-lang.org/Text/concatMapSep https://prelude.dhall-lang.org/JSON/render https://prelude.dhall-lang.org/JSON/package.dhall https://prelude.dhall-lang.org/Text/concat https://prelude.dhall-lang.org/Text/concatMap https://prelude.dhall-lang.org/Text/concatSep https://prelude.dhall-lang.org/Text/default https://prelude.dhall-lang.org/Text/defaultMap https://prelude.dhall-lang.org/Text/show https://prelude.dhall-lang.org/Text/package.dhall https://prelude.dhall-lang.org/XML/Type https://prelude.dhall-lang.org/XML/attribute https://prelude.dhall-lang.org/XML/render https://prelude.dhall-lang.org/XML/element https://prelude.dhall-lang.org/XML/leaf https://prelude.dhall-lang.org/XML/text https://prelude.dhall-lang.org/XML/emptyAttributes https://prelude.dhall-lang.org/XML/package.dhall https://prelude.dhall-lang.org/package.dhall ``` * Document order in `dhall resolve --help` output ... as suggested by @sjakobi * Fix dhall-lsp-server build
2019-11-21 17:20:48 +01:00
"List transitive import dependencies in post-order"
)
<|> pure Nothing
parseQuiet =
Options.Applicative.switch
( Options.Applicative.long "quiet"
<> Options.Applicative.help "Don't print the inferred type"
)
parseInplace = fmap f (optional p)
where
f Nothing = StandardInput
f (Just file) = InputFile file
p = Options.Applicative.strOption
( Options.Applicative.long "inplace"
<> Options.Applicative.help "Modify the specified file in-place"
<> Options.Applicative.metavar "FILE"
)
parseInput = fmap f (optional p)
where
f Nothing = StandardInput
f (Just path) = InputFile path
p = Options.Applicative.strOption
( Options.Applicative.long "path"
<> Options.Applicative.help "Index all files in path recursively. Will get list of files from STDIN if omitted."
<> Options.Applicative.metavar "PATH"
)
parseTagsOutput = fmap f (optional p)
where
f Nothing = OutputFile "tags"
f (Just file) = OutputFile file
p = Options.Applicative.strOption
( Options.Applicative.long "output"
<> Options.Applicative.help "The name of the file that the tags are written to. Defaults to \"tags\""
<> Options.Applicative.metavar "FILENAME"
)
parseSuffixes = fmap f (optional p)
where
f Nothing = Just [".dhall"]
f (Just "") = Nothing
f (Just line) = Just (Data.Text.splitOn " " line)
p = Options.Applicative.strOption
( Options.Applicative.long "suffixes"
<> Options.Applicative.help "Index only files with suffixes. \"\" to index all files."
<> Options.Applicative.metavar "SUFFIXES"
)
parseFollowSymlinks =
Options.Applicative.switch
( Options.Applicative.long "follow-symlinks"
<> Options.Applicative.help "Follow symlinks when recursing directories"
)
parseJSONFlag =
Options.Applicative.switch
( Options.Applicative.long "json"
<> Options.Applicative.help "Use JSON representation of CBOR"
)
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.
2019-02-01 16:46:03 +01:00
parseAllFlag =
Options.Applicative.switch
( Options.Applicative.long "all"
<> Options.Applicative.help "Add integrity checks to all imports (not just remote imports)"
)
parseCacheFlag =
Options.Applicative.switch
( Options.Applicative.long "cache"
<> Options.Applicative.help "Add fallback unprotected imports when using integrity checks purely for caching purposes"
)
parseCheck =
Options.Applicative.switch
( Options.Applicative.long "check"
<> Options.Applicative.help "Only check if the input is formatted"
)
parseFormatMode = adapt <$> parseCheck <*> parseInplace
where
adapt True path = Dhall.Format.Check {..}
adapt False inplace = Dhall.Format.Modify {..}
-- | `ParserInfo` for the `Options` type
parserInfoOptions :: ParserInfo Options
parserInfoOptions =
Options.Applicative.info
(Options.Applicative.helper <*> parseOptions)
( Options.Applicative.progDesc "Interpreter for the Dhall language"
<> Options.Applicative.fullDesc
)
-- | Run the command specified by the `Options` type
command :: Options -> IO ()
command (Options {..}) = do
let characterSet = case ascii of
True -> ASCII
False -> Unicode
GHC.IO.Encoding.setLocaleEncoding System.IO.utf8
let rootDirectory = \case
InputFile f -> System.FilePath.takeDirectory f
StandardInput -> "."
let toStatus = Dhall.Import.emptyStatus . rootDirectory
let getExpression = Dhall.Util.getExpression censor
let getExpressionAndHeader = Dhall.Util.getExpressionAndHeader censor
let handle io =
Control.Exception.catches io
[ Handler handleTypeError
, Handler handleImported
, Handler handleExitCode
]
where
handleAll e = do
let string = show (e :: SomeException)
if not (null string)
then System.IO.hPutStrLn System.IO.stderr string
else return ()
System.Exit.exitFailure
handleTypeError e = Control.Exception.handle handleAll $ do
let _ = e :: TypeError Src Void
System.IO.hPutStrLn System.IO.stderr ""
if explain
then
case censor of
Censor -> Control.Exception.throwIO (CensoredDetailed (DetailedTypeError e))
NoCensor -> Control.Exception.throwIO (DetailedTypeError e)
else do
Data.Text.IO.hPutStrLn System.IO.stderr "\ESC[2mUse \"dhall --explain\" for detailed errors\ESC[0m"
case censor of
Censor -> Control.Exception.throwIO (Censored e)
NoCensor -> Control.Exception.throwIO e
handleImported (Imported ps e) = Control.Exception.handle handleAll $ do
let _ = e :: TypeError Src Void
System.IO.hPutStrLn System.IO.stderr ""
if explain
then Control.Exception.throwIO (Imported ps (DetailedTypeError e))
else do
Data.Text.IO.hPutStrLn System.IO.stderr "\ESC[2mUse \"dhall --explain\" for detailed errors\ESC[0m"
Control.Exception.throwIO (Imported ps e)
handleExitCode e = do
Control.Exception.throwIO (e :: ExitCode)
let renderDoc :: Handle -> Doc Ann -> IO ()
renderDoc h doc = do
let stream = Dhall.Pretty.layout doc
supportsANSI <- System.Console.ANSI.hSupportsANSI h
let ansiStream =
if supportsANSI && not plain
then fmap annToAnsiStyle stream
else Pretty.unAnnotateS stream
Pretty.renderIO h ansiStream
Data.Text.IO.hPutStrLn h ""
let render :: Pretty a => Handle -> Expr Src a -> IO ()
render h expression = do
let doc = Dhall.Pretty.prettyCharacterSet characterSet expression
renderDoc h doc
2019-10-07 11:51:30 +02:00
when (not $ ignoreSemanticCache mode) Dhall.Import.warnAboutMissingCaches
handle $ case mode of
Version -> do
putStrLn dhallVersionString
Default {..} -> do
if version
then do
putStrLn dhallVersionString
Exit.exitSuccess
else return ()
expression <- getExpression file
resolvedExpression <-
Dhall.Import.loadRelativeTo (rootDirectory file) semanticCacheMode expression
inferredType <- Dhall.Core.throws (Dhall.TypeCheck.typeOf resolvedExpression)
let normalizedExpression = Dhall.Core.normalize resolvedExpression
let alphaNormalizedExpression =
if alpha
then Dhall.Core.alphaNormalize normalizedExpression
else normalizedExpression
let annotatedExpression =
if annotate
then Annot alphaNormalizedExpression inferredType
else alphaNormalizedExpression
2019-10-07 11:51:30 +02:00
case output of
StandardOutput -> render System.IO.stdout annotatedExpression
OutputFile file_ ->
System.IO.withFile file_ System.IO.WriteMode $ \h -> render h annotatedExpression
Resolve { resolveMode = Just Dot, ..} -> do
expression <- getExpression file
dhall-lsp-server: Fix cache to correctly invalidate transitive dependencies (#1069) * Move "Dot" import graph generation to Dhall.Main Previously `Dhall.Import` would generate the import graph in "dot" format while resolving imports. This change simplifies `Dhall.Import` to only keep track of the adjacency list representing the import graph, moving the logic for generating "dot" files to Dhall.Main. This change will allow us to implement proper cache invalidation for `dhall-lsp-server`. * Correctly invalidate transitive dependencies Fixes dhall-lsp-server`s caching behaviour to correctly invalidate cached imports that (possibly indirectly) depend on the changed file. Example: Suppose we have the following three files: {- In A.dhall -} 2 : ./B.dhall {- In B.dhall -} ./C.dhall {- In C.dhall -} Natural Previously, changing C.dhall to `Text` would not cause `A.dhall` to stop type-checking, since the old version of `B.dhall` (which evaluated to `Natural`) would still have been in the cache. This change fixes that behaviour. * Make edges of import graph self-documenting As suggested by @Gabriel439 * Don't cache expressions manually After computing the diagnostics for a given file we added its normal form to the cache, but forgot to add its dependencies to the dependency graph. This bug points out that keeping the import graph consistent manually is probably not a good idea. With this commit we never mess with the import cache manually; this means that files are only cached once they are depended upon by some other file, potentially causing us to duplicate work (but no more than once). * Fix left-overs from previous commit
2019-07-08 12:55:15 +02:00
(Dhall.Import.Types.Status { _graph, _stack }) <-
State.execStateT (Dhall.Import.loadWith expression) (toStatus file) { _semanticCacheMode = semanticCacheMode }
dhall-lsp-server: Fix cache to correctly invalidate transitive dependencies (#1069) * Move "Dot" import graph generation to Dhall.Main Previously `Dhall.Import` would generate the import graph in "dot" format while resolving imports. This change simplifies `Dhall.Import` to only keep track of the adjacency list representing the import graph, moving the logic for generating "dot" files to Dhall.Main. This change will allow us to implement proper cache invalidation for `dhall-lsp-server`. * Correctly invalidate transitive dependencies Fixes dhall-lsp-server`s caching behaviour to correctly invalidate cached imports that (possibly indirectly) depend on the changed file. Example: Suppose we have the following three files: {- In A.dhall -} 2 : ./B.dhall {- In B.dhall -} ./C.dhall {- In C.dhall -} Natural Previously, changing C.dhall to `Text` would not cause `A.dhall` to stop type-checking, since the old version of `B.dhall` (which evaluated to `Natural`) would still have been in the cache. This change fixes that behaviour. * Make edges of import graph self-documenting As suggested by @Gabriel439 * Don't cache expressions manually After computing the diagnostics for a given file we added its normal form to the cache, but forgot to add its dependencies to the dependency graph. This bug points out that keeping the import graph consistent manually is probably not a good idea. With this commit we never mess with the import cache manually; this means that files are only cached once they are depended upon by some other file, potentially causing us to duplicate work (but no more than once). * Fix left-overs from previous commit
2019-07-08 12:55:15 +02:00
let (rootImport :| _) = _stack
imports = rootImport : map parent _graph ++ map child _graph
importIds = Data.Map.fromList (zip imports [Text.Dot.userNodeId i | i <- [0..]])
let dotNode (i, nodeId) =
Text.Dot.userNode
nodeId
[ ("label", Data.Text.unpack $ pretty i)
, ("shape", "box")
, ("style", "rounded")
]
let dotEdge (Depends parent child) =
case (Data.Map.lookup parent importIds, Data.Map.lookup child importIds) of
(Just from, Just to) -> from .->. to
_ -> pure ()
let dot = do Text.Dot.attribute ("rankdir", "LR")
mapM_ dotNode (Data.Map.assocs importIds)
mapM_ dotEdge _graph
putStr . ("strict " <>) . Text.Dot.showDot $ dot
Resolve { resolveMode = Just ListImmediateDependencies, ..} -> do
expression <- getExpression file
mapM_ (print
. Pretty.pretty
. Dhall.Core.importHashed) expression
Resolve { resolveMode = Just ListTransitiveDependencies, ..} -> do
expression <- getExpression file
(Dhall.Import.Types.Status { _cache }) <-
State.execStateT (Dhall.Import.loadWith expression) (toStatus file) { _semanticCacheMode = semanticCacheMode }
mapM_ print
. fmap ( Pretty.pretty
. Dhall.Core.importType
Preparing `Dhall.Import` for "Semi-semantic" caching (#1113) * Fix misleading comment * Add `Chained` type to capture fully chained imports Until now we used `Import` two mean two different things: - The syntactic construct; e.g. `./a.dhall` corresponds to the following AST: ``` Embed (Import (ImportHashed Nothing (Local Here (Directory ["."]) "a.dhall")) Code) ``` - The physical location the import is pointing to, computed by 'chaining' the syntactical import with the the 'physical' parent import. For example the syntactic import `./a.dhall` might actually refer to the remote file `http://host/directory/a.dhall`. This commit adds a `Chained` newtype on top of `Import` to make this distinction explicit at type level. * Use `HTTPHeaders` alias for binary headers I claim that `HTTPHeaders` is more readable and informative than the unfolded type `(CI ByteString, ByteString)`. * Typecheck and normalise http headers earlier Previously we would typecheck and normalise http headers in `exprFromImport`, i.e. while loading the import. This commit adds the invariant that any headers in 'Chained' imports are already typechecked and normalised, and moves this step into `loadWith` accordingly. This causes a subtle difference in behaviour when importing remote files with headers `as Location`: previously, nonsensical expressions like `http://a using 0 0 as Location` were valid, while they would now cause a type error. * Fix dhall-lsp-server * Fix Dhall.Import API regarding `Chained` imports Do not expose the `Chained` constructor; we don't want external code breaking our invariants! Also further clarifies the comment describing the `Chained` type. * Fix dhall-lsp-server Since we are no longer able to construct `Chained` imports directly we need to export a few additional helper functions from Dhall.Import. Furthermore, since VSCode (and presumably the other editors out there implementing the LSP protocol) does not support opening remote files anyway we can get rid of some complications by dropping support for remote files entirely on the back-end. * Generalise decodeExpression, fixes TODO * Fix tests * Fix benchmarks * Remove Travis cache for `~/.local/bin` * Fix copy-pasted comment Thanks to @Gabriel439 for spotting this! * Add clarifying comment to `toHeaders`
2019-07-17 17:20:48 +02:00
. Dhall.Core.importHashed
. Dhall.Import.chainedImport )
List dependencies in "post-order" (#1539) * List dependencies in "post-order" Related to https://github.com/dhall-lang/dhall-lang/issues/823 This lists dependencies starting from the leaves and concluding with the root import, same as how `nix-store --query --requisites` does Example output: ```bash $ dhall resolve --no-cache --transitive-dependencies <<< 'https://prelude.dhall-lang.org/package.dhall' https://prelude.dhall-lang.org/Bool/and https://prelude.dhall-lang.org/Bool/build https://prelude.dhall-lang.org/Bool/even https://prelude.dhall-lang.org/Bool/fold https://prelude.dhall-lang.org/Bool/not https://prelude.dhall-lang.org/Bool/odd https://prelude.dhall-lang.org/Bool/or https://prelude.dhall-lang.org/Bool/show https://prelude.dhall-lang.org/Bool/package.dhall https://prelude.dhall-lang.org/Double/show https://prelude.dhall-lang.org/Double/package.dhall https://prelude.dhall-lang.org/Function/compose https://prelude.dhall-lang.org/Function/package.dhall https://prelude.dhall-lang.org/Integer/show https://prelude.dhall-lang.org/Integer/toDouble https://prelude.dhall-lang.org/Integer/package.dhall https://prelude.dhall-lang.org/List/all https://prelude.dhall-lang.org/List/any https://prelude.dhall-lang.org/List/build https://prelude.dhall-lang.org/List/concat https://prelude.dhall-lang.org/List/concatMap https://prelude.dhall-lang.org/List/default https://prelude.dhall-lang.org/List/empty https://prelude.dhall-lang.org/List/filter https://prelude.dhall-lang.org/List/fold https://prelude.dhall-lang.org/List/generate https://prelude.dhall-lang.org/List/head https://prelude.dhall-lang.org/List/indexed https://prelude.dhall-lang.org/List/iterate https://prelude.dhall-lang.org/List/last https://prelude.dhall-lang.org/List/length https://prelude.dhall-lang.org/List/map https://prelude.dhall-lang.org/List/null https://prelude.dhall-lang.org/List/partition https://prelude.dhall-lang.org/List/replicate https://prelude.dhall-lang.org/List/reverse https://prelude.dhall-lang.org/List/shifted https://prelude.dhall-lang.org/List/unzip https://prelude.dhall-lang.org/List/package.dhall https://prelude.dhall-lang.org/Location/Type https://prelude.dhall-lang.org/Location/package.dhall https://prelude.dhall-lang.org/Map/Type https://prelude.dhall-lang.org/Map/Entry https://prelude.dhall-lang.org/Map/empty https://prelude.dhall-lang.org/Map/keyText https://prelude.dhall-lang.org/Map/keyValue https://prelude.dhall-lang.org/Map/keys https://prelude.dhall-lang.org/Map/map https://prelude.dhall-lang.org/Map/values https://prelude.dhall-lang.org/Map/package.dhall https://prelude.dhall-lang.org/Monoid https://prelude.dhall-lang.org/Natural/build https://prelude.dhall-lang.org/Natural/enumerate https://prelude.dhall-lang.org/Natural/even https://prelude.dhall-lang.org/Natural/fold https://prelude.dhall-lang.org/Natural/isZero https://prelude.dhall-lang.org/Natural/odd https://prelude.dhall-lang.org/Natural/product https://prelude.dhall-lang.org/Natural/sum https://prelude.dhall-lang.org/Natural/show https://prelude.dhall-lang.org/Natural/toDouble https://prelude.dhall-lang.org/Natural/toInteger https://prelude.dhall-lang.org/Natural/lessThanEqual https://prelude.dhall-lang.org/Natural/greaterThanEqual https://prelude.dhall-lang.org/Natural/lessThan https://prelude.dhall-lang.org/Natural/equal https://prelude.dhall-lang.org/Natural/greaterThan https://prelude.dhall-lang.org/Natural/min https://prelude.dhall-lang.org/Natural/max https://prelude.dhall-lang.org/Optional/map https://prelude.dhall-lang.org/Natural/listMin https://prelude.dhall-lang.org/Natural/listMax https://prelude.dhall-lang.org/Natural/sort https://prelude.dhall-lang.org/Natural/subtract https://prelude.dhall-lang.org/Natural/package.dhall https://prelude.dhall-lang.org/Optional/all https://prelude.dhall-lang.org/Optional/any https://prelude.dhall-lang.org/Optional/build https://prelude.dhall-lang.org/Optional/concat https://prelude.dhall-lang.org/Optional/default https://prelude.dhall-lang.org/Optional/filter https://prelude.dhall-lang.org/Optional/fold https://prelude.dhall-lang.org/Optional/head https://prelude.dhall-lang.org/Optional/last https://prelude.dhall-lang.org/Optional/length https://prelude.dhall-lang.org/Optional/null https://prelude.dhall-lang.org/Optional/toList https://prelude.dhall-lang.org/Optional/unzip https://prelude.dhall-lang.org/Optional/package.dhall https://prelude.dhall-lang.org/JSON/Type https://prelude.dhall-lang.org/JSON/Nesting https://prelude.dhall-lang.org/JSON/Tagged https://prelude.dhall-lang.org/JSON/keyText https://prelude.dhall-lang.org/JSON/keyValue https://prelude.dhall-lang.org/JSON/string https://prelude.dhall-lang.org/JSON/number https://prelude.dhall-lang.org/JSON/object https://prelude.dhall-lang.org/JSON/array https://prelude.dhall-lang.org/JSON/bool https://prelude.dhall-lang.org/JSON/null https://prelude.dhall-lang.org/Text/concatMapSep https://prelude.dhall-lang.org/JSON/render https://prelude.dhall-lang.org/JSON/package.dhall https://prelude.dhall-lang.org/Text/concat https://prelude.dhall-lang.org/Text/concatMap https://prelude.dhall-lang.org/Text/concatSep https://prelude.dhall-lang.org/Text/default https://prelude.dhall-lang.org/Text/defaultMap https://prelude.dhall-lang.org/Text/show https://prelude.dhall-lang.org/Text/package.dhall https://prelude.dhall-lang.org/XML/Type https://prelude.dhall-lang.org/XML/attribute https://prelude.dhall-lang.org/XML/render https://prelude.dhall-lang.org/XML/element https://prelude.dhall-lang.org/XML/leaf https://prelude.dhall-lang.org/XML/text https://prelude.dhall-lang.org/XML/emptyAttributes https://prelude.dhall-lang.org/XML/package.dhall https://prelude.dhall-lang.org/package.dhall ``` * Document order in `dhall resolve --help` output ... as suggested by @sjakobi * Fix dhall-lsp-server build
2019-11-21 17:20:48 +01:00
. reverse
. Dhall.Map.keys
$ _cache
Resolve { resolveMode = Nothing, ..} -> do
expression <- getExpression file
resolvedExpression <-
Dhall.Import.loadRelativeTo (rootDirectory file) semanticCacheMode expression
render System.IO.stdout resolvedExpression
Normalize {..} -> do
expression <- getExpression file
resolvedExpression <- Dhall.Import.assertNoImports expression
_ <- Dhall.Core.throws (Dhall.TypeCheck.typeOf resolvedExpression)
let normalizedExpression = Dhall.Core.normalize resolvedExpression
let alphaNormalizedExpression =
if alpha
then Dhall.Core.alphaNormalize normalizedExpression
else normalizedExpression
render System.IO.stdout alphaNormalizedExpression
Type {..} -> do
expression <- getExpression file
resolvedExpression <-
Dhall.Import.loadRelativeTo (rootDirectory file) semanticCacheMode expression
inferredType <- Dhall.Core.throws (Dhall.TypeCheck.typeOf resolvedExpression)
if quiet
then return ()
else render System.IO.stdout inferredType
Repl -> do
Dhall.Repl.repl characterSet explain
Diff {..} -> do
expression1 <- Dhall.inputExpr expr1
expression2 <- Dhall.inputExpr expr2
let diff = Dhall.Diff.diffNormalized expression1 expression2
renderDoc System.IO.stdout (Dhall.Diff.doc diff)
if Dhall.Diff.same diff
then return ()
else Exit.exitFailure
Format {..} -> do
Dhall.Format.format (Dhall.Format.Format {..})
Freeze {..} -> do
let scope = if all_ then AllImports else OnlyRemoteImports
let intent = if cache then Cache else Secure
Dhall.Freeze.freeze inplace scope intent characterSet censor
Hash {..} -> do
expression <- getExpression file
resolvedExpression <-
Dhall.Import.loadRelativeTo (rootDirectory file) UseSemanticCache expression
_ <- Dhall.Core.throws (Dhall.TypeCheck.typeOf resolvedExpression)
let normalizedExpression =
Dhall.Core.alphaNormalize (Dhall.Core.normalize resolvedExpression)
Data.Text.IO.putStrLn (Dhall.Import.hashExpressionToCode normalizedExpression)
Lint {..} -> do
(Header header, expression) <- getExpressionAndHeader inplace
case inplace of
InputFile file -> do
let lintedExpression = Dhall.Lint.lint expression
let doc = Pretty.pretty header
<> Dhall.Pretty.prettyCharacterSet characterSet lintedExpression
System.IO.withFile file System.IO.WriteMode (\h -> do
renderDoc h doc )
StandardInput -> do
let lintedExpression = Dhall.Lint.lint expression
let doc = Pretty.pretty header
<> Dhall.Pretty.prettyCharacterSet characterSet lintedExpression
renderDoc System.IO.stdout doc
Encode {..} -> do
expression <- getExpression file
Improve encoding/decoding speed (#1500) ... by not going through a `Term` intermediate This gives a ~28% performance in decoding improvement, which means that cache looks are not faster. Here are the new decoding benchmarks before and after this change: Before: ``` benchmarked Issue #108/Binary time 266.5 μs (265.7 μs .. 267.4 μs) 1.000 R² (1.000 R² .. 1.000 R²) mean 266.3 μs (265.6 μs .. 267.1 μs) std dev 2.418 μs (1.891 μs .. 3.436 μs) benchmarking Kubernetes/Binary ... took 36.94 s, total 56 iterations benchmarked Kubernetes/Binary time 641.3 ms (623.0 ms .. 655.4 ms) 0.999 R² (0.997 R² .. 1.000 R²) mean 679.7 ms (665.5 ms .. 702.6 ms) std dev 29.48 ms (14.15 ms .. 39.05 ms) ``` After: ``` benchmarked Issue #108/Binary time 282.2 μs (279.6 μs .. 284.7 μs) 1.000 R² (0.999 R² .. 1.000 R²) mean 281.9 μs (280.7 μs .. 287.7 μs) std dev 7.089 μs (2.550 μs .. 15.44 μs) variance introduced by outliers: 11% (moderately inflated) benchmarking Kubernetes/Binary ... took 27.57 s, total 56 iterations benchmarked Kubernetes/Binary time 499.1 ms (488.1 ms .. 506.6 ms) 0.999 R² (0.998 R² .. 1.000 R²) mean 498.9 ms (494.4 ms .. 503.9 ms) std dev 8.539 ms (6.236 ms .. 12.56 ms) ``` There's a slight performance regression for the decoding microbenchmark, but in practice my testing on real examples matches performance improvements seen in the larger benchmark based on an example cache product from `dhall-kubernetes`. Note that is a breaking change because: * There is no longer a `FromTerm` nor `ToTerm` class. Now we use the `Serialise` class and `{encode,decode}Expression` now work on `ByteString`s instead of `Term`s * I further narrowed the types of several encoding/decoding utilites to expect a `Void` for the first type parameter of `Expr` * This is a regression with respect to stripping 55799 CBOR tags, mainly because properly handling the tags at every possible point in the syntax tree would considerably complicate the code
2019-11-01 04:05:22 +01:00
let bytes = Dhall.Binary.encodeExpression (Dhall.Core.denote expression)
if json
then do
let decoder = Codec.CBOR.JSON.decodeValue False
(_, value) <- Dhall.Core.throws (Codec.CBOR.Read.deserialiseFromBytes decoder bytes)
let jsonBytes = Data.Aeson.Encode.Pretty.encodePretty value
Data.ByteString.Lazy.Char8.putStrLn jsonBytes
else do
Data.ByteString.Lazy.putStr bytes
Decode {..} -> do
bytes <- do
case file of
InputFile f -> Data.ByteString.Lazy.readFile f
StandardInput -> Data.ByteString.Lazy.getContents
Improve encoding/decoding speed (#1500) ... by not going through a `Term` intermediate This gives a ~28% performance in decoding improvement, which means that cache looks are not faster. Here are the new decoding benchmarks before and after this change: Before: ``` benchmarked Issue #108/Binary time 266.5 μs (265.7 μs .. 267.4 μs) 1.000 R² (1.000 R² .. 1.000 R²) mean 266.3 μs (265.6 μs .. 267.1 μs) std dev 2.418 μs (1.891 μs .. 3.436 μs) benchmarking Kubernetes/Binary ... took 36.94 s, total 56 iterations benchmarked Kubernetes/Binary time 641.3 ms (623.0 ms .. 655.4 ms) 0.999 R² (0.997 R² .. 1.000 R²) mean 679.7 ms (665.5 ms .. 702.6 ms) std dev 29.48 ms (14.15 ms .. 39.05 ms) ``` After: ``` benchmarked Issue #108/Binary time 282.2 μs (279.6 μs .. 284.7 μs) 1.000 R² (0.999 R² .. 1.000 R²) mean 281.9 μs (280.7 μs .. 287.7 μs) std dev 7.089 μs (2.550 μs .. 15.44 μs) variance introduced by outliers: 11% (moderately inflated) benchmarking Kubernetes/Binary ... took 27.57 s, total 56 iterations benchmarked Kubernetes/Binary time 499.1 ms (488.1 ms .. 506.6 ms) 0.999 R² (0.998 R² .. 1.000 R²) mean 498.9 ms (494.4 ms .. 503.9 ms) std dev 8.539 ms (6.236 ms .. 12.56 ms) ``` There's a slight performance regression for the decoding microbenchmark, but in practice my testing on real examples matches performance improvements seen in the larger benchmark based on an example cache product from `dhall-kubernetes`. Note that is a breaking change because: * There is no longer a `FromTerm` nor `ToTerm` class. Now we use the `Serialise` class and `{encode,decode}Expression` now work on `ByteString`s instead of `Term`s * I further narrowed the types of several encoding/decoding utilites to expect a `Void` for the first type parameter of `Expr` * This is a regression with respect to stripping 55799 CBOR tags, mainly because properly handling the tags at every possible point in the syntax tree would considerably complicate the code
2019-11-01 04:05:22 +01:00
expression <- do
if json
then do
value <- case Data.Aeson.eitherDecode' bytes of
Left string -> fail string
Right value -> return value
let encoding = Codec.CBOR.JSON.encodeValue value
Improve encoding/decoding speed (#1500) ... by not going through a `Term` intermediate This gives a ~28% performance in decoding improvement, which means that cache looks are not faster. Here are the new decoding benchmarks before and after this change: Before: ``` benchmarked Issue #108/Binary time 266.5 μs (265.7 μs .. 267.4 μs) 1.000 R² (1.000 R² .. 1.000 R²) mean 266.3 μs (265.6 μs .. 267.1 μs) std dev 2.418 μs (1.891 μs .. 3.436 μs) benchmarking Kubernetes/Binary ... took 36.94 s, total 56 iterations benchmarked Kubernetes/Binary time 641.3 ms (623.0 ms .. 655.4 ms) 0.999 R² (0.997 R² .. 1.000 R²) mean 679.7 ms (665.5 ms .. 702.6 ms) std dev 29.48 ms (14.15 ms .. 39.05 ms) ``` After: ``` benchmarked Issue #108/Binary time 282.2 μs (279.6 μs .. 284.7 μs) 1.000 R² (0.999 R² .. 1.000 R²) mean 281.9 μs (280.7 μs .. 287.7 μs) std dev 7.089 μs (2.550 μs .. 15.44 μs) variance introduced by outliers: 11% (moderately inflated) benchmarking Kubernetes/Binary ... took 27.57 s, total 56 iterations benchmarked Kubernetes/Binary time 499.1 ms (488.1 ms .. 506.6 ms) 0.999 R² (0.998 R² .. 1.000 R²) mean 498.9 ms (494.4 ms .. 503.9 ms) std dev 8.539 ms (6.236 ms .. 12.56 ms) ``` There's a slight performance regression for the decoding microbenchmark, but in practice my testing on real examples matches performance improvements seen in the larger benchmark based on an example cache product from `dhall-kubernetes`. Note that is a breaking change because: * There is no longer a `FromTerm` nor `ToTerm` class. Now we use the `Serialise` class and `{encode,decode}Expression` now work on `ByteString`s instead of `Term`s * I further narrowed the types of several encoding/decoding utilites to expect a `Void` for the first type parameter of `Expr` * This is a regression with respect to stripping 55799 CBOR tags, mainly because properly handling the tags at every possible point in the syntax tree would considerably complicate the code
2019-11-01 04:05:22 +01:00
let cborgBytes = Codec.CBOR.Write.toLazyByteString encoding
Dhall.Core.throws (Dhall.Binary.decodeExpression cborgBytes)
else do
Improve encoding/decoding speed (#1500) ... by not going through a `Term` intermediate This gives a ~28% performance in decoding improvement, which means that cache looks are not faster. Here are the new decoding benchmarks before and after this change: Before: ``` benchmarked Issue #108/Binary time 266.5 μs (265.7 μs .. 267.4 μs) 1.000 R² (1.000 R² .. 1.000 R²) mean 266.3 μs (265.6 μs .. 267.1 μs) std dev 2.418 μs (1.891 μs .. 3.436 μs) benchmarking Kubernetes/Binary ... took 36.94 s, total 56 iterations benchmarked Kubernetes/Binary time 641.3 ms (623.0 ms .. 655.4 ms) 0.999 R² (0.997 R² .. 1.000 R²) mean 679.7 ms (665.5 ms .. 702.6 ms) std dev 29.48 ms (14.15 ms .. 39.05 ms) ``` After: ``` benchmarked Issue #108/Binary time 282.2 μs (279.6 μs .. 284.7 μs) 1.000 R² (0.999 R² .. 1.000 R²) mean 281.9 μs (280.7 μs .. 287.7 μs) std dev 7.089 μs (2.550 μs .. 15.44 μs) variance introduced by outliers: 11% (moderately inflated) benchmarking Kubernetes/Binary ... took 27.57 s, total 56 iterations benchmarked Kubernetes/Binary time 499.1 ms (488.1 ms .. 506.6 ms) 0.999 R² (0.998 R² .. 1.000 R²) mean 498.9 ms (494.4 ms .. 503.9 ms) std dev 8.539 ms (6.236 ms .. 12.56 ms) ``` There's a slight performance regression for the decoding microbenchmark, but in practice my testing on real examples matches performance improvements seen in the larger benchmark based on an example cache product from `dhall-kubernetes`. Note that is a breaking change because: * There is no longer a `FromTerm` nor `ToTerm` class. Now we use the `Serialise` class and `{encode,decode}Expression` now work on `ByteString`s instead of `Term`s * I further narrowed the types of several encoding/decoding utilites to expect a `Void` for the first type parameter of `Expr` * This is a regression with respect to stripping 55799 CBOR tags, mainly because properly handling the tags at every possible point in the syntax tree would considerably complicate the code
2019-11-01 04:05:22 +01:00
Dhall.Core.throws (Dhall.Binary.decodeExpression bytes)
Improve encoding/decoding speed (#1500) ... by not going through a `Term` intermediate This gives a ~28% performance in decoding improvement, which means that cache looks are not faster. Here are the new decoding benchmarks before and after this change: Before: ``` benchmarked Issue #108/Binary time 266.5 μs (265.7 μs .. 267.4 μs) 1.000 R² (1.000 R² .. 1.000 R²) mean 266.3 μs (265.6 μs .. 267.1 μs) std dev 2.418 μs (1.891 μs .. 3.436 μs) benchmarking Kubernetes/Binary ... took 36.94 s, total 56 iterations benchmarked Kubernetes/Binary time 641.3 ms (623.0 ms .. 655.4 ms) 0.999 R² (0.997 R² .. 1.000 R²) mean 679.7 ms (665.5 ms .. 702.6 ms) std dev 29.48 ms (14.15 ms .. 39.05 ms) ``` After: ``` benchmarked Issue #108/Binary time 282.2 μs (279.6 μs .. 284.7 μs) 1.000 R² (0.999 R² .. 1.000 R²) mean 281.9 μs (280.7 μs .. 287.7 μs) std dev 7.089 μs (2.550 μs .. 15.44 μs) variance introduced by outliers: 11% (moderately inflated) benchmarking Kubernetes/Binary ... took 27.57 s, total 56 iterations benchmarked Kubernetes/Binary time 499.1 ms (488.1 ms .. 506.6 ms) 0.999 R² (0.998 R² .. 1.000 R²) mean 498.9 ms (494.4 ms .. 503.9 ms) std dev 8.539 ms (6.236 ms .. 12.56 ms) ``` There's a slight performance regression for the decoding microbenchmark, but in practice my testing on real examples matches performance improvements seen in the larger benchmark based on an example cache product from `dhall-kubernetes`. Note that is a breaking change because: * There is no longer a `FromTerm` nor `ToTerm` class. Now we use the `Serialise` class and `{encode,decode}Expression` now work on `ByteString`s instead of `Term`s * I further narrowed the types of several encoding/decoding utilites to expect a `Void` for the first type parameter of `Expr` * This is a regression with respect to stripping 55799 CBOR tags, mainly because properly handling the tags at every possible point in the syntax tree would considerably complicate the code
2019-11-01 04:05:22 +01:00
let doc = Dhall.Pretty.prettyCharacterSet characterSet (Dhall.Core.renote expression :: Expr Src Import)
renderDoc System.IO.stdout doc
Text {..} -> do
expression <- getExpression file
resolvedExpression <-
Dhall.Import.loadRelativeTo (rootDirectory file) UseSemanticCache expression
_ <- Dhall.Core.throws (Dhall.TypeCheck.typeOf (Annot resolvedExpression Dhall.Core.Text))
let normalizedExpression = Dhall.Core.normalize resolvedExpression
case normalizedExpression of
Dhall.Core.TextLit (Dhall.Core.Chunks [] text) -> do
Data.Text.IO.putStr text
_ -> do
2019-10-30 16:13:51 +01:00
let invalidDecoderExpected :: Expr Void Void
invalidDecoderExpected = Dhall.Core.Text
2019-10-30 16:13:51 +01:00
let invalidDecoderExpression :: Expr Void Void
invalidDecoderExpression = normalizedExpression
Control.Exception.throwIO (Dhall.InvalidDecoder {..})
Tags {..} -> do
tags <- Dhall.Tags.generate input suffixes followSymlinks
case output of
OutputFile file ->
System.IO.withFile file System.IO.WriteMode (`Data.Text.IO.hPutStr` tags)
StandardOutput -> Data.Text.IO.putStrLn tags
SyntaxTree {..} -> do
expression <- getExpression file
let denoted :: Expr Void Import
denoted = Dhall.Core.denote expression
Text.Pretty.Simple.pPrintNoColor denoted
-- | Entry point for the @dhall@ executable
main :: IO ()
main = do
options <- Options.Applicative.execParser parserInfoOptions
command options