{-# LANGUAGE ApplicativeDo #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
module Dhall.Main
(
Options(..)
, Mode(..)
, ResolveMode(..)
, parseOptions
, parserInfoOptions
, Dhall.Main.command
, main
) where
import Control.Applicative (optional, (<|>))
import Control.Exception (Handler (..), SomeException)
import Control.Monad (when)
import Data.Foldable (for_)
import Data.List.NonEmpty (NonEmpty (..), nonEmpty)
import Data.Maybe (fromMaybe)
import Data.Text (Text)
import Data.Void (Void)
import Dhall.Freeze (Intent (..), Scope (..))
import Dhall.Import
( Depends (..)
, Imported (..)
, SemanticCacheMode (..)
, _semanticCacheMode
)
import Dhall.Package (writePackage)
import Dhall.Parser (Src)
import Dhall.Pretty
( Ann
, CharacterSet (..)
, annToAnsiStyle
, detectCharacterSet
)
import Dhall.Schemas (Schemas (..))
import Dhall.TypeCheck (Censored (..), DetailedTypeError (..), TypeError)
import Dhall.Version (dhallVersionString)
import Options.Applicative (Parser, ParserInfo)
import Prettyprinter (Doc, Pretty)
import System.Exit (ExitCode, exitFailure)
import System.IO (Handle)
import Text.Dot ((.->.))
import Dhall.Core
( Expr (Annot)
, Import (..)
, ImportHashed (..)
, ImportType (..)
, URL (..)
, pretty
)
import Dhall.Util
( Censor (..)
, CheckFailed (..)
, Header (..)
, Input (..)
, Output (..)
, OutputMode (..)
, Transitivity (..)
, handleMultipleChecksFailed
)
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 Dhall
import qualified Dhall.Binary
import qualified Dhall.Core
import qualified Dhall.Diff
import qualified Dhall.DirectoryTree as DirectoryTree
import qualified Dhall.Format
import qualified Dhall.Freeze
import qualified Dhall.Import
import qualified Dhall.Import.Types
import qualified Dhall.Lint
import qualified Dhall.Map
import qualified Dhall.Pretty
import qualified Dhall.Repl
import qualified Dhall.Schemas
import qualified Dhall.Tags
import qualified Dhall.TypeCheck
import qualified Dhall.Util
import qualified GHC.IO.Encoding
import qualified Options.Applicative
import qualified Prettyprinter as Pretty
import qualified Prettyprinter.Render.Terminal as Pretty
import qualified Prettyprinter.Render.Text as Pretty.Text
import qualified System.AtomicWrite.Writer.LazyText as AtomicWrite.LazyText
import qualified System.Console.ANSI
import qualified System.Exit as Exit
import qualified System.FilePath
import qualified System.IO
import qualified Text.Dot
import qualified Text.Pretty.Simple
data Options = Options
{ Options -> Mode
mode :: Mode
, Options -> Bool
explain :: Bool
, Options -> Bool
plain :: Bool
, Options -> Maybe CharacterSet
chosenCharacterSet :: Maybe CharacterSet
, Options -> Censor
censor :: Censor
}
data Mode
= Default
{ Mode -> Input
file :: Input
, Mode -> Output
output :: Output
, Mode -> Bool
annotate :: Bool
, Mode -> Bool
alpha :: Bool
, Mode -> SemanticCacheMode
semanticCacheMode :: SemanticCacheMode
, Mode -> Bool
version :: Bool
}
| Version
| Resolve
{ file :: Input
, Mode -> Maybe ResolveMode
resolveMode :: Maybe ResolveMode
, semanticCacheMode :: SemanticCacheMode
}
| Type
{ file :: Input
, Mode -> Bool
quiet :: Bool
, semanticCacheMode :: SemanticCacheMode
}
| Normalize { file :: Input , alpha :: Bool }
| Repl
| Format { Mode -> Bool
deprecatedInPlace :: Bool, Mode -> Transitivity
transitivity :: Transitivity, Mode -> OutputMode
outputMode :: OutputMode, Mode -> NonEmpty Input
inputs :: NonEmpty Input }
| Freeze { deprecatedInPlace :: Bool, transitivity :: Transitivity, Mode -> Bool
all_ :: Bool, Mode -> Bool
cache :: Bool, outputMode :: OutputMode, inputs :: NonEmpty Input }
| Hash { file :: Input, cache :: Bool }
| Diff { Mode -> Text
expr1 :: Text, Mode -> Text
expr2 :: Text }
| Lint { deprecatedInPlace :: Bool, transitivity :: Transitivity, outputMode :: OutputMode, inputs :: NonEmpty Input }
| Tags
{ Mode -> Input
input :: Input
, output :: Output
, Mode -> Maybe [Text]
suffixes :: Maybe [Text]
, Mode -> Bool
followSymlinks :: Bool
}
| Encode { file :: Input, Mode -> Bool
json :: Bool }
| Decode { file :: Input, json :: Bool, quiet :: Bool }
| Text { file :: Input, output :: Output }
| DirectoryTree { Mode -> Bool
allowSeparators :: Bool, file :: Input, Mode -> String
path :: FilePath }
| Schemas { file :: Input, outputMode :: OutputMode, Mode -> Text
schemas :: Text }
| SyntaxTree { file :: Input, Mode -> Bool
noted :: Bool }
| Package { Mode -> Maybe String
name :: Maybe String, Mode -> NonEmpty String
files :: NonEmpty FilePath }
data ResolveMode
= Dot
| ListTransitiveDependencies
| ListImmediateDependencies
data Group
= Manipulate
| Generate
| Interpret
| Convert
| Miscellaneous
| Debugging
groupDescription :: Group -> String
groupDescription :: Group -> String
groupDescription Group
group = case Group
group of
Group
Manipulate -> String
"Manipulate Dhall code"
Group
Generate -> String
"Generate other formats from Dhall"
Group
Interpret -> String
"Interpret Dhall"
Group
Convert -> String
"Convert Dhall to and from its binary representation"
Group
Miscellaneous -> String
"Miscellaneous"
Group
Debugging -> String
"Debugging this interpreter"
parseOptions :: Parser Options
parseOptions :: Parser Options
parseOptions =
Mode -> Bool -> Bool -> Maybe CharacterSet -> Censor -> Options
Options
(Mode -> Bool -> Bool -> Maybe CharacterSet -> Censor -> Options)
-> Parser Mode
-> Parser (Bool -> Bool -> Maybe CharacterSet -> Censor -> Options)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Mode
parseMode
Parser (Bool -> Bool -> Maybe CharacterSet -> Censor -> Options)
-> Parser Bool
-> Parser (Bool -> Maybe CharacterSet -> Censor -> Options)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> String -> String -> Parser Bool
switch String
"explain" String
"Explain error messages in more detail"
Parser (Bool -> Maybe CharacterSet -> Censor -> Options)
-> Parser Bool -> Parser (Maybe CharacterSet -> Censor -> Options)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> String -> String -> Parser Bool
switch String
"plain" String
"Disable syntax highlighting"
Parser (Maybe CharacterSet -> Censor -> Options)
-> Parser (Maybe CharacterSet) -> Parser (Censor -> Options)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser (Maybe CharacterSet)
parseCharacterSet
Parser (Censor -> Options) -> Parser Censor -> Parser Options
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Censor
parseCensor
where
switch :: String -> String -> Parser Bool
switch String
name String
description =
Mod FlagFields Bool -> Parser Bool
Options.Applicative.switch
( String -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => String -> Mod f a
Options.Applicative.long String
name
Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<> String -> Mod FlagFields Bool
forall (f :: * -> *) a. String -> Mod f a
Options.Applicative.help String
description
)
parseCensor :: Parser Censor
parseCensor = (Bool -> Censor) -> Parser Bool -> Parser Censor
forall a b. (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Bool -> Censor
f (String -> String -> Parser Bool
switch String
"censor" String
"Hide source code in error messages")
where
f :: Bool -> Censor
f Bool
True = Censor
Censor
f Bool
False = Censor
NoCensor
parseCharacterSet :: Parser (Maybe CharacterSet)
parseCharacterSet =
Maybe CharacterSet
-> Mod FlagFields (Maybe CharacterSet)
-> Parser (Maybe CharacterSet)
forall a. a -> Mod FlagFields a -> Parser a
Options.Applicative.flag'
(CharacterSet -> Maybe CharacterSet
forall a. a -> Maybe a
Just CharacterSet
Unicode)
( String -> Mod FlagFields (Maybe CharacterSet)
forall (f :: * -> *) a. HasName f => String -> Mod f a
Options.Applicative.long String
"unicode"
Mod FlagFields (Maybe CharacterSet)
-> Mod FlagFields (Maybe CharacterSet)
-> Mod FlagFields (Maybe CharacterSet)
forall a. Semigroup a => a -> a -> a
<> String -> Mod FlagFields (Maybe CharacterSet)
forall (f :: * -> *) a. String -> Mod f a
Options.Applicative.help String
"Format code using only Unicode syntax"
)
Parser (Maybe CharacterSet)
-> Parser (Maybe CharacterSet) -> Parser (Maybe CharacterSet)
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Maybe CharacterSet
-> Mod FlagFields (Maybe CharacterSet)
-> Parser (Maybe CharacterSet)
forall a. a -> Mod FlagFields a -> Parser a
Options.Applicative.flag'
(CharacterSet -> Maybe CharacterSet
forall a. a -> Maybe a
Just CharacterSet
ASCII)
( String -> Mod FlagFields (Maybe CharacterSet)
forall (f :: * -> *) a. HasName f => String -> Mod f a
Options.Applicative.long String
"ascii"
Mod FlagFields (Maybe CharacterSet)
-> Mod FlagFields (Maybe CharacterSet)
-> Mod FlagFields (Maybe CharacterSet)
forall a. Semigroup a => a -> a -> a
<> String -> Mod FlagFields (Maybe CharacterSet)
forall (f :: * -> *) a. String -> Mod f a
Options.Applicative.help String
"Format code using only ASCII syntax"
)
Parser (Maybe CharacterSet)
-> Parser (Maybe CharacterSet) -> Parser (Maybe CharacterSet)
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Maybe CharacterSet -> Parser (Maybe CharacterSet)
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe CharacterSet
forall a. Maybe a
Nothing
subcommand :: Group -> String -> String -> Parser a -> Parser a
subcommand :: forall a. Group -> String -> String -> Parser a -> Parser a
subcommand Group
group String
name String
description Parser a
parser =
Mod CommandFields a -> Parser a
forall a. Mod CommandFields a -> Parser a
Options.Applicative.hsubparser
( String -> ParserInfo a -> Mod CommandFields a
forall a. String -> ParserInfo a -> Mod CommandFields a
Options.Applicative.command String
name ParserInfo a
parserInfo
Mod CommandFields a -> Mod CommandFields a -> Mod CommandFields a
forall a. Semigroup a => a -> a -> a
<> String -> Mod CommandFields a
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
Options.Applicative.metavar String
name
Mod CommandFields a -> Mod CommandFields a -> Mod CommandFields a
forall a. Semigroup a => a -> a -> a
<> String -> Mod CommandFields a
forall a. String -> Mod CommandFields a
Options.Applicative.commandGroup (Group -> String
groupDescription Group
group)
)
where
parserInfo :: ParserInfo a
parserInfo =
Parser a -> InfoMod a -> ParserInfo a
forall a. Parser a -> InfoMod a -> ParserInfo a
Options.Applicative.info Parser a
parser
( InfoMod a
forall a. InfoMod a
Options.Applicative.fullDesc
InfoMod a -> InfoMod a -> InfoMod a
forall a. Semigroup a => a -> a -> a
<> String -> InfoMod a
forall a. String -> InfoMod a
Options.Applicative.progDesc String
description
)
parseMode :: Parser Mode
parseMode :: Parser Mode
parseMode =
Group -> String -> String -> Parser Mode -> Parser Mode
forall a. Group -> String -> String -> Parser a -> Parser a
subcommand
Group
Manipulate
String
"format"
String
"Standard code formatter for the Dhall language"
(Bool -> Transitivity -> OutputMode -> NonEmpty Input -> Mode
Format (Bool -> Transitivity -> OutputMode -> NonEmpty Input -> Mode)
-> Parser Bool
-> Parser (Transitivity -> OutputMode -> NonEmpty Input -> Mode)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Bool
deprecatedInPlace Parser (Transitivity -> OutputMode -> NonEmpty Input -> Mode)
-> Parser Transitivity
-> Parser (OutputMode -> NonEmpty Input -> Mode)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Transitivity
parseTransitiveSwitch Parser (OutputMode -> NonEmpty Input -> Mode)
-> Parser OutputMode -> Parser (NonEmpty Input -> Mode)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> String -> Parser OutputMode
parseCheck String
"formatted" Parser (NonEmpty Input -> Mode)
-> Parser (NonEmpty Input) -> Parser Mode
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser (NonEmpty Input)
parseFiles)
Parser Mode -> Parser Mode -> Parser Mode
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Group -> String -> String -> Parser Mode -> Parser Mode
forall a. Group -> String -> String -> Parser a -> Parser a
subcommand
Group
Manipulate
String
"freeze"
String
"Add integrity checks to remote import statements of an expression"
(Bool
-> Transitivity
-> Bool
-> Bool
-> OutputMode
-> NonEmpty Input
-> Mode
Freeze (Bool
-> Transitivity
-> Bool
-> Bool
-> OutputMode
-> NonEmpty Input
-> Mode)
-> Parser Bool
-> Parser
(Transitivity
-> Bool -> Bool -> OutputMode -> NonEmpty Input -> Mode)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Bool
deprecatedInPlace Parser
(Transitivity
-> Bool -> Bool -> OutputMode -> NonEmpty Input -> Mode)
-> Parser Transitivity
-> Parser (Bool -> Bool -> OutputMode -> NonEmpty Input -> Mode)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Transitivity
parseTransitiveSwitch Parser (Bool -> Bool -> OutputMode -> NonEmpty Input -> Mode)
-> Parser Bool
-> Parser (Bool -> OutputMode -> NonEmpty Input -> Mode)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Bool
parseAllFlag Parser (Bool -> OutputMode -> NonEmpty Input -> Mode)
-> Parser Bool -> Parser (OutputMode -> NonEmpty Input -> Mode)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Bool
parseCacheFlag Parser (OutputMode -> NonEmpty Input -> Mode)
-> Parser OutputMode -> Parser (NonEmpty Input -> Mode)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> String -> Parser OutputMode
parseCheck String
"frozen" Parser (NonEmpty Input -> Mode)
-> Parser (NonEmpty Input) -> Parser Mode
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser (NonEmpty Input)
parseFiles)
Parser Mode -> Parser Mode -> Parser Mode
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Group -> String -> String -> Parser Mode -> Parser Mode
forall a. Group -> String -> String -> Parser a -> Parser a
subcommand
Group
Manipulate
String
"lint"
String
"Improve Dhall code by using newer language features and removing dead code"
(Bool -> Transitivity -> OutputMode -> NonEmpty Input -> Mode
Lint (Bool -> Transitivity -> OutputMode -> NonEmpty Input -> Mode)
-> Parser Bool
-> Parser (Transitivity -> OutputMode -> NonEmpty Input -> Mode)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Bool
deprecatedInPlace Parser (Transitivity -> OutputMode -> NonEmpty Input -> Mode)
-> Parser Transitivity
-> Parser (OutputMode -> NonEmpty Input -> Mode)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Transitivity
parseTransitiveSwitch Parser (OutputMode -> NonEmpty Input -> Mode)
-> Parser OutputMode -> Parser (NonEmpty Input -> Mode)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> String -> Parser OutputMode
parseCheck String
"linted" Parser (NonEmpty Input -> Mode)
-> Parser (NonEmpty Input) -> Parser Mode
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser (NonEmpty Input)
parseFiles)
Parser Mode -> Parser Mode -> Parser Mode
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Group -> String -> String -> Parser Mode -> Parser Mode
forall a. Group -> String -> String -> Parser a -> Parser a
subcommand
Group
Manipulate
String
"rewrite-with-schemas"
String
"Simplify Dhall code using a schemas record"
(Input -> OutputMode -> Text -> Mode
Dhall.Main.Schemas (Input -> OutputMode -> Text -> Mode)
-> Parser Input -> Parser (OutputMode -> Text -> Mode)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Input
parseInplaceNonTransitive Parser (OutputMode -> Text -> Mode)
-> Parser OutputMode -> Parser (Text -> Mode)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> String -> Parser OutputMode
parseCheck String
"rewritten" Parser (Text -> Mode) -> Parser Text -> Parser Mode
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Text
parseSchemasRecord)
Parser Mode -> Parser Mode -> Parser Mode
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Group -> String -> String -> Parser Mode -> Parser Mode
forall a. Group -> String -> String -> Parser a -> Parser a
subcommand
Group
Generate
String
"text"
String
"Render a Dhall expression that evaluates to a Text literal"
(Input -> Output -> Mode
Text (Input -> Output -> Mode)
-> Parser Input -> Parser (Output -> Mode)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Input
parseFile Parser (Output -> Mode) -> Parser Output -> Parser Mode
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Output
parseOutput)
Parser Mode -> Parser Mode -> Parser Mode
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Group -> String -> String -> Parser Mode -> Parser Mode
forall a. Group -> String -> String -> Parser a -> Parser a
subcommand
Group
Generate
String
"to-directory-tree"
String
"Convert nested records of Text literals into a directory tree"
(Bool -> Input -> String -> Mode
DirectoryTree (Bool -> Input -> String -> Mode)
-> Parser Bool -> Parser (Input -> String -> Mode)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Bool
parseDirectoryTreeAllowSeparators Parser (Input -> String -> Mode)
-> Parser Input -> Parser (String -> Mode)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Input
parseFile Parser (String -> Mode) -> Parser String -> Parser Mode
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser String
parseDirectoryTreeOutput)
Parser Mode -> Parser Mode -> Parser Mode
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Group -> String -> String -> Parser Mode -> Parser Mode
forall a. Group -> String -> String -> Parser a -> Parser a
subcommand
Group
Interpret
String
"resolve"
String
"Resolve an expression's imports"
(Input -> Maybe ResolveMode -> SemanticCacheMode -> Mode
Resolve (Input -> Maybe ResolveMode -> SemanticCacheMode -> Mode)
-> Parser Input
-> Parser (Maybe ResolveMode -> SemanticCacheMode -> Mode)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Input
parseFile Parser (Maybe ResolveMode -> SemanticCacheMode -> Mode)
-> Parser (Maybe ResolveMode) -> Parser (SemanticCacheMode -> Mode)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser (Maybe ResolveMode)
parseResolveMode Parser (SemanticCacheMode -> Mode)
-> Parser SemanticCacheMode -> Parser Mode
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser SemanticCacheMode
parseSemanticCacheMode)
Parser Mode -> Parser Mode -> Parser Mode
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Group -> String -> String -> Parser Mode -> Parser Mode
forall a. Group -> String -> String -> Parser a -> Parser a
subcommand
Group
Interpret
String
"type"
String
"Infer an expression's type"
(Input -> Bool -> SemanticCacheMode -> Mode
Type (Input -> Bool -> SemanticCacheMode -> Mode)
-> Parser Input -> Parser (Bool -> SemanticCacheMode -> Mode)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Input
parseFile Parser (Bool -> SemanticCacheMode -> Mode)
-> Parser Bool -> Parser (SemanticCacheMode -> Mode)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Bool
parseQuiet Parser (SemanticCacheMode -> Mode)
-> Parser SemanticCacheMode -> Parser Mode
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser SemanticCacheMode
parseSemanticCacheMode)
Parser Mode -> Parser Mode -> Parser Mode
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Group -> String -> String -> Parser Mode -> Parser Mode
forall a. Group -> String -> String -> Parser a -> Parser a
subcommand
Group
Interpret
String
"normalize"
String
"Normalize an expression"
(Input -> Bool -> Mode
Normalize (Input -> Bool -> Mode) -> Parser Input -> Parser (Bool -> Mode)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Input
parseFile Parser (Bool -> Mode) -> Parser Bool -> Parser Mode
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Bool
parseAlpha)
Parser Mode -> Parser Mode -> Parser Mode
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Group -> String -> String -> Parser Mode -> Parser Mode
forall a. Group -> String -> String -> Parser a -> Parser a
subcommand
Group
Convert
String
"encode"
String
"Encode a Dhall expression to binary"
(Input -> Bool -> Mode
Encode (Input -> Bool -> Mode) -> Parser Input -> Parser (Bool -> Mode)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Input
parseFile Parser (Bool -> Mode) -> Parser Bool -> Parser Mode
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Bool
parseJSONFlag)
Parser Mode -> Parser Mode -> Parser Mode
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Group -> String -> String -> Parser Mode -> Parser Mode
forall a. Group -> String -> String -> Parser a -> Parser a
subcommand
Group
Convert
String
"decode"
String
"Decode a Dhall expression from binary"
(Input -> Bool -> Bool -> Mode
Decode (Input -> Bool -> Bool -> Mode)
-> Parser Input -> Parser (Bool -> Bool -> Mode)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Input
parseFile Parser (Bool -> Bool -> Mode)
-> Parser Bool -> Parser (Bool -> Mode)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Bool
parseJSONFlag Parser (Bool -> Mode) -> Parser Bool -> Parser Mode
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Bool
parseQuiet)
Parser Mode -> Parser Mode -> Parser Mode
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Group -> String -> String -> Parser Mode -> Parser Mode
forall a. Group -> String -> String -> Parser a -> Parser a
subcommand
Group
Miscellaneous
String
"repl"
String
"Interpret expressions in a REPL"
(Mode -> Parser Mode
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Mode
Repl)
Parser Mode -> Parser Mode -> Parser Mode
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Group -> String -> String -> Parser Mode -> Parser Mode
forall a. Group -> String -> String -> Parser a -> Parser a
subcommand
Group
Miscellaneous
String
"diff"
String
"Render the difference between the normal form of two expressions"
(Text -> Text -> Mode
Diff (Text -> Text -> Mode) -> Parser Text -> Parser (Text -> Mode)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> Parser Text
argument String
"expr1" Parser (Text -> Mode) -> Parser Text -> Parser Mode
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> String -> Parser Text
argument String
"expr2")
Parser Mode -> Parser Mode -> Parser Mode
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Group -> String -> String -> Parser Mode -> Parser Mode
forall a. Group -> String -> String -> Parser a -> Parser a
subcommand
Group
Miscellaneous
String
"hash"
String
"Compute semantic hashes for Dhall expressions"
(Input -> Bool -> Mode
Hash (Input -> Bool -> Mode) -> Parser Input -> Parser (Bool -> Mode)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Input
parseFile Parser (Bool -> Mode) -> Parser Bool -> Parser Mode
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Bool
parseCache)
Parser Mode -> Parser Mode -> Parser Mode
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Group -> String -> String -> Parser Mode -> Parser Mode
forall a. Group -> String -> String -> Parser a -> Parser a
subcommand
Group
Miscellaneous
String
"package"
String
"Create a package.dhall referencing the provided paths"
(Maybe String -> NonEmpty String -> Mode
Package (Maybe String -> NonEmpty String -> Mode)
-> Parser (Maybe String) -> Parser (NonEmpty String -> Mode)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser (Maybe String)
parsePackageName Parser (NonEmpty String -> Mode)
-> Parser (NonEmpty String) -> Parser Mode
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser (NonEmpty String)
parsePackageFiles)
Parser Mode -> Parser Mode -> Parser Mode
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Group -> String -> String -> Parser Mode -> Parser Mode
forall a. Group -> String -> String -> Parser a -> Parser a
subcommand
Group
Miscellaneous
String
"tags"
String
"Generate etags file"
(Input -> Output -> Maybe [Text] -> Bool -> Mode
Tags (Input -> Output -> Maybe [Text] -> Bool -> Mode)
-> Parser Input -> Parser (Output -> Maybe [Text] -> Bool -> Mode)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Input
parseInput Parser (Output -> Maybe [Text] -> Bool -> Mode)
-> Parser Output -> Parser (Maybe [Text] -> Bool -> Mode)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Output
parseTagsOutput Parser (Maybe [Text] -> Bool -> Mode)
-> Parser (Maybe [Text]) -> Parser (Bool -> Mode)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser (Maybe [Text])
parseSuffixes Parser (Bool -> Mode) -> Parser Bool -> Parser Mode
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Bool
parseFollowSymlinks)
Parser Mode -> Parser Mode -> Parser Mode
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Group -> String -> String -> Parser Mode -> Parser Mode
forall a. Group -> String -> String -> Parser a -> Parser a
subcommand
Group
Miscellaneous
String
"version"
String
"Display version"
(Mode -> Parser Mode
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Mode
Version)
Parser Mode -> Parser Mode -> Parser Mode
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Group -> String -> String -> Parser Mode -> Parser Mode
forall a. Group -> String -> String -> Parser a -> Parser a
subcommand
Group
Debugging
String
"haskell-syntax-tree"
String
"Output the parsed syntax tree (for debugging)"
(Input -> Bool -> Mode
SyntaxTree (Input -> Bool -> Mode) -> Parser Input -> Parser (Bool -> Mode)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Input
parseFile Parser (Bool -> Mode) -> Parser Bool -> Parser Mode
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Bool
parseNoted)
Parser Mode -> Parser Mode -> Parser Mode
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ( Input
-> Output -> Bool -> Bool -> SemanticCacheMode -> Bool -> Mode
Default
(Input
-> Output -> Bool -> Bool -> SemanticCacheMode -> Bool -> Mode)
-> Parser Input
-> Parser
(Output -> Bool -> Bool -> SemanticCacheMode -> Bool -> Mode)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Input
parseFile
Parser
(Output -> Bool -> Bool -> SemanticCacheMode -> Bool -> Mode)
-> Parser Output
-> Parser (Bool -> Bool -> SemanticCacheMode -> Bool -> Mode)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Output
parseOutput
Parser (Bool -> Bool -> SemanticCacheMode -> Bool -> Mode)
-> Parser Bool
-> Parser (Bool -> SemanticCacheMode -> Bool -> Mode)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Bool
parseAnnotate
Parser (Bool -> SemanticCacheMode -> Bool -> Mode)
-> Parser Bool -> Parser (SemanticCacheMode -> Bool -> Mode)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Bool
parseAlpha
Parser (SemanticCacheMode -> Bool -> Mode)
-> Parser SemanticCacheMode -> Parser (Bool -> Mode)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser SemanticCacheMode
parseSemanticCacheMode
Parser (Bool -> Mode) -> Parser Bool -> Parser Mode
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Bool
parseVersion
)
where
deprecatedInPlace :: Parser Bool
deprecatedInPlace =
Mod FlagFields Bool -> Parser Bool
Options.Applicative.switch
( String -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => String -> Mod f a
Options.Applicative.long String
"inplace"
Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<> Mod FlagFields Bool
forall (f :: * -> *) a. Mod f a
Options.Applicative.internal
)
argument :: String -> Parser Text
argument =
(String -> Text) -> Parser String -> Parser Text
forall a b. (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap String -> Text
Data.Text.pack
(Parser String -> Parser Text)
-> (String -> Parser String) -> String -> Parser Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Mod ArgumentFields String -> Parser String
forall s. IsString s => Mod ArgumentFields s -> Parser s
Options.Applicative.strArgument
(Mod ArgumentFields String -> Parser String)
-> (String -> Mod ArgumentFields String) -> String -> Parser String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Mod ArgumentFields String
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
Options.Applicative.metavar
parseFile :: Parser Input
parseFile = (Maybe String -> Input) -> Parser (Maybe String) -> Parser Input
forall a b. (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Maybe String -> Input
f (Parser String -> Parser (Maybe String)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional Parser String
p)
where
f :: Maybe String -> Input
f Maybe String
Nothing = Input
StandardInput
f (Just String
file) = String -> Input
InputFile String
file
p :: Parser String
p = Mod OptionFields String -> Parser String
forall s. IsString s => Mod OptionFields s -> Parser s
Options.Applicative.strOption
( String -> Mod OptionFields String
forall (f :: * -> *) a. HasName f => String -> Mod f a
Options.Applicative.long String
"file"
Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields String
forall (f :: * -> *) a. String -> Mod f a
Options.Applicative.help String
"Read expression from a file instead of standard input"
Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields String
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
Options.Applicative.metavar String
"FILE"
Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields String
forall (f :: * -> *) a. HasCompleter f => String -> Mod f a
Options.Applicative.action String
"file"
)
parseFiles :: Parser (NonEmpty Input)
parseFiles = ([String] -> NonEmpty Input)
-> Parser [String] -> Parser (NonEmpty Input)
forall a b. (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [String] -> NonEmpty Input
f (Parser String -> Parser [String]
forall a. Parser a -> Parser [a]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
Options.Applicative.many Parser String
p)
where
parseStdin :: [Input] -> [Input]
parseStdin [Input]
inputs
| String -> Input
InputFile String
"-" Input -> [Input] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Input]
inputs = Input
StandardInput Input -> [Input] -> [Input]
forall a. a -> [a] -> [a]
: (Input -> Bool) -> [Input] -> [Input]
forall a. (a -> Bool) -> [a] -> [a]
filter (Input -> Input -> Bool
forall a. Eq a => a -> a -> Bool
/= String -> Input
InputFile String
"-") [Input]
inputs
| Bool
otherwise = [Input]
inputs
f :: [String] -> NonEmpty Input
f = NonEmpty Input -> Maybe (NonEmpty Input) -> NonEmpty Input
forall a. a -> Maybe a -> a
fromMaybe (Input -> NonEmpty Input
forall a. a -> NonEmpty a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Input
StandardInput) (Maybe (NonEmpty Input) -> NonEmpty Input)
-> ([String] -> Maybe (NonEmpty Input))
-> [String]
-> NonEmpty Input
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Input] -> Maybe (NonEmpty Input)
forall a. [a] -> Maybe (NonEmpty a)
nonEmpty ([Input] -> Maybe (NonEmpty Input))
-> ([String] -> [Input]) -> [String] -> Maybe (NonEmpty Input)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Input] -> [Input]
parseStdin ([Input] -> [Input])
-> ([String] -> [Input]) -> [String] -> [Input]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String -> Input) -> [String] -> [Input]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap String -> Input
InputFile
p :: Parser String
p = Mod ArgumentFields String -> Parser String
forall s. IsString s => Mod ArgumentFields s -> Parser s
Options.Applicative.strArgument
( String -> Mod ArgumentFields String
forall (f :: * -> *) a. String -> Mod f a
Options.Applicative.help String
"Read expression from files instead of standard input"
Mod ArgumentFields String
-> Mod ArgumentFields String -> Mod ArgumentFields String
forall a. Semigroup a => a -> a -> a
<> String -> Mod ArgumentFields String
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
Options.Applicative.metavar String
"FILES"
Mod ArgumentFields String
-> Mod ArgumentFields String -> Mod ArgumentFields String
forall a. Semigroup a => a -> a -> a
<> String -> Mod ArgumentFields String
forall (f :: * -> *) a. HasCompleter f => String -> Mod f a
Options.Applicative.action String
"file"
)
parseOutput :: Parser Output
parseOutput = (Maybe String -> Output) -> Parser (Maybe String) -> Parser Output
forall a b. (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Maybe String -> Output
f (Parser String -> Parser (Maybe String)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional Parser String
p)
where
f :: Maybe String -> Output
f Maybe String
Nothing = Output
StandardOutput
f (Just String
file) = String -> Output
OutputFile String
file
p :: Parser String
p = Mod OptionFields String -> Parser String
forall s. IsString s => Mod OptionFields s -> Parser s
Options.Applicative.strOption
( String -> Mod OptionFields String
forall (f :: * -> *) a. HasName f => String -> Mod f a
Options.Applicative.long String
"output"
Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields String
forall (f :: * -> *) a. String -> Mod f a
Options.Applicative.help String
"Write result to a file instead of standard output"
Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields String
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
Options.Applicative.metavar String
"FILE"
Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields String
forall (f :: * -> *) a. HasCompleter f => String -> Mod f a
Options.Applicative.action String
"file"
)
parseAlpha :: Parser Bool
parseAlpha =
Mod FlagFields Bool -> Parser Bool
Options.Applicative.switch
( String -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => String -> Mod f a
Options.Applicative.long String
"alpha"
Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<> String -> Mod FlagFields Bool
forall (f :: * -> *) a. String -> Mod f a
Options.Applicative.help String
"α-normalize expression"
)
parseAnnotate :: Parser Bool
parseAnnotate =
Mod FlagFields Bool -> Parser Bool
Options.Applicative.switch
( String -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => String -> Mod f a
Options.Applicative.long String
"annotate"
Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<> String -> Mod FlagFields Bool
forall (f :: * -> *) a. String -> Mod f a
Options.Applicative.help String
"Add a type annotation to the output"
)
parseSemanticCacheMode :: Parser SemanticCacheMode
parseSemanticCacheMode =
SemanticCacheMode
-> SemanticCacheMode
-> Mod FlagFields SemanticCacheMode
-> Parser SemanticCacheMode
forall a. a -> a -> Mod FlagFields a -> Parser a
Options.Applicative.flag
SemanticCacheMode
UseSemanticCache
SemanticCacheMode
IgnoreSemanticCache
( String -> Mod FlagFields SemanticCacheMode
forall (f :: * -> *) a. HasName f => String -> Mod f a
Options.Applicative.long String
"no-cache"
Mod FlagFields SemanticCacheMode
-> Mod FlagFields SemanticCacheMode
-> Mod FlagFields SemanticCacheMode
forall a. Semigroup a => a -> a -> a
<> String -> Mod FlagFields SemanticCacheMode
forall (f :: * -> *) a. String -> Mod f a
Options.Applicative.help
String
"Handle protected imports as if the cache was empty"
)
parseVersion :: Parser Bool
parseVersion =
Mod FlagFields Bool -> Parser Bool
Options.Applicative.switch
( String -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => String -> Mod f a
Options.Applicative.long String
"version"
Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<> String -> Mod FlagFields Bool
forall (f :: * -> *) a. String -> Mod f a
Options.Applicative.help String
"Display version"
)
parseResolveMode :: Parser (Maybe ResolveMode)
parseResolveMode =
Maybe ResolveMode
-> Mod FlagFields (Maybe ResolveMode) -> Parser (Maybe ResolveMode)
forall a. a -> Mod FlagFields a -> Parser a
Options.Applicative.flag' (ResolveMode -> Maybe ResolveMode
forall a. a -> Maybe a
Just ResolveMode
Dot)
( String -> Mod FlagFields (Maybe ResolveMode)
forall (f :: * -> *) a. HasName f => String -> Mod f a
Options.Applicative.long String
"dot"
Mod FlagFields (Maybe ResolveMode)
-> Mod FlagFields (Maybe ResolveMode)
-> Mod FlagFields (Maybe ResolveMode)
forall a. Semigroup a => a -> a -> a
<> String -> Mod FlagFields (Maybe ResolveMode)
forall (f :: * -> *) a. String -> Mod f a
Options.Applicative.help
String
"Output import dependency graph in dot format"
)
Parser (Maybe ResolveMode)
-> Parser (Maybe ResolveMode) -> Parser (Maybe ResolveMode)
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
Maybe ResolveMode
-> Mod FlagFields (Maybe ResolveMode) -> Parser (Maybe ResolveMode)
forall a. a -> Mod FlagFields a -> Parser a
Options.Applicative.flag' (ResolveMode -> Maybe ResolveMode
forall a. a -> Maybe a
Just ResolveMode
ListImmediateDependencies)
( String -> Mod FlagFields (Maybe ResolveMode)
forall (f :: * -> *) a. HasName f => String -> Mod f a
Options.Applicative.long String
"immediate-dependencies"
Mod FlagFields (Maybe ResolveMode)
-> Mod FlagFields (Maybe ResolveMode)
-> Mod FlagFields (Maybe ResolveMode)
forall a. Semigroup a => a -> a -> a
<> String -> Mod FlagFields (Maybe ResolveMode)
forall (f :: * -> *) a. String -> Mod f a
Options.Applicative.help
String
"List immediate import dependencies"
)
Parser (Maybe ResolveMode)
-> Parser (Maybe ResolveMode) -> Parser (Maybe ResolveMode)
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
Maybe ResolveMode
-> Mod FlagFields (Maybe ResolveMode) -> Parser (Maybe ResolveMode)
forall a. a -> Mod FlagFields a -> Parser a
Options.Applicative.flag' (ResolveMode -> Maybe ResolveMode
forall a. a -> Maybe a
Just ResolveMode
ListTransitiveDependencies)
( String -> Mod FlagFields (Maybe ResolveMode)
forall (f :: * -> *) a. HasName f => String -> Mod f a
Options.Applicative.long String
"transitive-dependencies"
Mod FlagFields (Maybe ResolveMode)
-> Mod FlagFields (Maybe ResolveMode)
-> Mod FlagFields (Maybe ResolveMode)
forall a. Semigroup a => a -> a -> a
<> String -> Mod FlagFields (Maybe ResolveMode)
forall (f :: * -> *) a. String -> Mod f a
Options.Applicative.help
String
"List transitive import dependencies in post-order"
)
Parser (Maybe ResolveMode)
-> Parser (Maybe ResolveMode) -> Parser (Maybe ResolveMode)
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Maybe ResolveMode -> Parser (Maybe ResolveMode)
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe ResolveMode
forall a. Maybe a
Nothing
parseQuiet :: Parser Bool
parseQuiet =
Mod FlagFields Bool -> Parser Bool
Options.Applicative.switch
( String -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => String -> Mod f a
Options.Applicative.long String
"quiet"
Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<> String -> Mod FlagFields Bool
forall (f :: * -> *) a. String -> Mod f a
Options.Applicative.help String
"Don't print the result"
)
parseInplace :: Parser String
parseInplace =
Mod OptionFields String -> Parser String
forall s. IsString s => Mod OptionFields s -> Parser s
Options.Applicative.strOption
( String -> Mod OptionFields String
forall (f :: * -> *) a. HasName f => String -> Mod f a
Options.Applicative.long String
"inplace"
Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields String
forall (f :: * -> *) a. String -> Mod f a
Options.Applicative.help String
"Modify the specified file in-place"
Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields String
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
Options.Applicative.metavar String
"FILE"
Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields String
forall (f :: * -> *) a. HasCompleter f => String -> Mod f a
Options.Applicative.action String
"file"
)
parseTransitiveSwitch :: Parser Transitivity
parseTransitiveSwitch = Transitivity
-> Transitivity
-> Mod FlagFields Transitivity
-> Parser Transitivity
forall a. a -> a -> Mod FlagFields a -> Parser a
Options.Applicative.flag Transitivity
NonTransitive Transitivity
Transitive
( String -> Mod FlagFields Transitivity
forall (f :: * -> *) a. HasName f => String -> Mod f a
Options.Applicative.long String
"transitive"
Mod FlagFields Transitivity
-> Mod FlagFields Transitivity -> Mod FlagFields Transitivity
forall a. Semigroup a => a -> a -> a
<> String -> Mod FlagFields Transitivity
forall (f :: * -> *) a. String -> Mod f a
Options.Applicative.help String
"Modify the input and its transitive relative imports in-place"
)
parseInplaceNonTransitive :: Parser Input
parseInplaceNonTransitive =
(String -> Input) -> Parser String -> Parser Input
forall a b. (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap String -> Input
InputFile Parser String
parseInplace
Parser Input -> Parser Input -> Parser Input
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Input -> Parser Input
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Input
StandardInput
parseInput :: Parser Input
parseInput = (Maybe String -> Input) -> Parser (Maybe String) -> Parser Input
forall a b. (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Maybe String -> Input
f (Parser String -> Parser (Maybe String)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional Parser String
p)
where
f :: Maybe String -> Input
f Maybe String
Nothing = Input
StandardInput
f (Just String
path) = String -> Input
InputFile String
path
p :: Parser String
p = Mod OptionFields String -> Parser String
forall s. IsString s => Mod OptionFields s -> Parser s
Options.Applicative.strOption
( String -> Mod OptionFields String
forall (f :: * -> *) a. HasName f => String -> Mod f a
Options.Applicative.long String
"path"
Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields String
forall (f :: * -> *) a. String -> Mod f a
Options.Applicative.help String
"Index all files in path recursively. Will get list of files from STDIN if omitted."
Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields String
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
Options.Applicative.metavar String
"PATH"
Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields String
forall (f :: * -> *) a. HasCompleter f => String -> Mod f a
Options.Applicative.action String
"file"
Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields String
forall (f :: * -> *) a. HasCompleter f => String -> Mod f a
Options.Applicative.action String
"directory"
)
parseTagsOutput :: Parser Output
parseTagsOutput = (Maybe String -> Output) -> Parser (Maybe String) -> Parser Output
forall a b. (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Maybe String -> Output
f (Parser String -> Parser (Maybe String)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional Parser String
p)
where
f :: Maybe String -> Output
f Maybe String
Nothing = String -> Output
OutputFile String
"tags"
f (Just String
file) = String -> Output
OutputFile String
file
p :: Parser String
p = Mod OptionFields String -> Parser String
forall s. IsString s => Mod OptionFields s -> Parser s
Options.Applicative.strOption
( String -> Mod OptionFields String
forall (f :: * -> *) a. HasName f => String -> Mod f a
Options.Applicative.long String
"output"
Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields String
forall (f :: * -> *) a. String -> Mod f a
Options.Applicative.help String
"The name of the file that the tags are written to. Defaults to \"tags\""
Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields String
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
Options.Applicative.metavar String
"FILENAME"
Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields String
forall (f :: * -> *) a. HasCompleter f => String -> Mod f a
Options.Applicative.action String
"file"
)
parseSuffixes :: Parser (Maybe [Text])
parseSuffixes = (Maybe Text -> Maybe [Text])
-> Parser (Maybe Text) -> Parser (Maybe [Text])
forall a b. (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Maybe Text -> Maybe [Text]
f (Parser Text -> Parser (Maybe Text)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional Parser Text
p)
where
f :: Maybe Text -> Maybe [Text]
f Maybe Text
Nothing = [Text] -> Maybe [Text]
forall a. a -> Maybe a
Just [Text
".dhall"]
f (Just Text
"") = Maybe [Text]
forall a. Maybe a
Nothing
f (Just Text
line) = [Text] -> Maybe [Text]
forall a. a -> Maybe a
Just (HasCallStack => Text -> Text -> [Text]
Text -> Text -> [Text]
Data.Text.splitOn Text
" " Text
line)
p :: Parser Text
p = Mod OptionFields Text -> Parser Text
forall s. IsString s => Mod OptionFields s -> Parser s
Options.Applicative.strOption
( String -> Mod OptionFields Text
forall (f :: * -> *) a. HasName f => String -> Mod f a
Options.Applicative.long String
"suffixes"
Mod OptionFields Text
-> Mod OptionFields Text -> Mod OptionFields Text
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields Text
forall (f :: * -> *) a. String -> Mod f a
Options.Applicative.help String
"Index only files with suffixes. \"\" to index all files."
Mod OptionFields Text
-> Mod OptionFields Text -> Mod OptionFields Text
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields Text
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
Options.Applicative.metavar String
"SUFFIXES"
)
parseFollowSymlinks :: Parser Bool
parseFollowSymlinks =
Mod FlagFields Bool -> Parser Bool
Options.Applicative.switch
( String -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => String -> Mod f a
Options.Applicative.long String
"follow-symlinks"
Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<> String -> Mod FlagFields Bool
forall (f :: * -> *) a. String -> Mod f a
Options.Applicative.help String
"Follow symlinks when recursing directories"
)
parseJSONFlag :: Parser Bool
parseJSONFlag =
Mod FlagFields Bool -> Parser Bool
Options.Applicative.switch
( String -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => String -> Mod f a
Options.Applicative.long String
"json"
Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<> String -> Mod FlagFields Bool
forall (f :: * -> *) a. String -> Mod f a
Options.Applicative.help String
"Use JSON representation of CBOR"
)
parseAllFlag :: Parser Bool
parseAllFlag =
Mod FlagFields Bool -> Parser Bool
Options.Applicative.switch
( String -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => String -> Mod f a
Options.Applicative.long String
"all"
Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<> String -> Mod FlagFields Bool
forall (f :: * -> *) a. String -> Mod f a
Options.Applicative.help String
"Add integrity checks to all imports (not just remote imports) except for missing imports"
)
parseCacheFlag :: Parser Bool
parseCacheFlag =
Mod FlagFields Bool -> Parser Bool
Options.Applicative.switch
( String -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => String -> Mod f a
Options.Applicative.long String
"cache"
Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<> String -> Mod FlagFields Bool
forall (f :: * -> *) a. String -> Mod f a
Options.Applicative.help String
"Add fallback unprotected imports when using integrity checks purely for caching purposes"
)
parseCheck :: String -> Parser OutputMode
parseCheck String
processed = (Bool -> OutputMode) -> Parser Bool -> Parser OutputMode
forall a b. (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Bool -> OutputMode
adapt Parser Bool
switch
where
adapt :: Bool -> OutputMode
adapt Bool
True = OutputMode
Check
adapt Bool
False = OutputMode
Write
switch :: Parser Bool
switch =
Mod FlagFields Bool -> Parser Bool
Options.Applicative.switch
( String -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => String -> Mod f a
Options.Applicative.long String
"check"
Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<> String -> Mod FlagFields Bool
forall (f :: * -> *) a. String -> Mod f a
Options.Applicative.help (String
"Only check if the input is " String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
processed)
)
parseSchemasRecord :: Parser Text
parseSchemasRecord =
Mod OptionFields Text -> Parser Text
forall s. IsString s => Mod OptionFields s -> Parser s
Options.Applicative.strOption
( String -> Mod OptionFields Text
forall (f :: * -> *) a. HasName f => String -> Mod f a
Options.Applicative.long String
"schemas"
Mod OptionFields Text
-> Mod OptionFields Text -> Mod OptionFields Text
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields Text
forall (f :: * -> *) a. String -> Mod f a
Options.Applicative.help String
"A record of schemas"
Mod OptionFields Text
-> Mod OptionFields Text -> Mod OptionFields Text
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields Text
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
Options.Applicative.metavar String
"EXPR"
)
parseDirectoryTreeAllowSeparators :: Parser Bool
parseDirectoryTreeAllowSeparators =
Mod FlagFields Bool -> Parser Bool
Options.Applicative.switch
( String -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => String -> Mod f a
Options.Applicative.long String
"allow-path-separators"
Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<> String -> Mod FlagFields Bool
forall (f :: * -> *) a. String -> Mod f a
Options.Applicative.help String
"Whether to allow path separators in file names"
)
parseDirectoryTreeOutput :: Parser String
parseDirectoryTreeOutput =
Mod OptionFields String -> Parser String
forall s. IsString s => Mod OptionFields s -> Parser s
Options.Applicative.strOption
( String -> Mod OptionFields String
forall (f :: * -> *) a. HasName f => String -> Mod f a
Options.Applicative.long String
"output"
Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields String
forall (f :: * -> *) a. String -> Mod f a
Options.Applicative.help String
"The destination path to create"
Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields String
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
Options.Applicative.metavar String
"PATH"
Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields String
forall (f :: * -> *) a. HasCompleter f => String -> Mod f a
Options.Applicative.action String
"directory"
)
parseNoted :: Parser Bool
parseNoted =
Mod FlagFields Bool -> Parser Bool
Options.Applicative.switch
( String -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => String -> Mod f a
Options.Applicative.long String
"noted"
Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<> String -> Mod FlagFields Bool
forall (f :: * -> *) a. String -> Mod f a
Options.Applicative.help String
"Print `Note` constructors"
)
parseCache :: Parser Bool
parseCache =
Mod FlagFields Bool -> Parser Bool
Options.Applicative.switch
( String -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => String -> Mod f a
Options.Applicative.long String
"cache"
Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<> String -> Mod FlagFields Bool
forall (f :: * -> *) a. String -> Mod f a
Options.Applicative.help String
"Cache the hashed expression"
)
parsePackageName :: Parser (Maybe String)
parsePackageName = Parser String -> Parser (Maybe String)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (Parser String -> Parser (Maybe String))
-> Parser String -> Parser (Maybe String)
forall a b. (a -> b) -> a -> b
$
Mod OptionFields String -> Parser String
forall s. IsString s => Mod OptionFields s -> Parser s
Options.Applicative.strOption
( String -> Mod OptionFields String
forall (f :: * -> *) a. HasName f => String -> Mod f a
Options.Applicative.long String
"name"
Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields String
forall (f :: * -> *) a. String -> Mod f a
Options.Applicative.help String
"The filename of the package"
Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields String
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
Options.Applicative.metavar String
"NAME"
Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields String
forall (f :: * -> *) a. HasCompleter f => String -> Mod f a
Options.Applicative.action String
"file"
)
parsePackageFiles :: Parser (NonEmpty String)
parsePackageFiles = String -> [String] -> NonEmpty String
forall a. a -> [a] -> NonEmpty a
(:|) (String -> [String] -> NonEmpty String)
-> Parser String -> Parser ([String] -> NonEmpty String)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser String
p Parser ([String] -> NonEmpty String)
-> Parser [String] -> Parser (NonEmpty String)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser String -> Parser [String]
forall a. Parser a -> Parser [a]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
Options.Applicative.many Parser String
p
where
p :: Parser String
p = Mod ArgumentFields String -> Parser String
forall s. IsString s => Mod ArgumentFields s -> Parser s
Options.Applicative.strArgument
( String -> Mod ArgumentFields String
forall (f :: * -> *) a. String -> Mod f a
Options.Applicative.help String
"Paths that may either point to files or directories. If the latter is the case all *.dhall files in the directory will be included."
Mod ArgumentFields String
-> Mod ArgumentFields String -> Mod ArgumentFields String
forall a. Semigroup a => a -> a -> a
<> String -> Mod ArgumentFields String
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
Options.Applicative.metavar String
"PATH"
Mod ArgumentFields String
-> Mod ArgumentFields String -> Mod ArgumentFields String
forall a. Semigroup a => a -> a -> a
<> String -> Mod ArgumentFields String
forall (f :: * -> *) a. HasCompleter f => String -> Mod f a
Options.Applicative.action String
"file"
)
parserInfoOptions :: ParserInfo Options
parserInfoOptions :: ParserInfo Options
parserInfoOptions =
Parser Options -> InfoMod Options -> ParserInfo Options
forall a. Parser a -> InfoMod a -> ParserInfo a
Options.Applicative.info
(Parser (Options -> Options)
forall a. Parser (a -> a)
Options.Applicative.helper Parser (Options -> Options) -> Parser Options -> Parser Options
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Options
parseOptions)
( String -> InfoMod Options
forall a. String -> InfoMod a
Options.Applicative.progDesc String
"Interpreter for the Dhall language"
InfoMod Options -> InfoMod Options -> InfoMod Options
forall a. Semigroup a => a -> a -> a
<> InfoMod Options
forall a. InfoMod a
Options.Applicative.fullDesc
)
noHeaders :: Import -> Import
(Import { importHashed :: Import -> ImportHashed
importHashed = ImportHashed { importType :: ImportHashed -> ImportType
importType = Remote URL{ Maybe Text
Maybe (Expr Src Import)
Text
Scheme
File
scheme :: Scheme
authority :: Text
path :: File
query :: Maybe Text
headers :: Maybe (Expr Src Import)
scheme :: URL -> Scheme
authority :: URL -> Text
path :: URL -> File
query :: URL -> Maybe Text
headers :: URL -> Maybe (Expr Src Import)
.. }, Maybe SHA256Digest
hash :: Maybe SHA256Digest
hash :: ImportHashed -> Maybe SHA256Digest
..}, ImportMode
importMode :: ImportMode
importMode :: Import -> ImportMode
.. }) =
Import { importHashed :: ImportHashed
importHashed = ImportHashed { importType :: ImportType
importType = URL -> ImportType
Remote URL{ headers :: Maybe (Expr Src Import)
headers = Maybe (Expr Src Import)
forall a. Maybe a
Nothing, Maybe Text
Text
Scheme
File
scheme :: Scheme
authority :: Text
path :: File
query :: Maybe Text
scheme :: Scheme
authority :: Text
path :: File
query :: Maybe Text
.. }, Maybe SHA256Digest
hash :: Maybe SHA256Digest
hash :: Maybe SHA256Digest
.. }, ImportMode
importMode :: ImportMode
importMode :: ImportMode
.. }
noHeaders Import
i =
Import
i
command :: Options -> IO ()
command :: Options -> IO ()
command (Options {Bool
Maybe CharacterSet
Censor
Mode
mode :: Options -> Mode
explain :: Options -> Bool
plain :: Options -> Bool
chosenCharacterSet :: Options -> Maybe CharacterSet
censor :: Options -> Censor
mode :: Mode
explain :: Bool
plain :: Bool
chosenCharacterSet :: Maybe CharacterSet
censor :: Censor
..}) = do
TextEncoding -> IO ()
GHC.IO.Encoding.setLocaleEncoding TextEncoding
System.IO.utf8
let rootDirectory :: Input -> String
rootDirectory = \case
InputFile String
f -> String -> String
System.FilePath.takeDirectory String
f
Input
StandardInput -> String
"."
let toStatus :: Input -> Status
toStatus = String -> Status
Dhall.Import.emptyStatus (String -> Status) -> (Input -> String) -> Input -> Status
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Input -> String
rootDirectory
let getExpression :: Input -> IO (Expr Src Import)
getExpression = Censor -> Input -> IO (Expr Src Import)
Dhall.Util.getExpression Censor
censor
let getExpressionAndCharacterSet :: Input -> IO (Expr Src Import, CharacterSet)
getExpressionAndCharacterSet Input
file = do
Expr Src Import
expr <- Input -> IO (Expr Src Import)
getExpression Input
file
let characterSet :: CharacterSet
characterSet = CharacterSet -> Maybe CharacterSet -> CharacterSet
forall a. a -> Maybe a -> a
fromMaybe (Expr Src Import -> CharacterSet
forall a. Expr Src a -> CharacterSet
detectCharacterSet Expr Src Import
expr) Maybe CharacterSet
chosenCharacterSet
(Expr Src Import, CharacterSet)
-> IO (Expr Src Import, CharacterSet)
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
return (Expr Src Import
expr, CharacterSet
characterSet)
let handle :: IO a -> IO a
handle IO a
io =
IO a -> [Handler a] -> IO a
forall a. IO a -> [Handler a] -> IO a
Control.Exception.catches IO a
io
[ (TypeError Src Void -> IO a) -> Handler a
forall a e. Exception e => (e -> IO a) -> Handler a
Handler TypeError Src Void -> IO a
forall {a}. TypeError Src Void -> IO a
handleTypeError
, (Imported (TypeError Src Void) -> IO a) -> Handler a
forall a e. Exception e => (e -> IO a) -> Handler a
Handler Imported (TypeError Src Void) -> IO a
forall {a}. Imported (TypeError Src Void) -> IO a
handleImported
, (ExitCode -> IO a) -> Handler a
forall a e. Exception e => (e -> IO a) -> Handler a
Handler ExitCode -> IO a
forall {a}. ExitCode -> IO a
handleExitCode
]
where
handleAll :: SomeException -> IO b
handleAll SomeException
e = do
let string :: String
string = SomeException -> String
forall a. Show a => a -> String
show (SomeException
e :: SomeException)
if Bool -> Bool
not (String -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
string)
then Handle -> String -> IO ()
System.IO.hPutStrLn Handle
System.IO.stderr String
string
else () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
IO b
forall a. IO a
System.Exit.exitFailure
handleTypeError :: TypeError Src Void -> IO a
handleTypeError TypeError Src Void
e = (SomeException -> IO a) -> IO a -> IO a
forall e a. Exception e => (e -> IO a) -> IO a -> IO a
Control.Exception.handle SomeException -> IO a
forall {b}. SomeException -> IO b
handleAll (IO a -> IO a) -> IO a -> IO a
forall a b. (a -> b) -> a -> b
$ do
let TypeError Src Void
_ = TypeError Src Void
e :: TypeError Src Void
Handle -> String -> IO ()
System.IO.hPutStrLn Handle
System.IO.stderr String
""
if Bool
explain
then
case Censor
censor of
Censor
Censor -> Censored -> IO a
forall e a. Exception e => e -> IO a
Control.Exception.throwIO (DetailedTypeError Src Void -> Censored
CensoredDetailed (TypeError Src Void -> DetailedTypeError Src Void
forall s a. TypeError s a -> DetailedTypeError s a
DetailedTypeError TypeError Src Void
e))
Censor
NoCensor -> DetailedTypeError Src Void -> IO a
forall e a. Exception e => e -> IO a
Control.Exception.throwIO (TypeError Src Void -> DetailedTypeError Src Void
forall s a. TypeError s a -> DetailedTypeError s a
DetailedTypeError TypeError Src Void
e)
else do
Handle -> Text -> IO ()
Data.Text.IO.hPutStrLn Handle
System.IO.stderr Text
"\ESC[2mUse \"dhall --explain\" for detailed errors\ESC[0m"
case Censor
censor of
Censor
Censor -> Censored -> IO a
forall e a. Exception e => e -> IO a
Control.Exception.throwIO (TypeError Src Void -> Censored
Censored TypeError Src Void
e)
Censor
NoCensor -> TypeError Src Void -> IO a
forall e a. Exception e => e -> IO a
Control.Exception.throwIO TypeError Src Void
e
handleImported :: Imported (TypeError Src Void) -> IO a
handleImported (Imported NonEmpty Chained
ps TypeError Src Void
e) = (SomeException -> IO a) -> IO a -> IO a
forall e a. Exception e => (e -> IO a) -> IO a -> IO a
Control.Exception.handle SomeException -> IO a
forall {b}. SomeException -> IO b
handleAll (IO a -> IO a) -> IO a -> IO a
forall a b. (a -> b) -> a -> b
$ do
let TypeError Src Void
_ = TypeError Src Void
e :: TypeError Src Void
Handle -> String -> IO ()
System.IO.hPutStrLn Handle
System.IO.stderr String
""
if Bool
explain
then Imported (DetailedTypeError Src Void) -> IO a
forall e a. Exception e => e -> IO a
Control.Exception.throwIO (NonEmpty Chained
-> DetailedTypeError Src Void
-> Imported (DetailedTypeError Src Void)
forall e. NonEmpty Chained -> e -> Imported e
Imported NonEmpty Chained
ps (TypeError Src Void -> DetailedTypeError Src Void
forall s a. TypeError s a -> DetailedTypeError s a
DetailedTypeError TypeError Src Void
e))
else do
Handle -> Text -> IO ()
Data.Text.IO.hPutStrLn Handle
System.IO.stderr Text
"\ESC[2mUse \"dhall --explain\" for detailed errors\ESC[0m"
Imported (TypeError Src Void) -> IO a
forall e a. Exception e => e -> IO a
Control.Exception.throwIO (NonEmpty Chained
-> TypeError Src Void -> Imported (TypeError Src Void)
forall e. NonEmpty Chained -> e -> Imported e
Imported NonEmpty Chained
ps TypeError Src Void
e)
handleExitCode :: ExitCode -> IO a
handleExitCode ExitCode
e =
ExitCode -> IO a
forall e a. Exception e => e -> IO a
Control.Exception.throwIO (ExitCode
e :: ExitCode)
let renderDoc :: Handle -> Doc Ann -> IO ()
renderDoc :: Handle -> Doc Ann -> IO ()
renderDoc Handle
h Doc Ann
doc = do
let stream :: SimpleDocStream Ann
stream = Doc Ann -> SimpleDocStream Ann
forall ann. Doc ann -> SimpleDocStream ann
Dhall.Pretty.layout Doc Ann
doc
Bool
supportsANSI <- Handle -> IO Bool
System.Console.ANSI.hSupportsANSI Handle
h
let ansiStream :: SimpleDocStream AnsiStyle
ansiStream =
if Bool
supportsANSI Bool -> Bool -> Bool
&& Bool -> Bool
not Bool
plain
then (Ann -> AnsiStyle)
-> SimpleDocStream Ann -> SimpleDocStream AnsiStyle
forall a b. (a -> b) -> SimpleDocStream a -> SimpleDocStream b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Ann -> AnsiStyle
annToAnsiStyle SimpleDocStream Ann
stream
else SimpleDocStream Ann -> SimpleDocStream AnsiStyle
forall ann xxx. SimpleDocStream ann -> SimpleDocStream xxx
Pretty.unAnnotateS SimpleDocStream Ann
stream
Handle -> SimpleDocStream AnsiStyle -> IO ()
Pretty.renderIO Handle
h SimpleDocStream AnsiStyle
ansiStream
Handle -> Text -> IO ()
Data.Text.IO.hPutStrLn Handle
h Text
""
let render :: Pretty a => Handle -> CharacterSet -> Expr Src a -> IO ()
render :: forall a. Pretty a => Handle -> CharacterSet -> Expr Src a -> IO ()
render Handle
h CharacterSet
characterSet Expr Src a
expression = do
let doc :: Doc Ann
doc = CharacterSet -> Expr Src a -> Doc Ann
forall a. Pretty a => CharacterSet -> Expr Src a -> Doc Ann
Dhall.Pretty.prettyCharacterSet CharacterSet
characterSet Expr Src a
expression
Handle -> Doc Ann -> IO ()
renderDoc Handle
h Doc Ann
doc
let writeDocToFile :: FilePath -> Doc ann -> IO ()
writeDocToFile :: forall ann. String -> Doc ann -> IO ()
writeDocToFile String
file Doc ann
doc = do
let stream :: SimpleDocStream ann
stream = Doc ann -> SimpleDocStream ann
forall ann. Doc ann -> SimpleDocStream ann
Dhall.Pretty.layout (Doc ann
doc Doc ann -> Doc ann -> Doc ann
forall a. Semigroup a => a -> a -> a
<> Doc ann
"\n")
String -> Text -> IO ()
AtomicWrite.LazyText.atomicWriteFile String
file (SimpleDocStream ann -> Text
forall ann. SimpleDocStream ann -> Text
Pretty.Text.renderLazy SimpleDocStream ann
stream)
IO () -> IO ()
handle (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ case Mode
mode of
Mode
Version ->
String -> IO ()
putStrLn String
dhallVersionString
Default {Bool
Output
Input
SemanticCacheMode
file :: Mode -> Input
output :: Mode -> Output
annotate :: Mode -> Bool
alpha :: Mode -> Bool
semanticCacheMode :: Mode -> SemanticCacheMode
version :: Mode -> Bool
file :: Input
output :: Output
annotate :: Bool
alpha :: Bool
semanticCacheMode :: SemanticCacheMode
version :: Bool
..} -> do
if Bool
version
then do
String -> IO ()
putStrLn String
dhallVersionString
IO ()
forall a. IO a
Exit.exitSuccess
else () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
(Expr Src Import
expression, CharacterSet
characterSet) <- Input -> IO (Expr Src Import, CharacterSet)
getExpressionAndCharacterSet Input
file
Expr Src Void
resolvedExpression <-
String
-> SemanticCacheMode -> Expr Src Import -> IO (Expr Src Void)
Dhall.Import.loadRelativeTo (Input -> String
rootDirectory Input
file) SemanticCacheMode
semanticCacheMode Expr Src Import
expression
Expr Src Void
inferredType <- Either (TypeError Src Void) (Expr Src Void) -> IO (Expr Src Void)
forall e (io :: * -> *) a.
(Exception e, MonadIO io) =>
Either e a -> io a
Dhall.Core.throws (Expr Src Void -> Either (TypeError Src Void) (Expr Src Void)
forall s. Expr s Void -> Either (TypeError s Void) (Expr s Void)
Dhall.TypeCheck.typeOf Expr Src Void
resolvedExpression)
let normalizedExpression :: Expr t Void
normalizedExpression = Expr Src Void -> Expr t Void
forall a s t. Eq a => Expr s a -> Expr t a
Dhall.Core.normalize Expr Src Void
resolvedExpression
let alphaNormalizedExpression :: Expr s Void
alphaNormalizedExpression =
if Bool
alpha
then Expr s Void -> Expr s Void
forall s a. Expr s a -> Expr s a
Dhall.Core.alphaNormalize Expr s Void
forall {t}. Expr t Void
normalizedExpression
else Expr s Void
forall {t}. Expr t Void
normalizedExpression
let annotatedExpression :: Expr Src Void
annotatedExpression =
if Bool
annotate
then Expr Src Void -> Expr Src Void -> Expr Src Void
forall s a. Expr s a -> Expr s a -> Expr s a
Annot Expr Src Void
forall {t}. Expr t Void
alphaNormalizedExpression Expr Src Void
inferredType
else Expr Src Void
forall {t}. Expr t Void
alphaNormalizedExpression
case Output
output of
Output
StandardOutput -> Handle -> CharacterSet -> Expr Src Void -> IO ()
render Handle
System.IO.stdout CharacterSet
characterSet Expr Src Void
annotatedExpression
OutputFile String
file_ ->
String -> Doc Ann -> IO ()
writeDocToFile
String
file_
(CharacterSet -> Expr Src Void -> Doc Ann
forall a. Pretty a => CharacterSet -> Expr Src a -> Doc Ann
Dhall.Pretty.prettyCharacterSet CharacterSet
characterSet Expr Src Void
annotatedExpression)
Resolve { resolveMode :: Mode -> Maybe ResolveMode
resolveMode = Just ResolveMode
Dot, Input
SemanticCacheMode
file :: Mode -> Input
semanticCacheMode :: Mode -> SemanticCacheMode
file :: Input
semanticCacheMode :: SemanticCacheMode
..} -> do
Expr Src Import
expression <- Input -> IO (Expr Src Import)
getExpression Input
file
(Dhall.Import.Types.Status { [Depends]
_graph :: [Depends]
_graph :: Status -> [Depends]
_graph, NonEmpty Chained
_stack :: NonEmpty Chained
_stack :: Status -> NonEmpty Chained
_stack }) <-
StateT Status IO (Expr Src Void) -> Status -> IO Status
forall (m :: * -> *) s a. Monad m => StateT s m a -> s -> m s
State.execStateT (Expr Src Import -> StateT Status IO (Expr Src Void)
Dhall.Import.loadWith Expr Src Import
expression) (Input -> Status
toStatus Input
file) { _semanticCacheMode = semanticCacheMode }
let (Chained
rootImport :| [Chained]
_) = NonEmpty Chained
_stack
imports :: [Chained]
imports = Chained
rootImport Chained -> [Chained] -> [Chained]
forall a. a -> [a] -> [a]
: (Depends -> Chained) -> [Depends] -> [Chained]
forall a b. (a -> b) -> [a] -> [b]
map Depends -> Chained
parent [Depends]
_graph [Chained] -> [Chained] -> [Chained]
forall a. [a] -> [a] -> [a]
++ (Depends -> Chained) -> [Depends] -> [Chained]
forall a b. (a -> b) -> [a] -> [b]
map Depends -> Chained
child [Depends]
_graph
importIds :: Map Chained NodeId
importIds = [(Chained, NodeId)] -> Map Chained NodeId
forall k a. Ord k => [(k, a)] -> Map k a
Data.Map.fromList ([Chained] -> [NodeId] -> [(Chained, NodeId)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Chained]
imports [Int -> NodeId
Text.Dot.userNodeId Int
i | Int
i <- [Int
0..]])
let dotNode :: (Chained, NodeId) -> Dot ()
dotNode (Chained
i, NodeId
nodeId) =
NodeId -> [(String, String)] -> Dot ()
Text.Dot.userNode
NodeId
nodeId
[ (String
"label", Text -> String
Data.Text.unpack (Text -> String) -> Text -> String
forall a b. (a -> b) -> a -> b
$ Import -> Text
forall a. Pretty a => a -> Text
pretty (Chained -> Import
convert Chained
i))
, (String
"shape", String
"box")
, (String
"style", String
"rounded")
]
where
convert :: Chained -> Import
convert = Import -> Import
noHeaders (Import -> Import) -> (Chained -> Import) -> Chained -> Import
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Chained -> Import
Dhall.Import.chainedImport
let dotEdge :: Depends -> Dot ()
dotEdge (Depends Chained
parent Chained
child) =
case (Chained -> Map Chained NodeId -> Maybe NodeId
forall k a. Ord k => k -> Map k a -> Maybe a
Data.Map.lookup Chained
parent Map Chained NodeId
importIds, Chained -> Map Chained NodeId -> Maybe NodeId
forall k a. Ord k => k -> Map k a -> Maybe a
Data.Map.lookup Chained
child Map Chained NodeId
importIds) of
(Just NodeId
from, Just NodeId
to) -> NodeId
from NodeId -> NodeId -> Dot ()
.->. NodeId
to
(Maybe NodeId, Maybe NodeId)
_ -> () -> Dot ()
forall a. a -> Dot a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
let dot :: Dot ()
dot = do (String, String) -> Dot ()
Text.Dot.attribute (String
"rankdir", String
"LR")
((Chained, NodeId) -> Dot ()) -> [(Chained, NodeId)] -> Dot ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (Chained, NodeId) -> Dot ()
dotNode (Map Chained NodeId -> [(Chained, NodeId)]
forall k a. Map k a -> [(k, a)]
Data.Map.assocs Map Chained NodeId
importIds)
(Depends -> Dot ()) -> [Depends] -> Dot ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ Depends -> Dot ()
dotEdge [Depends]
_graph
String -> IO ()
putStr (String -> IO ()) -> (Dot () -> String) -> Dot () -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String
"strict " String -> String -> String
forall a. Semigroup a => a -> a -> a
<>) (String -> String) -> (Dot () -> String) -> Dot () -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Dot () -> String
forall a. Dot a -> String
Text.Dot.showDot (Dot () -> IO ()) -> Dot () -> IO ()
forall a b. (a -> b) -> a -> b
$ Dot ()
dot
Resolve { resolveMode :: Mode -> Maybe ResolveMode
resolveMode = Just ResolveMode
ListImmediateDependencies, Input
SemanticCacheMode
file :: Mode -> Input
semanticCacheMode :: Mode -> SemanticCacheMode
file :: Input
semanticCacheMode :: SemanticCacheMode
..} -> do
Expr Src Import
expression <- Input -> IO (Expr Src Import)
getExpression Input
file
(Import -> IO ()) -> Expr Src Import -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (Doc Any -> IO ()
forall a. Show a => a -> IO ()
print (Doc Any -> IO ()) -> (Import -> Doc Any) -> Import -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Import -> Doc Any
forall a ann. Pretty a => a -> Doc ann
forall ann. Import -> Doc ann
Pretty.pretty (Import -> Doc Any) -> (Import -> Import) -> Import -> Doc Any
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Import -> Import
noHeaders) Expr Src Import
expression
Resolve { resolveMode :: Mode -> Maybe ResolveMode
resolveMode = Just ResolveMode
ListTransitiveDependencies, Input
SemanticCacheMode
file :: Mode -> Input
semanticCacheMode :: Mode -> SemanticCacheMode
file :: Input
semanticCacheMode :: SemanticCacheMode
..} -> do
Expr Src Import
expression <- Input -> IO (Expr Src Import)
getExpression Input
file
(Dhall.Import.Types.Status { Map Chained ImportSemantics
_cache :: Map Chained ImportSemantics
_cache :: Status -> Map Chained ImportSemantics
_cache }) <-
StateT Status IO (Expr Src Void) -> Status -> IO Status
forall (m :: * -> *) s a. Monad m => StateT s m a -> s -> m s
State.execStateT (Expr Src Import -> StateT Status IO (Expr Src Void)
Dhall.Import.loadWith Expr Src Import
expression) (Input -> Status
toStatus Input
file) { _semanticCacheMode = semanticCacheMode }
(Doc Any -> IO ()) -> [Doc Any] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ Doc Any -> IO ()
forall a. Show a => a -> IO ()
print
([Doc Any] -> IO ())
-> (Map Chained ImportSemantics -> [Doc Any])
-> Map Chained ImportSemantics
-> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Chained -> Doc Any) -> [Chained] -> [Doc Any]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ( Import -> Doc Any
forall a ann. Pretty a => a -> Doc ann
forall ann. Import -> Doc ann
Pretty.pretty
(Import -> Doc Any) -> (Chained -> Import) -> Chained -> Doc Any
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Import -> Import
noHeaders
(Import -> Import) -> (Chained -> Import) -> Chained -> Import
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Chained -> Import
Dhall.Import.chainedImport
)
([Chained] -> [Doc Any])
-> (Map Chained ImportSemantics -> [Chained])
-> Map Chained ImportSemantics
-> [Doc Any]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Chained] -> [Chained]
forall a. [a] -> [a]
reverse
([Chained] -> [Chained])
-> (Map Chained ImportSemantics -> [Chained])
-> Map Chained ImportSemantics
-> [Chained]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Map Chained ImportSemantics -> [Chained]
forall k v. Map k v -> [k]
Dhall.Map.keys
(Map Chained ImportSemantics -> IO ())
-> Map Chained ImportSemantics -> IO ()
forall a b. (a -> b) -> a -> b
$ Map Chained ImportSemantics
_cache
Resolve { resolveMode :: Mode -> Maybe ResolveMode
resolveMode = Maybe ResolveMode
Nothing, Input
SemanticCacheMode
file :: Mode -> Input
semanticCacheMode :: Mode -> SemanticCacheMode
file :: Input
semanticCacheMode :: SemanticCacheMode
..} -> do
(Expr Src Import
expression, CharacterSet
characterSet) <- Input -> IO (Expr Src Import, CharacterSet)
getExpressionAndCharacterSet Input
file
Expr Src Void
resolvedExpression <-
String
-> SemanticCacheMode -> Expr Src Import -> IO (Expr Src Void)
Dhall.Import.loadRelativeTo (Input -> String
rootDirectory Input
file) SemanticCacheMode
semanticCacheMode Expr Src Import
expression
Handle -> CharacterSet -> Expr Src Void -> IO ()
render Handle
System.IO.stdout CharacterSet
characterSet Expr Src Void
resolvedExpression
Normalize {Bool
Input
file :: Mode -> Input
alpha :: Mode -> Bool
file :: Input
alpha :: Bool
..} -> do
(Expr Src Import
expression, CharacterSet
characterSet) <- Input -> IO (Expr Src Import, CharacterSet)
getExpressionAndCharacterSet Input
file
Expr Src Void
resolvedExpression <- Expr Src Import -> IO (Expr Src Void)
forall (io :: * -> *).
MonadIO io =>
Expr Src Import -> io (Expr Src Void)
Dhall.Import.assertNoImports Expr Src Import
expression
Expr Src Void
_ <- Either (TypeError Src Void) (Expr Src Void) -> IO (Expr Src Void)
forall e (io :: * -> *) a.
(Exception e, MonadIO io) =>
Either e a -> io a
Dhall.Core.throws (Expr Src Void -> Either (TypeError Src Void) (Expr Src Void)
forall s. Expr s Void -> Either (TypeError s Void) (Expr s Void)
Dhall.TypeCheck.typeOf Expr Src Void
resolvedExpression)
let normalizedExpression :: Expr t Void
normalizedExpression = Expr Src Void -> Expr t Void
forall a s t. Eq a => Expr s a -> Expr t a
Dhall.Core.normalize Expr Src Void
resolvedExpression
let alphaNormalizedExpression :: Expr s Void
alphaNormalizedExpression =
if Bool
alpha
then Expr s Void -> Expr s Void
forall s a. Expr s a -> Expr s a
Dhall.Core.alphaNormalize Expr s Void
forall {t}. Expr t Void
normalizedExpression
else Expr s Void
forall {t}. Expr t Void
normalizedExpression
Handle -> CharacterSet -> Expr Src Void -> IO ()
render Handle
System.IO.stdout CharacterSet
characterSet Expr Src Void
alphaNormalizedExpression
Type {Bool
Input
SemanticCacheMode
file :: Mode -> Input
semanticCacheMode :: Mode -> SemanticCacheMode
quiet :: Mode -> Bool
file :: Input
quiet :: Bool
semanticCacheMode :: SemanticCacheMode
..} -> do
(Expr Src Import
expression, CharacterSet
characterSet) <- Input -> IO (Expr Src Import, CharacterSet)
getExpressionAndCharacterSet Input
file
Expr Src Void
resolvedExpression <-
String
-> SemanticCacheMode -> Expr Src Import -> IO (Expr Src Void)
Dhall.Import.loadRelativeTo (Input -> String
rootDirectory Input
file) SemanticCacheMode
semanticCacheMode Expr Src Import
expression
Expr Src Void
inferredType <- Either (TypeError Src Void) (Expr Src Void) -> IO (Expr Src Void)
forall e (io :: * -> *) a.
(Exception e, MonadIO io) =>
Either e a -> io a
Dhall.Core.throws (Expr Src Void -> Either (TypeError Src Void) (Expr Src Void)
forall s. Expr s Void -> Either (TypeError s Void) (Expr s Void)
Dhall.TypeCheck.typeOf Expr Src Void
resolvedExpression)
if Bool
quiet
then () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
else Handle -> CharacterSet -> Expr Src Void -> IO ()
render Handle
System.IO.stdout CharacterSet
characterSet Expr Src Void
inferredType
Mode
Repl ->
CharacterSet -> Bool -> IO ()
Dhall.Repl.repl
(CharacterSet -> Maybe CharacterSet -> CharacterSet
forall a. a -> Maybe a -> a
fromMaybe CharacterSet
Unicode Maybe CharacterSet
chosenCharacterSet)
Bool
explain
Diff {Text
expr1 :: Mode -> Text
expr2 :: Mode -> Text
expr1 :: Text
expr2 :: Text
..} -> do
Expr Src Void
expression1 <- Text -> IO (Expr Src Void)
Dhall.inputExpr Text
expr1
Expr Src Void
expression2 <- Text -> IO (Expr Src Void)
Dhall.inputExpr Text
expr2
let diff :: Diff
diff = Expr Src Void -> Expr Src Void -> Diff
forall a s. (Eq a, Pretty a) => Expr s a -> Expr s a -> Diff
Dhall.Diff.diffNormalized Expr Src Void
expression1 Expr Src Void
expression2
Handle -> Doc Ann -> IO ()
renderDoc Handle
System.IO.stdout (Diff -> Doc Ann
Dhall.Diff.doc Diff
diff)
if Diff -> Bool
Dhall.Diff.same Diff
diff
then () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
else IO ()
forall a. IO a
Exit.exitFailure
Format {Bool
NonEmpty Input
OutputMode
Transitivity
deprecatedInPlace :: Mode -> Bool
transitivity :: Mode -> Transitivity
outputMode :: Mode -> OutputMode
inputs :: Mode -> NonEmpty Input
deprecatedInPlace :: Bool
transitivity :: Transitivity
outputMode :: OutputMode
inputs :: NonEmpty Input
..} -> do
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
deprecatedInPlace (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
Handle -> String -> IO ()
System.IO.hPutStrLn Handle
System.IO.stderr String
"Warning: the flag \"--inplace\" is deprecated"
Format -> IO ()
Dhall.Format.format Dhall.Format.Format{Maybe CharacterSet
NonEmpty Input
OutputMode
Transitivity
Censor
chosenCharacterSet :: Maybe CharacterSet
censor :: Censor
transitivity :: Transitivity
outputMode :: OutputMode
inputs :: NonEmpty Input
chosenCharacterSet :: Maybe CharacterSet
censor :: Censor
transitivity :: Transitivity
inputs :: NonEmpty Input
outputMode :: OutputMode
..}
Freeze {Bool
NonEmpty Input
OutputMode
Transitivity
deprecatedInPlace :: Mode -> Bool
transitivity :: Mode -> Transitivity
outputMode :: Mode -> OutputMode
inputs :: Mode -> NonEmpty Input
all_ :: Mode -> Bool
cache :: Mode -> Bool
deprecatedInPlace :: Bool
transitivity :: Transitivity
all_ :: Bool
cache :: Bool
outputMode :: OutputMode
inputs :: NonEmpty Input
..} -> do
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
deprecatedInPlace (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
Handle -> String -> IO ()
System.IO.hPutStrLn Handle
System.IO.stderr String
"Warning: the flag \"--inplace\" is deprecated"
let scope :: Scope
scope = if Bool
all_ then Scope
AllImports else Scope
OnlyRemoteImports
let intent :: Intent
intent = if Bool
cache then Intent
Cache else Intent
Secure
OutputMode
-> Transitivity
-> NonEmpty Input
-> Scope
-> Intent
-> Maybe CharacterSet
-> Censor
-> IO ()
Dhall.Freeze.freeze OutputMode
outputMode Transitivity
transitivity NonEmpty Input
inputs Scope
scope Intent
intent Maybe CharacterSet
chosenCharacterSet Censor
censor
Hash {Bool
Input
file :: Mode -> Input
cache :: Mode -> Bool
file :: Input
cache :: Bool
..} -> do
Expr Src Import
expression <- Input -> IO (Expr Src Import)
getExpression Input
file
Expr Src Void
resolvedExpression <-
String
-> SemanticCacheMode -> Expr Src Import -> IO (Expr Src Void)
Dhall.Import.loadRelativeTo (Input -> String
rootDirectory Input
file) SemanticCacheMode
UseSemanticCache Expr Src Import
expression
Expr Src Void
_ <- Either (TypeError Src Void) (Expr Src Void) -> IO (Expr Src Void)
forall e (io :: * -> *) a.
(Exception e, MonadIO io) =>
Either e a -> io a
Dhall.Core.throws (Expr Src Void -> Either (TypeError Src Void) (Expr Src Void)
forall s. Expr s Void -> Either (TypeError s Void) (Expr s Void)
Dhall.TypeCheck.typeOf Expr Src Void
resolvedExpression)
let normalizedExpression :: Expr s Void
normalizedExpression =
Expr s Void -> Expr s Void
forall s a. Expr s a -> Expr s a
Dhall.Core.alphaNormalize (Expr Src Void -> Expr s Void
forall a s t. Eq a => Expr s a -> Expr t a
Dhall.Core.normalize Expr Src Void
resolvedExpression)
if Bool
cache
then Expr Void Void -> IO ()
Dhall.Import.writeExpressionToSemanticCache Expr Void Void
forall {t}. Expr t Void
normalizedExpression
else () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
Text -> IO ()
Data.Text.IO.putStrLn (Expr Void Void -> Text
Dhall.Import.hashExpressionToCode Expr Void Void
normalizedExpression)
Lint { transitivity :: Mode -> Transitivity
transitivity = Transitivity
transitivity0, Bool
NonEmpty Input
OutputMode
deprecatedInPlace :: Mode -> Bool
outputMode :: Mode -> OutputMode
inputs :: Mode -> NonEmpty Input
deprecatedInPlace :: Bool
outputMode :: OutputMode
inputs :: NonEmpty Input
..} -> do
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
deprecatedInPlace (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
Handle -> String -> IO ()
System.IO.hPutStrLn Handle
System.IO.stderr String
"Warning: the flag \"--inplace\" is deprecated"
Text
-> Text
-> (Input -> IO (Either CheckFailed ()))
-> NonEmpty Input
-> IO ()
forall (t :: * -> *) a.
(Foldable t, Traversable t) =>
Text -> Text -> (a -> IO (Either CheckFailed ())) -> t a -> IO ()
handleMultipleChecksFailed Text
"lint" Text
"linted" Input -> IO (Either CheckFailed ())
go NonEmpty Input
inputs
where
go :: Input -> IO (Either CheckFailed ())
go Input
input = do
let directory :: String
directory = case Input
input of
Input
StandardInput -> String
"."
InputFile String
file -> String -> String
System.FilePath.takeDirectory String
file
let status :: Status
status = String -> Status
Dhall.Import.emptyStatus String
directory
(String
inputName, Text
originalText, Transitivity
transitivity) <- case Input
input of
InputFile String
file -> do
Text
text <- String -> IO Text
Data.Text.IO.readFile String
file
return (String
file, Text
text, Transitivity
transitivity0)
Input
StandardInput -> do
Text
text <- IO Text
Data.Text.IO.getContents
return (String
"(input)", Text
text, Transitivity
NonTransitive)
(Header Text
header, Expr Src Import
parsedExpression) <-
Censor -> String -> Text -> IO (Header, Expr Src Import)
Dhall.Util.getExpressionAndHeaderFromStdinText Censor
censor String
inputName Text
originalText
let characterSet :: CharacterSet
characterSet = CharacterSet -> Maybe CharacterSet -> CharacterSet
forall a. a -> Maybe a -> a
fromMaybe (Expr Src Import -> CharacterSet
forall a. Expr Src a -> CharacterSet
detectCharacterSet Expr Src Import
parsedExpression) Maybe CharacterSet
chosenCharacterSet
case Transitivity
transitivity of
Transitivity
Transitive ->
Expr Src Import -> (Import -> IO ()) -> IO ()
forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
t a -> (a -> f b) -> f ()
for_ Expr Src Import
parsedExpression ((Import -> IO ()) -> IO ()) -> (Import -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Import
import_ -> do
Maybe String
maybeFilepath <- Status -> Import -> IO (Maybe String)
Dhall.Import.dependencyToFile Status
status Import
import_
Maybe String -> (String -> IO (Either CheckFailed ())) -> IO ()
forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
t a -> (a -> f b) -> f ()
for_ Maybe String
maybeFilepath ((String -> IO (Either CheckFailed ())) -> IO ())
-> (String -> IO (Either CheckFailed ())) -> IO ()
forall a b. (a -> b) -> a -> b
$ \String
filepath ->
Input -> IO (Either CheckFailed ())
go (String -> Input
InputFile String
filepath)
Transitivity
NonTransitive ->
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
let lintedExpression :: Expr Src Import
lintedExpression = Expr Src Import -> Expr Src Import
forall s. Eq s => Expr s Import -> Expr s Import
Dhall.Lint.lint Expr Src Import
parsedExpression
let doc :: Doc Ann
doc = Text -> Doc Ann
forall ann. Text -> Doc ann
forall a ann. Pretty a => a -> Doc ann
Pretty.pretty Text
header
Doc Ann -> Doc Ann -> Doc Ann
forall a. Semigroup a => a -> a -> a
<> CharacterSet -> Expr Src Import -> Doc Ann
forall a. Pretty a => CharacterSet -> Expr Src a -> Doc Ann
Dhall.Pretty.prettyCharacterSet CharacterSet
characterSet Expr Src Import
lintedExpression
let stream :: SimpleDocStream Ann
stream = Doc Ann -> SimpleDocStream Ann
forall ann. Doc ann -> SimpleDocStream ann
Dhall.Pretty.layout Doc Ann
doc
let modifiedText :: Text
modifiedText = SimpleDocStream Ann -> Text
forall ann. SimpleDocStream ann -> Text
Pretty.Text.renderStrict SimpleDocStream Ann
stream Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"\n"
case OutputMode
outputMode of
OutputMode
Write -> do
case Input
input of
InputFile String
file ->
if Text
originalText Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
modifiedText
then () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
else String -> Doc Ann -> IO ()
writeDocToFile String
file Doc Ann
doc
Input
StandardInput ->
Handle -> Doc Ann -> IO ()
renderDoc Handle
System.IO.stdout Doc Ann
doc
return (() -> Either CheckFailed ()
forall a b. b -> Either a b
Right ())
OutputMode
Check ->
Either CheckFailed () -> IO (Either CheckFailed ())
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Either CheckFailed () -> IO (Either CheckFailed ()))
-> Either CheckFailed () -> IO (Either CheckFailed ())
forall a b. (a -> b) -> a -> b
$
if Text
originalText Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
modifiedText
then () -> Either CheckFailed ()
forall a b. b -> Either a b
Right ()
else CheckFailed -> Either CheckFailed ()
forall a b. a -> Either a b
Left CheckFailed{Input
input :: Input
input :: Input
..}
Encode {Bool
Input
file :: Mode -> Input
json :: Mode -> Bool
file :: Input
json :: Bool
..} -> do
Expr Src Import
expression <- Input -> IO (Expr Src Import)
getExpression Input
file
let bytes :: ByteString
bytes = Expr Void Import -> ByteString
forall a. Serialise (Expr Void a) => Expr Void a -> ByteString
Dhall.Binary.encodeExpression (Expr Src Import -> Expr Void Import
forall s a t. Expr s a -> Expr t a
Dhall.Core.denote Expr Src Import
expression)
if Bool
json
then do
let decoder :: Decoder s Value
decoder = Bool -> Decoder s Value
forall s. Bool -> Decoder s Value
Codec.CBOR.JSON.decodeValue Bool
False
(ByteString
_, Value
value) <- Either DeserialiseFailure (ByteString, Value)
-> IO (ByteString, Value)
forall e (io :: * -> *) a.
(Exception e, MonadIO io) =>
Either e a -> io a
Dhall.Core.throws ((forall s. Decoder s Value)
-> ByteString -> Either DeserialiseFailure (ByteString, Value)
forall a.
(forall s. Decoder s a)
-> ByteString -> Either DeserialiseFailure (ByteString, a)
Codec.CBOR.Read.deserialiseFromBytes Decoder s Value
forall s. Decoder s Value
decoder ByteString
bytes)
let jsonBytes :: ByteString
jsonBytes = Value -> ByteString
forall a. ToJSON a => a -> ByteString
Data.Aeson.Encode.Pretty.encodePretty Value
value
ByteString -> IO ()
Data.ByteString.Lazy.Char8.putStrLn ByteString
jsonBytes
else
ByteString -> IO ()
Data.ByteString.Lazy.putStr ByteString
bytes
Decode {Bool
Input
file :: Mode -> Input
quiet :: Mode -> Bool
json :: Mode -> Bool
file :: Input
json :: Bool
quiet :: Bool
..} -> do
ByteString
bytes <-
case Input
file of
InputFile String
f -> String -> IO ByteString
Data.ByteString.Lazy.readFile String
f
Input
StandardInput -> IO ByteString
Data.ByteString.Lazy.getContents
Expr Void Import
expression <-
if Bool
json
then do
Value
value <- case ByteString -> Either String Value
forall a. FromJSON a => ByteString -> Either String a
Data.Aeson.eitherDecode' ByteString
bytes of
Left String
string -> String -> IO Value
forall a. String -> IO a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
string
Right Value
value -> Value -> IO Value
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Value
value
let encoding :: Encoding
encoding = Value -> Encoding
Codec.CBOR.JSON.encodeValue Value
value
let cborgBytes :: ByteString
cborgBytes = Encoding -> ByteString
Codec.CBOR.Write.toLazyByteString Encoding
encoding
Either DecodingFailure (Expr Void Import) -> IO (Expr Void Import)
forall e (io :: * -> *) a.
(Exception e, MonadIO io) =>
Either e a -> io a
Dhall.Core.throws (ByteString -> Either DecodingFailure (Expr Void Import)
forall s a.
Serialise (Expr s a) =>
ByteString -> Either DecodingFailure (Expr s a)
Dhall.Binary.decodeExpression ByteString
cborgBytes)
else
Either DecodingFailure (Expr Void Import) -> IO (Expr Void Import)
forall e (io :: * -> *) a.
(Exception e, MonadIO io) =>
Either e a -> io a
Dhall.Core.throws (ByteString -> Either DecodingFailure (Expr Void Import)
forall s a.
Serialise (Expr s a) =>
ByteString -> Either DecodingFailure (Expr s a)
Dhall.Binary.decodeExpression ByteString
bytes)
if Bool
quiet
then () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
else do
let doc :: Doc Ann
doc =
CharacterSet -> Expr Src Import -> Doc Ann
forall a. Pretty a => CharacterSet -> Expr Src a -> Doc Ann
Dhall.Pretty.prettyCharacterSet
(CharacterSet -> Maybe CharacterSet -> CharacterSet
forall a. a -> Maybe a -> a
fromMaybe CharacterSet
Unicode Maybe CharacterSet
chosenCharacterSet)
(Expr Void Import -> Expr Src Import
forall a s. Expr Void a -> Expr s a
Dhall.Core.renote Expr Void Import
expression :: Expr Src Import)
Handle -> Doc Ann -> IO ()
renderDoc Handle
System.IO.stdout Doc Ann
doc
Text {Output
Input
file :: Mode -> Input
output :: Mode -> Output
file :: Input
output :: Output
..} -> do
Expr Src Import
expression <- Input -> IO (Expr Src Import)
getExpression Input
file
Expr Src Void
resolvedExpression <-
String
-> SemanticCacheMode -> Expr Src Import -> IO (Expr Src Void)
Dhall.Import.loadRelativeTo (Input -> String
rootDirectory Input
file) SemanticCacheMode
UseSemanticCache Expr Src Import
expression
Expr Src Void
_ <- Either (TypeError Src Void) (Expr Src Void) -> IO (Expr Src Void)
forall e (io :: * -> *) a.
(Exception e, MonadIO io) =>
Either e a -> io a
Dhall.Core.throws (Expr Src Void -> Either (TypeError Src Void) (Expr Src Void)
forall s. Expr s Void -> Either (TypeError s Void) (Expr s Void)
Dhall.TypeCheck.typeOf (Expr Src Void -> Expr Src Void -> Expr Src Void
forall s a. Expr s a -> Expr s a -> Expr s a
Annot Expr Src Void
resolvedExpression Expr Src Void
forall s a. Expr s a
Dhall.Core.Text))
let normalizedExpression :: Expr t Void
normalizedExpression = Expr Src Void -> Expr t Void
forall a s t. Eq a => Expr s a -> Expr t a
Dhall.Core.normalize Expr Src Void
resolvedExpression
case Expr Void Void
normalizedExpression of
Dhall.Core.TextLit (Dhall.Core.Chunks [] Text
text) ->
let write :: Text -> IO ()
write = case Output
output of
Output
StandardOutput -> Text -> IO ()
Data.Text.IO.putStr
OutputFile String
file_ -> String -> Text -> IO ()
Data.Text.IO.writeFile String
file_
in Text -> IO ()
write Text
text
Expr Void Void
_ -> do
let invalidDecoderExpected :: Expr Void Void
invalidDecoderExpected :: Expr Void Void
invalidDecoderExpected = Expr Void Void
forall s a. Expr s a
Dhall.Core.Text
let invalidDecoderExpression :: Expr Void Void
invalidDecoderExpression :: Expr Void Void
invalidDecoderExpression = Expr Void Void
normalizedExpression
InvalidDecoder Void Void -> IO ()
forall e a. Exception e => e -> IO a
Control.Exception.throwIO (Dhall.InvalidDecoder {Expr Void Void
invalidDecoderExpected :: Expr Void Void
invalidDecoderExpression :: Expr Void Void
invalidDecoderExpected :: Expr Void Void
invalidDecoderExpression :: Expr Void Void
..})
Tags {Bool
Maybe [Text]
Output
Input
output :: Mode -> Output
input :: Mode -> Input
suffixes :: Mode -> Maybe [Text]
followSymlinks :: Mode -> Bool
input :: Input
output :: Output
suffixes :: Maybe [Text]
followSymlinks :: Bool
..} -> do
Text
tags <- Input -> Maybe [Text] -> Bool -> IO Text
Dhall.Tags.generate Input
input Maybe [Text]
suffixes Bool
followSymlinks
case Output
output of
OutputFile String
file ->
String -> IOMode -> (Handle -> IO ()) -> IO ()
forall r. String -> IOMode -> (Handle -> IO r) -> IO r
System.IO.withFile String
file IOMode
System.IO.WriteMode (Handle -> Text -> IO ()
`Data.Text.IO.hPutStr` Text
tags)
Output
StandardOutput -> Text -> IO ()
Data.Text.IO.putStrLn Text
tags
DirectoryTree {Bool
String
Input
file :: Mode -> Input
allowSeparators :: Mode -> Bool
path :: Mode -> String
allowSeparators :: Bool
file :: Input
path :: String
..} -> do
Expr Src Import
expression <- Input -> IO (Expr Src Import)
getExpression Input
file
Expr Src Void
resolvedExpression <-
String
-> SemanticCacheMode -> Expr Src Import -> IO (Expr Src Void)
Dhall.Import.loadRelativeTo (Input -> String
rootDirectory Input
file) SemanticCacheMode
UseSemanticCache Expr Src Import
expression
Expr Src Void
_ <- Either (TypeError Src Void) (Expr Src Void) -> IO (Expr Src Void)
forall e (io :: * -> *) a.
(Exception e, MonadIO io) =>
Either e a -> io a
Dhall.Core.throws (Expr Src Void -> Either (TypeError Src Void) (Expr Src Void)
forall s. Expr s Void -> Either (TypeError s Void) (Expr s Void)
Dhall.TypeCheck.typeOf Expr Src Void
resolvedExpression)
let normalizedExpression :: Expr t Void
normalizedExpression = Expr Src Void -> Expr t Void
forall a s t. Eq a => Expr s a -> Expr t a
Dhall.Core.normalize Expr Src Void
resolvedExpression
Bool -> String -> Expr Void Void -> IO ()
DirectoryTree.toDirectoryTree Bool
allowSeparators String
path Expr Void Void
normalizedExpression
Dhall.Main.Schemas{Text
OutputMode
Input
file :: Mode -> Input
outputMode :: Mode -> OutputMode
schemas :: Mode -> Text
file :: Input
outputMode :: OutputMode
schemas :: Text
..} ->
Schemas -> IO ()
Dhall.Schemas.schemasCommand Dhall.Schemas.Schemas{ input :: Input
input = Input
file, Maybe CharacterSet
Text
OutputMode
Censor
chosenCharacterSet :: Maybe CharacterSet
censor :: Censor
outputMode :: OutputMode
schemas :: Text
chosenCharacterSet :: Maybe CharacterSet
censor :: Censor
outputMode :: OutputMode
schemas :: Text
..}
SyntaxTree {Bool
Input
file :: Mode -> Input
noted :: Mode -> Bool
file :: Input
noted :: Bool
..} -> do
Expr Src Import
expression <- Input -> IO (Expr Src Import)
getExpression Input
file
if Bool
noted then
Expr Src Import -> IO ()
forall (m :: * -> *) a. (MonadIO m, Show a) => a -> m ()
Text.Pretty.Simple.pPrintNoColor Expr Src Import
expression
else
let denoted :: Expr Void Import
denoted :: Expr Void Import
denoted = Expr Src Import -> Expr Void Import
forall s a t. Expr s a -> Expr t a
Dhall.Core.denote Expr Src Import
expression
in Expr Void Import -> IO ()
forall (m :: * -> *) a. (MonadIO m, Show a) => a -> m ()
Text.Pretty.Simple.pPrintNoColor Expr Void Import
denoted
Package {Maybe String
NonEmpty String
name :: Mode -> Maybe String
files :: Mode -> NonEmpty String
name :: Maybe String
files :: NonEmpty String
..} -> CharacterSet -> Maybe String -> NonEmpty String -> IO ()
writePackage (CharacterSet -> Maybe CharacterSet -> CharacterSet
forall a. a -> Maybe a -> a
fromMaybe CharacterSet
Unicode Maybe CharacterSet
chosenCharacterSet) Maybe String
name NonEmpty String
files
main :: IO ()
main :: IO ()
main = do
Options
options <- ParserInfo Options -> IO Options
forall a. ParserInfo a -> IO a
Options.Applicative.execParser ParserInfo Options
parserInfoOptions
Options -> IO ()
Dhall.Main.command Options
options